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
959eef66
Commit
959eef66
authored
Nov 06, 2013
by
Simon Peyton Jones
Browse files
Test Trac
#7477
parent
136dc98e
Changes
3
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/th/T7477.hs
0 → 100644
View file @
959eef66
{-# LANGUAGE DataKinds, KindSignatures, PolyKinds, TypeFamilies, TemplateHaskell #-}
module
T7477
where
import
Language.Haskell.TH
type
family
F
(
a
::
k
)
type
instance
F
Int
=
Bool
$
(
do
{
info
<-
reifyInstances
''F
[
ConT
''Int
]
;
reportWarning
(
pprint
info
)
;
return
[]
})
testsuite/tests/th/T7477.stderr
0 → 100644
View file @
959eef66
T7477.hs:10:4: Warning:
type instance T7477.F GHC.Prim.* GHC.Types.Int = GHC.Types.Bool
testsuite/tests/th/all.T
View file @
959eef66
...
...
@@ -304,3 +304,4 @@ test('T7667', normal, compile, ['-v0'])
test
('
T7667a
',
normal
,
compile_fail
,
['
-v0
'])
test
('
T8455
',
normal
,
compile
,
['
-v0
'])
test
('
T8499
',
normal
,
compile
,
['
-v0
'])
test
('
T7477
',
normal
,
compile
,
['
-v0
'])
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