summaryrefslogtreecommitdiff
path: root/testsuite/tests
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests')
-rw-r--r--testsuite/tests/ghci/scripts/T9181.stdout4
-rw-r--r--testsuite/tests/typecheck/should_compile/T19535.hs44
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T2
3 files changed, 50 insertions, 0 deletions
diff --git a/testsuite/tests/ghci/scripts/T9181.stdout b/testsuite/tests/ghci/scripts/T9181.stdout
index 8ca20e265d..89c18c2f6b 100644
--- a/testsuite/tests/ghci/scripts/T9181.stdout
+++ b/testsuite/tests/ghci/scripts/T9181.stdout
@@ -1,6 +1,8 @@
type GHC.TypeLits.AppendSymbol :: GHC.Types.Symbol
-> GHC.Types.Symbol -> GHC.Types.Symbol
type family GHC.TypeLits.AppendSymbol a b
+type GHC.TypeLits.CharToNat :: Char -> GHC.Num.Natural.Natural
+type family GHC.TypeLits.CharToNat a
type GHC.TypeLits.ConsSymbol :: Char
-> GHC.Types.Symbol -> GHC.Types.Symbol
type family GHC.TypeLits.ConsSymbol a b
@@ -22,6 +24,8 @@ type GHC.TypeLits.KnownSymbol :: GHC.Types.Symbol -> Constraint
class GHC.TypeLits.KnownSymbol n where
GHC.TypeLits.symbolSing :: GHC.TypeLits.SSymbol n
{-# MINIMAL symbolSing #-}
+type GHC.TypeLits.NatToChar :: GHC.Num.Natural.Natural -> Char
+type family GHC.TypeLits.NatToChar a
type GHC.TypeLits.SomeChar :: *
data GHC.TypeLits.SomeChar
= forall (n :: Char).
diff --git a/testsuite/tests/typecheck/should_compile/T19535.hs b/testsuite/tests/typecheck/should_compile/T19535.hs
new file mode 100644
index 0000000000..e05b599b38
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T19535.hs
@@ -0,0 +1,44 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE AllowAmbiguousTypes #-}
+
+module T19535 where
+
+import GHC.TypeNats (natVal)
+import GHC.TypeLits hiding (natVal)
+import Data.Type.Equality
+import Data.Proxy
+
+e1 :: CharToNat 'a' :~: 97
+e1 = Refl
+
+e2 :: NatToChar 120 :~: 'x'
+e2 = Refl
+
+ntc :: forall {n} c. (KnownNat n, NatToChar n ~ c) => Natural
+ntc = natVal (Proxy @n)
+
+ctn :: forall {c} n. (KnownChar c, CharToNat c ~ n) => Char
+ctn = charVal (Proxy @c)
+
+n1 :: Natural
+n1 = ntc @'z'
+
+c1 :: Char
+c1 = ctn @122
+
+ntc_ntc :: forall {n} m. (KnownNat n, NatToChar n ~ NatToChar (m + 1)) => Natural
+ntc_ntc = natVal (Proxy @n)
+
+ctn_ctn :: forall {c} d. (KnownChar c, CharToNat c ~ (CharToNat d + 1)) => Char
+ctn_ctn = charVal (Proxy @c)
+
+n2 :: Natural
+n2 = ntc_ntc @119
+
+c2 :: Char
+c2 = ctn_ctn @'w'
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 6d3505c33d..392f6fb40c 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -777,3 +777,5 @@ test('InlinePatSyn_ExplicitBidiMatcher', [], makefile_test, [])
test('T18467', normal, compile, [''])
test('T19315', normal, compile, [''])
+
+test('T19535', normal, compile, [''])