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
Glasgow Haskell Compiler
GHC
Commits
b6c88428
Commit
b6c88428
authored
May 27, 2008
by
Simon Marlow
Browse files
add test for hs-boot consistency checking
parent
3d8eccba
Changes
5
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/rename/should_fail/RnFail055.hs
0 → 100644
View file @
b6c88428
{-# LANGUAGE MultiParamTypeClasses,RankNTypes,ExistentialQuantification #-}
module
RnFail055
where
import
RnFail055_aux
-- Id with different type
f1
::
Int
->
Float
f1
=
undefined
-- type synonym with different arity
type
S1
a
b
=
(
a
,
b
)
-- type synonym with different rhs
type
S2
a
b
=
forall
a
.
(
a
,
b
)
-- type synonym with alpha-renaming (should be ok)
type
S3
a
=
[
a
]
-- datatype with different fields
data
T1
a
b
=
T1
[
b
]
[
a
]
-- datatype with different stupid theta
data
(
Eq
b
)
=>
T2
a
b
=
T2
a
-- different constructor name
data
T3'
=
T3
data
T3
=
T3'
-- check alpha equivalence
data
T4
a
=
T4
(
forall
b
.
a
->
b
)
-- different field labels
data
T5
a
=
T5
{
field5
::
a
}
-- different strict marks
data
T6
=
T6
Int
-- different existential quantification
data
T7
a
=
forall
a
.
T7
a
-- extra method in the hs-boot
class
C1
a
b
where
{}
-- missing method in the hs-boot
class
C2
a
b
where
{
m2
::
a
->
b
;
m2'
::
a
->
b
}
-- different superclasses
class
(
Eq
a
,
Ord
a
)
=>
C3
a
where
{
}
testsuite/tests/ghc-regress/rename/should_fail/RnFail055.hs-boot
0 → 100644
View file @
b6c88428
{-# LANGUAGE MultiParamTypeClasses,RankNTypes,ExistentialQuantification #-}
module
RnFail055
where
f1
::
Float
->
Int
type
S1
a
b
c
=
(
a
,
b
)
type
S2
a
b
=
forall
b
.
(
a
,
b
)
type
S3
t
=
[
t
]
data
T1
a
b
=
T1
[
a
]
[
b
]
data
(
Eq
a
)
=>
T2
a
b
=
T2
a
data
T3
=
T3
data
T3'
=
T3'
data
T4
b
=
T4
(
forall
a
.
b
->
a
)
data
T5
a
=
T5
a
data
T6
=
T6
!
Int
data
T7
a
=
forall
b
.
T7
a
class
C1
a
b
where
{
m1
::
a
->
b
}
class
C2
a
b
where
{
m2
::
a
->
b
}
class
(
Ord
a
,
Eq
a
)
=>
C3
a
where
{
}
testsuite/tests/ghc-regress/rename/should_fail/RnFail055_aux.hs
0 → 100644
View file @
b6c88428
module
RnFail055_aux
where
import
{-#
SOURCE
#-
}
RnFail055
testsuite/tests/ghc-regress/rename/should_fail/all.T
View file @
b6c88428
...
...
@@ -56,6 +56,7 @@ test('rnfail051', if_compiler_lt('ghc', '6.9', skip), compile_fail, [''])
test
('
rnfail052
',
normal
,
compile_fail
,
[''])
test
('
rnfail053
',
normal
,
compile_fail
,
[''])
test
('
rnfail054
',
normal
,
compile_fail
,
[''])
test
('
rnfail055
',
normal
,
multimod_compile_fail
,
['
RnFail055
','
-v0
'])
test
('
rn_dup
',
normal
,
compile_fail
,
[''])
testsuite/tests/ghc-regress/rename/should_fail/rnfail055.stderr
0 → 100644
View file @
b6c88428
RnFail055.hs-boot:4:0:
Identifier `f1' has conflicting definitions in the module and its hs-boot file
Main module: f1 :: Int -> Float
Boot file: f1 :: Float -> Int
RnFail055.hs-boot:6:5:
Type constructor `S1' has conflicting definitions in the module and its hs-boot file
Main module: type S1 a b
= (a, b)
FamilyInstance: none
Boot file: type S1 a b c
= (a, b)
FamilyInstance: none
RnFail055.hs-boot:8:5:
Type constructor `S2' has conflicting definitions in the module and its hs-boot file
Main module: type S2 a b
= forall a. (a, b)
FamilyInstance: none
Boot file: type S2 a b
= forall b. (a, b)
FamilyInstance: none
RnFail055.hs-boot:12:5:
Type constructor `T1' has conflicting definitions in the module and its hs-boot file
Main module: data T1 a b
RecFlag Recursive
Generics: no
= T1 :: forall a b. [b] -> [a] -> T1 a b Stricts: _ _
FamilyInstance: none
Boot file: data T1 a b
RecFlag NonRecursive
Generics: no
= T1 :: forall a b. [a] -> [b] -> T1 a b Stricts: _ _
FamilyInstance: none
RnFail055.hs-boot:14:15:
Type constructor `T2' has conflicting definitions in the module and its hs-boot file
Main module: data Eq b => T2 a b
RecFlag Recursive
Generics: no
= T2 :: forall a b. a -> T2 a b Stricts: _
FamilyInstance: none
Boot file: data Eq a => T2 a b
RecFlag NonRecursive
Generics: no
= T2 :: forall a b. a -> T2 a b Stricts: _
FamilyInstance: none
RnFail055.hs-boot:16:10:
T3 is exported by the hs-boot file, but not exported by the module
RnFail055.hs-boot:17:11:
T3' is exported by the hs-boot file, but not exported by the module
RnFail055.hs-boot:21:5:
Type constructor `T5' has conflicting definitions in the module and its hs-boot file
Main module: data T5 a
RecFlag Recursive
Generics: no
= T5 :: forall a. a -> T5 a Stricts: _ Fields: field5
FamilyInstance: none
Boot file: data T5 a
RecFlag NonRecursive
Generics: no
= T5 :: forall a. a -> T5 a Stricts: _
FamilyInstance: none
RnFail055.hs-boot:23:5:
Type constructor `T6' has conflicting definitions in the module and its hs-boot file
Main module: data T6
RecFlag Recursive
Generics: no
= T6 :: Int -> T6 Stricts: _
FamilyInstance: none
Boot file: data T6
RecFlag NonRecursive
Generics: no
= T6 :: Int -> T6 Stricts: !
FamilyInstance: none
RnFail055.hs-boot:25:5:
Type constructor `T7' has conflicting definitions in the module and its hs-boot file
Main module: data T7 a
RecFlag Recursive
Generics: no
= T7 :: forall a a. a -> T7 a Stricts: _
FamilyInstance: none
Boot file: data T7 a
RecFlag NonRecursive
Generics: no
= T7 :: forall a b. a -> T7 a Stricts: _
FamilyInstance: none
RnFail055.hs-boot:27:21:
RnFail055.m1 is exported by the hs-boot file, but not exported by the module
RnFail055.hs-boot:28:6:
Class `C2' has conflicting definitions in the module and its hs-boot file
Main module: class C2 a b
RecFlag NonRecursive
m2 :: a -> b m2' :: a -> b
Boot file: class C2 a b
RecFlag NonRecursive
m2 :: a -> b
RnFail055.hs-boot:29:23:
Class `C3' has conflicting definitions in the module and its hs-boot file
Main module: class (Eq a, Ord a) => C3 a RecFlag NonRecursive
Boot file: class (Ord a, Eq a) => C3 a RecFlag NonRecursive
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