diff options
author | Richard Eisenberg <eir@cis.upenn.edu> | 2016-03-16 14:30:00 -0400 |
---|---|---|
committer | Richard Eisenberg <eir@cis.upenn.edu> | 2016-03-17 10:07:22 -0400 |
commit | b5565f1a79fd24fc45a6f1a58821a317852d4b89 (patch) | |
tree | 1b309bdfa7d842635e731151286c651343f2a783 /testsuite | |
parent | 46f9a476e17714e27d893b491cc0dcf68c745249 (diff) | |
download | haskell-b5565f1a79fd24fc45a6f1a58821a317852d4b89.tar.gz |
Fix #11711.
There were two bugs here, both simple: we need to filter out
covars before calling isMetaTyVar in the solver, and TcPat had
a tcSubType the wrong way round.
test case: dependent/should_compile/T11711
Diffstat (limited to 'testsuite')
-rw-r--r-- | testsuite/tests/dependent/should_compile/T11711.hs | 58 | ||||
-rw-r--r-- | testsuite/tests/dependent/should_compile/all.T | 1 | ||||
-rw-r--r-- | testsuite/tests/patsyn/should_fail/mono.stderr | 20 |
3 files changed, 69 insertions, 10 deletions
diff --git a/testsuite/tests/dependent/should_compile/T11711.hs b/testsuite/tests/dependent/should_compile/T11711.hs new file mode 100644 index 0000000000..633ae35e64 --- /dev/null +++ b/testsuite/tests/dependent/should_compile/T11711.hs @@ -0,0 +1,58 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE TypeSynonymInstances #-} +{-# LANGUAGE FlexibleInstances #-} + +module T11711 where + +import Data.Kind (Type) + +data (:~~:) (a :: k1) (b :: k2) where + HRefl :: a :~~: a + +data TypeRep (a :: k) where + TrTyCon :: String -> TypeRep k -> TypeRep (a :: k) + TrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). + TypeRep (a :: k1 -> k2) + -> TypeRep (b :: k1) + -> TypeRep (a b) + +class Typeable (a :: k) where + typeRep :: TypeRep a + +data TypeRepX where + TypeRepX :: forall k (a :: k). TypeRep a -> TypeRepX + +eqTypeRep :: TypeRep a -> TypeRep b -> Maybe (a :~~: b) +eqTypeRep = undefined + +typeRepKind :: forall k (a :: k). TypeRep a -> TypeRep k +typeRepKind = undefined + +instance Typeable Type where + typeRep = TrTyCon "Type" typeRep + +funResultTy :: TypeRepX -> TypeRepX -> Maybe TypeRepX +funResultTy (TypeRepX f) (TypeRepX x) + | Just HRefl <- (typeRep :: TypeRep Type) `eqTypeRep` typeRepKind f + , TRFun arg res <- f + , Just HRefl <- arg `eqTypeRep` x + = Just (TypeRepX res) + | otherwise + = Nothing + +trArrow :: TypeRep (->) +trArrow = undefined + +pattern TRFun :: forall fun. () + => forall arg res. (fun ~ (arg -> res)) + => TypeRep arg + -> TypeRep res + -> TypeRep fun +pattern TRFun arg res <- TrApp (TrApp (eqTypeRep trArrow -> Just HRefl) arg) res diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T index 783fa16f55..8ecd105a09 100644 --- a/testsuite/tests/dependent/should_compile/all.T +++ b/testsuite/tests/dependent/should_compile/all.T @@ -17,3 +17,4 @@ test('dynamic-paper', expect_fail_for(['optasm', 'optllvm']), compile, ['']) test('T11311', normal, compile, ['']) test('T11405', normal, compile, ['']) test('T11241', normal, compile, ['']) +test('T11711', normal, compile, ['']) diff --git a/testsuite/tests/patsyn/should_fail/mono.stderr b/testsuite/tests/patsyn/should_fail/mono.stderr index 2bed60eafb..20714e7565 100644 --- a/testsuite/tests/patsyn/should_fail/mono.stderr +++ b/testsuite/tests/patsyn/should_fail/mono.stderr @@ -1,12 +1,12 @@ -mono.hs:7:4: - Couldn't match type ‘Int’ with ‘Bool’ - Expected type: [Bool] - Actual type: [Int] - In the pattern: Single x - In an equation for ‘f’: f (Single x) = x +mono.hs:7:4: error: + • Couldn't match type ‘Bool’ with ‘Int’ + Expected type: [Int] + Actual type: [Bool] + • In the pattern: Single x + In an equation for ‘f’: f (Single x) = x -mono.hs:7:16: - Couldn't match expected type ‘Bool’ with actual type ‘Int’ - In the expression: x - In an equation for ‘f’: f (Single x) = x +mono.hs:7:16: error: + • Couldn't match expected type ‘Bool’ with actual type ‘Int’ + • In the expression: x + In an equation for ‘f’: f (Single x) = x |