diff options
Diffstat (limited to 'testsuite/tests/patsyn')
-rw-r--r-- | testsuite/tests/patsyn/should_compile/T10997_1.hs | 1 | ||||
-rw-r--r-- | testsuite/tests/patsyn/should_compile/T10997_1a.hs | 1 | ||||
-rw-r--r-- | testsuite/tests/patsyn/should_compile/T12698.hs | 1 | ||||
-rw-r--r-- | testsuite/tests/patsyn/should_compile/T14394.script | 3 | ||||
-rw-r--r-- | testsuite/tests/patsyn/should_compile/T14394.stdout | 6 | ||||
-rw-r--r-- | testsuite/tests/patsyn/should_fail/T14507.hs | 1 | ||||
-rw-r--r-- | testsuite/tests/patsyn/should_fail/T14507.stderr | 2 | ||||
-rw-r--r-- | testsuite/tests/patsyn/should_fail/T15694.hs | 1 | ||||
-rw-r--r-- | testsuite/tests/patsyn/should_fail/T15694.stderr | 4 | ||||
-rw-r--r-- | testsuite/tests/patsyn/should_fail/T15695.hs | 1 | ||||
-rw-r--r-- | testsuite/tests/patsyn/should_fail/T15695.stderr | 12 |
11 files changed, 20 insertions, 13 deletions
diff --git a/testsuite/tests/patsyn/should_compile/T10997_1.hs b/testsuite/tests/patsyn/should_compile/T10997_1.hs index 4cc4b40eec..7855343d5a 100644 --- a/testsuite/tests/patsyn/should_compile/T10997_1.hs +++ b/testsuite/tests/patsyn/should_compile/T10997_1.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} module T10997_1 where import T10997_1a diff --git a/testsuite/tests/patsyn/should_compile/T10997_1a.hs b/testsuite/tests/patsyn/should_compile/T10997_1a.hs index 11af525c53..bf69c41fa3 100644 --- a/testsuite/tests/patsyn/should_compile/T10997_1a.hs +++ b/testsuite/tests/patsyn/should_compile/T10997_1a.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# LANGUAGE PatternSynonyms, ViewPatterns, ConstraintKinds, TypeFamilies, PolyKinds, KindSignatures #-} module T10997_1a where diff --git a/testsuite/tests/patsyn/should_compile/T12698.hs b/testsuite/tests/patsyn/should_compile/T12698.hs index 68cd817677..bb2bccbb44 100644 --- a/testsuite/tests/patsyn/should_compile/T12698.hs +++ b/testsuite/tests/patsyn/should_compile/T12698.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# Language ViewPatterns, TypeOperators, KindSignatures, PolyKinds, StandaloneDeriving, GADTs, RebindableSyntax, RankNTypes, LambdaCase, PatternSynonyms, TypeApplications #-} diff --git a/testsuite/tests/patsyn/should_compile/T14394.script b/testsuite/tests/patsyn/should_compile/T14394.script index 208df0ca36..29f738bbbd 100644 --- a/testsuite/tests/patsyn/should_compile/T14394.script +++ b/testsuite/tests/patsyn/should_compile/T14394.script @@ -1,3 +1,4 @@ +:set -XHaskell2010 :set -XPatternSynonyms -XGADTs -XViewPatterns -XScopedTypeVariables import Data.Type.Equality @@ -21,4 +22,4 @@ data S a where { MkS :: Ord a => a -> S a } pattern Bam x y <- (MkS (x::a), MkS (y::a)) :info Bam --- Expecting only one provided Ord constraint
\ No newline at end of file +-- Expecting only one provided Ord constraint diff --git a/testsuite/tests/patsyn/should_compile/T14394.stdout b/testsuite/tests/patsyn/should_compile/T14394.stdout index 83e745c60a..5838db9f43 100644 --- a/testsuite/tests/patsyn/should_compile/T14394.stdout +++ b/testsuite/tests/patsyn/should_compile/T14394.stdout @@ -1,10 +1,10 @@ pattern Foo :: () => (b ~ a) => a :~~: b - -- Defined at <interactive>:5:1 + -- Defined at <interactive>:6:1 pattern Bar :: forall {k1} {k2} {a :: k1} {b :: k2}. () => (k2 ~ k1, b ~~ a) => a :~~: b - -- Defined at <interactive>:11:1 + -- Defined at <interactive>:12:1 pattern Bam :: () => Ord a => a -> a -> (S a, S a) - -- Defined at <interactive>:21:1 + -- Defined at <interactive>:22:1 diff --git a/testsuite/tests/patsyn/should_fail/T14507.hs b/testsuite/tests/patsyn/should_fail/T14507.hs index 9599b73c77..b803f50734 100644 --- a/testsuite/tests/patsyn/should_fail/T14507.hs +++ b/testsuite/tests/patsyn/should_fail/T14507.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# Language PatternSynonyms, ViewPatterns, GADTs, ConstraintKinds, RankNTypes, PolyKinds, ScopedTypeVariables, DataKinds, TypeOperators, TypeApplications, TypeFamilies, TypeFamilyDependencies #-} diff --git a/testsuite/tests/patsyn/should_fail/T14507.stderr b/testsuite/tests/patsyn/should_fail/T14507.stderr index 1279ec1e4e..beeb4de685 100644 --- a/testsuite/tests/patsyn/should_fail/T14507.stderr +++ b/testsuite/tests/patsyn/should_fail/T14507.stderr @@ -1,5 +1,5 @@ -T14507.hs:20:9: error: +T14507.hs:21:9: error: • Iceland Jack! Iceland Jack! Stop torturing me! Pattern-bound variable x :: TypeRep a has a type that mentions pattern-bound coercion: co diff --git a/testsuite/tests/patsyn/should_fail/T15694.hs b/testsuite/tests/patsyn/should_fail/T15694.hs index 915ad7e7dd..44b3c7a8d6 100644 --- a/testsuite/tests/patsyn/should_fail/T15694.hs +++ b/testsuite/tests/patsyn/should_fail/T15694.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# Language RankNTypes, PatternSynonyms, TypeOperators, DataKinds, PolyKinds, KindSignatures, GADTs #-} module T15694 where diff --git a/testsuite/tests/patsyn/should_fail/T15694.stderr b/testsuite/tests/patsyn/should_fail/T15694.stderr index 2b0b7b77b1..2c3421321c 100644 --- a/testsuite/tests/patsyn/should_fail/T15694.stderr +++ b/testsuite/tests/patsyn/should_fail/T15694.stderr @@ -1,8 +1,8 @@ -T15694.hs:22:35: error: +T15694.hs:23:35: error: • Expected kind ‘k1 -> k0’, but ‘f a1’ has kind ‘ks’ ‘ks’ is a rigid type variable bound by an explicit forall ks k (f :: k -> ks) (a1 :: k) (ctx :: Ctx ks) (ks1 :: Type) k1 (a2 :: k1) (ctx1 :: Ctx ks1) a3 - at T15694.hs:18:30-31 + at T15694.hs:19:30-31 • In the first argument of ‘(~~)’, namely ‘f a1 a2’ diff --git a/testsuite/tests/patsyn/should_fail/T15695.hs b/testsuite/tests/patsyn/should_fail/T15695.hs index de8035c728..ebccb8a02e 100644 --- a/testsuite/tests/patsyn/should_fail/T15695.hs +++ b/testsuite/tests/patsyn/should_fail/T15695.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Haskell2010 #-} {-# Language RankNTypes, PatternSynonyms, DataKinds, PolyKinds, GADTs, TypeOperators, MultiParamTypeClasses, TypeFamilies, TypeSynonymInstances, FlexibleInstances, InstanceSigs, FlexibleContexts #-} diff --git a/testsuite/tests/patsyn/should_fail/T15695.stderr b/testsuite/tests/patsyn/should_fail/T15695.stderr index 9418f15a71..555c004360 100644 --- a/testsuite/tests/patsyn/should_fail/T15695.stderr +++ b/testsuite/tests/patsyn/should_fail/T15695.stderr @@ -1,5 +1,5 @@ -T15695.hs:39:14: warning: [-Wdeferred-type-errors (in -Wdefault)] +T15695.hs:40:14: warning: [-Wdeferred-type-errors (in -Wdefault)] • Could not deduce: a2 ~ NA 'VO from the context: ((* -> * -> *) ~ (k -> k1 -> *), Either ~~ f, ctx ~~ (a2 ':&: (a3 ':&: 'E)), f a2 ~~ f1, f1 a3 ~~ a4) @@ -12,7 +12,7 @@ T15695.hs:39:14: warning: [-Wdeferred-type-errors (in -Wdefault)] f a1 ~~ f1, f1 a2 ~~ a3) => a3 -> ApplyT kind a b, in an equation for ‘from'’ - at T15695.hs:39:8-21 + at T15695.hs:40:8-21 Expected: a4 Actual: Either (NA 'VO) a3 ‘a2’ is a rigid type variable bound by @@ -25,15 +25,15 @@ T15695.hs:39:14: warning: [-Wdeferred-type-errors (in -Wdefault)] f a1 ~~ f1, f1 a2 ~~ a3) => a3 -> ApplyT kind a b, in an equation for ‘from'’ - at T15695.hs:39:8-21 + at T15695.hs:40:8-21 • In the pattern: Left a In the pattern: ASSO (Left a) In an equation for ‘from'’: from' (ASSO (Left a)) = Here (a :* Nil) • Relevant bindings include from' :: ApplyT (* -> * -> *) Either ctx -> NS (NP NA) '[ '[ 'VO]] - (bound at T15695.hs:39:1) + (bound at T15695.hs:40:1) -T15695.hs:40:33: warning: [-Wdeferred-type-errors (in -Wdefault)] +T15695.hs:41:33: warning: [-Wdeferred-type-errors (in -Wdefault)] • Couldn't match type: a0 : as0 with: '[] Expected: NS (NP NA) '[] @@ -44,4 +44,4 @@ T15695.hs:40:33: warning: [-Wdeferred-type-errors (in -Wdefault)] from' (ASSO (Right b)) = There (Here undefined) • Relevant bindings include from' :: ApplyT (* -> * -> *) Either ctx -> NS (NP NA) '[ '[ 'VO]] - (bound at T15695.hs:39:1) + (bound at T15695.hs:40:1) |