diff options
author | Jan Stolarek <jan.stolarek@p.lodz.pl> | 2014-04-19 06:58:07 +0200 |
---|---|---|
committer | Jan Stolarek <jan.stolarek@p.lodz.pl> | 2014-04-19 11:20:51 +0200 |
commit | 1d2ffb6ab1ef973c85f893b5ea4a72cfa59ce484 (patch) | |
tree | 5f698d69fe2383300f51e71e824e86dad6cc8508 /testsuite | |
parent | 41f5b7e3e0648302b9c5dc485917a391d21d15a1 (diff) | |
download | haskell-1d2ffb6ab1ef973c85f893b5ea4a72cfa59ce484.tar.gz |
Validate inferred theta. Fixes #8883
This checks that all the required extensions are enabled for the
inferred type signature.
Updates binary and vector submodules.
Diffstat (limited to 'testsuite')
12 files changed, 38 insertions, 9 deletions
diff --git a/testsuite/tests/indexed-types/should_compile/ColInference6.hs b/testsuite/tests/indexed-types/should_compile/ColInference6.hs index 9273632e2b..bc15aa1dbf 100644 --- a/testsuite/tests/indexed-types/should_compile/ColInference6.hs +++ b/testsuite/tests/indexed-types/should_compile/ColInference6.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeFamilies, FlexibleContexts #-} module ColInference6 where diff --git a/testsuite/tests/indexed-types/should_compile/IndTypesPerf.hs b/testsuite/tests/indexed-types/should_compile/IndTypesPerf.hs index 4edcd03988..30c92c3a88 100644 --- a/testsuite/tests/indexed-types/should_compile/IndTypesPerf.hs +++ b/testsuite/tests/indexed-types/should_compile/IndTypesPerf.hs @@ -2,6 +2,8 @@ -- This used lots of memory, and took a long time to compile, with GHC 6.12: -- http://www.haskell.org/pipermail/glasgow-haskell-users/2010-May/018835.html +{-# LANGUAGE FlexibleContexts, TypeFamilies #-} + module IndTypesPerf where import IndTypesPerfMerge diff --git a/testsuite/tests/indexed-types/should_compile/IndTypesPerfMerge.hs b/testsuite/tests/indexed-types/should_compile/IndTypesPerfMerge.hs index 18ed35bdc1..dbba60d595 100644 --- a/testsuite/tests/indexed-types/should_compile/IndTypesPerfMerge.hs +++ b/testsuite/tests/indexed-types/should_compile/IndTypesPerfMerge.hs @@ -1,7 +1,7 @@ {-# LANGUAGE EmptyDataDecls, TypeFamilies, UndecidableInstances, ScopedTypeVariables, OverlappingInstances, TypeOperators, FlexibleInstances, NoMonomorphismRestriction, - MultiParamTypeClasses #-} + MultiParamTypeClasses, FlexibleContexts #-} module IndTypesPerfMerge where data a :* b = a :* b diff --git a/testsuite/tests/perf/should_run/T2902_A.hs b/testsuite/tests/perf/should_run/T2902_A.hs index c0939104f3..cb2cec990c 100644 --- a/testsuite/tests/perf/should_run/T2902_A.hs +++ b/testsuite/tests/perf/should_run/T2902_A.hs @@ -1,5 +1,5 @@ -{-# LANGUAGE UnicodeSyntax #-} +{-# LANGUAGE UnicodeSyntax, FlexibleContexts #-} module Main (main) where diff --git a/testsuite/tests/perf/should_run/T2902_B.hs b/testsuite/tests/perf/should_run/T2902_B.hs index c6558c625b..65cb1a6a90 100644 --- a/testsuite/tests/perf/should_run/T2902_B.hs +++ b/testsuite/tests/perf/should_run/T2902_B.hs @@ -1,5 +1,5 @@ -{-# LANGUAGE UnicodeSyntax #-} +{-# LANGUAGE UnicodeSyntax, FlexibleContexts #-} module Main (main) where diff --git a/testsuite/tests/perf/should_run/T5113.hs b/testsuite/tests/perf/should_run/T5113.hs index e87bcb6cad..6ad6750aab 100644 --- a/testsuite/tests/perf/should_run/T5113.hs +++ b/testsuite/tests/perf/should_run/T5113.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE BangPatterns, FlexibleContexts #-} module Main where import Data.Array.Base (unsafeRead, unsafeWrite) diff --git a/testsuite/tests/rebindable/DoRestrictedM.hs b/testsuite/tests/rebindable/DoRestrictedM.hs index dea2b1ea03..2e982c1532 100644 --- a/testsuite/tests/rebindable/DoRestrictedM.hs +++ b/testsuite/tests/rebindable/DoRestrictedM.hs @@ -1,5 +1,5 @@ {-# LANGUAGE RebindableSyntax, MultiParamTypeClasses, - FlexibleInstances #-} + FlexibleInstances, FlexibleContexts #-} -- Tests of the do-notation for the restricted monads -- We demonstrate that all ordinary monads are restricted monads, diff --git a/testsuite/tests/typecheck/should_compile/tc168.hs b/testsuite/tests/typecheck/should_compile/tc168.hs index 0aa56d169a..bd515331c4 100644 --- a/testsuite/tests/typecheck/should_compile/tc168.hs +++ b/testsuite/tests/typecheck/should_compile/tc168.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE MultiParamTypeClasses, FlexibleContexts #-} -- We want to get the type -- g :: forall a b c. C a (b,c) => a -> b diff --git a/testsuite/tests/typecheck/should_compile/tc231.hs b/testsuite/tests/typecheck/should_compile/tc231.hs index 304748994b..a7270ef769 100644 --- a/testsuite/tests/typecheck/should_compile/tc231.hs +++ b/testsuite/tests/typecheck/should_compile/tc231.hs @@ -1,5 +1,5 @@ {-# OPTIONS_GHC -ddump-types #-} -{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} +{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleContexts #-} -- See Trac #1456 diff --git a/testsuite/tests/typecheck/should_fail/T8883.hs b/testsuite/tests/typecheck/should_fail/T8883.hs new file mode 100644 index 0000000000..5b0fc5922c --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T8883.hs @@ -0,0 +1,20 @@ +{-# LANGUAGE TypeFamilies #-} + +-- Trac #8883 + +module T8883 where + +type family PF a :: * -> * + +class Regular a where + from :: a -> PF a a + +-- For fold we infer following type signature: +-- +-- fold :: (Functor (PF a), Regular a) => (PF a b -> b) -> a -> b +-- +-- However, this signature requires FlexibleContexts since the first +-- type-class constraint is not of the form (class type-variable) nor +-- (class (type-variable type1 type2 ... typen)). Since this extension +-- is not enabled compilation should fail. +fold f = f . fmap (fold f) . from diff --git a/testsuite/tests/typecheck/should_fail/T8883.stderr b/testsuite/tests/typecheck/should_fail/T8883.stderr new file mode 100644 index 0000000000..0ea136869b --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T8883.stderr @@ -0,0 +1,7 @@ + + +T8883.hs:17:1: + Non type-variable argument in the constraint: Functor (PF a) + (Use FlexibleContexts to permit this) + In the context: (Regular a, Functor (PF a)) + While checking the inferred type for ‘fold’ diff --git a/testsuite/tests/typecheck/should_fail/tcfail093.hs b/testsuite/tests/typecheck/should_fail/tcfail093.hs index 9c2d8ea80a..1f2063a1c2 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail093.hs +++ b/testsuite/tests/typecheck/should_fail/tcfail093.hs @@ -1,5 +1,5 @@ {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, - FlexibleInstances, UndecidableInstances #-} + FlexibleInstances, UndecidableInstances, FlexibleContexts #-} -- UndecidableInstances now needed because the Coverage Condition fails module ShouldFail where |