summaryrefslogtreecommitdiff
path: root/testsuite/tests/dependent/should_compile/RaeJobTalk.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/dependent/should_compile/RaeJobTalk.hs')
-rw-r--r--testsuite/tests/dependent/should_compile/RaeJobTalk.hs11
1 files changed, 7 insertions, 4 deletions
diff --git a/testsuite/tests/dependent/should_compile/RaeJobTalk.hs b/testsuite/tests/dependent/should_compile/RaeJobTalk.hs
index 6c74e10a7c..c2173d38f5 100644
--- a/testsuite/tests/dependent/should_compile/RaeJobTalk.hs
+++ b/testsuite/tests/dependent/should_compile/RaeJobTalk.hs
@@ -6,7 +6,7 @@
DataKinds, PolyKinds , ConstraintKinds, UndecidableInstances,
FlexibleInstances, MultiParamTypeClasses, FunctionalDependencies,
FlexibleContexts, StandaloneDeriving, InstanceSigs,
- RankNTypes, UndecidableSuperClasses #-}
+ RankNTypes, UndecidableSuperClasses, StandaloneKindSignatures #-}
module RaeJobTalk where
@@ -24,7 +24,8 @@ import Data.Maybe
-- Utilities
-- Heterogeneous propositional equality
-data (a :: k1) :~~: (b :: k2) where
+type (:~~:) :: k1 -> k2 -> Type
+data a :~~: b where
HRefl :: a :~~: a
-- Type-level inequality
@@ -73,7 +74,8 @@ Nil %:++ x = x
-- Type-indexed type representations
-- Based on "A reflection on types"
-data TyCon (a :: k) where
+type TyCon :: k -> Type
+data TyCon a where
Int :: TyCon Int
Bool :: TyCon Bool
Char :: TyCon Char
@@ -103,7 +105,8 @@ type family Primitive (a :: k) :: Constraint where
Primitive (_ _) = ('False ~ 'True)
Primitive _ = (() :: Constraint)
-data TypeRep (a :: k) where
+type TypeRep :: k -> Type
+data TypeRep a where
TyCon :: forall k (a :: k). (Primitive a, Typeable k) => TyCon a -> TypeRep a
TyApp :: TypeRep a -> TypeRep b -> TypeRep (a b)