summaryrefslogtreecommitdiff
path: root/testsuite/tests
diff options
context:
space:
mode:
authorRyan Scott <ryan.gl.scott@gmail.com>2020-04-07 18:08:17 -0400
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-04-12 11:22:10 -0400
commit54ca66a7d30d7f7cfbf3753ebe547f5a20d76b96 (patch)
treeaf83038fc466f23590bc9c66964f42219fd8c8cd /testsuite/tests
parent0efaf301fec9ed9ea827392cbe03de3335e995c7 (diff)
downloadhaskell-54ca66a7d30d7f7cfbf3753ebe547f5a20d76b96.tar.gz
Use conLikeUserTyVarBinders to quantify field selector types
This patch: 1. Writes up a specification for how the types of top-level field selectors should be determined in a new section of the GHC User's Guide, and 2. Makes GHC actually implement that specification by using `conLikeUserTyVarBinders` in `mkOneRecordSelector` to preserve the order and specificity of type variables written by the user. Fixes #18023.
Diffstat (limited to 'testsuite/tests')
-rw-r--r--testsuite/tests/typecheck/should_compile/T18023.hs34
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T1
2 files changed, 35 insertions, 0 deletions
diff --git a/testsuite/tests/typecheck/should_compile/T18023.hs b/testsuite/tests/typecheck/should_compile/T18023.hs
new file mode 100644
index 0000000000..4bc5c6eede
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T18023.hs
@@ -0,0 +1,34 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
+module T18023 where
+
+import Data.Kind
+import Data.Proxy
+
+newtype N :: Type -> Type -> Type where
+ MkN :: forall b a. { unN :: Either a b } -> N a b
+
+toN :: Either Int Bool -> N Int Bool
+toN = MkN @Bool @Int
+
+fromN :: N Int Bool -> Either Int Bool
+fromN = unN @Bool @Int
+
+newtype P a = MkP { unP :: Proxy a }
+
+toPTrue :: Proxy True -> P True
+toPTrue = MkP @True
+
+fromPTrue :: P True -> Proxy True
+fromPTrue = unP @True
+
+newtype P2 a b = MkP2 { unP2 :: (Proxy a, Proxy b) }
+
+toP2True :: (Proxy True, Proxy True) -> P2 True True
+toP2True = MkP2 @True @True
+
+fromP2True :: P2 True True -> (Proxy True, Proxy True)
+fromP2True = unP2 @True @True
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 9b60c6cfb0..04a45f6008 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -702,3 +702,4 @@ test('T17792', normal, compile, [''])
test('T17024', normal, compile, [''])
test('T17021a', normal, compile, [''])
test('T18005', normal, compile, [''])
+test('T18023', normal, compile, [''])