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
f6f9eb36
Commit
f6f9eb36
authored
Nov 06, 2013
by
Simon Peyton Jones
Browse files
Test for Trac
#4135
, comment 2
parent
a69fea8e
Changes
2
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/th/T4135a.hs
0 → 100644
View file @
f6f9eb36
{-# LANGUAGE TemplateHaskell, MultiParamTypeClasses, TypeFamilies,
FlexibleInstances, OverlappingInstances #-}
module
T4135a
where
import
Control.Monad
import
Language.Haskell.TH
class
Foo
a
where
type
FooType
a
createInstance'
::
Q
Type
->
Q
Dec
createInstance'
t
=
liftM
head
[
d
|
instance Foo $t where
type FooType $t = String
|]
testsuite/tests/th/all.T
View file @
f6f9eb36
...
...
@@ -235,7 +235,8 @@ test('T5883', normal, compile, ['-v0 -dsuppress-uniques -ddump-splices'])
test
('
T5882
',
normal
,
compile
,
['
-v0
'])
test
('
T5886
',
extra_clean
(['
T5886a.hi
','
T5886a.o
']),
multimod_compile
,
['
T5886
','
-v0
'
+
config
.
ghc_th_way_flags
])
test
('
T4135
',
normal
,
compile
,
['
-v0
'])
test
('
T4135
',
normal
,
compile
,
['
-v0
'])
test
('
T4135a
',
normal
,
compile
,
['
-v0
'])
test
('
T5971
',
normal
,
compile_fail
,
['
-v0 -dsuppress-uniques
'])
test
('
T5968
',
normal
,
compile
,
['
-v0
'])
test
('
T5984
',
extra_clean
(['
T5984_Lib.hi
',
'
T5984_Lib.o
']),
...
...
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