summaryrefslogtreecommitdiff
path: root/testsuite/tests/ghci/scripts
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/ghci/scripts')
-rw-r--r--testsuite/tests/ghci/scripts/T12550.stdout3
-rw-r--r--testsuite/tests/ghci/scripts/T21088.hs29
-rw-r--r--testsuite/tests/ghci/scripts/T21088.script11
-rw-r--r--testsuite/tests/ghci/scripts/T21088.stdout19
-rwxr-xr-xtestsuite/tests/ghci/scripts/all.T1
5 files changed, 62 insertions, 1 deletions
diff --git a/testsuite/tests/ghci/scripts/T12550.stdout b/testsuite/tests/ghci/scripts/T12550.stdout
index 48a1b8e11c..d753d4f666 100644
--- a/testsuite/tests/ghci/scripts/T12550.stdout
+++ b/testsuite/tests/ghci/scripts/T12550.stdout
@@ -62,7 +62,8 @@ instance Functor (URec Int) -- Defined in ‘GHC.Generics’
instance Functor (URec Word) -- Defined in ‘GHC.Generics’
instance Functor V1 -- Defined in ‘GHC.Generics’
datatypeName
- ∷ ∀ d k1 (t ∷ ★ → (k1 → ★) → k1 → ★) (f ∷ k1 → ★) (a ∷ k1).
+ ∷ ∀ {k} (d ∷ k) k1 (t ∷ k → (k1 → ★) → k1 → ★) (f ∷ k1 → ★)
+ (a ∷ k1).
Datatype d ⇒
t d f a → [Char]
type Datatype :: ∀ {k}. k → Constraint
diff --git a/testsuite/tests/ghci/scripts/T21088.hs b/testsuite/tests/ghci/scripts/T21088.hs
new file mode 100644
index 0000000000..efe4e8ab93
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T21088.hs
@@ -0,0 +1,29 @@
+{-# LANGUAGE PolyKinds, DataKinds, ScopedTypeVariables #-}
+
+module T21088 where
+
+import Data.Proxy
+ ( Proxy(..) )
+import GHC.Exts
+ ( TYPE, RuntimeRep )
+
+-- We don't change the order of quantification,
+-- so we check we are not instantiating `r1` but not `r2`,
+-- which would be quite confusing.
+foo :: forall {r1 :: RuntimeRep} (a1 :: TYPE r1)
+ {r2 :: RuntimeRep} (a2 :: TYPE r2)
+ . Proxy a1 -> Proxy a2
+foo _ = Proxy
+
+bar :: forall {r1 :: RuntimeRep} {r2 :: RuntimeRep}
+ (a1 :: TYPE r1) (a2 :: TYPE r2)
+ . Proxy a1 -> Proxy a2
+bar _ = Proxy
+
+baz :: forall {k1} (a1 :: k1) {k2} (a2 :: k2)
+ . Proxy a1 -> Proxy a2
+baz _ = Proxy
+
+quux :: forall {k1} {k2} (a1 :: k1) (a2 :: k2)
+ . Proxy a1 -> Proxy a2
+quux _ = Proxy
diff --git a/testsuite/tests/ghci/scripts/T21088.script b/testsuite/tests/ghci/scripts/T21088.script
new file mode 100644
index 0000000000..fe809b1970
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T21088.script
@@ -0,0 +1,11 @@
+:l T21088
+:type foo
+:type bar
+:type baz
+:type quux
+
+:set -fprint-explicit-kinds -fprint-explicit-runtime-reps -fprint-explicit-foralls
+:type foo
+:type bar
+:type baz
+:type quux
diff --git a/testsuite/tests/ghci/scripts/T21088.stdout b/testsuite/tests/ghci/scripts/T21088.stdout
new file mode 100644
index 0000000000..ca3c4ddcc7
--- /dev/null
+++ b/testsuite/tests/ghci/scripts/T21088.stdout
@@ -0,0 +1,19 @@
+foo :: Proxy a1 -> Proxy a2
+bar :: Proxy a1 -> Proxy a2
+baz :: forall {k1} (a1 :: k1) {k2} (a2 :: k2). Proxy a1 -> Proxy a2
+quux
+ :: forall {k1} {k2} (a1 :: k1) (a2 :: k2). Proxy a1 -> Proxy a2
+foo
+ :: forall {r1 :: RuntimeRep} (a1 :: TYPE r1) {r2 :: RuntimeRep}
+ (a2 :: TYPE r2).
+ Proxy @{TYPE r1} a1 -> Proxy @{TYPE r2} a2
+bar
+ :: forall {r1 :: RuntimeRep} {r2 :: RuntimeRep} (a1 :: TYPE r1)
+ (a2 :: TYPE r2).
+ Proxy @{TYPE r1} a1 -> Proxy @{TYPE r2} a2
+baz
+ :: forall {k1} (a1 :: k1) {k2} (a2 :: k2).
+ Proxy @{k1} a1 -> Proxy @{k2} a2
+quux
+ :: forall {k1} {k2} (a1 :: k1) (a2 :: k2).
+ Proxy @{k1} a1 -> Proxy @{k2} a2
diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T
index bccfa977e5..0f6ed54ddb 100755
--- a/testsuite/tests/ghci/scripts/all.T
+++ b/testsuite/tests/ghci/scripts/all.T
@@ -363,3 +363,4 @@ test('T20587', [extra_files(['../shell.hs'])], ghci_script,
test('T20909', normal, ghci_script, ['T20909.script'])
test('T20150', normal, ghci_script, ['T20150.script'])
test('T20974', normal, ghci_script, ['T20974.script'])
+test('T21088', normal, ghci_script, ['T21088.script'])