Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Alex D
GHC
Commits
4976d0e0
Commit
4976d0e0
authored
Dec 23, 2011
by
Simon Peyton Jones
Browse files
Merge branch 'master' of
http://darcs.haskell.org/testsuite
parents
d3c9c1db
e08432d8
Changes
17
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/indexed-types/should_fail/T3330c.stderr
View file @
4976d0e0
T3330c.hs:23:43:
Couldn't match type `Der ((->) x)' with `R'
In the first argument of `plug', namely `rf'
In the first argument of `Inl', namely `(plug rf df x)'
In the expression: Inl (plug rf df x)
T3330c.hs:23:43:
Couldn't match type `f1' with `f1 x'
`f1' is a rigid type variable bound by
a pattern with constructor
RSum :: forall (f :: * -> *) (g :: * -> *).
R f -> R g -> R (f :+: g),
in an equation for plug'
at T3330c.hs:23:8
In the first argument of `plug', namely `rf'
In the first argument of `Inl', namely `(plug rf df x)'
In the expression: Inl (plug rf df x)
T3330c.hs:23:33:
Kind incompatibility when matching types:
f0 :: * -> *
f0 x :: *
In the return type of a call of `Inl'
In the expression: Inl (plug rf df x)
In an equation for plug':
plug' (RSum rf rg) (Inl df) x = Inl (plug rf df x)
T3330c.hs:23:43:
Couldn't match kind `*' with `* -> *'
Kind incompatibility when matching types:
Der ((->) x) :: * -> *
R :: (* -> *) -> *
In the first argument of `plug', namely `rf'
In the first argument of `Inl', namely `(plug rf df x)'
testsuite/tests/safeHaskell/check/Check06.hs
0 → 100644
View file @
4976d0e0
{-# LANGUAGE Trustworthy, NoImplicitPrelude #-}
{-# OPTIONS_GHC -fpackage-trust #-}
-- make sure importing a safe-infered module brings in the
-- pkg trust requirements correctly.
module
Check06
(
main'
)
where
import
safe
Check06_A
main'
=
let
n
=
mainM
1
in
n
testsuite/tests/safeHaskell/check/Check06.stderr
0 → 100644
View file @
4976d0e0
[1 of 2] Compiling Check06_A ( Check06_A.hs, Check06_A.o )
[2 of 2] Compiling Check06 ( Check06.hs, Check06.o )
<no location info>:
The package (base) is required to be trusted but it isn't!
testsuite/tests/safeHaskell/check/Check06_A.hs
0 → 100644
View file @
4976d0e0
-- safe infered, with requirement base is trusted
module
Check06_A
where
mainM
::
Int
->
Int
mainM
n
=
n
+
1
testsuite/tests/safeHaskell/check/Check07.hs
0 → 100644
View file @
4976d0e0
{-# LANGUAGE Trustworthy, NoImplicitPrelude #-}
{-# OPTIONS_GHC -fpackage-trust #-}
-- make sure selective safe imports brings in pkg trust requirements correctly.
-- (e.g only for the imports that are safe ones)
module
Check07
(
main'
)
where
import
safe
Check07_A
-- no pkg trust reqs
import
Check07_B
-- base pkg trust req
main'
=
let
n
=
a
(
b
1
)
in
n
testsuite/tests/safeHaskell/check/Check07.stderr
0 → 100644
View file @
4976d0e0
[1 of 3] Compiling Check07_B ( Check07_B.hs, Check07_B.o )
[2 of 3] Compiling Check07_A ( Check07_A.hs, Check07_A.o )
[3 of 3] Compiling Check07 ( Check07.hs, Check07.o )
testsuite/tests/safeHaskell/check/Check07_A.hs
0 → 100644
View file @
4976d0e0
{-# LANGUAGE NoImplicitPrelude #-}
-- safe infered, with no pkg trust reqs
module
Check07_A
where
a
::
a
->
a
a
n
=
n
testsuite/tests/safeHaskell/check/Check07_B.hs
0 → 100644
View file @
4976d0e0
-- safe infered, with requirement base is trusted
module
Check07_B
where
import
Prelude
b
::
Int
->
Int
b
n
=
n
+
1
testsuite/tests/safeHaskell/check/Check08.hs
0 → 100644
View file @
4976d0e0
{-# LANGUAGE Trustworthy, NoImplicitPrelude #-}
{-# OPTIONS_GHC -fpackage-trust #-}
-- make sure selective safe imports brings in pkg trust requirements correctly.
-- (e.g only for the imports that are safe ones)
module
Check08
(
main'
)
where
import
safe
Check08_A
-- no pkg trust reqs
import
safe
Check08_B
-- base pkg trust req
main'
=
let
n
=
a
(
b
1
)
in
n
testsuite/tests/safeHaskell/check/Check08.stderr
0 → 100644
View file @
4976d0e0
[1 of 3] Compiling Check08_B ( Check08_B.hs, Check08_B.o )
[2 of 3] Compiling Check08_A ( Check08_A.hs, Check08_A.o )
[3 of 3] Compiling Check08 ( Check08.hs, Check08.o )
<no location info>:
The package (base) is required to be trusted but it isn't!
testsuite/tests/safeHaskell/check/Check08_A.hs
0 → 100644
View file @
4976d0e0
{-# LANGUAGE NoImplicitPrelude #-}
-- safe infered, with no pkg trust reqs
module
Check08_A
where
a
::
a
->
a
a
n
=
n
testsuite/tests/safeHaskell/check/Check08_B.hs
0 → 100644
View file @
4976d0e0
-- safe infered, with requirement base is trusted
module
Check08_B
where
import
Prelude
b
::
Int
->
Int
b
n
=
n
+
1
testsuite/tests/safeHaskell/check/all.T
View file @
4976d0e0
...
...
@@ -42,3 +42,18 @@ test('Check04', normal, multi_compile, ['Check04', [
# Check -fpackage-trust with no safe haskell flag is an error
test
('
Check05
',
normal
,
compile
,
[''])
# Check safe-infered modules have correct pkg trust requirements
test
('
Check06
',
extra_clean
(['
Check06_A.hi
',
'
Check06_A.o
']),
multimod_compile_fail
,
['
Check06
',
''])
# Check selective safe imports bring in correct pkg trust requirements
test
('
Check07
',
extra_clean
(['
Check07_A.hi
',
'
Check07_A.o
',
'
Check07_B.hi
',
'
Check07_B.o
']),
multimod_compile
,
['
Check07
',
''])
# Check selective safe imports bring in correct pkg trust requirements
test
('
Check08
',
extra_clean
(['
Check08_A.hi
',
'
Check08_A.o
',
'
Check08_B.hi
',
'
Check08_B.o
']),
multimod_compile_fail
,
['
Check08
',
''])
testsuite/tests/safeHaskell/check/pkg01/M_SafePkg5.hs
0 → 100644
View file @
4976d0e0
-- safe inference
-- same module as M_SafePkg4 which compiles with -XSafe.
-- Want to make sure compiles fine and is infered safe and
-- also picks up corrected pkg trust requirements.
module
M_SafePkg5
where
import
qualified
M_SafePkg3
as
M3
import
Data.Word
bigInt
::
Int
bigInt
=
M3
.
bigInt
type
MyWord
=
Word
testsuite/tests/safeHaskell/check/pkg01/Makefile
View file @
4976d0e0
...
...
@@ -44,6 +44,9 @@ safePkg01:
echo
'M_SafePkg4'
'
$(TEST_HC)
'
--show-iface
dist/build/M_SafePkg4.hi |
grep
-E
'^package dependencies:|^trusted:|^require own pkg trusted:'
echo
echo
'M_SafePkg5'
'
$(TEST_HC)
'
--show-iface
dist/build/M_SafePkg5.hi |
grep
-E
'^package dependencies:|^trusted:|^require own pkg trusted:'
echo
echo
'Testing setting trust'
$(LGHC_PKG)
trust safePkg01-1.0
$(LGHC_PKG)
field safePkg01-1.0 trusted
...
...
testsuite/tests/safeHaskell/check/pkg01/p.cabal
View file @
4976d0e0
...
...
@@ -11,5 +11,6 @@ Library {
M_SafePkg2
M_SafePkg3
M_SafePkg4
M_SafePkg5
}
testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout
View file @
4976d0e0
...
...
@@ -23,6 +23,11 @@ package dependencies: base* ghc-prim integer-gmp
trusted
:
safe
require
own
pkg
trusted
:
True
M_SafePkg5
package
dependencies
:
base
*
ghc
-
prim
integer
-
gmp
trusted
:
safe
-
infered
require
own
pkg
trusted
:
True
Testing
setting
trust
trusted
:
True
trusted
:
False
...
...
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment