summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/T11342/T11342d.hs
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/typecheck/T11342/T11342d.hs')
-rw-r--r--testsuite/tests/typecheck/T11342/T11342d.hs31
1 files changed, 31 insertions, 0 deletions
diff --git a/testsuite/tests/typecheck/T11342/T11342d.hs b/testsuite/tests/typecheck/T11342/T11342d.hs
new file mode 100644
index 0000000000..9c973d8c8c
--- /dev/null
+++ b/testsuite/tests/typecheck/T11342/T11342d.hs
@@ -0,0 +1,31 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE UndecidableInstances #-}
+
+module T11342d where
+
+import GHC.TypeLits
+import Data.Type.Equality
+
+f1 :: CmpChar 'x' 'x' :~: EQ
+f1 = Refl
+
+f2 :: CmpChar 'x' 'y' :~: LT
+f2 = Refl
+
+f3 :: forall (a :: Char). CmpChar a a :~: EQ
+f3 = Refl
+
+testConsSymbol
+ :: '[ConsSymbol 'a' "bcd", ConsSymbol ' ' "hi mark"] :~: '["abcd", " hi mark"]
+testConsSymbol = Refl
+
+testUnconsSymbol
+ :: '[UnconsSymbol "abc", UnconsSymbol "a", UnconsSymbol ""] :~: [Just '( 'a', "bc" ), Just '( 'a', ""), Nothing]
+testUnconsSymbol = Refl
+
+testUncons :: ConsSymbol '\xD800' "foo" :~: "\55296foo"
+testUncons = Refl