summaryrefslogtreecommitdiff
path: root/testsuite
diff options
context:
space:
mode:
authorsheaf <sam.derbyshire@gmail.com>2021-11-08 13:40:05 +0100
committersheaf <sam.derbyshire@gmail.com>2021-11-08 13:40:05 +0100
commit28334b475a109bdeb8d53d58c48adb1690e2c9b4 (patch)
tree9ab0bc969b97b659b62669a405397e5861cbe35d /testsuite
parent56705da84a8e954d9755270ca8bb37a43d7d03a9 (diff)
downloadhaskell-28334b475a109bdeb8d53d58c48adb1690e2c9b4.tar.gz
Default kind vars in tyfams with -XNoPolyKinds
We should still default kind variables in type families in the presence of -XNoPolyKinds, to avoid suggesting enabling -XPolyKinds just because the function arrow introduced kind variables, e.g. type family F (t :: Type) :: Type where F (a -> b) = b With -XNoPolyKinds, we should still default `r :: RuntimeRep` in `a :: TYPE r`. Fixes #20584
Diffstat (limited to 'testsuite')
-rw-r--r--testsuite/tests/indexed-types/should_compile/T17536.hs2
-rw-r--r--testsuite/tests/indexed-types/should_compile/T17536c.hs17
-rw-r--r--testsuite/tests/indexed-types/should_compile/all.T1
-rw-r--r--testsuite/tests/typecheck/should_compile/T20584.hs12
-rw-r--r--testsuite/tests/typecheck/should_compile/T20584b.hs24
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T2
6 files changed, 57 insertions, 1 deletions
diff --git a/testsuite/tests/indexed-types/should_compile/T17536.hs b/testsuite/tests/indexed-types/should_compile/T17536.hs
index b007dfecfe..7ae2ba9904 100644
--- a/testsuite/tests/indexed-types/should_compile/T17536.hs
+++ b/testsuite/tests/indexed-types/should_compile/T17536.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE DataKinds #-}
-{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE NoPolyKinds #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
diff --git a/testsuite/tests/indexed-types/should_compile/T17536c.hs b/testsuite/tests/indexed-types/should_compile/T17536c.hs
new file mode 100644
index 0000000000..860a2c357a
--- /dev/null
+++ b/testsuite/tests/indexed-types/should_compile/T17536c.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE PolyKinds #-}
+
+module T17536c where
+
+import Data.Kind
+import GHC.Exts
+
+type R :: forall (r :: RuntimeRep) -> TYPE r -> Type
+type family R r a where
+ R _ _ = Int
+
+r :: R FloatRep Float# -> Int
+r x = x
diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T
index 9e0558cf5b..d03de782c6 100644
--- a/testsuite/tests/indexed-types/should_compile/all.T
+++ b/testsuite/tests/indexed-types/should_compile/all.T
@@ -295,6 +295,7 @@ test('T17008b', normal, compile, [''])
test('T17056', normal, compile, [''])
test('T17405', normal, multimod_compile, ['T17405c', '-v0'])
test('T17536', normal, compile, [''])
+test('T17536c', normal, compile, [''])
test('T17923', normal, compile, [''])
test('T18065', normal, compile, ['-O'])
test('T18809', normal, compile, ['-O'])
diff --git a/testsuite/tests/typecheck/should_compile/T20584.hs b/testsuite/tests/typecheck/should_compile/T20584.hs
new file mode 100644
index 0000000000..2d72a3ad41
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T20584.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE Haskell2010 #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE NoPolyKinds #-}
+
+module T20584 where
+
+data Decision_Wrap
+data Decision_Map
+
+type family DecideFn p where
+ DecideFn (r -> p) = Decision_Map
+ DecideFn p = Decision_Wrap
diff --git a/testsuite/tests/typecheck/should_compile/T20584b.hs b/testsuite/tests/typecheck/should_compile/T20584b.hs
new file mode 100644
index 0000000000..a3e3287265
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T20584b.hs
@@ -0,0 +1,24 @@
+{-# LANGUAGE Haskell2010 #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
+module T20584b where
+
+import Text.Printf ( printf )
+
+secs :: Double -> String
+secs k
+ | k < 0 = '-' : secs (-k)
+ | k >= 1 = k `with` "s"
+ | k >= 1e-3 = (k*1e3) `with` "ms"
+ | k >= 1e-6 = (k*1e6) `with` "μs"
+ | k >= 1e-9 = (k*1e9) `with` "ns"
+ | k >= 1e-12 = (k*1e12) `with` "ps"
+ | k >= 1e-15 = (k*1e15) `with` "fs"
+ | k >= 1e-18 = (k*1e18) `with` "as"
+ | otherwise = printf "%g s" k
+ where with (t :: Double) (u :: String)
+ | t >= 1e9 = printf "%.4g %s" t u
+ | t >= 1e3 = printf "%.0f %s" t u
+ | t >= 1e2 = printf "%.1f %s" t u
+ | t >= 1e1 = printf "%.2f %s" t u
+ | otherwise = printf "%.3f %s" t u
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index a2bb10ba02..9aad00f982 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -806,3 +806,5 @@ test('T20241', normal, compile, [''])
test('T20187a', normal, compile, ['-Wredundant-strictness-flags'])
test('T20187b', normal, compile, ['-Wredundant-strictness-flags'])
test('T20356', normal, compile, [''])
+test('T20584', normal, compile, [''])
+test('T20584b', normal, compile, [''])