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
cc4f1a94
Commit
cc4f1a94
authored
Mar 19, 2009
by
chak@cse.unsw.edu.au.
Browse files
Template Haskell: test for equality constraints
parent
fa0e334b
Changes
5
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/th/TH_genExLib.hs
View file @
cc4f1a94
...
...
@@ -16,6 +16,6 @@ genAnyClass name decls
=
DataD
[]
anyName
[]
[
constructor
]
[]
where
anyName
=
mkName
(
"Any"
++
nameBase
name
++
"1111"
)
constructor
=
ForallC
[
var_a
]
[
AppT
(
ConT
name
)
(
VarT
var_a
)
]
$
constructor
=
ForallC
[
var_a
]
[
ClassP
name
[
VarT
var_a
]
]
$
NormalC
anyName
[(
NotStrict
,
VarT
var_a
)]
var_a
=
mkName
"a"
testsuite/tests/ghc-regress/th/TH_tf1.hs
View file @
cc4f1a94
{-# OPTIONS -fglasgow-exts #-}
{-# LANGUAGE TypeFamilies #-}
module
TH_tf1
where
$
(
[
d
|
data family T a
|]
)
...
...
testsuite/tests/ghc-regress/th/TH_tf2.hs
View file @
cc4f1a94
{-# OPTIONS -fglasgow-exts #-}
module
TH_tf2
where
{-# LANGUAGE TypeFamilies #-}
import
Language.Haskell.TH
module
TH_tf2
where
$
(
[
d
|
class C a where
data T a
...
...
testsuite/tests/ghc-regress/th/TH_tf3.hs
0 → 100644
View file @
cc4f1a94
{-# LANGUAGE TypeFamilies, FlexibleInstances, UndecidableInstances #-}
module
TH_tf3
where
type
family
T
a
$
(
[
d
|
foo :: T [a] ~ Bool => a -> a
foo x = x
|]
)
$
(
[
d
|
class C a
instance a ~ Int => C a
|]
)
\ No newline at end of file
testsuite/tests/ghc-regress/th/all.T
View file @
cc4f1a94
...
...
@@ -135,3 +135,4 @@ test('TH_sections', normal, compile, ['-v0'])
test
('
TH_tf1
',
normal
,
compile
,
['
-v0
'])
test
('
TH_tf2
',
normal
,
compile
,
['
-v0
'])
test
('
TH_tf3
',
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