diff --git a/ghc/tests/typecheck/should_compile/tc005.stderr b/ghc/tests/typecheck/should_compile/tc005.stderr index 12f3124dccee74a4ea3a3c622172c4b70d5eab94..ba482968e668e0a05196033e910043160b337a3a 100644 --- a/ghc/tests/typecheck/should_compile/tc005.stderr +++ b/ghc/tests/typecheck/should_compile/tc005.stderr @@ -1,3 +1,3 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed g; -1 g :: __forall [t _116] {PrelBase.Num t} => ([t], _116) -> t ; +1 g :: __forall [t t1] {PrelBase.Num t} => ([t], t1) -> t ; diff --git a/ghc/tests/typecheck/should_compile/tc015.stderr b/ghc/tests/typecheck/should_compile/tc015.stderr index 0bec60afbcb46b3c38a652132db7ae81f1bf53e8..251f2ec94d60c788be3009acb4c2cdb7e7a644e5 100644 --- a/ghc/tests/typecheck/should_compile/tc015.stderr +++ b/ghc/tests/typecheck/should_compile/tc015.stderr @@ -1,3 +1,3 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed u; -1 u :: __forall [t _116 _1161] => t -> (_116, _1161) -> t ; +1 u :: __forall [t t1 t2] => t -> (t1, t2) -> t ; diff --git a/ghc/tests/typecheck/should_compile/tc016.stderr b/ghc/tests/typecheck/should_compile/tc016.stderr index 79c6d1d90a99147bdeb45e7aed602e43c82a5586..b470238db59a3994ddf56c99382a90dbba734152 100644 --- a/ghc/tests/typecheck/should_compile/tc016.stderr +++ b/ghc/tests/typecheck/should_compile/tc016.stderr @@ -1,3 +1,3 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed f; -1 f :: __forall [t _116] => t -> _116 -> t ; +1 f :: __forall [t t1] => t -> t1 -> t ; diff --git a/ghc/tests/typecheck/should_compile/tc021.stderr b/ghc/tests/typecheck/should_compile/tc021.stderr index d302f76e16299b27db9b037d392deb2c7b6a117e..787fd539837b66344558b2b45922f7ffd5fe04ea 100644 --- a/ghc/tests/typecheck/should_compile/tc021.stderr +++ b/ghc/tests/typecheck/should_compile/tc021.stderr @@ -1,5 +1,5 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed a f x; -1 a :: __forall [t _116] => (t, _116) ; -1 f :: __forall [t _116 _1161] => t -> (_116, _1161) ; +1 a :: __forall [t t1] => (t, t1) ; +1 f :: __forall [t t1 t2] => t -> (t1, t2) ; 1 x :: __forall [t] => t ; diff --git a/ghc/tests/typecheck/should_compile/tc023.stderr b/ghc/tests/typecheck/should_compile/tc023.stderr index 9e7987a06a78260b6e9b2f0b9fd973b8a8021386..eeaa682cab63e1db12f9a3f8e3c464df80485dac 100644 --- a/ghc/tests/typecheck/should_compile/tc023.stderr +++ b/ghc/tests/typecheck/should_compile/tc023.stderr @@ -1,5 +1,5 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed k main s; -1 k :: __forall [t _116] => t -> _116 -> t ; +1 k :: __forall [t t1] => t -> t1 -> t ; 1 main :: __forall [t] => t -> t ; -1 s :: __forall [t _116 _1161] => (_1161 -> _116 -> t) -> (_1161 -> _116) -> _1161 -> t ; +1 s :: __forall [t t1 t2] => (t2 -> t1 -> t) -> (t2 -> t1) -> t2 -> t ; diff --git a/ghc/tests/typecheck/should_compile/tc024.stderr b/ghc/tests/typecheck/should_compile/tc024.stderr index 9e7987a06a78260b6e9b2f0b9fd973b8a8021386..eeaa682cab63e1db12f9a3f8e3c464df80485dac 100644 --- a/ghc/tests/typecheck/should_compile/tc024.stderr +++ b/ghc/tests/typecheck/should_compile/tc024.stderr @@ -1,5 +1,5 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed k main s; -1 k :: __forall [t _116] => t -> _116 -> t ; +1 k :: __forall [t t1] => t -> t1 -> t ; 1 main :: __forall [t] => t -> t ; -1 s :: __forall [t _116 _1161] => (_1161 -> _116 -> t) -> (_1161 -> _116) -> _1161 -> t ; +1 s :: __forall [t t1 t2] => (t2 -> t1 -> t) -> (t2 -> t1) -> t2 -> t ; diff --git a/ghc/tests/typecheck/should_compile/tc034.stderr b/ghc/tests/typecheck/should_compile/tc034.stderr index 1ec12a9b46a6491118dd31a31500b79b855da9e4..5c3bed42a493a693e4a9c73e23e7fb141bd5b393 100644 --- a/ghc/tests/typecheck/should_compile/tc034.stderr +++ b/ghc/tests/typecheck/should_compile/tc034.stderr @@ -1,5 +1,5 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed g AList{ANull ANode} IntList; +__export ShouldSucceed AList{ANull ANode} IntList g; 1 data AList a = ANull | ANode a (AList a) ; 1 g :: __forall [t] {PrelBase.Num t} => AList PrelBase.Bool -> t ; 1 type IntList = AList PrelBase.Int ; diff --git a/ghc/tests/typecheck/should_compile/tc035.stderr b/ghc/tests/typecheck/should_compile/tc035.stderr index 4d85e65710c40d19ab649163224738293148bb63..55de03e05c6f43940016de11c61bf27e9628ff01 100644 --- a/ghc/tests/typecheck/should_compile/tc035.stderr +++ b/ghc/tests/typecheck/should_compile/tc035.stderr @@ -1,5 +1,5 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed g AnnExpr Expr{Var App}; +__export ShouldSucceed AnnExpr Expr{Var App} g; 1 data Expr a = Var [PrelBase.Char] | App (AnnExpr a) (AnnExpr a) ; 1 g :: __forall [a] => (a, Expr a) -> [[PrelBase.Char]] ; 1 type AnnExpr a = (a, Expr a) ; diff --git a/ghc/tests/typecheck/should_compile/tc037.stderr b/ghc/tests/typecheck/should_compile/tc037.stderr index 6c4a4937064f2df3357dd097f45b5f38439f3a1f..5b34e0d2948f4842b02c52e3d373a653e04baa8a 100644 --- a/ghc/tests/typecheck/should_compile/tc037.stderr +++ b/ghc/tests/typecheck/should_compile/tc037.stderr @@ -1,5 +1,5 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed Eq'{deq}; -instance __forall [a] {Eq' a} => {Eq' [a]} = _gEq'_91_93; -1 _gEq'_91_93 :: __forall [a] {Eq' a} => {Eq' [a]} ; -1 class Eq' a where {deq :: a -> a -> PrelBase.Bool} ; +__export ShouldSucceed Eqzq{deq}; +instance __forall [a] {Eqzq a} => {Eqzq [a]} = zdfEqzqZMZN; +1 class Eqzq a where {deq :: a -> a -> PrelBase.Bool} ; +1 zdfEqzqZMZN :: __forall [a] {Eqzq a} => {Eqzq [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc041.stderr b/ghc/tests/typecheck/should_compile/tc041.stderr index 552aa395357df9bb23cb8e34661eb139155bae6e..b29c3bd83f2d4405ca5dc0f550cbf5a12c787eb3 100644 --- a/ghc/tests/typecheck/should_compile/tc041.stderr +++ b/ghc/tests/typecheck/should_compile/tc041.stderr @@ -1,6 +1,6 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f H{op1}; -instance {H PrelBase.Bool} = _fHBool; -1 _fHBool :: {H PrelBase.Bool} ; +__export ShouldSucceed H{op1} f; +instance {H PrelBase.Bool} = zdfHBool; 1 class H a where {op1 :: a -> a -> a} ; 1 f :: PrelBase.Bool -> PrelBase.Int -> PrelBase.Bool ; +1 zdfHBool :: {H PrelBase.Bool} ; diff --git a/ghc/tests/typecheck/should_compile/tc042.stderr b/ghc/tests/typecheck/should_compile/tc042.stderr index cdba6f18c839fd3148f33bcdbd864a89750663b9..b9fff93f25a0ecebb0dfbacd0e2759afbcaba569 100644 --- a/ghc/tests/typecheck/should_compile/tc042.stderr +++ b/ghc/tests/typecheck/should_compile/tc042.stderr @@ -1,11 +1,11 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed add app before flatten idb idl lEngth nUll neg rEverse sUm swap Boolean{FF TT} List{Nil Cons} Nat{Zero Succ} Pair{Mkpair} Tree{Leaf Node}; +__export ShouldSucceed Boolean{FF TT} List{Nil Cons} Nat{ZZero Succ} Pair{Mkpair} Tree{Leaf Node} add app before flatten idb idl lEngth nUll neg rEverse sUm swap; 1 add :: Nat -> Nat -> Nat ; 1 app :: __forall [alpha] => List alpha -> List alpha -> List alpha ; 1 before :: List Nat -> List Nat ; 1 data Boolean = FF | TT ; 1 data List alpha = Nil | Cons alpha (List alpha) ; -1 data Nat = Zero | Succ Nat ; +1 data Nat = ZZero | Succ Nat ; 1 data Pair a b = Mkpair a b ; 1 data Tree t = Leaf t | Node (Tree t) (Tree t) ; 1 flatten :: __forall [alpha] => Tree alpha -> List alpha ; diff --git a/ghc/tests/typecheck/should_compile/tc043.stderr b/ghc/tests/typecheck/should_compile/tc043.stderr index bc905fee024ab10760bd81b6878385db3afc6fc4..59e5b4cf1c5c51bf09752c72d5b5e783e6eeb486 100644 --- a/ghc/tests/typecheck/should_compile/tc043.stderr +++ b/ghc/tests/typecheck/should_compile/tc043.stderr @@ -1,9 +1,9 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f A{op1} B{op2}; -instance {A PrelBase.Int} = _fAInt; -instance __forall [a] {B a} => {B [a]} = _gB_91_93; -1 _fAInt :: {A PrelBase.Int} ; -1 _gB_91_93 :: __forall [a] {B a} => {B [a]} ; +__export ShouldSucceed A{op1} B{op2} f; +instance {A PrelBase.Int} = zdfAInt; +instance __forall [a] {B a} => {B [a]} = zdfBZMZN; 1 class A a where {op1 :: a} ; 1 class B b where {op2 :: b -> PrelBase.Int} ; 1 f :: __forall [t a] {A a} => t -> a ; +1 zdfAInt :: {A PrelBase.Int} ; +1 zdfBZMZN :: __forall [a] {B a} => {B [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc044.stderr b/ghc/tests/typecheck/should_compile/tc044.stderr index ca6a89a1de095511da696a12416f0488c0da23b1..4205cb19cf57d3cddc664f92f153a2fcaccf8d18 100644 --- a/ghc/tests/typecheck/should_compile/tc044.stderr +++ b/ghc/tests/typecheck/should_compile/tc044.stderr @@ -1,3 +1,3 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed f; -1 f :: __forall [t] => t -> PrelBase.() ; +1 f :: __forall [t] => t -> PrelBase.Z0T ; diff --git a/ghc/tests/typecheck/should_compile/tc045.stderr b/ghc/tests/typecheck/should_compile/tc045.stderr index 6b2d62d09c38def5bd95840f13c751179c711fe3..e371b203676ffc7f8309fb898947bcbbd5169eb8 100644 --- a/ghc/tests/typecheck/should_compile/tc045.stderr +++ b/ghc/tests/typecheck/should_compile/tc045.stderr @@ -1,8 +1,8 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed B{op2} C{op1}; -instance __forall [a] {B a} => {B [a]} = _gB_91_93; -instance __forall [a] => {C [a]} = _gC_91_93; -1 _gB_91_93 :: __forall [a] {B a, C [a]} => {B [a]} ; -1 _gC_91_93 :: __forall [a] => {C [a]} ; +instance __forall [a] {B a} => {B [a]} = zdfBZMZN; +instance __forall [a] => {C [a]} = zdfCZMZN; 1 class {C a} => B a where {op2 :: a -> a -> a} ; 1 class C a where {op1 :: a -> a} ; +1 zdfBZMZN :: __forall [a] {B a, C [a]} => {B [a]} ; +1 zdfCZMZN :: __forall [a] => {C [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc047.stderr b/ghc/tests/typecheck/should_compile/tc047.stderr index 78107a38013f9de4b5cf2e1fa07985ed0aed8ec0..d0cc01fc5f1e8098497f625d9b3d5f028ffcdf94 100644 --- a/ghc/tests/typecheck/should_compile/tc047.stderr +++ b/ghc/tests/typecheck/should_compile/tc047.stderr @@ -1,6 +1,6 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f mp sd OL; -1 f :: __forall [t _116 _1161] => t -> [(_116, _1161)] -> [_1161] ; -1 mp :: __forall [t _116] => (_116 -> t) -> [_116] -> [t] ; -1 sd :: __forall [t _116] => (_116, t) -> t ; +__export ShouldSucceed OL f mp sd; +1 f :: __forall [t t1 t2] => t -> [(t1, t2)] -> [t2] ; +1 mp :: __forall [t t1] => (t1 -> t) -> [t1] -> [t] ; +1 sd :: __forall [t t1] => (t1, t) -> t ; 1 type OL a = [a] ; diff --git a/ghc/tests/typecheck/should_compile/tc048.stderr b/ghc/tests/typecheck/should_compile/tc048.stderr index 72be5f63745ddf683d9989c1f7f26f3cef2229e6..4d6ad93b5c3907666ecf2d872a50257c9d51a4df 100644 --- a/ghc/tests/typecheck/should_compile/tc048.stderr +++ b/ghc/tests/typecheck/should_compile/tc048.stderr @@ -1,9 +1,9 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed mAp ranAFE ranOAL sNd AFE{MkAFE} FG{MkFG} OL{MkOL}; +__export ShouldSucceed AFE{MkAFE} FG{MkFG} OL{MkOL} mAp ranAFE ranOAL sNd; 1 data AFE n a b = MkAFE (OL (n, FG a b)) ; 1 data FG a b = MkFG (OL (a, b)) ; 1 data OL a = MkOL [a] ; -1 mAp :: __forall [t _116] => (_116 -> t) -> [_116] -> [t] ; +1 mAp :: __forall [t t1] => (t1 -> t) -> [t1] -> [t] ; 1 ranAFE :: __forall [n a b] => AFE n a b -> [FG a b] ; 1 ranOAL :: __forall [a v] => OL (a, v) -> [v] ; -1 sNd :: __forall [t _116] => (_116, t) -> t ; +1 sNd :: __forall [t t1] => (t1, t) -> t ; diff --git a/ghc/tests/typecheck/should_compile/tc050.stderr b/ghc/tests/typecheck/should_compile/tc050.stderr index 43a7fd395b1f274a4acc5c23c393881ac15d69b4..033ba556e7df5579f236adbf128508d630d7c43d 100644 --- a/ghc/tests/typecheck/should_compile/tc050.stderr +++ b/ghc/tests/typecheck/should_compile/tc050.stderr @@ -1,9 +1,9 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f g Foo{o_and}; -instance {Foo PrelBase.Bool} = _fFooBool; -instance {Foo PrelBase.Int} = _fFooInt; -1 _fFooBool :: {Foo PrelBase.Bool} ; -1 _fFooInt :: {Foo PrelBase.Int} ; +__export ShouldSucceed Foo{o_and} f g; +instance {Foo PrelBase.Bool} = zdfFooBool; +instance {Foo PrelBase.Int} = zdfFooInt; 1 class Foo a where {o_and :: a -> a -> a} ; 1 f :: __forall [t] => PrelBase.Bool -> t -> PrelBase.Bool ; 1 g :: __forall [t a] {PrelBase.Num a, Foo a} => a -> t -> a ; +1 zdfFooBool :: {Foo PrelBase.Bool} ; +1 zdfFooInt :: {Foo PrelBase.Int} ; diff --git a/ghc/tests/typecheck/should_compile/tc051.stderr b/ghc/tests/typecheck/should_compile/tc051.stderr index 9e88ca9a791aa2e2799a816635ddcb65433bdadf..bd3569ae3a8b0aca9496ed388e747623ad9eaf31 100644 --- a/ghc/tests/typecheck/should_compile/tc051.stderr +++ b/ghc/tests/typecheck/should_compile/tc051.stderr @@ -1,10 +1,10 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed Eq'{doubleeq} Ord'{lt}; -instance {Eq' PrelBase.Int} = _fEq'Int; -instance {Ord' PrelBase.Int} = _fOrd'Int; -instance __forall [a] {Eq' a} => {Eq' [a]} = _gEq'_91_93; -1 _fEq'Int :: {Eq' PrelBase.Int} ; -1 _fOrd'Int :: {Ord' PrelBase.Int} ; -1 _gEq'_91_93 :: __forall [a] {Eq' a} => {Eq' [a]} ; -1 class Eq' a where {doubleeq :: a -> a -> PrelBase.Bool} ; -1 class {Eq' a} => Ord' a where {lt :: a -> a -> PrelBase.Bool} ; +__export ShouldSucceed Eqzq{doubleeq} Ordzq{lt}; +instance {Eqzq PrelBase.Int} = zdfEqzqInt; +instance __forall [a] {Eqzq a} => {Eqzq [a]} = zdfEqzqZMZN; +instance {Ordzq PrelBase.Int} = zdfOrdzqInt; +1 class Eqzq a where {doubleeq :: a -> a -> PrelBase.Bool} ; +1 class {Eqzq a} => Ordzq a where {lt :: a -> a -> PrelBase.Bool} ; +1 zdfEqzqInt :: {Eqzq PrelBase.Int} ; +1 zdfEqzqZMZN :: __forall [a] {Eqzq a} => {Eqzq [a]} ; +1 zdfOrdzqInt :: {Ordzq PrelBase.Int} ; diff --git a/ghc/tests/typecheck/should_compile/tc053.stderr b/ghc/tests/typecheck/should_compile/tc053.stderr index 05c54ff2783ffbf886a93b90f1a2a58dd5edab21..204a1797f94484788906036194203dfd73a130ce 100644 --- a/ghc/tests/typecheck/should_compile/tc053.stderr +++ b/ghc/tests/typecheck/should_compile/tc053.stderr @@ -1,8 +1,8 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f Eq'{deq}; -instance {Eq' PrelBase.Int} = _fEq'Int; -instance __forall [a] {Eq' a} => {Eq' [a]} = _gEq'_91_93; -1 _fEq'Int :: {Eq' PrelBase.Int} ; -1 _gEq'_91_93 :: __forall [a] {Eq' a} => {Eq' [a]} ; -1 class Eq' a where {deq :: a -> a -> PrelBase.Bool} ; -1 f :: __forall [t] {PrelBase.Num t, Eq' [t]} => [t] -> PrelBase.Bool ; +__export ShouldSucceed Eqzq{deq} f; +instance {Eqzq PrelBase.Int} = zdfEqzqInt; +instance __forall [a] {Eqzq a} => {Eqzq [a]} = zdfEqzqZMZN; +1 class Eqzq a where {deq :: a -> a -> PrelBase.Bool} ; +1 f :: __forall [t] {PrelBase.Num t, Eqzq [t]} => [t] -> PrelBase.Bool ; +1 zdfEqzqInt :: {Eqzq PrelBase.Int} ; +1 zdfEqzqZMZN :: __forall [a] {Eqzq a} => {Eqzq [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc054.stderr b/ghc/tests/typecheck/should_compile/tc054.stderr index 46806e2ed84aa064baab41da683d87310142aae7..c0af51703c70baf348ae3620f1f17d3ab371ed70 100644 --- a/ghc/tests/typecheck/should_compile/tc054.stderr +++ b/ghc/tests/typecheck/should_compile/tc054.stderr @@ -1,9 +1,9 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f Eq'{doubleeq} Ord'{lt}; -instance {Eq' PrelBase.Int} = _fEq'Int; -instance {Ord' PrelBase.Int} = _fOrd'Int; -1 _fEq'Int :: {Eq' PrelBase.Int} ; -1 _fOrd'Int :: {Ord' PrelBase.Int} ; -1 class Eq' a where {doubleeq :: a -> a -> PrelBase.Bool} ; -1 class {Eq' a} => Ord' a where {lt :: a -> a -> PrelBase.Bool} ; -1 f :: __forall [t a] {PrelBase.Num a, Ord' a} => a -> t -> PrelBase.Bool ; +__export ShouldSucceed Eqzq{doubleeq} Ordzq{lt} f; +instance {Eqzq PrelBase.Int} = zdfEqzqInt; +instance {Ordzq PrelBase.Int} = zdfOrdzqInt; +1 class Eqzq a where {doubleeq :: a -> a -> PrelBase.Bool} ; +1 class {Eqzq a} => Ordzq a where {lt :: a -> a -> PrelBase.Bool} ; +1 f :: __forall [t a] {PrelBase.Num a, Ordzq a} => a -> t -> PrelBase.Bool ; +1 zdfEqzqInt :: {Eqzq PrelBase.Int} ; +1 zdfOrdzqInt :: {Ordzq PrelBase.Int} ; diff --git a/ghc/tests/typecheck/should_compile/tc055.stderr b/ghc/tests/typecheck/should_compile/tc055.stderr index c883b4872789db1fef255d9be5831adb35a943a6..40424478ceb75e95309fcae61b362acf35e2472e 100644 --- a/ghc/tests/typecheck/should_compile/tc055.stderr +++ b/ghc/tests/typecheck/should_compile/tc055.stderr @@ -1,4 +1,4 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed x y; -1 x :: __forall [t _116] => t -> t ; -1 y :: __forall [t _116] => _116 -> _116 ; +1 x :: __forall [t t1] => t -> t ; +1 y :: __forall [t t1] => t1 -> t1 ; diff --git a/ghc/tests/typecheck/should_compile/tc056.stderr b/ghc/tests/typecheck/should_compile/tc056.stderr index 7f187542bd95ae2655f295766fbc5b5c691e0fef..e856eb1f439b168b39d768733c591ba47f53358a 100644 --- a/ghc/tests/typecheck/should_compile/tc056.stderr +++ b/ghc/tests/typecheck/should_compile/tc056.stderr @@ -1,13 +1,15 @@ - -tc056.hs:15: Warning: - Duplicate class assertion `Eq' a' in the context: (Eq' a, Eq' a) => + +tc056.hs:15: + Warning: Duplicate class assertion `Eq' a' in the context: + (Eq' a, Eq' a) => ... + ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f Eq'{doubleeq} Ord'{lt}; -instance {Eq' PrelBase.Int} = _fEq'Int; -instance __forall [a] {Eq' a, Eq' a} => {Eq' [a]} = _gEq'_91_93; -1 _fEq'Int :: {Eq' PrelBase.Int} ; -1 _gEq'_91_93 :: __forall [a] {Eq' a} => {Eq' [a]} ; -1 class Eq' a where {doubleeq :: a -> a -> PrelBase.Bool} ; -1 class {Eq' a} => Ord' a where {lt :: a -> a -> PrelBase.Bool} ; -1 f :: __forall [t _116] {PrelBase.Num _116, Eq' [_116]} => [_116] -> t -> PrelBase.Bool ; +__export ShouldSucceed Eqzq{doubleeq} Ordzq{lt} f; +instance {Eqzq PrelBase.Int} = zdfEqzqInt; +instance __forall [a] {Eqzq a, Eqzq a} => {Eqzq [a]} = zdfEqzqZMZN; +1 class Eqzq a where {doubleeq :: a -> a -> PrelBase.Bool} ; +1 class {Eqzq a} => Ordzq a where {lt :: a -> a -> PrelBase.Bool} ; +1 f :: __forall [t t1] {PrelBase.Num t1, Eqzq [t1]} => [t1] -> t -> PrelBase.Bool ; +1 zdfEqzqInt :: {Eqzq PrelBase.Int} ; +1 zdfEqzqZMZN :: __forall [a] {Eqzq a} => {Eqzq [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc057.stderr b/ghc/tests/typecheck/should_compile/tc057.stderr index 92186f154a33ceb9a1625e3018215313e37b4b38..aa9bb599767b15b86d8de441976b5d81cec0cd61 100644 --- a/ghc/tests/typecheck/should_compile/tc057.stderr +++ b/ghc/tests/typecheck/should_compile/tc057.stderr @@ -1,9 +1,9 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed dand f Eq'{deq}; -instance {Eq' PrelBase.Int} = _fEq'Int; -instance __forall [a] {Eq' a} => {Eq' [a]} = _gEq'_91_93; -1 _fEq'Int :: {Eq' PrelBase.Int} ; -1 _gEq'_91_93 :: __forall [a] {Eq' a} => {Eq' [a]} ; -1 class Eq' a where {deq :: a -> a -> PrelBase.Bool} ; +__export ShouldSucceed Eqzq{deq} dand f; +instance {Eqzq PrelBase.Int} = zdfEqzqInt; +instance __forall [a] {Eqzq a} => {Eqzq [a]} = zdfEqzqZMZN; +1 class Eqzq a where {deq :: a -> a -> PrelBase.Bool} ; 1 dand :: PrelBase.Bool -> PrelBase.Bool -> PrelBase.Bool ; -1 f :: __forall [a] {Eq' a} => a -> a -> PrelBase.Bool ; +1 f :: __forall [a] {Eqzq a} => a -> a -> PrelBase.Bool ; +1 zdfEqzqInt :: {Eqzq PrelBase.Int} ; +1 zdfEqzqZMZN :: __forall [a] {Eqzq a} => {Eqzq [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc058.stderr b/ghc/tests/typecheck/should_compile/tc058.stderr index e3aad7abb58628c102dffa4aa7b8834dd01aa340..61c2027cf16cc20a282ee25a388dffff1b953298 100644 --- a/ghc/tests/typecheck/should_compile/tc058.stderr +++ b/ghc/tests/typecheck/should_compile/tc058.stderr @@ -1,11 +1,11 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f Eq2{doubleeq} Ord2{lt}; -instance {Eq2 PrelBase.Int} = _fEq2Int; -instance {Ord2 PrelBase.Int} = _fOrd2Int; -instance __forall [a] {Eq2 a, Ord2 a} => {Eq2 [a]} = _gEq2_91_93; -1 _fEq2Int :: {Eq2 PrelBase.Int} ; -1 _fOrd2Int :: {Ord2 PrelBase.Int} ; -1 _gEq2_91_93 :: __forall [a] {Eq2 a, Ord2 a} => {Eq2 [a]} ; +__export ShouldSucceed Eq2{doubleeq} Ord2{lt} f; +instance {Eq2 PrelBase.Int} = zdfEq2Int; +instance __forall [a] {Eq2 a, Ord2 a} => {Eq2 [a]} = zdfEq2ZMZN; +instance {Ord2 PrelBase.Int} = zdfOrd2Int; 1 class Eq2 a where {doubleeq :: a -> a -> PrelBase.Bool} ; 1 class {Eq2 a} => Ord2 a where {lt :: a -> a -> PrelBase.Bool} ; -1 f :: __forall [t _116] {PrelBase.Num _116, Eq2 [_116]} => [_116] -> t -> PrelBase.Bool ; +1 f :: __forall [t t1] {PrelBase.Num t1, Eq2 [t1]} => [t1] -> t -> PrelBase.Bool ; +1 zdfEq2Int :: {Eq2 PrelBase.Int} ; +1 zdfEq2ZMZN :: __forall [a] {Eq2 a, Ord2 a} => {Eq2 [a]} ; +1 zdfOrd2Int :: {Ord2 PrelBase.Int} ; diff --git a/ghc/tests/typecheck/should_compile/tc059.stderr b/ghc/tests/typecheck/should_compile/tc059.stderr index 7a2aa08e4b55d8c161205f7d3063d5d5cbb56a1f..f8d91ca3b38874918d6aa9732519a3ea84be7723 100644 --- a/ghc/tests/typecheck/should_compile/tc059.stderr +++ b/ghc/tests/typecheck/should_compile/tc059.stderr @@ -1,8 +1,8 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f Eq2{foo deq}; -instance {Eq2 PrelBase.Int} = _fEq2Int; -instance __forall [a] {Eq2 a} => {Eq2 [a]} = _gEq2_91_93; -1 _fEq2Int :: {Eq2 PrelBase.Int} ; -1 _gEq2_91_93 :: __forall [a] {Eq2 a} => {Eq2 [a]} ; +__export ShouldSucceed Eq2{foo deq} f; +instance {Eq2 PrelBase.Int} = zdfEq2Int; +instance __forall [a] {Eq2 a} => {Eq2 [a]} = zdfEq2ZMZN; 1 class Eq2 a where {foo :: a -> a; deq :: a -> a -> PrelBase.Bool} ; 1 f :: __forall [t] {PrelBase.Num t, Eq2 [t]} => [t] -> PrelBase.Bool ; +1 zdfEq2Int :: {Eq2 PrelBase.Int} ; +1 zdfEq2ZMZN :: __forall [a] {Eq2 a} => {Eq2 [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc060.stderr b/ghc/tests/typecheck/should_compile/tc060.stderr index dfaeb77a2ba44f2d10b1b19689e040135efe21cd..d1db20d82f7a5be1799732b12462f11150ad2bbd 100644 --- a/ghc/tests/typecheck/should_compile/tc060.stderr +++ b/ghc/tests/typecheck/should_compile/tc060.stderr @@ -1,7 +1,7 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed Eq2{deq}; -instance {Eq2 PrelBase.Int} = _fEq2Int; -instance __forall [a] {Eq2 a} => {Eq2 [a]} = _gEq2_91_93; -1 _fEq2Int :: {Eq2 PrelBase.Int} ; -1 _gEq2_91_93 :: __forall [a] {Eq2 a} => {Eq2 [a]} ; +instance {Eq2 PrelBase.Int} = zdfEq2Int; +instance __forall [a] {Eq2 a} => {Eq2 [a]} = zdfEq2ZMZN; 1 class Eq2 a where {deq :: a -> a -> PrelBase.Bool} ; +1 zdfEq2Int :: {Eq2 PrelBase.Int} ; +1 zdfEq2ZMZN :: __forall [a] {Eq2 a} => {Eq2 [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc061.stderr b/ghc/tests/typecheck/should_compile/tc061.stderr index ce5d6cfa5ee16f6ca0c8f6e545ebee78f6b735c4..3df4b541a0ee9443a590fcb8c9dcbc990835b807 100644 --- a/ghc/tests/typecheck/should_compile/tc061.stderr +++ b/ghc/tests/typecheck/should_compile/tc061.stderr @@ -1,7 +1,7 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed Eq1{deq}; -instance {Eq1 PrelBase.Int} = _fEq1Int; -instance __forall [a] {Eq1 a} => {Eq1 [a]} = _gEq1_91_93; -1 _fEq1Int :: {Eq1 PrelBase.Int} ; -1 _gEq1_91_93 :: __forall [a] {Eq1 a} => {Eq1 [a]} ; +instance {Eq1 PrelBase.Int} = zdfEq1Int; +instance __forall [a] {Eq1 a} => {Eq1 [a]} = zdfEq1ZMZN; 1 class Eq1 a where {deq :: a -> a -> PrelBase.Bool} ; +1 zdfEq1Int :: {Eq1 PrelBase.Int} ; +1 zdfEq1ZMZN :: __forall [a] {Eq1 a} => {Eq1 [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc062.stderr b/ghc/tests/typecheck/should_compile/tc062.stderr index 73966d6bce50beff6b2519f3cfa1d4b83a6ffc38..85085f054bfbe5000f079a7796e58d715ca7e876 100644 --- a/ghc/tests/typecheck/should_compile/tc062.stderr +++ b/ghc/tests/typecheck/should_compile/tc062.stderr @@ -1,8 +1,8 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f Eq1{deq}; -instance {Eq1 PrelBase.Int} = _fEq1Int; -instance __forall [a] {Eq1 a} => {Eq1 [a]} = _gEq1_91_93; -1 _fEq1Int :: {Eq1 PrelBase.Int} ; -1 _gEq1_91_93 :: __forall [a] {Eq1 a} => {Eq1 [a]} ; +__export ShouldSucceed Eq1{deq} f; +instance {Eq1 PrelBase.Int} = zdfEq1Int; +instance __forall [a] {Eq1 a} => {Eq1 [a]} = zdfEq1ZMZN; 1 class Eq1 a where {deq :: a -> a -> PrelBase.Bool} ; 1 f :: __forall [t] {Eq1 [t]} => [t] -> [t] -> PrelBase.Bool ; +1 zdfEq1Int :: {Eq1 PrelBase.Int} ; +1 zdfEq1ZMZN :: __forall [a] {Eq1 a} => {Eq1 [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc063.stderr b/ghc/tests/typecheck/should_compile/tc063.stderr index aec818dfd8cfaf03b3306a4653b7b04c9b5f788e..1183f020d0e936046cce8b260cd8675acbf8ee7a 100644 --- a/ghc/tests/typecheck/should_compile/tc063.stderr +++ b/ghc/tests/typecheck/should_compile/tc063.stderr @@ -1,9 +1,9 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed g Reps{f} X{Tag}; -instance {Reps PrelBase.Bool} = _fRepsBool; -instance __forall [q] => {Reps (X q)} = _fRepsX; -1 _fRepsBool :: {Reps PrelBase.Bool} ; -1 _fRepsX :: __forall [q] => {Reps (X q)} ; +__export ShouldSucceed Reps{f} X{Tag} g; +instance {Reps PrelBase.Bool} = zdfRepsBool; +instance __forall [q] => {Reps (X q)} = zdfRepsX; 1 class Reps r where {f :: r -> r -> r} ; 1 data X a = Tag a ; 1 g :: __forall [r] {Reps r} => r -> r ; +1 zdfRepsBool :: {Reps PrelBase.Bool} ; +1 zdfRepsX :: __forall [q] => {Reps (X q)} ; diff --git a/ghc/tests/typecheck/should_compile/tc064.stderr b/ghc/tests/typecheck/should_compile/tc064.stderr index fea6ee589c4ed8fe3aca73a59ddaa4d32097e8e6..119d82eb3cd8405cbc793dc1855babd8fcaa32d7 100644 --- a/ghc/tests/typecheck/should_compile/tc064.stderr +++ b/ghc/tests/typecheck/should_compile/tc064.stderr @@ -1,4 +1,4 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed idb Boolean{FF TT}; +__export ShouldSucceed Boolean{FF TT} idb; 1 data Boolean = FF | TT ; 1 idb :: Boolean -> Boolean ; diff --git a/ghc/tests/typecheck/should_compile/tc065.stderr b/ghc/tests/typecheck/should_compile/tc065.stderr index fc69c10e300af1cf36682341b618ac505e182af0..c13d9e7be738cbfacd8a8c2a147c4c3406a2b9ab 100644 --- a/ghc/tests/typecheck/should_compile/tc065.stderr +++ b/ghc/tests/typecheck/should_compile/tc065.stderr @@ -1,5 +1,5 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed dfs isCyclic isRecursiveCycle lookupVertex mkDigraph mkEdges mkVertices stronglyConnComp topSort Cycle Digraph{MkDigraph} Edge FlattenedDependencyInfo MaybeErr{Succeeded Failed}; +__export ShouldSucceed Cycle Digraph{MkDigraph} Edge FlattenedDependencyInfo MaybeErr{Succeeded Failed} dfs isCyclic isRecursiveCycle lookupVertex mkDigraph mkEdges mkVertices stronglyConnComp topSort; 1 data Digraph vertex = MkDigraph [vertex] ; 1 data MaybeErr a b = Succeeded a | Failed b ; 1 dfs :: __forall [a] {PrelBase.Eq a} => (a -> [a]) -> ([a], [a]) -> [a] -> ([a], [a]) ; diff --git a/ghc/tests/typecheck/should_compile/tc066.stderr b/ghc/tests/typecheck/should_compile/tc066.stderr index 81893238c1c76fe792a9e7f5a04ffac009038fc2..fe1a93957f6b7dcd126c56bf21e5851ed0e7a328 100644 --- a/ghc/tests/typecheck/should_compile/tc066.stderr +++ b/ghc/tests/typecheck/should_compile/tc066.stderr @@ -1,4 +1,4 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f Pair{MkPair}; +__export ShouldSucceed Pair{MkPair} f; 1 data Pair a b = MkPair a b ; 1 f :: __forall [a b] => [Pair a b] -> [b] ; diff --git a/ghc/tests/typecheck/should_compile/tc068.stderr b/ghc/tests/typecheck/should_compile/tc068.stderr index e3c8be182bf2c496f3c6012bede1454acdccf32e..587ce7c23828b8667c02f4234730a505099a0a8e 100644 --- a/ghc/tests/typecheck/should_compile/tc068.stderr +++ b/ghc/tests/typecheck/should_compile/tc068.stderr @@ -1,8 +1,8 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed B{X Y} T{D C}; -instance __forall [b] {PrelBase.Eq b} => {PrelBase.Eq (B b)} = _fEqB; -instance __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} = _fEqT; -1 _fEqB :: __forall [b] {PrelBase.Eq b} => {PrelBase.Eq (B b)} ; -1 _fEqT :: __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} ; +instance __forall [b] {PrelBase.Eq b} => {PrelBase.Eq (B b)} = zdfEqB; +instance __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} = zdfEqT; 1 data B b = X | Y b ; 1 data T a = D (B a) | C ; +1 zdfEqB :: __forall [b] {PrelBase.Eq b} => {PrelBase.Eq (B b)} ; +1 zdfEqT :: __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} ; diff --git a/ghc/tests/typecheck/should_compile/tc070.stderr b/ghc/tests/typecheck/should_compile/tc070.stderr index fea6ee589c4ed8fe3aca73a59ddaa4d32097e8e6..119d82eb3cd8405cbc793dc1855babd8fcaa32d7 100644 --- a/ghc/tests/typecheck/should_compile/tc070.stderr +++ b/ghc/tests/typecheck/should_compile/tc070.stderr @@ -1,4 +1,4 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed idb Boolean{FF TT}; +__export ShouldSucceed Boolean{FF TT} idb; 1 data Boolean = FF | TT ; 1 idb :: Boolean -> Boolean ; diff --git a/ghc/tests/typecheck/should_compile/tc074.stderr b/ghc/tests/typecheck/should_compile/tc074.stderr index e3c8be182bf2c496f3c6012bede1454acdccf32e..587ce7c23828b8667c02f4234730a505099a0a8e 100644 --- a/ghc/tests/typecheck/should_compile/tc074.stderr +++ b/ghc/tests/typecheck/should_compile/tc074.stderr @@ -1,8 +1,8 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed B{X Y} T{D C}; -instance __forall [b] {PrelBase.Eq b} => {PrelBase.Eq (B b)} = _fEqB; -instance __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} = _fEqT; -1 _fEqB :: __forall [b] {PrelBase.Eq b} => {PrelBase.Eq (B b)} ; -1 _fEqT :: __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} ; +instance __forall [b] {PrelBase.Eq b} => {PrelBase.Eq (B b)} = zdfEqB; +instance __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} = zdfEqT; 1 data B b = X | Y b ; 1 data T a = D (B a) | C ; +1 zdfEqB :: __forall [b] {PrelBase.Eq b} => {PrelBase.Eq (B b)} ; +1 zdfEqT :: __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (T a)} ; diff --git a/ghc/tests/typecheck/should_compile/tc077.stderr b/ghc/tests/typecheck/should_compile/tc077.stderr index d4a3c4ba0d2eb3c9902fd7e2060c5ac35b374c60..54d30b4a9adcaa979e679e9b4a428b5806a4f27c 100644 --- a/ghc/tests/typecheck/should_compile/tc077.stderr +++ b/ghc/tests/typecheck/should_compile/tc077.stderr @@ -1,5 +1,5 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed EQ{===} NUM{ONE TWO} ORD; -1 class {ORD a, PrelBase.Show a} => EQ a where {=== :: a -> a -> PrelBase.Bool} ; +__export ShouldSucceed EQ{zezeze} NUM{ONE TWO} ORD; +1 class {ORD a, PrelBase.Show a} => EQ a where {zezeze :: a -> a -> PrelBase.Bool} ; 1 class {PrelBase.Num a} => ORD a ; 1 data NUM = ONE | TWO ; diff --git a/ghc/tests/typecheck/should_compile/tc078.stderr b/ghc/tests/typecheck/should_compile/tc078.stderr index 4dd15bb2bf482c1c8b3296faaf104e09a210daad..1e0c8b456d1b1c3eba89390a14cac7352b7db830 100644 --- a/ghc/tests/typecheck/should_compile/tc078.stderr +++ b/ghc/tests/typecheck/should_compile/tc078.stderr @@ -1,7 +1,7 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldFail Bar{MkBar}; -instance __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (Bar a)} = _fEqBar; -instance __forall [a] {PrelBase.Ord a} => {PrelBase.Ord (Bar a)} = _fOrdBar; -1 _fEqBar :: __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (Bar a)} ; -1 _fOrdBar :: __forall [a] {PrelBase.Ord a, PrelBase.Eq (Bar a)} => {PrelBase.Ord (Bar a)} ; +instance __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (Bar a)} = zdfEqBar; +instance __forall [a] {PrelBase.Ord a} => {PrelBase.Ord (Bar a)} = zdfOrdBar; 1 data Bar a = MkBar PrelBase.Int a ; +1 zdfEqBar :: __forall [a] {PrelBase.Eq a} => {PrelBase.Eq (Bar a)} ; +1 zdfOrdBar :: __forall [a] {PrelBase.Ord a, PrelBase.Eq (Bar a)} => {PrelBase.Ord (Bar a)} ; diff --git a/ghc/tests/typecheck/should_compile/tc079.stderr b/ghc/tests/typecheck/should_compile/tc079.stderr index 6e89914f02acabf5326d1f19f299a0a0d6854f75..34efb105d46451774e107e86347b4c7d4fe77f9a 100644 --- a/ghc/tests/typecheck/should_compile/tc079.stderr +++ b/ghc/tests/typecheck/should_compile/tc079.stderr @@ -1,9 +1,9 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed Foo{op2 op1}; -instance {Foo PrelBase.Int} = _fFooInt; -instance __forall [a] {Foo a} => {Foo [a]} = _gFoo_91_93; -1 _fFooInt :: {Foo PrelBase.Int} ; -1 _gFoo_91_93 :: __forall [a] {Foo a} => {Foo [a]} ; -1 _mop1 :: __forall [a] {Foo a} => a -> PrelBase.Bool ; -1 _mop2 :: __forall [a] {Foo a} => __forall [b] {PrelBase.Ord b} => a -> b -> b -> b ; +instance {Foo PrelBase.Int} = zdfFooInt; +instance __forall [a] {Foo a} => {Foo [a]} = zdfFooZMZN; 1 class Foo a where {op2 = :: __forall [b] {PrelBase.Ord b} => a -> b -> b -> b; op1 = :: a -> PrelBase.Bool} ; +1 zddmop1 :: __forall [a] {Foo a} => a -> PrelBase.Bool ; +1 zddmop2 :: __forall [a] {Foo a} => __forall [b] {PrelBase.Ord b} => a -> b -> b -> b ; +1 zdfFooInt :: {Foo PrelBase.Int} ; +1 zdfFooZMZN :: __forall [a] {Foo a} => {Foo [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc080.stderr b/ghc/tests/typecheck/should_compile/tc080.stderr index b389bdddb8d3923ed19708c2a9fc90f2c107e284..64503a91173a5ca2b46538f225bf355b224578eb 100644 --- a/ghc/tests/typecheck/should_compile/tc080.stderr +++ b/ghc/tests/typecheck/should_compile/tc080.stderr @@ -1,19 +1,19 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed charToInt lines' seperatedBy span' strToInt whiteSpace Parse{forced parse parseType parseLine parseFile}; -instance {Parse PrelBase.Char} = _fParseChar; -instance {Parse PrelBase.Int} = _fParseInt; -instance __forall [a] {Parse a} => {Parse [a]} = _gParse_91_93; -1 _fParseChar :: {Parse PrelBase.Char} ; -1 _fParseInt :: {Parse PrelBase.Int} ; -1 _gParse_91_93 :: __forall [a] {Parse a} => {Parse [a]} ; -1 _mforced :: __forall [a] {Parse a} => a -> PrelBase.Bool ; -1 _mparse :: __forall [a] {Parse a} => PrelBase.String -> (a, PrelBase.String) ; -1 _mparseFile :: __forall [a] {Parse a} => PrelBase.String -> [a] ; -1 _mparseLine :: __forall [a] {Parse a} => PrelBase.String -> a ; +__export ShouldSucceed Parse{forced parse parseType parseLine parseFile} charToInt lineszq seperatedBy spanzq strToInt whiteSpace; +instance {Parse PrelBase.Char} = zdfParseChar; +instance {Parse PrelBase.Int} = zdfParseInt; +instance __forall [a] {Parse a} => {Parse [a]} = zdfParseZMZN; 1 charToInt :: PrelBase.Char -> PrelBase.Int ; 1 class Parse a where {forced = :: a -> PrelBase.Bool; parse = :: PrelBase.String -> (a, PrelBase.String); parseType :: PrelBase.String -> (a, PrelBase.String); parseLine = :: PrelBase.String -> a; parseFile = :: PrelBase.String -> [a]} ; -1 lines' :: [PrelBase.Char] -> [[PrelBase.Char]] ; +1 lineszq :: [PrelBase.Char] -> [[PrelBase.Char]] ; 1 seperatedBy :: PrelBase.Char -> PrelBase.String -> [PrelBase.String] ; -1 span' :: __forall [a] => (a -> PrelBase.Bool) -> [a] -> ([a], [a]) ; +1 spanzq :: __forall [a] => (a -> PrelBase.Bool) -> [a] -> ([a], [a]) ; 1 strToInt :: PrelBase.String -> PrelBase.Int ; 1 whiteSpace :: PrelBase.String -> PrelBase.String ; +1 zddmforced :: __forall [a] {Parse a} => a -> PrelBase.Bool ; +1 zddmparse :: __forall [a] {Parse a} => PrelBase.String -> (a, PrelBase.String) ; +1 zddmparseFile :: __forall [a] {Parse a} => PrelBase.String -> [a] ; +1 zddmparseLine :: __forall [a] {Parse a} => PrelBase.String -> a ; +1 zdfParseChar :: {Parse PrelBase.Char} ; +1 zdfParseInt :: {Parse PrelBase.Int} ; +1 zdfParseZMZN :: __forall [a] {Parse a} => {Parse [a]} ; diff --git a/ghc/tests/typecheck/should_compile/tc082.stderr b/ghc/tests/typecheck/should_compile/tc082.stderr index 3823a79d12ae723ef98ad3bbb87dfbd542ee9967..25129c805bc0f01be83b67ab9fc8114f05b9e1b9 100644 --- a/ghc/tests/typecheck/should_compile/tc082.stderr +++ b/ghc/tests/typecheck/should_compile/tc082.stderr @@ -1,6 +1,6 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed f Normal{normal}; -instance __forall [a b] => {Normal (a -> b)} = _gNormalmg; -1 _gNormalmg :: __forall [a b] => {Normal (a -> b)} ; +__export ShouldSucceed Normal{normal} f; +instance __forall [a b] => {Normal (a -> b)} = zdfNormalZLzmzgZR; 1 class Normal a where {normal :: a -> PrelBase.Bool} ; 1 f :: __forall [t] => t -> PrelBase.Bool ; +1 zdfNormalZLzmzgZR :: __forall [a b] => {Normal (a -> b)} ; diff --git a/ghc/tests/typecheck/should_compile/tc085.stderr b/ghc/tests/typecheck/should_compile/tc085.stderr index 6fa0afbaf2ffac9e3ae3b696a90c09430d47933b..f21b47af6af4ce010aa74b4105046481b04b3db2 100644 --- a/ghc/tests/typecheck/should_compile/tc085.stderr +++ b/ghc/tests/typecheck/should_compile/tc085.stderr @@ -1,7 +1,7 @@ ghc: module version changed to 1; reason: no old .hi file -__export IOExts boundsIOArray freezeIOArray newIOArray newIORef performGC readIOArray readIORef thawIOArray trace unsafePtrEq writeIOArray writeIORef IOArray IORef; -__export PrelGHC *# *## **## +# +## -# -## /## /=# /=## <# <## <=# <=## ==# ==## ># >## >=# >=## acosDouble# acosFloat# addr2Int# addr2Integer# and# asinDouble# asinFloat# assert atanDouble# atanFloat# catch# chr# cmpInteger# cosDouble# cosFloat# coshDouble# coshFloat# deRefStablePtr# deRefWeak# decodeDouble# decodeFloat# delay# divideFloat# double2Float# double2Int# encodeDouble# encodeFloat# eqAddr# eqChar# eqFloat# eqStablePtr# eqWord# expDouble# expFloat# float2Double# float2Int# fork# geAddr# geChar# geFloat# geWord# gtAddr# gtChar# gtFloat# gtWord# iShiftL# iShiftRA# iShiftRL# indexAddrArray# indexAddrOffAddr# indexAddrOffForeignObj# indexArray# indexCharArray# indexCharOffAddr# indexCharOffForeignObj# indexDoubleArray# indexDoubleOffAddr# indexDoubleOffForeignObj# indexFloatArray# indexFloatOffAddr# indexFloatOffForeignObj# indexInt64Array# indexInt64OffAddr# indexInt64OffForeignObj# indexIntArray# indexIntOffAddr# indexIntOffForeignObj# indexStablePtrArray# indexStablePtrOffAddr# indexStablePtrOffForeignObj# indexWord64Array# indexWord64OffAddr# indexWord64OffForeignObj# indexWordArray# indexWordOffAddr# indexWordOffForeignObj# int2Addr# int2Double# int2Float# int2Integer# int2Word# int64ToInteger# integer2Int# integer2Word# integerToInt64# integerToWord64# isEmptyMVar# killThread# leAddr# leChar# leFloat# leWord# logDouble# logFloat# ltAddr# ltChar# ltFloat# ltWord# makeForeignObj# makeStablePtr# minusFloat# minusInteger# mkWeak# neAddr# neChar# neFloat# neWord# negateDouble# negateFloat# negateInt# negateInteger# newAddrArray# newArray# newCharArray# newDoubleArray# newFloatArray# newIntArray# newMVar# newMutVar# newStablePtrArray# newWordArray# not# or# ord# par# parAt# parAtAbs# parAtForNow# parAtRel# parGlobal# parLocal# plusFloat# plusInteger# powerFloat# putMVar# quotInt# quotRemInteger# quotWord# raise# readAddrArray# readArray# readCharArray# readDoubleArray# readFloatArray# readInt64Array# readIntArray# readMutVar# readStablePtrArray# readWord64Array# readWordArray# realWorld# reallyUnsafePtrEquality# remInt# remWord# sameMVar# sameMutVar# sameMutableArray# sameMutableByteArray# seq# shiftL# shiftRL# sinDouble# sinFloat# sinhDouble# sinhFloat# sizeofByteArray# sizeofMutableByteArray# sqrtDouble# sqrtFloat# takeMVar# tanDouble# tanFloat# tanhDouble# tanhFloat# timesFloat# timesInteger# unsafeCoerce# unsafeFreezeArray# unsafeFreezeByteArray# waitRead# waitWrite# word2Int# word2Integer# word64ToInteger# writeAddrArray# writeAddrOffAddr# writeArray# writeCharArray# writeCharOffAddr# writeDoubleArray# writeDoubleOffAddr# writeFloatArray# writeFloatOffAddr# writeForeignObj# writeForeignObjOffAddr# writeInt64Array# writeInt64OffAddr# writeIntArray# writeIntOffAddr# writeMutVar# writeStablePtrArray# writeStablePtrOffAddr# writeWord64Array# writeWord64OffAddr# writeWordArray# writeWordOffAddr# xor# -> Addr# All Array# ByteArray# CCallable CReturnable Char# Double# Float# ForeignObj# Int# Int64# MVar# MutVar# MutableArray# MutableByteArray# RealWorld StablePtr# State# ThreadId# Weak# Word# Word64#; -__export PrelHandle hConnectTo hGetEcho hIsTerminalDevice hSetEcho openFileEx IOModeEx{BinaryMode TextMode}; +__export IOExts IOArray IORef boundsIOArray freezzeIOArray newIOArray newIORef performGC readIOArray readIORef thawIOArray trace unsafePtrEq writeIOArray writeIORef; +__export PrelGHC Addrzh All Arrayzh ByteArrayzh CCallable CReturnable Charzh Doublezh Floatzh ForeignObjzh Int64zh Intzh MVarzh MutVarzh MutableArrayzh MutableByteArrayzh RealWorld StableNamezh StablePtrzh Statezh ThreadIdzh Weakzh Word64zh Wordzh ZLzmzgZR acosDoublezh acosFloatzh addr2Integerzh addr2Intzh andzh asinDoublezh asinFloatzh assert atanDoublezh atanFloatzh catchzh chrzh cmpIntegerzh cosDoublezh cosFloatzh coshDoublezh coshFloatzh deRefStablePtrzh deRefWeakzh decodeDoublezh decodeFloatzh delayzh divideFloatzh double2Floatzh double2Intzh encodeDoublezh encodeFloatzh eqAddrzh eqCharzh eqFloatzh eqStableNamezh eqStablePtrzh eqWordzh expDoublezh expFloatzh finaliseWeakzh float2Doublezh float2Intzh forkzh geAddrzh geCharzh geFloatzh geWordzh gtAddrzh gtCharzh gtFloatzh gtWordzh iShiftLzh iShiftRAzh iShiftRLzh indexAddrArrayzh indexAddrOffAddrzh indexAddrOffForeignObjzh indexArrayzh indexCharArrayzh indexCharOffAddrzh indexCharOffForeignObjzh indexDoubleArrayzh indexDoubleOffAddrzh indexDoubleOffForeignObjzh indexFloatArrayzh indexFloatOffAddrzh indexFloatOffForeignObjzh indexInt64Arrayzh indexInt64OffAddrzh indexInt64OffForeignObjzh indexIntArrayzh indexIntOffAddrzh indexIntOffForeignObjzh indexStablePtrArrayzh indexStablePtrOffAddrzh indexStablePtrOffForeignObjzh indexWord64Arrayzh indexWord64OffAddrzh indexWord64OffForeignObjzh indexWordArrayzh indexWordOffAddrzh indexWordOffForeignObjzh int2Addrzh int2Doublezh int2Floatzh int2Integerzh int2Wordzh int64ToIntegerzh integer2Intzh integer2Wordzh integerToInt64zh integerToWord64zh isEmptyMVarzh killThreadzh leAddrzh leCharzh leFloatzh leWordzh logDoublezh logFloatzh ltAddrzh ltCharzh ltFloatzh ltWordzh makeForeignObjzh makeStableNamezh makeStablePtrzh minusFloatzh minusIntegerzh mkWeakzh neAddrzh neCharzh neFloatzh neWordzh negateDoublezh negateFloatzh negateIntegerzh negateIntzh newAddrArrayzh newArrayzh newCharArrayzh newDoubleArrayzh newFloatArrayzh newIntArrayzh newMVarzh newMutVarzh newStablePtrArrayzh newWordArrayzh notzh ordzh orzh parAtAbszh parAtForNowzh parAtRelzh parAtzh parGlobalzh parLocalzh parzh plusFloatzh plusIntegerzh powerFloatzh putMVarzh quotIntzh quotRemIntegerzh quotWordzh raisezh readAddrArrayzh readArrayzh readCharArrayzh readDoubleArrayzh readFloatArrayzh readInt64Arrayzh readIntArrayzh readMutVarzh readStablePtrArrayzh readWord64Arrayzh readWordArrayzh realWorldzh reallyUnsafePtrEqualityzh remIntzh remWordzh sameMVarzh sameMutVarzh sameMutableArrayzh sameMutableByteArrayzh seqzh shiftLzh shiftRLzh sinDoublezh sinFloatzh sinhDoublezh sinhFloatzh sizzeofByteArrayzh sizzeofMutableByteArrayzh sqrtDoublezh sqrtFloatzh stableNameToIntzh takeMVarzh tanDoublezh tanFloatzh tanhDoublezh tanhFloatzh timesFloatzh timesIntegerzh unsafeCoercezh unsafeFreezzeArrayzh unsafeFreezzeByteArrayzh waitReadzh waitWritezh word2Integerzh word2Intzh word64ToIntegerzh writeAddrArrayzh writeAddrOffAddrzh writeArrayzh writeCharArrayzh writeCharOffAddrzh writeDoubleArrayzh writeDoubleOffAddrzh writeFloatArrayzh writeFloatOffAddrzh writeForeignObjOffAddrzh writeForeignObjzh writeInt64Arrayzh writeInt64OffAddrzh writeIntArrayzh writeIntOffAddrzh writeMutVarzh writeStablePtrArrayzh writeStablePtrOffAddrzh writeWord64Arrayzh writeWord64OffAddrzh writeWordArrayzh writeWordOffAddrzh xorzh zezezh zezezhzh zgzezh zgzezhzh zgzh zgzhzh zlzezh zlzezhzh zlzh zlzhzh zmzh zmzhzh zpzh zpzhzh zszezh zszezhzh zszh zszhzh ztzh ztzhzh ztztzhzh; +__export PrelHandle IOModeEx{BinaryMode TextMode} hConnectTo hGetEcho hIsTerminalDevice hSetEcho openFileEx; __export PrelIOBase fixIO unsafeInterleaveIO unsafePerformIO; 1 data FooData = FooData ; 1 type FooType = PrelBase.Int ; diff --git a/ghc/tests/typecheck/should_compile/tc086.stderr b/ghc/tests/typecheck/should_compile/tc086.stderr index cbbee4844f6f51acaaa0db0372d96179b4d0c148..83dea7291dbdc9c8ee1feab003eca8621b0c10e8 100644 --- a/ghc/tests/typecheck/should_compile/tc086.stderr +++ b/ghc/tests/typecheck/should_compile/tc086.stderr @@ -1,7 +1,7 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed Group Ring; -1 _mone :: __forall [a] {Group a} => a ; -1 _mzero :: __forall [a] {Group a} => a ; -1 _nt :: __forall [a] {Ring a} => a -> a -> a ; -1 class Group a where {one = :: a; zero = :: a; - :: a -> a -> a; + :: a -> a -> a; fromInteger :: PrelBase.Integer -> a; compare :: a -> a -> PrelBase.Ordering} ; -1 class {Group a} => Ring a where {* = :: a -> a -> a} ; +1 class Group a where {one = :: a; zzero = :: a; zm :: a -> a -> a; zp :: a -> a -> a; fromInteger :: PrelBase.Integer -> a; compare :: a -> a -> PrelBase.Ordering} ; +1 class {Group a} => Ring a where {zt = :: a -> a -> a} ; +1 zddmone :: __forall [a] {Group a} => a ; +1 zddmzt :: __forall [a] {Ring a} => a -> a -> a ; +1 zddmzzero :: __forall [a] {Group a} => a ; diff --git a/ghc/tests/typecheck/should_compile/tc087.stderr b/ghc/tests/typecheck/should_compile/tc087.stderr index 24e34144b1a3a5526cefab0956356631f7b47ef7..38bc7e14d180d1cfc13c64cdd6ee2e0226f76842 100644 --- a/ghc/tests/typecheck/should_compile/tc087.stderr +++ b/ghc/tests/typecheck/should_compile/tc087.stderr @@ -1,10 +1,10 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed check insertMany out pqSort toOrderedList PriorityQueue{splitMin meld insert single empty} SeqView{Null Cons}; -1 _minsert :: __forall [q :: (* -> *)] {PriorityQueue q} => __forall [a] {PrelBase.Ord a} => a -> q a -> q a ; -1 check :: __forall [q :: (* -> *)] {PriorityQueue q} => (__forall [a] {PrelBase.Ord a} => q a) -> PrelIOBase.IO PrelBase.() ; +__export ShouldSucceed PriorityQueue{splitMin meld insert single empty} SeqView{Null Cons} check insertMany out pqSort toOrderedList; +1 check :: __forall [q :: (* -> *)] {PriorityQueue q} => (__forall [a] {PrelBase.Ord a} => q a) -> PrelIOBase.IO PrelBase.Z0T ; 1 class PriorityQueue q :: (* -> *) where {splitMin :: __forall [a] {PrelBase.Ord a} => q a -> SeqView q a; meld :: __forall [a] {PrelBase.Ord a} => q a -> q a -> q a; insert = :: __forall [a] {PrelBase.Ord a} => a -> q a -> q a; single :: __forall [a] {PrelBase.Ord a} => a -> q a; empty :: __forall [a] {PrelBase.Ord a} => q a} ; 1 data SeqView t :: (* -> *) a = Null | Cons a (t a) ; 1 insertMany :: __forall [a q :: (* -> *)] {PrelBase.Ord a, PriorityQueue q} => [a] -> q a -> q a ; -1 out :: __forall [a] {PrelBase.Num a} => [a] -> PrelIOBase.IO PrelBase.() ; +1 out :: __forall [a] {PrelBase.Num a} => [a] -> PrelIOBase.IO PrelBase.Z0T ; 1 pqSort :: __forall [q :: (* -> *) a] {PriorityQueue q, PrelBase.Ord a} => q a -> [a] -> [a] ; 1 toOrderedList :: __forall [q :: (* -> *) a] {PrelBase.Ord a, PriorityQueue q} => q a -> [a] ; +1 zddminsert :: __forall [q :: (* -> *)] {PriorityQueue q} => __forall [a] {PrelBase.Ord a} => a -> q a -> q a ; diff --git a/ghc/tests/typecheck/should_compile/tc088.stderr b/ghc/tests/typecheck/should_compile/tc088.stderr index d61bd1cbe0d6d17f79535db2ed1868f219598547..d36d102176f63a0ff48c37eb66f928be65155152 100644 --- a/ghc/tests/typecheck/should_compile/tc088.stderr +++ b/ghc/tests/typecheck/should_compile/tc088.stderr @@ -1,5 +1,5 @@ ghc: module version changed to 1; reason: no old .hi file -instance __forall [a b] {PrelBase.Eq b} => {PrelBase.Eq (a -> b)} = _gEqmg; -instance __forall [a b] {PrelBase.Num b} => {PrelBase.Num (a -> b)} = _gNummg; -1 _gEqmg :: __forall [a b] {PrelBase.Eq b} => {PrelBase.Eq (a -> b)} ; -1 _gNummg :: __forall [a b] {PrelBase.Num b, PrelBase.Eq (a -> b), PrelBase.Show (a -> b)} => {PrelBase.Num (a -> b)} ; +instance __forall [a b] {PrelBase.Eq b} => {PrelBase.Eq (a -> b)} = zdfEqZLzmzgZR; +instance __forall [a b] {PrelBase.Num b} => {PrelBase.Num (a -> b)} = zdfNumZLzmzgZR; +1 zdfEqZLzmzgZR :: __forall [a b] {PrelBase.Eq b} => {PrelBase.Eq (a -> b)} ; +1 zdfNumZLzmzgZR :: __forall [a b] {PrelBase.Num b, PrelBase.Eq (a -> b), PrelBase.Show (a -> b)} => {PrelBase.Num (a -> b)} ; diff --git a/ghc/tests/typecheck/should_compile/tc089.stderr b/ghc/tests/typecheck/should_compile/tc089.stderr index 5e3cf97f19cc1430b85273b4afe34e8d08024a48..860479b33a9237949234c532e929d7cc75964773 100644 --- a/ghc/tests/typecheck/should_compile/tc089.stderr +++ b/ghc/tests/typecheck/should_compile/tc089.stderr @@ -1,36 +1,36 @@ ghc: module version changed to 1; reason: no old .hi file __export ShouldSucceed absAnd absIf bottom f f_rec f_rec0 f_rec1 f_rec2 fac fac_rec fac_rec0 fac_rec1 fac_rec2 fac_rec3 fac_rec4 g g_rec g_rec0 g_rec1 g_rec2 g_rec3 g_rec4 g_rec5 g_rec6 g_rec7 g_rec8 head one s_1_0 s_2_0 s_2_1 s_3_0 s_3_1 s_3_2; 1 absAnd :: __forall [t] => t -> t -> t ; -1 absIf :: __forall [t _116 _1161] => _116 -> t -> _1161 -> _116 ; +1 absIf :: __forall [t t1 t2] => t1 -> t -> t2 -> t1 ; 1 bottom :: __forall [t] => [t] -> t ; 1 f :: __forall [t] => t -> t ; -1 f_rec :: __forall [t _116] => (_116 -> t) -> _116 -> t ; +1 f_rec :: __forall [t t1] => (t1 -> t) -> t1 -> t ; 1 f_rec0 :: __forall [t] => t -> t ; 1 f_rec1 :: __forall [t] => t -> t ; 1 f_rec2 :: __forall [t] => t -> t ; -1 fac :: __forall [t _116 _1161 _1162 _1163 _1164 _1165 _1166 _1167 _1168 _1169] => (t, (_1167, (_116, (_1161, (_1162, _1163)))), (_1168, (_116, (_1161, (_1162, _1163))), (_1164, (_1161, (_1162, _1163)), (_1165, (_1162, _1163), (_1166, _1163, _1163))))) -> (_1169, (_1167, (_116, (_1161, (_1162, _1163))))) -> t ; -1 fac_rec :: __forall [t _116 _1161 _1162 _1163] => (_1162 -> t -> _116) -> (_1161, t, _1162) -> (_1163, t) -> _1161 ; +1 fac :: __forall [t t1 t2 t3 t4 t5 t6 t7 t8 t9 t10] => (t, (t8, (t1, (t2, (t3, t4)))), (t9, (t1, (t2, (t3, t4))), (t5, (t2, (t3, t4)), (t6, (t3, t4), (t7, t4, t4))))) -> (t10, (t8, (t1, (t2, (t3, t4))))) -> t ; +1 fac_rec :: __forall [t t1 t2 t3 t4] => (t3 -> t -> t1) -> (t2, t, t3) -> (t4, t) -> t2 ; 1 fac_rec0 :: __forall [t] => t -> t -> t ; -1 fac_rec1 :: __forall [t _116 _1161] => (t, _116, _116) -> (_1161, _116) -> t ; -1 fac_rec2 :: __forall [t _116 _1161 _1162 _1163] => (t, (_1161, _116), (_1162, _116, _116)) -> (_1163, (_1161, _116)) -> t ; -1 fac_rec3 :: __forall [t _116 _1161 _1162 _1163 _1164 _1165] => (t, (_1163, (_116, _1161)), (_1164, (_116, _1161), (_1162, _1161, _1161))) -> (_1165, (_1163, (_116, _1161))) -> t ; -1 fac_rec4 :: __forall [t _116 _1161 _1162 _1163 _1164 _1165 _1166 _1167] => (t, (_1165, (_116, (_1161, _1162))), (_1166, (_116, (_1161, _1162)), (_1163, (_1161, _1162), (_1164, _1162, _1162)))) -> (_1167, (_1165, (_116, (_1161, _1162)))) -> t ; -1 g :: __forall [t _116 _1161 _1162 _1163 _1164 _1165 _1166 _1167 _1168 _1169 _11610 _11611 _11612 _11613 _11614 _11615 _11616 _11617 _11618 _11619 _11620 _11621 _11622 _11623 _11624 _11625 _11626 _11627 _11628 _11629 _11630 _11631 _11632 _11633 _11634 _11635 _11636 _11637 _11638 _11639 _11640 _11641 _11642 _11643 _11644 _11645 _11646 _11647 _11648 _11649 _11650 _11651 _11652 _11653 _11654 _11655 _11656 _11657 _11658 _11659 _11660 _11661 _11662 _11663 _11664 _11665 _11666 _11667 _11668 _11669 _11670 _11671 _11672 _11673 _11674 _11675 _11676 _11677 _11678 _11679 _11680 _11681 _11682 _11683 _11684 _11685 _11686 _11687 _11688 _11689 _11690 _11691 _11692 _11693 _11694 _11695 _11696 _11697 _11698 _11699 _116100 _116101 _116102 _116103 _116104 _116105 _116106 _116107 _116108 _116109 _116110 _116111 _116112 _116113 _116114 _116115 _116116 _116117 _116118 _116119 _116120 _116121 _116122 _116123 _116124 _116125 _116126 _116127 _116128 _116129 _116130 _116131 _116132 _116133 _116134 _116135 _116136 _116137 _116138 _116139 _116140 _116141 _116142 _116143 _116144 _116145 _116146 _116147 _116148 _116149 _116150 _116151 _116152 _116153 _116154 _116155 _116156 _116157 _116158 _116159 _116160 _116161 _116162 _116163 _116164 _116165 _116166 _116167 _116168 _116169 _116170 _116171 _116172 _116173 _116174 _116175 _116176 _116177 _116178 _116179 _116180 _116181 _116182 _116183 _116184 _116185 _116186 _116187 _116188 _116189 _116190 _116191 _116192 _116193 _116194 _116195 _116196 _116197 _116198 _116199 _116200 _116201 _116202 _116203 _116204 _116205 _116206 _116207 _116208 _116209 _116210 _116211 _116212 _116213 _116214 _116215 _116216 _116217 _116218 _116219 _116220 _116221 _116222 _116223 _116224 _116225 _116226 _116227 _116228 _116229 _116230 _116231 _116232 _116233 _116234 _116235 _116236 _116237 _116238 _116239 _116240 _116241 _116242 _116243 _116244 _116245 _116246 _116247 _116248 _116249 _116250 _116251 _116252 _116253 _116254 _116255 _116256 _116257 _116258 _116259 _116260 _116261 _116262 _116263 _116264 _116265 _116266 _116267 _116268 _116269 _116270 _116271 _116272 _116273 _116274 _116275 _116276 _116277 _116278 _116279 _116280 _116281 _116282 _116283 _116284 _116285 _116286 _116287 _116288 _116289 _116290 _116291 _116292 _116293 _116294 _116295 _116296 _116297 _116298 _116299 _116300 _116301 _116302 _116303 _116304 _116305 _116306 _116307 _116308 _116309 _116310 _116311 _116312 _116313 _116314 _116315 _116316 _116317 _116318 _116319 _116320 _116321 _116322 _116323 _116324 _116325 _116326 _116327 _116328 _116329 _116330 _116331 _116332 _116333 _116334 _116335 _116336 _116337 _116338 _116339 _116340 _116341 _116342 _116343 _116344 _116345 _116346 _116347 _116348 _116349 _116350 _116351 _116352 _116353 _116354 _116355 _116356 _116357 _116358 _116359 _116360 _116361 _116362 _116363 _116364 _116365 _116366 _116367 _116368 _116369 _116370 _116371 _116372 _116373 _116374 _116375 _116376 _116377 _116378 _116379 _116380 _116381 _116382 _116383 _116384 _116385 _116386 _116387 _116388 _116389 _116390 _116391 _116392 _116393 _116394 _116395 _116396 _116397 _116398 _116399 _116400 _116401 _116402 _116403 _116404 _116405 _116406 _116407 _116408 _116409 _116410 _116411 _116412 _116413 _116414 _116415 _116416 _116417 _116418 _116419 _116420 _116421 _116422 _116423 _116424 _116425 _116426 _116427 _116428 _116429 _116430 _116431 _116432 _116433 _116434 _116435 _116436 _116437 _116438 _116439 _116440 _116441 _116442 _116443 _116444 _116445 _116446 _116447 _116448 _116449 _116450 _116451 _116452 _116453 _116454 _116455 _116456 _116457 _116458 _116459 _116460 _116461 _116462 _116463 _116464 _116465 _116466 _116467 _116468 _116469 _116470 _116471 _116472 _116473 _116474 _116475 _116476 _116477 _116478 _116479 _116480 _116481 _116482 _116483 _116484 _116485 _116486 _116487 _116488 _116489 _116490 _116491 _116492 _116493 _116494 _116495 _116496 _116497 _116498 _116499 _116500 _116501 _116502 _116503 _116504 _116505 _116506 _116507 _116508 _116509 _116510 _116511 _116512 _116513 _116514] => _116514 -> _116 -> (_116514, _116258, _116257) -> (t, (_116256, (_1161, (_1162, (_1163, (_1164, (_1165, (_1166, (_1167, _1168, _1168), (_1167, _1169, _1169)), (_1166, (_11610, _11611, _11611), (_11610, _11612, _11612))), (_1165, (_11613, (_11614, _11615, _11615), (_11614, _11616, _11616)), (_11613, (_11617, _11618, _11618), (_11617, _11619, _11619)))), (_1164, (_11620, (_11621, (_11622, _11623, _11623), (_11622, _11624, _11624)), (_11621, (_11625, _11626, _11626), (_11625, _11627, _11627))), (_11620, (_11628, (_11629, _11630, _11630), (_11629, _11631, _11631)), (_11628, (_11632, _11633, _11633), (_11632, _11634, _11634))))), (_1163, (_11635, (_11636, (_11637, (_11638, _11639, _11639), (_11638, _11640, _11640)), (_11637, (_11641, _11642, _11642), (_11641, _11643, _11643))), (_11636, (_11644, (_11645, _11646, _11646), (_11645, _11647, _11647)), (_11644, (_11648, _11649, _11649), (_11648, _11650, _11650)))), (_11635, (_11651, (_11652, (_11653, _11654, _11654), (_11653, _11655, _11655)), (_11652, (_11656, _11657, _11657), (_11656, _11658, _11658))), (_11651, (_11659, (_11660, _11661, _11661), (_11660, _11662, _11662)), (_11659, (_11663, _11664, _11664), (_11663, _11665, _11665)))))), (_1162, (_11666, (_11667, (_11668, (_11669, (_11670, _11671, _11671), (_11670, _11672, _11672)), (_11669, (_11673, _11674, _11674), (_11673, _11675, _11675))), (_11668, (_11676, (_11677, _11678, _11678), (_11677, _11679, _11679)), (_11676, (_11680, _11681, _11681), (_11680, _11682, _11682)))), (_11667, (_11683, (_11684, (_11685, _11686, _11686), (_11685, _11687, _11687)), (_11684, (_11688, _11689, _11689), (_11688, _11690, _11690))), (_11683, (_11691, (_11692, _11693, _11693), (_11692, _11694, _11694)), (_11691, (_11695, _11696, _11696), (_11695, _11697, _11697))))), (_11666, (_11698, (_11699, (_116100, (_116101, _116102, _116102), (_116101, _116103, _116103)), (_116100, (_116104, _116105, _116105), (_116104, _116106, _116106))), (_11699, (_116107, (_116108, _116109, _116109), (_116108, _116110, _116110)), (_116107, (_116111, _116112, _116112), (_116111, _116113, _116113)))), (_11698, (_116114, (_116115, (_116116, _116117, _116117), (_116116, _116118, _116118)), (_116115, (_116119, _116120, _116120), (_116119, _116121, _116121))), (_116114, (_116122, (_116123, _116124, _116124), (_116123, _116125, _116125)), (_116122, (_116126, _116127, _116127), (_116126, _116128, _116128))))))), (_1161, (_116129, (_116130, (_116131, (_116132, (_116133, (_116134, _116135, _116135), (_116134, _116136, _116136)), (_116133, (_116137, _116138, _116138), (_116137, _116139, _116139))), (_116132, (_116140, (_116141, _116142, _116142), (_116141, _116143, _116143)), (_116140, (_116144, _116145, _116145), (_116144, _116146, _116146)))), (_116131, (_116147, (_116148, (_116149, _116150, _116150), (_116149, _116151, _116151)), (_116148, (_116152, _116153, _116153), (_116152, _116154, _116154))), (_116147, (_116155, (_116156, _116157, _116157), (_116156, _116158, _116158)), (_116155, (_116159, _116160, _116160), (_116159, _116161, _116161))))), (_116130, (_116162, (_116163, (_116164, (_116165, _116166, _116166), (_116165, _116167, _116167)), (_116164, (_116168, _116169, _116169), (_116168, _116170, _116170))), (_116163, (_116171, (_116172, _116173, _116173), (_116172, _116174, _116174)), (_116171, (_116175, _116176, _116176), (_116175, _116177, _116177)))), (_116162, (_116178, (_116179, (_116180, _116181, _116181), (_116180, _116182, _116182)), (_116179, (_116183, _116184, _116184), (_116183, _116185, _116185))), (_116178, (_116186, (_116187, _116188, _116188), (_116187, _116189, _116189)), (_116186, (_116190, _116191, _116191), (_116190, _116192, _116192)))))), (_116129, (_116193, (_116194, (_116195, (_116196, (_116197, _116198, _116198), (_116197, _116199, _116199)), (_116196, (_116200, _116201, _116201), (_116200, _116202, _116202))), (_116195, (_116203, (_116204, _116205, _116205), (_116204, _116206, _116206)), (_116203, (_116207, _116208, _116208), (_116207, _116209, _116209)))), (_116194, (_116210, (_116211, (_116212, _116213, _116213), (_116212, _116214, _116214)), (_116211, (_116215, _116216, _116216), (_116215, _116217, _116217))), (_116210, (_116218, (_116219, _116220, _116220), (_116219, _116221, _116221)), (_116218, (_116222, _116223, _116223), (_116222, _116224, _116224))))), (_116193, (_116225, (_116226, (_116227, (_116228, _116229, _116229), (_116228, _116230, _116230)), (_116227, (_116231, _116232, _116232), (_116231, _116233, _116233))), (_116226, (_116234, (_116235, _116236, _116236), (_116235, _116237, _116237)), (_116234, (_116238, _116239, _116239), (_116238, _116240, _116240)))), (_116225, (_116241, (_116242, (_116243, _116244, _116244), (_116243, _116245, _116245)), (_116242, (_116246, _116247, _116247), (_116246, _116248, _116248))), (_116241, (_116249, (_116250, _116251, _116251), (_116250, _116252, _116252)), (_116249, (_116253, _116254, _116254), (_116253, _116255, _116255)))))))), (_116256, (_116259, (_116260, (_116261, (_116262, (_116263, (_116264, (_116265, _116266, _116266), (_116265, _116267, _116267)), (_116264, (_116268, _116269, _116269), (_116268, _116270, _116270))), (_116263, (_116271, (_116272, _116273, _116273), (_116272, _116274, _116274)), (_116271, (_116275, _116276, _116276), (_116275, _116277, _116277)))), (_116262, (_116278, (_116279, (_116280, _116281, _116281), (_116280, _116282, _116282)), (_116279, (_116283, _116284, _116284), (_116283, _116285, _116285))), (_116278, (_116286, (_116287, _116288, _116288), (_116287, _116289, _116289)), (_116286, (_116290, _116291, _116291), (_116290, _116292, _116292))))), (_116261, (_116293, (_116294, (_116295, (_116296, _116297, _116297), (_116296, _116298, _116298)), (_116295, (_116299, _116300, _116300), (_116299, _116301, _116301))), (_116294, (_116302, (_116303, _116304, _116304), (_116303, _116305, _116305)), (_116302, (_116306, _116307, _116307), (_116306, _116308, _116308)))), (_116293, (_116309, (_116310, (_116311, _116312, _116312), (_116311, _116313, _116313)), (_116310, (_116314, _116315, _116315), (_116314, _116316, _116316))), (_116309, (_116317, (_116318, _116319, _116319), (_116318, _116320, _116320)), (_116317, (_116321, _116322, _116322), (_116321, _116323, _116323)))))), (_116260, (_116324, (_116325, (_116326, (_116327, (_116328, _116329, _116329), (_116328, _116330, _116330)), (_116327, (_116331, _116332, _116332), (_116331, _116333, _116333))), (_116326, (_116334, (_116335, _116336, _116336), (_116335, _116337, _116337)), (_116334, (_116338, _116339, _116339), (_116338, _116340, _116340)))), (_116325, (_116341, (_116342, (_116343, _116344, _116344), (_116343, _116345, _116345)), (_116342, (_116346, _116347, _116347), (_116346, _116348, _116348))), (_116341, (_116349, (_116350, _116351, _116351), (_116350, _116352, _116352)), (_116349, (_116353, _116354, _116354), (_116353, _116355, _116355))))), (_116324, (_116356, (_116357, (_116358, (_116359, _116360, _116360), (_116359, _116361, _116361)), (_116358, (_116362, _116363, _116363), (_116362, _116364, _116364))), (_116357, (_116365, (_116366, _116367, _116367), (_116366, _116368, _116368)), (_116365, (_116369, _116370, _116370), (_116369, _116371, _116371)))), (_116356, (_116372, (_116373, (_116374, _116375, _116375), (_116374, _116376, _116376)), (_116373, (_116377, _116378, _116378), (_116377, _116379, _116379))), (_116372, (_116380, (_116381, _116382, _116382), (_116381, _116383, _116383)), (_116380, (_116384, _116385, _116385), (_116384, _116386, _116386))))))), (_116259, (_116387, (_116388, (_116389, (_116390, (_116391, (_116392, _116393, _116393), (_116392, _116394, _116394)), (_116391, (_116395, _116396, _116396), (_116395, _116397, _116397))), (_116390, (_116398, (_116399, _116400, _116400), (_116399, _116401, _116401)), (_116398, (_116402, _116403, _116403), (_116402, _116404, _116404)))), (_116389, (_116405, (_116406, (_116407, _116408, _116408), (_116407, _116409, _116409)), (_116406, (_116410, _116411, _116411), (_116410, _116412, _116412))), (_116405, (_116413, (_116414, _116415, _116415), (_116414, _116416, _116416)), (_116413, (_116417, _116418, _116418), (_116417, _116419, _116419))))), (_116388, (_116420, (_116421, (_116422, (_116423, _116424, _116424), (_116423, _116425, _116425)), (_116422, (_116426, _116427, _116427), (_116426, _116428, _116428))), (_116421, (_116429, (_116430, _116431, _116431), (_116430, _116432, _116432)), (_116429, (_116433, _116434, _116434), (_116433, _116435, _116435)))), (_116420, (_116436, (_116437, (_116438, _116439, _116439), (_116438, _116440, _116440)), (_116437, (_116441, _116442, _116442), (_116441, _116443, _116443))), (_116436, (_116444, (_116445, _116446, _116446), (_116445, _116447, _116447)), (_116444, (_116448, _116449, _116449), (_116448, _116450, _116450)))))), (_116387, (_116451, (_116452, (_116453, (_116454, (_116455, _116456, _116456), (_116455, _116457, _116457)), (_116454, (_116458, _116459, _116459), (_116458, _116460, _116460))), (_116453, (_116461, (_116462, _116463, _116463), (_116462, _116464, _116464)), (_116461, (_116465, _116466, _116466), (_116465, _116467, _116467)))), (_116452, (_116468, (_116469, (_116470, _116471, _116471), (_116470, _116472, _116472)), (_116469, (_116473, _116474, _116474), (_116473, _116475, _116475))), (_116468, (_116476, (_116477, _116478, _116478), (_116477, _116479, _116479)), (_116476, (_116480, _116481, _116481), (_116480, _116482, _116482))))), (_116451, (_116483, (_116484, (_116485, (_116486, _116487, _116487), (_116486, _116488, _116488)), (_116485, (_116489, _116490, _116490), (_116489, _116491, _116491))), (_116484, (_116492, (_116493, _116494, _116494), (_116493, _116495, _116495)), (_116492, (_116496, _116497, _116497), (_116496, _116498, _116498)))), (_116483, (_116499, (_116500, (_116501, _116502, _116502), (_116501, _116503, _116503)), (_116500, (_116504, _116505, _116505), (_116504, _116506, _116506))), (_116499, (_116507, (_116508, _116509, _116509), (_116508, _116510, _116510)), (_116507, (_116511, _116512, _116512), (_116511, _116513, _116513))))))))) -> t ; -1 g_rec :: __forall [t _116 _1161 _1162 _1163 _1164 _1165 _1166 _1167 _1168 _1169] => (_116 -> _1161 -> _1162 -> _1169 -> t) -> (_1167 -> _1163 -> _1164 -> _1165 -> t) -> _1166 -> _116 -> (_1166, _1163, _1167) -> (_1168, _1169, _1165) -> _1168 ; +1 fac_rec1 :: __forall [t t1 t2] => (t, t1, t1) -> (t2, t1) -> t ; +1 fac_rec2 :: __forall [t t1 t2 t3 t4] => (t, (t2, t1), (t3, t1, t1)) -> (t4, (t2, t1)) -> t ; +1 fac_rec3 :: __forall [t t1 t2 t3 t4 t5 t6] => (t, (t4, (t1, t2)), (t5, (t1, t2), (t3, t2, t2))) -> (t6, (t4, (t1, t2))) -> t ; +1 fac_rec4 :: __forall [t t1 t2 t3 t4 t5 t6 t7 t8] => (t, (t6, (t1, (t2, t3))), (t7, (t1, (t2, t3)), (t4, (t2, t3), (t5, t3, t3)))) -> (t8, (t6, (t1, (t2, t3)))) -> t ; +1 g :: __forall [t t1 t2 t3 t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104 t105 t106 t107 t108 t109 t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131 t132 t133 t134 t135 t136 t137 t138 t139 t140 t141 t142 t143 t144 t145 t146 t147 t148 t149 t150 t151 t152 t153 t154 t155 t156 t157 t158 t159 t160 t161 t162 t163 t164 t165 t166 t167 t168 t169 t170 t171 t172 t173 t174 t175 t176 t177 t178 t179 t180 t181 t182 t183 t184 t185 t186 t187 t188 t189 t190 t191 t192 t193 t194 t195 t196 t197 t198 t199 t200 t201 t202 t203 t204 t205 t206 t207 t208 t209 t210 t211 t212 t213 t214 t215 t216 t217 t218 t219 t220 t221 t222 t223 t224 t225 t226 t227 t228 t229 t230 t231 t232 t233 t234 t235 t236 t237 t238 t239 t240 t241 t242 t243 t244 t245 t246 t247 t248 t249 t250 t251 t252 t253 t254 t255 t256 t257 t258 t259 t260 t261 t262 t263 t264 t265 t266 t267 t268 t269 t270 t271 t272 t273 t274 t275 t276 t277 t278 t279 t280 t281 t282 t283 t284 t285 t286 t287 t288 t289 t290 t291 t292 t293 t294 t295 t296 t297 t298 t299 t300 t301 t302 t303 t304 t305 t306 t307 t308 t309 t310 t311 t312 t313 t314 t315 t316 t317 t318 t319 t320 t321 t322 t323 t324 t325 t326 t327 t328 t329 t330 t331 t332 t333 t334 t335 t336 t337 t338 t339 t340 t341 t342 t343 t344 t345 t346 t347 t348 t349 t350 t351 t352 t353 t354 t355 t356 t357 t358 t359 t360 t361 t362 t363 t364 t365 t366 t367 t368 t369 t370 t371 t372 t373 t374 t375 t376 t377 t378 t379 t380 t381 t382 t383 t384 t385 t386 t387 t388 t389 t390 t391 t392 t393 t394 t395 t396 t397 t398 t399 t400 t401 t402 t403 t404 t405 t406 t407 t408 t409 t410 t411 t412 t413 t414 t415 t416 t417 t418 t419 t420 t421 t422 t423 t424 t425 t426 t427 t428 t429 t430 t431 t432 t433 t434 t435 t436 t437 t438 t439 t440 t441 t442 t443 t444 t445 t446 t447 t448 t449 t450 t451 t452 t453 t454 t455 t456 t457 t458 t459 t460 t461 t462 t463 t464 t465 t466 t467 t468 t469 t470 t471 t472 t473 t474 t475 t476 t477 t478 t479 t480 t481 t482 t483 t484 t485 t486 t487 t488 t489 t490 t491 t492 t493 t494 t495 t496 t497 t498 t499 t500 t501 t502 t503 t504 t505 t506 t507 t508 t509 t510 t511 t512 t513 t514 t515] => t515 -> t1 -> (t515, t259, t258) -> (t, (t257, (t2, (t3, (t4, (t5, (t6, (t7, (t8, t9, t9), (t8, t10, t10)), (t7, (t11, t12, t12), (t11, t13, t13))), (t6, (t14, (t15, t16, t16), (t15, t17, t17)), (t14, (t18, t19, t19), (t18, t20, t20)))), (t5, (t21, (t22, (t23, t24, t24), (t23, t25, t25)), (t22, (t26, t27, t27), (t26, t28, t28))), (t21, (t29, (t30, t31, t31), (t30, t32, t32)), (t29, (t33, t34, t34), (t33, t35, t35))))), (t4, (t36, (t37, (t38, (t39, t40, t40), (t39, t41, t41)), (t38, (t42, t43, t43), (t42, t44, t44))), (t37, (t45, (t46, t47, t47), (t46, t48, t48)), (t45, (t49, t50, t50), (t49, t51, t51)))), (t36, (t52, (t53, (t54, t55, t55), (t54, t56, t56)), (t53, (t57, t58, t58), (t57, t59, t59))), (t52, (t60, (t61, t62, t62), (t61, t63, t63)), (t60, (t64, t65, t65), (t64, t66, t66)))))), (t3, (t67, (t68, (t69, (t70, (t71, t72, t72), (t71, t73, t73)), (t70, (t74, t75, t75), (t74, t76, t76))), (t69, (t77, (t78, t79, t79), (t78, t80, t80)), (t77, (t81, t82, t82), (t81, t83, t83)))), (t68, (t84, (t85, (t86, t87, t87), (t86, t88, t88)), (t85, (t89, t90, t90), (t89, t91, t91))), (t84, (t92, (t93, t94, t94), (t93, t95, t95)), (t92, (t96, t97, t97), (t96, t98, t98))))), (t67, (t99, (t100, (t101, (t102, t103, t103), (t102, t104, t104)), (t101, (t105, t106, t106), (t105, t107, t107))), (t100, (t108, (t109, t110, t110), (t109, t111, t111)), (t108, (t112, t113, t113), (t112, t114, t114)))), (t99, (t115, (t116, (t117, t118, t118), (t117, t119, t119)), (t116, (t120, t121, t121), (t120, t122, t122))), (t115, (t123, (t124, t125, t125), (t124, t126, t126)), (t123, (t127, t128, t128), (t127, t129, t129))))))), (t2, (t130, (t131, (t132, (t133, (t134, (t135, t136, t136), (t135, t137, t137)), (t134, (t138, t139, t139), (t138, t140, t140))), (t133, (t141, (t142, t143, t143), (t142, t144, t144)), (t141, (t145, t146, t146), (t145, t147, t147)))), (t132, (t148, (t149, (t150, t151, t151), (t150, t152, t152)), (t149, (t153, t154, t154), (t153, t155, t155))), (t148, (t156, (t157, t158, t158), (t157, t159, t159)), (t156, (t160, t161, t161), (t160, t162, t162))))), (t131, (t163, (t164, (t165, (t166, t167, t167), (t166, t168, t168)), (t165, (t169, t170, t170), (t169, t171, t171))), (t164, (t172, (t173, t174, t174), (t173, t175, t175)), (t172, (t176, t177, t177), (t176, t178, t178)))), (t163, (t179, (t180, (t181, t182, t182), (t181, t183, t183)), (t180, (t184, t185, t185), (t184, t186, t186))), (t179, (t187, (t188, t189, t189), (t188, t190, t190)), (t187, (t191, t192, t192), (t191, t193, t193)))))), (t130, (t194, (t195, (t196, (t197, (t198, t199, t199), (t198, t200, t200)), (t197, (t201, t202, t202), (t201, t203, t203))), (t196, (t204, (t205, t206, t206), (t205, t207, t207)), (t204, (t208, t209, t209), (t208, t210, t210)))), (t195, (t211, (t212, (t213, t214, t214), (t213, t215, t215)), (t212, (t216, t217, t217), (t216, t218, t218))), (t211, (t219, (t220, t221, t221), (t220, t222, t222)), (t219, (t223, t224, t224), (t223, t225, t225))))), (t194, (t226, (t227, (t228, (t229, t230, t230), (t229, t231, t231)), (t228, (t232, t233, t233), (t232, t234, t234))), (t227, (t235, (t236, t237, t237), (t236, t238, t238)), (t235, (t239, t240, t240), (t239, t241, t241)))), (t226, (t242, (t243, (t244, t245, t245), (t244, t246, t246)), (t243, (t247, t248, t248), (t247, t249, t249))), (t242, (t250, (t251, t252, t252), (t251, t253, t253)), (t250, (t254, t255, t255), (t254, t256, t256)))))))), (t257, (t260, (t261, (t262, (t263, (t264, (t265, (t266, t267, t267), (t266, t268, t268)), (t265, (t269, t270, t270), (t269, t271, t271))), (t264, (t272, (t273, t274, t274), (t273, t275, t275)), (t272, (t276, t277, t277), (t276, t278, t278)))), (t263, (t279, (t280, (t281, t282, t282), (t281, t283, t283)), (t280, (t284, t285, t285), (t284, t286, t286))), (t279, (t287, (t288, t289, t289), (t288, t290, t290)), (t287, (t291, t292, t292), (t291, t293, t293))))), (t262, (t294, (t295, (t296, (t297, t298, t298), (t297, t299, t299)), (t296, (t300, t301, t301), (t300, t302, t302))), (t295, (t303, (t304, t305, t305), (t304, t306, t306)), (t303, (t307, t308, t308), (t307, t309, t309)))), (t294, (t310, (t311, (t312, t313, t313), (t312, t314, t314)), (t311, (t315, t316, t316), (t315, t317, t317))), (t310, (t318, (t319, t320, t320), (t319, t321, t321)), (t318, (t322, t323, t323), (t322, t324, t324)))))), (t261, (t325, (t326, (t327, (t328, (t329, t330, t330), (t329, t331, t331)), (t328, (t332, t333, t333), (t332, t334, t334))), (t327, (t335, (t336, t337, t337), (t336, t338, t338)), (t335, (t339, t340, t340), (t339, t341, t341)))), (t326, (t342, (t343, (t344, t345, t345), (t344, t346, t346)), (t343, (t347, t348, t348), (t347, t349, t349))), (t342, (t350, (t351, t352, t352), (t351, t353, t353)), (t350, (t354, t355, t355), (t354, t356, t356))))), (t325, (t357, (t358, (t359, (t360, t361, t361), (t360, t362, t362)), (t359, (t363, t364, t364), (t363, t365, t365))), (t358, (t366, (t367, t368, t368), (t367, t369, t369)), (t366, (t370, t371, t371), (t370, t372, t372)))), (t357, (t373, (t374, (t375, t376, t376), (t375, t377, t377)), (t374, (t378, t379, t379), (t378, t380, t380))), (t373, (t381, (t382, t383, t383), (t382, t384, t384)), (t381, (t385, t386, t386), (t385, t387, t387))))))), (t260, (t388, (t389, (t390, (t391, (t392, (t393, t394, t394), (t393, t395, t395)), (t392, (t396, t397, t397), (t396, t398, t398))), (t391, (t399, (t400, t401, t401), (t400, t402, t402)), (t399, (t403, t404, t404), (t403, t405, t405)))), (t390, (t406, (t407, (t408, t409, t409), (t408, t410, t410)), (t407, (t411, t412, t412), (t411, t413, t413))), (t406, (t414, (t415, t416, t416), (t415, t417, t417)), (t414, (t418, t419, t419), (t418, t420, t420))))), (t389, (t421, (t422, (t423, (t424, t425, t425), (t424, t426, t426)), (t423, (t427, t428, t428), (t427, t429, t429))), (t422, (t430, (t431, t432, t432), (t431, t433, t433)), (t430, (t434, t435, t435), (t434, t436, t436)))), (t421, (t437, (t438, (t439, t440, t440), (t439, t441, t441)), (t438, (t442, t443, t443), (t442, t444, t444))), (t437, (t445, (t446, t447, t447), (t446, t448, t448)), (t445, (t449, t450, t450), (t449, t451, t451)))))), (t388, (t452, (t453, (t454, (t455, (t456, t457, t457), (t456, t458, t458)), (t455, (t459, t460, t460), (t459, t461, t461))), (t454, (t462, (t463, t464, t464), (t463, t465, t465)), (t462, (t466, t467, t467), (t466, t468, t468)))), (t453, (t469, (t470, (t471, t472, t472), (t471, t473, t473)), (t470, (t474, t475, t475), (t474, t476, t476))), (t469, (t477, (t478, t479, t479), (t478, t480, t480)), (t477, (t481, t482, t482), (t481, t483, t483))))), (t452, (t484, (t485, (t486, (t487, t488, t488), (t487, t489, t489)), (t486, (t490, t491, t491), (t490, t492, t492))), (t485, (t493, (t494, t495, t495), (t494, t496, t496)), (t493, (t497, t498, t498), (t497, t499, t499)))), (t484, (t500, (t501, (t502, t503, t503), (t502, t504, t504)), (t501, (t505, t506, t506), (t505, t507, t507))), (t500, (t508, (t509, t510, t510), (t509, t511, t511)), (t508, (t512, t513, t513), (t512, t514, t514))))))))) -> t ; +1 g_rec :: __forall [t t1 t2 t3 t4 t5 t6 t7 t8 t9 t10] => (t1 -> t2 -> t3 -> t10 -> t) -> (t8 -> t4 -> t5 -> t6 -> t) -> t7 -> t1 -> (t7, t4, t8) -> (t9, t10, t6) -> t9 ; 1 g_rec0 :: __forall [t] => t -> t -> t -> t -> t ; -1 g_rec1 :: __forall [t _116 _1161] => _1161 -> _116 -> (_1161, _116, _116) -> (t, _116, _116) -> t ; -1 g_rec2 :: __forall [t _116 _1161 _1162 _1163 _1164 _1165] => _1165 -> _116 -> (_1165, _1164, _1163) -> (t, (_1162, _1161, _1161), (_1162, _1164, _1164)) -> t ; -1 g_rec3 :: __forall [t _116 _1161 _1162 _1163 _1164 _1165 _1166 _1167 _1168 _1169 _11610] => _11610 -> _116 -> (_11610, _1166, _1165) -> (t, (_1164, (_1162, _1163, _1163), (_1162, _1161, _1161)), (_1164, (_1168, _1169, _1169), (_1168, _1167, _1167))) -> t ; -1 g_rec4 :: __forall [t _116 _1161 _1162 _1163 _1164 _1165 _1166 _1167 _1168 _1169 _11610 _11611 _11612 _11613 _11614 _11615 _11616 _11617 _11618] => _11618 -> _116 -> (_11618, _11610, _1169) -> (t, (_1168, (_1161, (_1162, _1163, _1163), (_1162, _1164, _1164)), (_1161, (_1165, _1166, _1166), (_1165, _1167, _1167))), (_1168, (_11611, (_11612, _11613, _11613), (_11612, _11614, _11614)), (_11611, (_11615, _11616, _11616), (_11615, _11617, _11617)))) -> t ; -1 g_rec5 :: __forall [t _116 _1161 _1162 _1163 _1164 _1165 _1166 _1167 _1168 _1169 _11610 _11611 _11612 _11613 _11614 _11615 _11616 _11617 _11618 _11619 _11620 _11621 _11622 _11623 _11624 _11625 _11626 _11627 _11628 _11629 _11630 _11631 _11632 _11633 _11634] => _11634 -> _116 -> (_11634, _11618, _11617) -> (t, (_11616, (_1161, (_1162, (_1163, _1164, _1164), (_1163, _1165, _1165)), (_1162, (_1166, _1167, _1167), (_1166, _1168, _1168))), (_1161, (_1169, (_11610, _11611, _11611), (_11610, _11612, _11612)), (_1169, (_11613, _11614, _11614), (_11613, _11615, _11615)))), (_11616, (_11619, (_11620, (_11621, _11622, _11622), (_11621, _11623, _11623)), (_11620, (_11624, _11625, _11625), (_11624, _11626, _11626))), (_11619, (_11627, (_11628, _11629, _11629), (_11628, _11630, _11630)), (_11627, (_11631, _11632, _11632), (_11631, _11633, _11633))))) -> t ; -1 g_rec6 :: __forall [t _116 _1161 _1162 _1163 _1164 _1165 _1166 _1167 _1168 _1169 _11610 _11611 _11612 _11613 _11614 _11615 _11616 _11617 _11618 _11619 _11620 _11621 _11622 _11623 _11624 _11625 _11626 _11627 _11628 _11629 _11630 _11631 _11632 _11633 _11634 _11635 _11636 _11637 _11638 _11639 _11640 _11641 _11642 _11643 _11644 _11645 _11646 _11647 _11648 _11649 _11650 _11651 _11652 _11653 _11654 _11655 _11656 _11657 _11658 _11659 _11660 _11661 _11662 _11663 _11664 _11665 _11666] => _11666 -> _116 -> (_11666, _11634, _11633) -> (t, (_11632, (_1161, (_1162, (_1163, (_1164, _1165, _1165), (_1164, _1166, _1166)), (_1163, (_1167, _1168, _1168), (_1167, _1169, _1169))), (_1162, (_11610, (_11611, _11612, _11612), (_11611, _11613, _11613)), (_11610, (_11614, _11615, _11615), (_11614, _11616, _11616)))), (_1161, (_11617, (_11618, (_11619, _11620, _11620), (_11619, _11621, _11621)), (_11618, (_11622, _11623, _11623), (_11622, _11624, _11624))), (_11617, (_11625, (_11626, _11627, _11627), (_11626, _11628, _11628)), (_11625, (_11629, _11630, _11630), (_11629, _11631, _11631))))), (_11632, (_11635, (_11636, (_11637, (_11638, _11639, _11639), (_11638, _11640, _11640)), (_11637, (_11641, _11642, _11642), (_11641, _11643, _11643))), (_11636, (_11644, (_11645, _11646, _11646), (_11645, _11647, _11647)), (_11644, (_11648, _11649, _11649), (_11648, _11650, _11650)))), (_11635, (_11651, (_11652, (_11653, _11654, _11654), (_11653, _11655, _11655)), (_11652, (_11656, _11657, _11657), (_11656, _11658, _11658))), (_11651, (_11659, (_11660, _11661, _11661), (_11660, _11662, _11662)), (_11659, (_11663, _11664, _11664), (_11663, _11665, _11665)))))) -> t ; -1 g_rec7 :: __forall [t _116 _1161 _1162 _1163 _1164 _1165 _1166 _1167 _1168 _1169 _11610 _11611 _11612 _11613 _11614 _11615 _11616 _11617 _11618 _11619 _11620 _11621 _11622 _11623 _11624 _11625 _11626 _11627 _11628 _11629 _11630 _11631 _11632 _11633 _11634 _11635 _11636 _11637 _11638 _11639 _11640 _11641 _11642 _11643 _11644 _11645 _11646 _11647 _11648 _11649 _11650 _11651 _11652 _11653 _11654 _11655 _11656 _11657 _11658 _11659 _11660 _11661 _11662 _11663 _11664 _11665 _11666 _11667 _11668 _11669 _11670 _11671 _11672 _11673 _11674 _11675 _11676 _11677 _11678 _11679 _11680 _11681 _11682 _11683 _11684 _11685 _11686 _11687 _11688 _11689 _11690 _11691 _11692 _11693 _11694 _11695 _11696 _11697 _11698 _11699 _116100 _116101 _116102 _116103 _116104 _116105 _116106 _116107 _116108 _116109 _116110 _116111 _116112 _116113 _116114 _116115 _116116 _116117 _116118 _116119 _116120 _116121 _116122 _116123 _116124 _116125 _116126 _116127 _116128 _116129 _116130] => _116130 -> _116 -> (_116130, _11666, _11665) -> (t, (_11664, (_1161, (_1162, (_1163, (_1164, (_1165, _1166, _1166), (_1165, _1167, _1167)), (_1164, (_1168, _1169, _1169), (_1168, _11610, _11610))), (_1163, (_11611, (_11612, _11613, _11613), (_11612, _11614, _11614)), (_11611, (_11615, _11616, _11616), (_11615, _11617, _11617)))), (_1162, (_11618, (_11619, (_11620, _11621, _11621), (_11620, _11622, _11622)), (_11619, (_11623, _11624, _11624), (_11623, _11625, _11625))), (_11618, (_11626, (_11627, _11628, _11628), (_11627, _11629, _11629)), (_11626, (_11630, _11631, _11631), (_11630, _11632, _11632))))), (_1161, (_11633, (_11634, (_11635, (_11636, _11637, _11637), (_11636, _11638, _11638)), (_11635, (_11639, _11640, _11640), (_11639, _11641, _11641))), (_11634, (_11642, (_11643, _11644, _11644), (_11643, _11645, _11645)), (_11642, (_11646, _11647, _11647), (_11646, _11648, _11648)))), (_11633, (_11649, (_11650, (_11651, _11652, _11652), (_11651, _11653, _11653)), (_11650, (_11654, _11655, _11655), (_11654, _11656, _11656))), (_11649, (_11657, (_11658, _11659, _11659), (_11658, _11660, _11660)), (_11657, (_11661, _11662, _11662), (_11661, _11663, _11663)))))), (_11664, (_11667, (_11668, (_11669, (_11670, (_11671, _11672, _11672), (_11671, _11673, _11673)), (_11670, (_11674, _11675, _11675), (_11674, _11676, _11676))), (_11669, (_11677, (_11678, _11679, _11679), (_11678, _11680, _11680)), (_11677, (_11681, _11682, _11682), (_11681, _11683, _11683)))), (_11668, (_11684, (_11685, (_11686, _11687, _11687), (_11686, _11688, _11688)), (_11685, (_11689, _11690, _11690), (_11689, _11691, _11691))), (_11684, (_11692, (_11693, _11694, _11694), (_11693, _11695, _11695)), (_11692, (_11696, _11697, _11697), (_11696, _11698, _11698))))), (_11667, (_11699, (_116100, (_116101, (_116102, _116103, _116103), (_116102, _116104, _116104)), (_116101, (_116105, _116106, _116106), (_116105, _116107, _116107))), (_116100, (_116108, (_116109, _116110, _116110), (_116109, _116111, _116111)), (_116108, (_116112, _116113, _116113), (_116112, _116114, _116114)))), (_11699, (_116115, (_116116, (_116117, _116118, _116118), (_116117, _116119, _116119)), (_116116, (_116120, _116121, _116121), (_116120, _116122, _116122))), (_116115, (_116123, (_116124, _116125, _116125), (_116124, _116126, _116126)), (_116123, (_116127, _116128, _116128), (_116127, _116129, _116129))))))) -> t ; -1 g_rec8 :: __forall [t _116 _1161 _1162 _1163 _1164 _1165 _1166 _1167 _1168 _1169 _11610 _11611 _11612 _11613 _11614 _11615 _11616 _11617 _11618 _11619 _11620 _11621 _11622 _11623 _11624 _11625 _11626 _11627 _11628 _11629 _11630 _11631 _11632 _11633 _11634 _11635 _11636 _11637 _11638 _11639 _11640 _11641 _11642 _11643 _11644 _11645 _11646 _11647 _11648 _11649 _11650 _11651 _11652 _11653 _11654 _11655 _11656 _11657 _11658 _11659 _11660 _11661 _11662 _11663 _11664 _11665 _11666 _11667 _11668 _11669 _11670 _11671 _11672 _11673 _11674 _11675 _11676 _11677 _11678 _11679 _11680 _11681 _11682 _11683 _11684 _11685 _11686 _11687 _11688 _11689 _11690 _11691 _11692 _11693 _11694 _11695 _11696 _11697 _11698 _11699 _116100 _116101 _116102 _116103 _116104 _116105 _116106 _116107 _116108 _116109 _116110 _116111 _116112 _116113 _116114 _116115 _116116 _116117 _116118 _116119 _116120 _116121 _116122 _116123 _116124 _116125 _116126 _116127 _116128 _116129 _116130 _116131 _116132 _116133 _116134 _116135 _116136 _116137 _116138 _116139 _116140 _116141 _116142 _116143 _116144 _116145 _116146 _116147 _116148 _116149 _116150 _116151 _116152 _116153 _116154 _116155 _116156 _116157 _116158 _116159 _116160 _116161 _116162 _116163 _116164 _116165 _116166 _116167 _116168 _116169 _116170 _116171 _116172 _116173 _116174 _116175 _116176 _116177 _116178 _116179 _116180 _116181 _116182 _116183 _116184 _116185 _116186 _116187 _116188 _116189 _116190 _116191 _116192 _116193 _116194 _116195 _116196 _116197 _116198 _116199 _116200 _116201 _116202 _116203 _116204 _116205 _116206 _116207 _116208 _116209 _116210 _116211 _116212 _116213 _116214 _116215 _116216 _116217 _116218 _116219 _116220 _116221 _116222 _116223 _116224 _116225 _116226 _116227 _116228 _116229 _116230 _116231 _116232 _116233 _116234 _116235 _116236 _116237 _116238 _116239 _116240 _116241 _116242 _116243 _116244 _116245 _116246 _116247 _116248 _116249 _116250 _116251 _116252 _116253 _116254 _116255 _116256 _116257 _116258] => _116258 -> _116 -> (_116258, _116130, _116129) -> (t, (_116128, (_1161, (_1162, (_1163, (_1164, (_1165, (_1166, _1167, _1167), (_1166, _1168, _1168)), (_1165, (_1169, _11610, _11610), (_1169, _11611, _11611))), (_1164, (_11612, (_11613, _11614, _11614), (_11613, _11615, _11615)), (_11612, (_11616, _11617, _11617), (_11616, _11618, _11618)))), (_1163, (_11619, (_11620, (_11621, _11622, _11622), (_11621, _11623, _11623)), (_11620, (_11624, _11625, _11625), (_11624, _11626, _11626))), (_11619, (_11627, (_11628, _11629, _11629), (_11628, _11630, _11630)), (_11627, (_11631, _11632, _11632), (_11631, _11633, _11633))))), (_1162, (_11634, (_11635, (_11636, (_11637, _11638, _11638), (_11637, _11639, _11639)), (_11636, (_11640, _11641, _11641), (_11640, _11642, _11642))), (_11635, (_11643, (_11644, _11645, _11645), (_11644, _11646, _11646)), (_11643, (_11647, _11648, _11648), (_11647, _11649, _11649)))), (_11634, (_11650, (_11651, (_11652, _11653, _11653), (_11652, _11654, _11654)), (_11651, (_11655, _11656, _11656), (_11655, _11657, _11657))), (_11650, (_11658, (_11659, _11660, _11660), (_11659, _11661, _11661)), (_11658, (_11662, _11663, _11663), (_11662, _11664, _11664)))))), (_1161, (_11665, (_11666, (_11667, (_11668, (_11669, _11670, _11670), (_11669, _11671, _11671)), (_11668, (_11672, _11673, _11673), (_11672, _11674, _11674))), (_11667, (_11675, (_11676, _11677, _11677), (_11676, _11678, _11678)), (_11675, (_11679, _11680, _11680), (_11679, _11681, _11681)))), (_11666, (_11682, (_11683, (_11684, _11685, _11685), (_11684, _11686, _11686)), (_11683, (_11687, _11688, _11688), (_11687, _11689, _11689))), (_11682, (_11690, (_11691, _11692, _11692), (_11691, _11693, _11693)), (_11690, (_11694, _11695, _11695), (_11694, _11696, _11696))))), (_11665, (_11697, (_11698, (_11699, (_116100, _116101, _116101), (_116100, _116102, _116102)), (_11699, (_116103, _116104, _116104), (_116103, _116105, _116105))), (_11698, (_116106, (_116107, _116108, _116108), (_116107, _116109, _116109)), (_116106, (_116110, _116111, _116111), (_116110, _116112, _116112)))), (_11697, (_116113, (_116114, (_116115, _116116, _116116), (_116115, _116117, _116117)), (_116114, (_116118, _116119, _116119), (_116118, _116120, _116120))), (_116113, (_116121, (_116122, _116123, _116123), (_116122, _116124, _116124)), (_116121, (_116125, _116126, _116126), (_116125, _116127, _116127))))))), (_116128, (_116131, (_116132, (_116133, (_116134, (_116135, (_116136, _116137, _116137), (_116136, _116138, _116138)), (_116135, (_116139, _116140, _116140), (_116139, _116141, _116141))), (_116134, (_116142, (_116143, _116144, _116144), (_116143, _116145, _116145)), (_116142, (_116146, _116147, _116147), (_116146, _116148, _116148)))), (_116133, (_116149, (_116150, (_116151, _116152, _116152), (_116151, _116153, _116153)), (_116150, (_116154, _116155, _116155), (_116154, _116156, _116156))), (_116149, (_116157, (_116158, _116159, _116159), (_116158, _116160, _116160)), (_116157, (_116161, _116162, _116162), (_116161, _116163, _116163))))), (_116132, (_116164, (_116165, (_116166, (_116167, _116168, _116168), (_116167, _116169, _116169)), (_116166, (_116170, _116171, _116171), (_116170, _116172, _116172))), (_116165, (_116173, (_116174, _116175, _116175), (_116174, _116176, _116176)), (_116173, (_116177, _116178, _116178), (_116177, _116179, _116179)))), (_116164, (_116180, (_116181, (_116182, _116183, _116183), (_116182, _116184, _116184)), (_116181, (_116185, _116186, _116186), (_116185, _116187, _116187))), (_116180, (_116188, (_116189, _116190, _116190), (_116189, _116191, _116191)), (_116188, (_116192, _116193, _116193), (_116192, _116194, _116194)))))), (_116131, (_116195, (_116196, (_116197, (_116198, (_116199, _116200, _116200), (_116199, _116201, _116201)), (_116198, (_116202, _116203, _116203), (_116202, _116204, _116204))), (_116197, (_116205, (_116206, _116207, _116207), (_116206, _116208, _116208)), (_116205, (_116209, _116210, _116210), (_116209, _116211, _116211)))), (_116196, (_116212, (_116213, (_116214, _116215, _116215), (_116214, _116216, _116216)), (_116213, (_116217, _116218, _116218), (_116217, _116219, _116219))), (_116212, (_116220, (_116221, _116222, _116222), (_116221, _116223, _116223)), (_116220, (_116224, _116225, _116225), (_116224, _116226, _116226))))), (_116195, (_116227, (_116228, (_116229, (_116230, _116231, _116231), (_116230, _116232, _116232)), (_116229, (_116233, _116234, _116234), (_116233, _116235, _116235))), (_116228, (_116236, (_116237, _116238, _116238), (_116237, _116239, _116239)), (_116236, (_116240, _116241, _116241), (_116240, _116242, _116242)))), (_116227, (_116243, (_116244, (_116245, _116246, _116246), (_116245, _116247, _116247)), (_116244, (_116248, _116249, _116249), (_116248, _116250, _116250))), (_116243, (_116251, (_116252, _116253, _116253), (_116252, _116254, _116254)), (_116251, (_116255, _116256, _116256), (_116255, _116257, _116257)))))))) -> t ; +1 g_rec1 :: __forall [t t1 t2] => t2 -> t1 -> (t2, t1, t1) -> (t, t1, t1) -> t ; +1 g_rec2 :: __forall [t t1 t2 t3 t4 t5 t6] => t6 -> t1 -> (t6, t5, t4) -> (t, (t3, t2, t2), (t3, t5, t5)) -> t ; +1 g_rec3 :: __forall [t t1 t2 t3 t4 t5 t6 t7 t8 t9 t10 t11] => t11 -> t1 -> (t11, t7, t6) -> (t, (t5, (t3, t4, t4), (t3, t2, t2)), (t5, (t9, t10, t10), (t9, t8, t8))) -> t ; +1 g_rec4 :: __forall [t t1 t2 t3 t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19] => t19 -> t1 -> (t19, t11, t10) -> (t, (t9, (t2, (t3, t4, t4), (t3, t5, t5)), (t2, (t6, t7, t7), (t6, t8, t8))), (t9, (t12, (t13, t14, t14), (t13, t15, t15)), (t12, (t16, t17, t17), (t16, t18, t18)))) -> t ; +1 g_rec5 :: __forall [t t1 t2 t3 t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35] => t35 -> t1 -> (t35, t19, t18) -> (t, (t17, (t2, (t3, (t4, t5, t5), (t4, t6, t6)), (t3, (t7, t8, t8), (t7, t9, t9))), (t2, (t10, (t11, t12, t12), (t11, t13, t13)), (t10, (t14, t15, t15), (t14, t16, t16)))), (t17, (t20, (t21, (t22, t23, t23), (t22, t24, t24)), (t21, (t25, t26, t26), (t25, t27, t27))), (t20, (t28, (t29, t30, t30), (t29, t31, t31)), (t28, (t32, t33, t33), (t32, t34, t34))))) -> t ; +1 g_rec6 :: __forall [t t1 t2 t3 t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67] => t67 -> t1 -> (t67, t35, t34) -> (t, (t33, (t2, (t3, (t4, (t5, t6, t6), (t5, t7, t7)), (t4, (t8, t9, t9), (t8, t10, t10))), (t3, (t11, (t12, t13, t13), (t12, t14, t14)), (t11, (t15, t16, t16), (t15, t17, t17)))), (t2, (t18, (t19, (t20, t21, t21), (t20, t22, t22)), (t19, (t23, t24, t24), (t23, t25, t25))), (t18, (t26, (t27, t28, t28), (t27, t29, t29)), (t26, (t30, t31, t31), (t30, t32, t32))))), (t33, (t36, (t37, (t38, (t39, t40, t40), (t39, t41, t41)), (t38, (t42, t43, t43), (t42, t44, t44))), (t37, (t45, (t46, t47, t47), (t46, t48, t48)), (t45, (t49, t50, t50), (t49, t51, t51)))), (t36, (t52, (t53, (t54, t55, t55), (t54, t56, t56)), (t53, (t57, t58, t58), (t57, t59, t59))), (t52, (t60, (t61, t62, t62), (t61, t63, t63)), (t60, (t64, t65, t65), (t64, t66, t66)))))) -> t ; +1 g_rec7 :: __forall [t t1 t2 t3 t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104 t105 t106 t107 t108 t109 t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131] => t131 -> t1 -> (t131, t67, t66) -> (t, (t65, (t2, (t3, (t4, (t5, (t6, t7, t7), (t6, t8, t8)), (t5, (t9, t10, t10), (t9, t11, t11))), (t4, (t12, (t13, t14, t14), (t13, t15, t15)), (t12, (t16, t17, t17), (t16, t18, t18)))), (t3, (t19, (t20, (t21, t22, t22), (t21, t23, t23)), (t20, (t24, t25, t25), (t24, t26, t26))), (t19, (t27, (t28, t29, t29), (t28, t30, t30)), (t27, (t31, t32, t32), (t31, t33, t33))))), (t2, (t34, (t35, (t36, (t37, t38, t38), (t37, t39, t39)), (t36, (t40, t41, t41), (t40, t42, t42))), (t35, (t43, (t44, t45, t45), (t44, t46, t46)), (t43, (t47, t48, t48), (t47, t49, t49)))), (t34, (t50, (t51, (t52, t53, t53), (t52, t54, t54)), (t51, (t55, t56, t56), (t55, t57, t57))), (t50, (t58, (t59, t60, t60), (t59, t61, t61)), (t58, (t62, t63, t63), (t62, t64, t64)))))), (t65, (t68, (t69, (t70, (t71, (t72, t73, t73), (t72, t74, t74)), (t71, (t75, t76, t76), (t75, t77, t77))), (t70, (t78, (t79, t80, t80), (t79, t81, t81)), (t78, (t82, t83, t83), (t82, t84, t84)))), (t69, (t85, (t86, (t87, t88, t88), (t87, t89, t89)), (t86, (t90, t91, t91), (t90, t92, t92))), (t85, (t93, (t94, t95, t95), (t94, t96, t96)), (t93, (t97, t98, t98), (t97, t99, t99))))), (t68, (t100, (t101, (t102, (t103, t104, t104), (t103, t105, t105)), (t102, (t106, t107, t107), (t106, t108, t108))), (t101, (t109, (t110, t111, t111), (t110, t112, t112)), (t109, (t113, t114, t114), (t113, t115, t115)))), (t100, (t116, (t117, (t118, t119, t119), (t118, t120, t120)), (t117, (t121, t122, t122), (t121, t123, t123))), (t116, (t124, (t125, t126, t126), (t125, t127, t127)), (t124, (t128, t129, t129), (t128, t130, t130))))))) -> t ; +1 g_rec8 :: __forall [t t1 t2 t3 t4 t5 t6 t7 t8 t9 t10 t11 t12 t13 t14 t15 t16 t17 t18 t19 t20 t21 t22 t23 t24 t25 t26 t27 t28 t29 t30 t31 t32 t33 t34 t35 t36 t37 t38 t39 t40 t41 t42 t43 t44 t45 t46 t47 t48 t49 t50 t51 t52 t53 t54 t55 t56 t57 t58 t59 t60 t61 t62 t63 t64 t65 t66 t67 t68 t69 t70 t71 t72 t73 t74 t75 t76 t77 t78 t79 t80 t81 t82 t83 t84 t85 t86 t87 t88 t89 t90 t91 t92 t93 t94 t95 t96 t97 t98 t99 t100 t101 t102 t103 t104 t105 t106 t107 t108 t109 t110 t111 t112 t113 t114 t115 t116 t117 t118 t119 t120 t121 t122 t123 t124 t125 t126 t127 t128 t129 t130 t131 t132 t133 t134 t135 t136 t137 t138 t139 t140 t141 t142 t143 t144 t145 t146 t147 t148 t149 t150 t151 t152 t153 t154 t155 t156 t157 t158 t159 t160 t161 t162 t163 t164 t165 t166 t167 t168 t169 t170 t171 t172 t173 t174 t175 t176 t177 t178 t179 t180 t181 t182 t183 t184 t185 t186 t187 t188 t189 t190 t191 t192 t193 t194 t195 t196 t197 t198 t199 t200 t201 t202 t203 t204 t205 t206 t207 t208 t209 t210 t211 t212 t213 t214 t215 t216 t217 t218 t219 t220 t221 t222 t223 t224 t225 t226 t227 t228 t229 t230 t231 t232 t233 t234 t235 t236 t237 t238 t239 t240 t241 t242 t243 t244 t245 t246 t247 t248 t249 t250 t251 t252 t253 t254 t255 t256 t257 t258 t259] => t259 -> t1 -> (t259, t131, t130) -> (t, (t129, (t2, (t3, (t4, (t5, (t6, (t7, t8, t8), (t7, t9, t9)), (t6, (t10, t11, t11), (t10, t12, t12))), (t5, (t13, (t14, t15, t15), (t14, t16, t16)), (t13, (t17, t18, t18), (t17, t19, t19)))), (t4, (t20, (t21, (t22, t23, t23), (t22, t24, t24)), (t21, (t25, t26, t26), (t25, t27, t27))), (t20, (t28, (t29, t30, t30), (t29, t31, t31)), (t28, (t32, t33, t33), (t32, t34, t34))))), (t3, (t35, (t36, (t37, (t38, t39, t39), (t38, t40, t40)), (t37, (t41, t42, t42), (t41, t43, t43))), (t36, (t44, (t45, t46, t46), (t45, t47, t47)), (t44, (t48, t49, t49), (t48, t50, t50)))), (t35, (t51, (t52, (t53, t54, t54), (t53, t55, t55)), (t52, (t56, t57, t57), (t56, t58, t58))), (t51, (t59, (t60, t61, t61), (t60, t62, t62)), (t59, (t63, t64, t64), (t63, t65, t65)))))), (t2, (t66, (t67, (t68, (t69, (t70, t71, t71), (t70, t72, t72)), (t69, (t73, t74, t74), (t73, t75, t75))), (t68, (t76, (t77, t78, t78), (t77, t79, t79)), (t76, (t80, t81, t81), (t80, t82, t82)))), (t67, (t83, (t84, (t85, t86, t86), (t85, t87, t87)), (t84, (t88, t89, t89), (t88, t90, t90))), (t83, (t91, (t92, t93, t93), (t92, t94, t94)), (t91, (t95, t96, t96), (t95, t97, t97))))), (t66, (t98, (t99, (t100, (t101, t102, t102), (t101, t103, t103)), (t100, (t104, t105, t105), (t104, t106, t106))), (t99, (t107, (t108, t109, t109), (t108, t110, t110)), (t107, (t111, t112, t112), (t111, t113, t113)))), (t98, (t114, (t115, (t116, t117, t117), (t116, t118, t118)), (t115, (t119, t120, t120), (t119, t121, t121))), (t114, (t122, (t123, t124, t124), (t123, t125, t125)), (t122, (t126, t127, t127), (t126, t128, t128))))))), (t129, (t132, (t133, (t134, (t135, (t136, (t137, t138, t138), (t137, t139, t139)), (t136, (t140, t141, t141), (t140, t142, t142))), (t135, (t143, (t144, t145, t145), (t144, t146, t146)), (t143, (t147, t148, t148), (t147, t149, t149)))), (t134, (t150, (t151, (t152, t153, t153), (t152, t154, t154)), (t151, (t155, t156, t156), (t155, t157, t157))), (t150, (t158, (t159, t160, t160), (t159, t161, t161)), (t158, (t162, t163, t163), (t162, t164, t164))))), (t133, (t165, (t166, (t167, (t168, t169, t169), (t168, t170, t170)), (t167, (t171, t172, t172), (t171, t173, t173))), (t166, (t174, (t175, t176, t176), (t175, t177, t177)), (t174, (t178, t179, t179), (t178, t180, t180)))), (t165, (t181, (t182, (t183, t184, t184), (t183, t185, t185)), (t182, (t186, t187, t187), (t186, t188, t188))), (t181, (t189, (t190, t191, t191), (t190, t192, t192)), (t189, (t193, t194, t194), (t193, t195, t195)))))), (t132, (t196, (t197, (t198, (t199, (t200, t201, t201), (t200, t202, t202)), (t199, (t203, t204, t204), (t203, t205, t205))), (t198, (t206, (t207, t208, t208), (t207, t209, t209)), (t206, (t210, t211, t211), (t210, t212, t212)))), (t197, (t213, (t214, (t215, t216, t216), (t215, t217, t217)), (t214, (t218, t219, t219), (t218, t220, t220))), (t213, (t221, (t222, t223, t223), (t222, t224, t224)), (t221, (t225, t226, t226), (t225, t227, t227))))), (t196, (t228, (t229, (t230, (t231, t232, t232), (t231, t233, t233)), (t230, (t234, t235, t235), (t234, t236, t236))), (t229, (t237, (t238, t239, t239), (t238, t240, t240)), (t237, (t241, t242, t242), (t241, t243, t243)))), (t228, (t244, (t245, (t246, t247, t247), (t246, t248, t248)), (t245, (t249, t250, t250), (t249, t251, t251))), (t244, (t252, (t253, t254, t254), (t253, t255, t255)), (t252, (t256, t257, t257), (t256, t258, t258)))))))) -> t ; 1 head :: __forall [t] => [t] -> t ; 1 one :: __forall [t] => t ; 1 s_1_0 :: __forall [t] => t -> t ; -1 s_2_0 :: __forall [t _116] => (t, _116) -> t ; -1 s_2_1 :: __forall [t _116] => (_116, t) -> t ; -1 s_3_0 :: __forall [t _116 _1161] => (t, _116, _1161) -> t ; -1 s_3_1 :: __forall [t _116 _1161] => (_116, t, _1161) -> t ; -1 s_3_2 :: __forall [t _116 _1161] => (_116, _1161, t) -> t ; +1 s_2_0 :: __forall [t t1] => (t, t1) -> t ; +1 s_2_1 :: __forall [t t1] => (t1, t) -> t ; +1 s_3_0 :: __forall [t t1 t2] => (t, t1, t2) -> t ; +1 s_3_1 :: __forall [t t1 t2] => (t1, t, t2) -> t ; +1 s_3_2 :: __forall [t t1 t2] => (t1, t2, t) -> t ; diff --git a/ghc/tests/typecheck/should_compile/tc092.stderr b/ghc/tests/typecheck/should_compile/tc092.stderr index 13e620de94dde88b1cde8427bbe194d6a3be6dda..0e312866fd36bd33d08809de0dadbc04d04f0eb9 100644 --- a/ghc/tests/typecheck/should_compile/tc092.stderr +++ b/ghc/tests/typecheck/should_compile/tc092.stderr @@ -1,7 +1,7 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed e0 e1 e2 q Empty{Empty}; +__export ShouldSucceed Empty{Empty} e0 e1 e2 q; 1 data Empty q :: (* -> *) = Empty (__forall [a] {PrelBase.Ord a} => q a) ; -1 e0 :: Empty PrelBase.[] ; -1 e1 :: Empty PrelBase.[] ; -1 e2 :: Empty PrelBase.[] ; +1 e0 :: Empty PrelBase.ZMZN ; +1 e1 :: Empty PrelBase.ZMZN ; +1 e2 :: Empty PrelBase.ZMZN ; 1 q :: __forall [a] {PrelBase.Ord a} => [a] ; diff --git a/ghc/tests/typecheck/should_compile/tc093.stderr b/ghc/tests/typecheck/should_compile/tc093.stderr index a9bb9f8054832883648fa2764613379dca0734ba..934e947bfee0f4197c316c1bac7e841a59c2ba22 100644 --- a/ghc/tests/typecheck/should_compile/tc093.stderr +++ b/ghc/tests/typecheck/should_compile/tc093.stderr @@ -1,11 +1,8 @@ ghc: module version changed to 1; reason: no old .hi file -__export ShouldSucceed bindState foo unState unitState St State{State} TS{TS vs}; -instance {PrelBase.Eq TS} = _fEqTS; -instance __forall [c] {PrelBase.Eq c} => {PrelBase.Monad (State c)} = _fMonadState; -instance {PrelBase.Show TS} = _fShowTS; -1 _fEqTS :: {PrelBase.Eq TS} ; -1 _fMonadState :: __forall [c] {PrelBase.Eq c} => {PrelBase.Monad (State c)} ; -1 _fShowTS :: {PrelBase.Show TS} ; +__export ShouldSucceed St State{State} TS{TS vs} bindState foo unState unitState; +instance {PrelBase.Eq TS} = zdfEqTS; +instance __forall [c] {PrelBase.Eq c} => {PrelBase.Monad (State c)} = zdfMonadState; +instance {PrelBase.Show TS} = zdfShowTS; 1 bindState :: __forall [c a b] => State c a -> (a -> State c b) -> State c b ; 1 data State c a = State (c -> (a, c)) ; 1 data TS = TS {vs :: PrelBase.Int} ; @@ -13,3 +10,6 @@ instance {PrelBase.Show TS} = _fShowTS; 1 type St a = State TS a ; 1 unState :: __forall [c a] => State c a -> c -> (a, c) ; 1 unitState :: __forall [a c] => a -> State c a ; +1 zdfEqTS :: {PrelBase.Eq TS} ; +1 zdfMonadState :: __forall [c] {PrelBase.Eq c} => {PrelBase.Monad (State c)} ; +1 zdfShowTS :: {PrelBase.Show TS} ; diff --git a/ghc/tests/typecheck/should_compile/tc095.stderr b/ghc/tests/typecheck/should_compile/tc095.stderr index dd425eb7c1152103ed58735b68f8d1d8888faae5..4d7b6c67ed53cae349c538848fa1ee6b76f19b23 100644 --- a/ghc/tests/typecheck/should_compile/tc095.stderr +++ b/ghc/tests/typecheck/should_compile/tc095.stderr @@ -1,39 +1,36 @@ -NOTE: Simplifier still going after 4 iterations; baling out. +NOTE: Simplifier still going after 4 iterations; bailing out. ghc: module version changed to 1; reason: no old .hi file -_exports_ -ShouldSucceed action_0 action_1 action_2 action_3 action_4 action_5 action_6 happyAccept happyError happyFail happyGoto happyMonadReduce happyNewToken happyParse happyReduce happyReduce_1 happyReduce_2 happyReduce_3 happyReturn happyShift happySpecReduce_0 happySpecReduce_1 happySpecReduce_2 happySpecReduce_3 happyThen main myparser notHappyAtAll HappyAbsSyn{HappyTerminal HappyErrorToken HappyAbsSyn1 HappyAbsSyn2 HappyAbsSyn3} HappyState{HappyState} Token{TokenInt TokenVar TokenEq}; -_instances_ -instance {PrelBase.Show Token} = $dShowToken0; -_declarations_ -1 $dShowToken0 _:_ {PrelBase.Show Token} ;; -1 action_0 _:_ _forall_ [$a $b] {PrelBase.Num $a} => $a -> PrelBase.Int -> Token -> HappyState Token ([HappyAbsSyn ($b -> PrelBase.Double) [(PrelBase.String, $b -> PrelBase.Int)] ($b -> PrelBase.Int)] -> [Token] -> $b -> PrelBase.Double) -> [HappyState Token ([HappyAbsSyn ($b -> PrelBase.Double) [(PrelBase.String, $b -> PrelBase.Int)] ($b -> PrelBase.Int)] -> [Token] -> $b -> PrelBase.Double)] -> [HappyAbsSyn ($b -> PrelBase.Double) [(PrelBase.String, $b -> PrelBase.Int)] ($b -> PrelBase.Int)] -> [Token] -> $b -> PrelBase.Double ;; -1 action_1 _:_ _forall_ [$a $b $c $d $e] {PrelBase.Num $a} => $a -> PrelBase.Int -> $b -> HappyState $b ([HappyAbsSyn $e $c $d] -> [Token] -> $e) -> [HappyState $b ([HappyAbsSyn $e $c $d] -> [Token] -> $e)] -> [HappyAbsSyn $e $c $d] -> [Token] -> $e ;; -1 action_2 _:_ _forall_ [$a $b $c $d $e $f $g $h] => $a -> PrelBase.Int -> $b -> $c -> [HappyState $b ([HappyAbsSyn ($d -> PrelBase.Double) [($e, $d -> $f)] $g] -> $h)] -> [HappyAbsSyn ($d -> PrelBase.Double) [($e, $d -> $f)] $g] -> $h ;; -1 action_3 _:_ _forall_ [$a $b $c $d] {PrelBase.Num $a} => $a -> PrelBase.Int -> Token -> HappyState Token ([HappyAbsSyn $c [(PrelBase.String, $b -> PrelBase.Int)] ($b -> PrelBase.Int)] -> [Token] -> $d) -> [HappyState Token ([HappyAbsSyn $c [(PrelBase.String, $b -> PrelBase.Int)] ($b -> PrelBase.Int)] -> [Token] -> $d)] -> [HappyAbsSyn $c [(PrelBase.String, $b -> PrelBase.Int)] ($b -> PrelBase.Int)] -> [Token] -> $d ;; -1 action_4 _:_ _forall_ [$a $b $c $d] {PrelBase.Num $a} => $a -> PrelBase.Int -> Token -> HappyState Token ([HappyAbsSyn $c [(PrelBase.String, $b -> PrelBase.Int)] ($b -> PrelBase.Int)] -> [Token] -> $d) -> [HappyState Token ([HappyAbsSyn $c [(PrelBase.String, $b -> PrelBase.Int)] ($b -> PrelBase.Int)] -> [Token] -> $d)] -> [HappyAbsSyn $c [(PrelBase.String, $b -> PrelBase.Int)] ($b -> PrelBase.Int)] -> [Token] -> $d ;; -1 action_5 _:_ _forall_ [$a $b $c $d $e $f] => $a -> PrelBase.Int -> $b -> $c -> [HappyState $b ([HappyAbsSyn $d [(PrelBase.String, $e)] $e] -> $f)] -> [HappyAbsSyn $d [(PrelBase.String, $e)] $e] -> $f ;; -1 action_6 _:_ _forall_ [$a $b $c $d $e $f $g] => $a -> PrelBase.Int -> $b -> $c -> [HappyState $b ([HappyAbsSyn $d $e ($f -> PrelBase.Int)] -> $g)] -> [HappyAbsSyn $d $e ($f -> PrelBase.Int)] -> $g ;; -1 data HappyAbsSyn $r8T $r8U $r8V = HappyTerminal Token | HappyErrorToken PrelBase.Int | HappyAbsSyn1 $r8T | HappyAbsSyn2 $r8U | HappyAbsSyn3 $r8V ; -1 newtype HappyState $r8I $r8J = HappyState (PrelBase.Int -> PrelBase.Int -> $r8I -> HappyState $r8I $r8J -> [HappyState $r8I $r8J] -> $r8J) ; +__export ShouldSucceed HappyAbsSyn{HappyTerminal HappyErrorToken HappyAbsSyn1 HappyAbsSyn2 HappyAbsSyn3} HappyState{HappyState} Token{TokenInt TokenVar TokenEq} action_0 action_1 action_2 action_3 action_4 action_5 action_6 happyAccept happyError happyFail happyGoto happyMonadReduce happyNewToken happyParse happyReduce happyReduce_1 happyReduce_2 happyReduce_3 happyReturn happyShift happySpecReduce_0 happySpecReduce_1 happySpecReduce_2 happySpecReduce_3 happyThen main myparser notHappyAtAll; +instance {PrelBase.Show Token} = zdfShowToken; +1 action_0 :: __forall [t t1] {PrelBase.Num t} => t -> PrelBase.Int -> Token -> HappyState Token ([HappyAbsSyn (t1 -> PrelBase.Double) [(PrelBase.String, t1 -> PrelBase.Int)] (t1 -> PrelBase.Int)] -> [Token] -> t1 -> PrelBase.Double) -> [HappyState Token ([HappyAbsSyn (t1 -> PrelBase.Double) [(PrelBase.String, t1 -> PrelBase.Int)] (t1 -> PrelBase.Int)] -> [Token] -> t1 -> PrelBase.Double)] -> [HappyAbsSyn (t1 -> PrelBase.Double) [(PrelBase.String, t1 -> PrelBase.Int)] (t1 -> PrelBase.Int)] -> [Token] -> t1 -> PrelBase.Double ; +1 action_1 :: __forall [t b t2 t3 a] {PrelBase.Num t} => t -> PrelBase.Int -> b -> HappyState b ([HappyAbsSyn a t2 t3] -> [Token] -> a) -> [HappyState b ([HappyAbsSyn a t2 t3] -> [Token] -> a)] -> [HappyAbsSyn a t2 t3] -> [Token] -> a ; +1 action_2 :: __forall [t t1 b t2 t3 t4 t5 t31] => t -> PrelBase.Int -> b -> t2 -> [HappyState b ([HappyAbsSyn (t3 -> PrelBase.Double) [(t4, t3 -> t5)] t31] -> t1)] -> [HappyAbsSyn (t3 -> PrelBase.Double) [(t4, t3 -> t5)] t31] -> t1 ; +1 action_3 :: __forall [t t1 t11 a] {PrelBase.Num t} => t -> PrelBase.Int -> Token -> HappyState Token ([HappyAbsSyn t11 [(PrelBase.String, t1 -> PrelBase.Int)] (t1 -> PrelBase.Int)] -> [Token] -> a) -> [HappyState Token ([HappyAbsSyn t11 [(PrelBase.String, t1 -> PrelBase.Int)] (t1 -> PrelBase.Int)] -> [Token] -> a)] -> [HappyAbsSyn t11 [(PrelBase.String, t1 -> PrelBase.Int)] (t1 -> PrelBase.Int)] -> [Token] -> a ; +1 action_4 :: __forall [t t1 t11 a] {PrelBase.Num t} => t -> PrelBase.Int -> Token -> HappyState Token ([HappyAbsSyn t11 [(PrelBase.String, t1 -> PrelBase.Int)] (t1 -> PrelBase.Int)] -> [Token] -> a) -> [HappyState Token ([HappyAbsSyn t11 [(PrelBase.String, t1 -> PrelBase.Int)] (t1 -> PrelBase.Int)] -> [Token] -> a)] -> [HappyAbsSyn t11 [(PrelBase.String, t1 -> PrelBase.Int)] (t1 -> PrelBase.Int)] -> [Token] -> a ; +1 action_5 :: __forall [t t1 b t2 t11 t3] => t -> PrelBase.Int -> b -> t2 -> [HappyState b ([HappyAbsSyn t11 [(PrelBase.String, t3)] t3] -> t1)] -> [HappyAbsSyn t11 [(PrelBase.String, t3)] t3] -> t1 ; +1 action_6 :: __forall [t t1 b t2 t11 t21 t3] => t -> PrelBase.Int -> b -> t2 -> [HappyState b ([HappyAbsSyn t11 t21 (t3 -> PrelBase.Int)] -> t1)] -> [HappyAbsSyn t11 t21 (t3 -> PrelBase.Int)] -> t1 ; +1 data HappyAbsSyn t1 t2 t3 = HappyTerminal Token | HappyErrorToken PrelBase.Int | HappyAbsSyn1 t1 | HappyAbsSyn2 t2 | HappyAbsSyn3 t3 ; +1 newtype HappyState b c = HappyState (PrelBase.Int -> PrelBase.Int -> b -> HappyState b c -> [HappyState b c] -> c) ; 1 data Token = TokenInt PrelBase.Int | TokenVar PrelBase.String | TokenEq ; -1 happyAccept _:_ _forall_ [$a $b $c $d $e $f $g $h] => $a -> $b -> $c -> $d -> [HappyAbsSyn $e $f $g] -> $h -> $e ;; -1 happyError _:_ _forall_ [$a] => [Token] -> $a ;; -1 happyFail _:_ _forall_ [$a $b $c $d $e] => PrelBase.Int -> $b -> HappyState $b ([HappyAbsSyn $c $d $e] -> [Token] -> $a) -> [HappyState $b ([HappyAbsSyn $c $d $e] -> [Token] -> $a)] -> [HappyAbsSyn $c $d $e] -> [Token] -> $a ;; -1 happyGoto _:_ _forall_ [$a $b $c] => (PrelBase.Int -> PrelBase.Int -> $b -> HappyState $b $c -> [HappyState $b $c] -> $c) -> PrelBase.Int -> $b -> $a -> [HappyState $b $c] -> $c ;; -1 happyMonadReduce _:_ _forall_ [$a $b $c $d] => PrelBase.Int -> PrelBase.Int -> ($d -> $c) -> ([$c] -> $d) -> PrelBase.Int -> $a -> HappyState $a ([$c] -> [Token] -> $b) -> [HappyState $a ([$c] -> [Token] -> $b)] -> [$c] -> [Token] -> $b ;; -1 happyNewToken _:_ _forall_ [$a $b] => (PrelBase.Int -> PrelBase.Int -> Token -> HappyState Token ($a -> [Token] -> $b) -> [HappyState Token ($a -> [Token] -> $b)] -> $a -> [Token] -> $b) -> [HappyState Token ($a -> [Token] -> $b)] -> $a -> [Token] -> $b ;; -1 happyParse _:_ _forall_ [$a] => [Token] -> $a -> PrelBase.Double ;; -1 happyReduce _:_ _forall_ [$a $b $c] => PrelBase.Int -> PrelBase.Int -> ($c -> $c) -> PrelBase.Int -> $a -> HappyState $a ($c -> $b) -> [HappyState $a ($c -> $b)] -> $c -> $b ;; -1 happyReduce_1 _:_ _forall_ [$a $b $c $d $e $f $g] => PrelBase.Int -> $a -> $b -> [HappyState $a ([HappyAbsSyn ($e -> PrelBase.Double) [($d, $e -> $f)] $g] -> $c)] -> [HappyAbsSyn ($e -> PrelBase.Double) [($d, $e -> $f)] $g] -> $c ;; -1 happyReduce_2 _:_ _forall_ [$a $b $c $d $e] => PrelBase.Int -> $a -> $b -> [HappyState $a ([HappyAbsSyn $d [(PrelBase.String, $e)] $e] -> $c)] -> [HappyAbsSyn $d [(PrelBase.String, $e)] $e] -> $c ;; -1 happyReduce_3 _:_ _forall_ [$a $b $c $d $e $f] => PrelBase.Int -> $a -> $b -> [HappyState $a ([HappyAbsSyn $d $e ($f -> PrelBase.Int)] -> $c)] -> [HappyAbsSyn $d $e ($f -> PrelBase.Int)] -> $c ;; -1 happyReturn _:_ _forall_ [$a $b] => $b -> $a -> $b ;; -1 happyShift _:_ _forall_ [$a $b $c $d $e] {PrelBase.Num $a} => (PrelBase.Int -> PrelBase.Int -> Token -> HappyState Token ([HappyAbsSyn $c $d $e] -> [Token] -> $b) -> [HappyState Token ([HappyAbsSyn $c $d $e] -> [Token] -> $b)] -> [HappyAbsSyn $c $d $e] -> [Token] -> $b) -> $a -> Token -> HappyState Token ([HappyAbsSyn $c $d $e] -> [Token] -> $b) -> [HappyState Token ([HappyAbsSyn $c $d $e] -> [Token] -> $b)] -> [HappyAbsSyn $c $d $e] -> [Token] -> $b ;; -1 happySpecReduce_0 _:_ _forall_ [$a $b $c] => PrelBase.Int -> $c -> PrelBase.Int -> $a -> HappyState $a ([$c] -> [Token] -> $b) -> [HappyState $a ([$c] -> [Token] -> $b)] -> [$c] -> [Token] -> $b ;; -1 happySpecReduce_1 _:_ _forall_ [$a $b $c $d] => PrelBase.Int -> ($c -> $c) -> PrelBase.Int -> $b -> $a -> [HappyState $b ([$c] -> $d)] -> [$c] -> $d ;; -1 happySpecReduce_2 _:_ _forall_ [$a $b $c $d] => PrelBase.Int -> ($c -> $c -> $c) -> PrelBase.Int -> $b -> $a -> [HappyState $b ([$c] -> $d)] -> [$c] -> $d ;; -1 happySpecReduce_3 _:_ _forall_ [$a $b $c $d] => PrelBase.Int -> ($c -> $c -> $c -> $c) -> PrelBase.Int -> $b -> $a -> [HappyState $b ([$c] -> $d)] -> [$c] -> $d ;; -1 happyThen _:_ _forall_ [$a $b] => $b -> ($b -> $a) -> $a ;; -1 main _:_ PrelIOBase.IO PrelBase.() ;; -1 myparser _:_ _forall_ [$a] => [Token] -> $a -> PrelBase.Double ;; -1 notHappyAtAll _:_ _forall_ [$a] => $a ;; +1 happyAccept :: __forall [t t1 t2 t3 t11 t21 t31 t4] => t -> t1 -> t2 -> t3 -> [HappyAbsSyn t11 t21 t31] -> t4 -> t11 ; +1 happyError :: __forall [a] => [Token] -> a ; +1 happyFail :: __forall [a b t1 t2 t3] => PrelBase.Int -> b -> HappyState b ([HappyAbsSyn t1 t2 t3] -> [Token] -> a) -> [HappyState b ([HappyAbsSyn t1 t2 t3] -> [Token] -> a)] -> [HappyAbsSyn t1 t2 t3] -> [Token] -> a ; +1 happyGoto :: __forall [t b c] => (PrelBase.Int -> PrelBase.Int -> b -> HappyState b c -> [HappyState b c] -> c) -> PrelBase.Int -> b -> t -> [HappyState b c] -> c ; +1 happyMonadReduce :: __forall [b a b1 t] => PrelBase.Int -> PrelBase.Int -> (t -> b1) -> ([b1] -> t) -> PrelBase.Int -> b -> HappyState b ([b1] -> [Token] -> a) -> [HappyState b ([b1] -> [Token] -> a)] -> [b1] -> [Token] -> a ; +1 happyNewToken :: __forall [t t1] => (PrelBase.Int -> PrelBase.Int -> Token -> HappyState Token (t -> [Token] -> t1) -> [HappyState Token (t -> [Token] -> t1)] -> t -> [Token] -> t1) -> [HappyState Token (t -> [Token] -> t1)] -> t -> [Token] -> t1 ; +1 happyParse :: __forall [t] => [Token] -> t -> PrelBase.Double ; +1 happyReduce :: __forall [b t t1] => PrelBase.Int -> PrelBase.Int -> (t1 -> t1) -> PrelBase.Int -> b -> HappyState b (t1 -> t) -> [HappyState b (t1 -> t)] -> t1 -> t ; +1 happyReduce_1 :: __forall [t b t1 t2 t3 t4 t31] => PrelBase.Int -> b -> t1 -> [HappyState b ([HappyAbsSyn (t3 -> PrelBase.Double) [(t2, t3 -> t4)] t31] -> t)] -> [HappyAbsSyn (t3 -> PrelBase.Double) [(t2, t3 -> t4)] t31] -> t ; +1 happyReduce_2 :: __forall [t b t1 t11 t3] => PrelBase.Int -> b -> t1 -> [HappyState b ([HappyAbsSyn t11 [(PrelBase.String, t3)] t3] -> t)] -> [HappyAbsSyn t11 [(PrelBase.String, t3)] t3] -> t ; +1 happyReduce_3 :: __forall [t b t1 t11 t2 t21] => PrelBase.Int -> b -> t1 -> [HappyState b ([HappyAbsSyn t11 t2 (t21 -> PrelBase.Int)] -> t)] -> [HappyAbsSyn t11 t2 (t21 -> PrelBase.Int)] -> t ; +1 happyReturn :: __forall [t t1] => t -> t1 -> t ; +1 happyShift :: __forall [t t1 t11 t2 t3] {PrelBase.Num t} => (PrelBase.Int -> PrelBase.Int -> Token -> HappyState Token ([HappyAbsSyn t11 t2 t3] -> [Token] -> t1) -> [HappyState Token ([HappyAbsSyn t11 t2 t3] -> [Token] -> t1)] -> [HappyAbsSyn t11 t2 t3] -> [Token] -> t1) -> t -> Token -> HappyState Token ([HappyAbsSyn t11 t2 t3] -> [Token] -> t1) -> [HappyState Token ([HappyAbsSyn t11 t2 t3] -> [Token] -> t1)] -> [HappyAbsSyn t11 t2 t3] -> [Token] -> t1 ; +1 happySpecReduce_0 :: __forall [b a t] => PrelBase.Int -> t -> PrelBase.Int -> b -> HappyState b ([t] -> [Token] -> a) -> [HappyState b ([t] -> [Token] -> a)] -> [t] -> [Token] -> a ; +1 happySpecReduce_1 :: __forall [t t1 b t2] => PrelBase.Int -> (t2 -> t2) -> PrelBase.Int -> b -> t -> [HappyState b ([t2] -> t1)] -> [t2] -> t1 ; +1 happySpecReduce_2 :: __forall [t t1 b t2] => PrelBase.Int -> (t2 -> t2 -> t2) -> PrelBase.Int -> b -> t -> [HappyState b ([t2] -> t1)] -> [t2] -> t1 ; +1 happySpecReduce_3 :: __forall [t t1 b t2] => PrelBase.Int -> (t2 -> t2 -> t2 -> t2) -> PrelBase.Int -> b -> t -> [HappyState b ([t2] -> t1)] -> [t2] -> t1 ; +1 happyThen :: __forall [t t1] => t1 -> (t1 -> t) -> t ; +1 main :: PrelIOBase.IO PrelBase.Z0T ; +1 myparser :: __forall [t] => [Token] -> t -> PrelBase.Double ; +1 notHappyAtAll :: __forall [t] => t ; +1 zdfShowToken :: {PrelBase.Show Token} ; diff --git a/ghc/tests/typecheck/should_compile/tc096.stderr b/ghc/tests/typecheck/should_compile/tc096.stderr index a5e5580974bdcba1b6d0b37fd3b8ca2618bd5f4d..a4a65d7b46ba04ea0e696749e6b0de17b265f7af 100644 --- a/ghc/tests/typecheck/should_compile/tc096.stderr +++ b/ghc/tests/typecheck/should_compile/tc096.stderr @@ -1,6 +1,4 @@ ghc: module version changed to 1; reason: no old .hi file -_exports_ -ShouldSucceed main x; -_declarations_ -1 main _:_ PrelIOBase.IO PrelBase.() ;; -1 x _:_ PrelBase.Double ;; +__export ShouldSucceed main x; +1 main :: PrelIOBase.IO PrelBase.Z0T ; +1 x :: PrelBase.Double ; diff --git a/ghc/tests/typecheck/should_compile/tc098.stderr b/ghc/tests/typecheck/should_compile/tc098.stderr index 108150950cce1c03c9a960e8f0a6aa63ea7a7b40..1842f8698986f242e4918073d3f5b96b105c6401 100644 --- a/ghc/tests/typecheck/should_compile/tc098.stderr +++ b/ghc/tests/typecheck/should_compile/tc098.stderr @@ -1,8 +1,6 @@ ghc: module version changed to 1; reason: no old .hi file -_exports_ -ShouldSucceed cpPairs m mp Cp; -_declarations_ -1 cpPairs _:_ _forall_ [a b] => Cp [a] -> (b, [a]) -> (b, [a]) -> PrelBase.Ordering ;; -1 m _:_ _forall_ [a] {PrelBase.Eq a} => Cp a -> [a] -> a ;; -1 mp _:_ _forall_ [a b] {PrelBase.Eq b, PrelBase.Eq a} => Cp [a] -> [(b, [a])] -> (b, [a]) ;; +__export ShouldSucceed Cp cpPairs m mp; +1 cpPairs :: __forall [j a] => Cp [j] -> (a, [j]) -> (a, [j]) -> PrelBase.Ordering ; +1 m :: __forall [a] {PrelBase.Eq a} => Cp a -> [a] -> a ; +1 mp :: __forall [j i] {PrelBase.Eq i, PrelBase.Eq j} => Cp [j] -> [(i, [j])] -> (i, [j]) ; 1 type Cp a = a -> a -> PrelBase.Ordering ; diff --git a/ghc/tests/typecheck/should_compile/tc099.stderr b/ghc/tests/typecheck/should_compile/tc099.stderr index 985f8e8503ca49fc2ecba802535c6a966b5390f1..e85a66e66747b2e67bcb0caa9d05deb610797ad2 100644 --- a/ghc/tests/typecheck/should_compile/tc099.stderr +++ b/ghc/tests/typecheck/should_compile/tc099.stderr @@ -1,6 +1,4 @@ ghc: module version changed to 1; reason: no old .hi file -_exports_ -ShouldCompile f g; -_declarations_ -1 f _:_ _forall_ [a b] {PrelBase.Eq a} => (a, b) ;; -1 g _:_ _forall_ [a b] {PrelBase.Eq a} => (a, b) ;; +__export ShouldCompile f g; +1 f :: __forall [a b] {PrelBase.Eq a} => (a, b) ; +1 g :: __forall [a b] {PrelBase.Eq a} => (a, b) ; diff --git a/ghc/tests/typecheck/should_fail/Digraph.stderr b/ghc/tests/typecheck/should_fail/Digraph.stderr index f28161f617b827b60839490832899c63cb85835c..4c217aeec72668382f3604e44773f0bb8f36ef40 100644 --- a/ghc/tests/typecheck/should_fail/Digraph.stderr +++ b/ghc/tests/typecheck/should_fail/Digraph.stderr @@ -1,4 +1,4 @@ - + Digraph.hs:19: Inferred type is less polymorphic than expected Quantified type variable `v' escapes @@ -7,7 +7,7 @@ Digraph.hs:19: es :: [Edge vertex] vs :: [vertex] When checking the type signature - reversed_edges :: forall _118. {PrelBase.Eq _118} => [Edge _118] + reversed_edges :: forall v1. {Eq v1} => [Edge v1] In an equation for function `stronglyConnComp': stronglyConnComp es vs = snd (span_tree (new_range reversed_edges) @@ -31,5 +31,6 @@ Digraph.hs:19: reversed_edges = map swap es + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail001.stderr b/ghc/tests/typecheck/should_fail/tcfail001.stderr index a577ffbf5ee2a0f434816e1f3c278eddfc055f72..376d3a0d06a26c75a7fd4bb61fdd3a0a0aa04cd4 100644 --- a/ghc/tests/typecheck/should_fail/tcfail001.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail001.stderr @@ -1,15 +1,18 @@ - -tcfail001.hs:9: Warning: - Duplicate class assertion `A a' in the context: (A a, A a) => - tcfail001.hs:9: - Couldn't match `[a]' against `t -> _116' + Warning: Duplicate class assertion `A a' in the context: + (A a, A a) => ... + + + +tcfail001.hs:9: + Couldn't match `[a]' against `t -> t1' Expected type: [a] - Inferred type: t -> _116 + Inferred type: t -> t1 In an equation for function `op': op [] = [] In the definition for method `op' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail002.stderr b/ghc/tests/typecheck/should_fail/tcfail002.stderr index 227b2f4720dfebdea448d5e262c245a6531b3a7d..410a1ad05c112554b4e5ef631698d2549d7953e3 100644 --- a/ghc/tests/typecheck/should_fail/tcfail002.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail002.stderr @@ -1,4 +1,4 @@ - + tcfail002.hs:4: Occurs check: cannot construct the infinite type: t = [t] Expected type: t @@ -6,5 +6,6 @@ tcfail002.hs:4: In the right-hand side of an equation for `c': z + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail003.stderr b/ghc/tests/typecheck/should_fail/tcfail003.stderr index 2cb11fcf1f414350e5fd0be5fe64e1d7fbc0139a..7650b3b6c73c6161ca69f2a06e496539764f6248 100644 --- a/ghc/tests/typecheck/should_fail/tcfail003.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail003.stderr @@ -1,8 +1,9 @@ - + tcfail003.hs:3: - No instance for `PrelBase.Num Char' + No instance for `Num Char' arising from the literal `1' at tcfail003.hs:3 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail004.stderr b/ghc/tests/typecheck/should_fail/tcfail004.stderr index a8a9457952da9188fb1f9a3c58c047ea2ccaa95e..66feb42842919faeaad231490c5ffe99865cd477 100644 --- a/ghc/tests/typecheck/should_fail/tcfail004.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail004.stderr @@ -1,10 +1,11 @@ - + tcfail004.hs:3: - Couldn't match `(t, _116)' against `(_1161, _1162, _1163)' - Expected type: (t, _116) - Inferred type: (_1161, _1162, _1163) + Couldn't match `(t, t1)' against `(t2, t3, t4)' + Expected type: (t, t1) + Inferred type: (t2, t3, t4) In the right-hand side of a pattern binding: (1, 2, 3) + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail005.stderr b/ghc/tests/typecheck/should_fail/tcfail005.stderr index f2c2741f6aa0c6855770edd2499064888baf7faf..7ed8275d6665bcb0406f2f5200f316b2e466d3f9 100644 --- a/ghc/tests/typecheck/should_fail/tcfail005.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail005.stderr @@ -1,10 +1,11 @@ - + tcfail005.hs:3: - Couldn't match `[t]' against `(_116, _1161)' + Couldn't match `[t]' against `(t1, t2)' Expected type: [t] - Inferred type: (_116, _1161) + Inferred type: (t1, t2) In the right-hand side of a pattern binding: (1, 'a') + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail006.stderr b/ghc/tests/typecheck/should_fail/tcfail006.stderr index 29cce73bcc3ea79a4197e79b7f0cad74c54467ef..9815c5a610abc21470c61462633417c70875b904 100644 --- a/ghc/tests/typecheck/should_fail/tcfail006.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail006.stderr @@ -1,8 +1,9 @@ - + tcfail006.hs:4: - No instance for `PrelBase.Num Bool' + No instance for `Num Bool' arising from the literal `1' at tcfail006.hs:4 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail007.stderr b/ghc/tests/typecheck/should_fail/tcfail007.stderr index 435c825410a4dbe44d5776145b847cc125ebd861..b823d9abd84ad4ff06e776e524d2c9700968e243 100644 --- a/ghc/tests/typecheck/should_fail/tcfail007.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail007.stderr @@ -1,7 +1,8 @@ - + tcfail007.hs:3: - No instance for `PrelBase.Num Bool' - arising from use of `PrelBase.+' at tcfail007.hs:3 + No instance for `Num Bool' + arising from use of `+' at tcfail007.hs:3 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail008.stderr b/ghc/tests/typecheck/should_fail/tcfail008.stderr index a7f15d651a2e8f99a2ac19662a89efcf3500704e..9b2dee0f72a58b5bc29f817085ac373e8f72cf10 100644 --- a/ghc/tests/typecheck/should_fail/tcfail008.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail008.stderr @@ -1,14 +1,15 @@ - + tcfail008.hs:3: Ambiguous type variable(s) `t' - in the constraint `PrelBase.Num [t]' + in the constraint `Num [t]' arising from the literal `2' at tcfail008.hs:3 - + tcfail008.hs:3: Ambiguous type variable(s) `t' - in the constraint `PrelBase.Num t' + in the constraint `Num t' arising from the literal `1' at tcfail008.hs:3 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail009.stderr b/ghc/tests/typecheck/should_fail/tcfail009.stderr index f8c305ee47a8c1a7939169c8af52bb3b5f42075c..dd3c85e21adb1ac6b86ade3bdd9135c716e5e535 100644 --- a/ghc/tests/typecheck/should_fail/tcfail009.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail009.stderr @@ -1,4 +1,4 @@ - + tcfail009.hs:3: Couldn't match `Integer' against `Int' Expected type: Integer @@ -6,5 +6,6 @@ tcfail009.hs:3: In an expression with a type signature: 2 :: Integer + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail010.stderr b/ghc/tests/typecheck/should_fail/tcfail010.stderr index 14e30ff811fb7c09dee1e3eb55e943636db68e7d..affb03e0a29f41fc2b90ac8db03a99e51822523c 100644 --- a/ghc/tests/typecheck/should_fail/tcfail010.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail010.stderr @@ -1,8 +1,9 @@ - + tcfail010.hs:3: Ambiguous type variable(s) `t' - in the constraint `PrelBase.Num [t]' - arising from use of `PrelBase.+' at tcfail010.hs:3 + in the constraint `Num [t]' + arising from use of `+' at tcfail010.hs:3 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail011.stderr b/ghc/tests/typecheck/should_fail/tcfail011.stderr index c454605f799f2c5b83a2be39474bf8402c4a4320..d86d2c973f4a1233964a2178155d01363d7494be 100644 --- a/ghc/tests/typecheck/should_fail/tcfail011.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail011.stderr @@ -1,5 +1,6 @@ - -tcfail011.hs:3: Value not in scope: `y' + +tcfail011.hs:3: Variable not in scope: `y' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail012.stderr b/ghc/tests/typecheck/should_fail/tcfail012.stderr index e17283568bb34024b05a817ecfc145e9855863c3..1bd5c89c6ec80a1f2ea412746433cb5405888f00 100644 --- a/ghc/tests/typecheck/should_fail/tcfail012.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail012.stderr @@ -1,4 +1,4 @@ - + tcfail012.hs:3: Couldn't match `Bool' against `[t]' Expected type: Bool @@ -6,5 +6,6 @@ tcfail012.hs:3: In the right-hand side of a pattern binding: [] + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail013.stderr b/ghc/tests/typecheck/should_fail/tcfail013.stderr index 594cd493c5ada0485689793b24d7ae3f0773fd2b..429fefc62416d8713317ca0e9f128ee789702a3f 100644 --- a/ghc/tests/typecheck/should_fail/tcfail013.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail013.stderr @@ -1,4 +1,4 @@ - + tcfail013.hs:4: Couldn't match `[t]' against `Bool' Expected type: [t] @@ -7,5 +7,6 @@ tcfail013.hs:4: In an equation for function `f': f True = 2 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail014.stderr b/ghc/tests/typecheck/should_fail/tcfail014.stderr index 457dea5eb56332476bbce84d4871c187ff25acb7..5812e986aba5d0551d2ff5d43e5c23e961636757 100644 --- a/ghc/tests/typecheck/should_fail/tcfail014.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail014.stderr @@ -1,11 +1,12 @@ - + tcfail014.hs:5: - Occurs check: cannot construct the infinite type: t = t -> _116 + Occurs check: cannot construct the infinite type: t = t -> t1 Expected type: t - Inferred type: t -> _116 + Inferred type: t -> t1 In the first argument of `z', namely `z' In the right-hand side of an equation for `h': z z + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail015.stderr b/ghc/tests/typecheck/should_fail/tcfail015.stderr index d67573894dd57cb9bf01eb1488bfebf4892837fa..ab90aa6348ad54e2dd7377763974f88302f7a64a 100644 --- a/ghc/tests/typecheck/should_fail/tcfail015.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail015.stderr @@ -1,8 +1,9 @@ - + tcfail015.hs:7: - No instance for `PrelBase.Num Bool' + No instance for `Num Bool' arising from the literal `2' at tcfail015.hs:7 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail016.stderr b/ghc/tests/typecheck/should_fail/tcfail016.stderr index 758417ca940d2a2275c44ccd0ffabeb75916637a..af0d5f2847d962245ae2256a9e22b77e4c7cf811 100644 --- a/ghc/tests/typecheck/should_fail/tcfail016.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail016.stderr @@ -1,11 +1,12 @@ - + tcfail016.hs:9: - Couldn't match `Expr a' against `AnnExpr _97' - Expected type: Expr _97 - Inferred type: AnnExpr _97 + Couldn't match `Expr a' against `AnnExpr a' + Expected type: Expr a + Inferred type: AnnExpr a In the first argument of `g', namely `e1' In the first argument of `++', namely `(g e1)' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail017.stderr b/ghc/tests/typecheck/should_fail/tcfail017.stderr index adc86a44e4f57df3b86b9487ed9fafac01718890..3ebb93c2b0a590c2eb3b07d1600ae7563730be66 100644 --- a/ghc/tests/typecheck/should_fail/tcfail017.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail017.stderr @@ -1,4 +1,4 @@ - + tcfail017.hs:11: Could not deduce `C [a]' (arising from an instance declaration at tcfail017.hs:11) @@ -8,5 +8,6 @@ tcfail017.hs:11: When checking the superclasses of an instance declaration + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail018.stderr b/ghc/tests/typecheck/should_fail/tcfail018.stderr index f645b9d8ca172a33bb595962c8ebfcb5522ce6e2..565d1e97e9a776b70f6a4464c3849c592d766226 100644 --- a/ghc/tests/typecheck/should_fail/tcfail018.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail018.stderr @@ -1,9 +1,10 @@ - + tcfail018.hs:5: Ambiguous type variable(s) `t' - in the constraint `PrelBase.Num [t]' + in the constraint `Num [t]' arising from the literal `1' at tcfail018.hs:5 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail019.stderr b/ghc/tests/typecheck/should_fail/tcfail019.stderr index 2788d897d78efd2d39197d7a10b576d259d0dd2c..9eda575a6935bcce3e1a01bfd94d37126a3d4db7 100644 --- a/ghc/tests/typecheck/should_fail/tcfail019.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail019.stderr @@ -1,4 +1,4 @@ - + tcfail019.hs:19: Could not deduce `C [a]' (arising from an instance declaration at tcfail019.hs:19) @@ -6,7 +6,7 @@ tcfail019.hs:19: Probable cause: missing `C [a]' in instance declaration context or missing instance declaration for `C [a]' When checking the superclasses of an instance declaration - + tcfail019.hs:19: Could not deduce `B [a]' (arising from an instance declaration at tcfail019.hs:19) @@ -16,5 +16,6 @@ tcfail019.hs:19: When checking the superclasses of an instance declaration + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail020.stderr b/ghc/tests/typecheck/should_fail/tcfail020.stderr index 1fe6f0293cb0df4b87283528478855b3e2bfe4c9..78405f701ab17543613dc29de5d3656ce24b9b7a 100644 --- a/ghc/tests/typecheck/should_fail/tcfail020.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail020.stderr @@ -1,4 +1,4 @@ - + tcfail020.hs:11: Could not deduce `A [a]' (arising from an instance declaration at tcfail020.hs:11) @@ -8,5 +8,6 @@ tcfail020.hs:11: When checking the superclasses of an instance declaration + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail021.stderr b/ghc/tests/typecheck/should_fail/tcfail021.stderr index ffd31e4ac93c78faf707a5a70bf48be3d92f515d..0d6371ccb1e7fcbf8174240333a7ffa5bd38ccfe 100644 --- a/ghc/tests/typecheck/should_fail/tcfail021.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail021.stderr @@ -1,8 +1,9 @@ - + tcfail021.hs:8: Can't handle multiple methods defined by one pattern binding (==, /=) = (\ x -> \ y -> ..., \ x -> \ y -> ...) + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail023.stderr b/ghc/tests/typecheck/should_fail/tcfail023.stderr index 283da451ec9e97ab865fca014d3c8cc7d5ae43ef..47f1cba48fb003ef4be34e65085cd69bb552054b 100644 --- a/ghc/tests/typecheck/should_fail/tcfail023.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail023.stderr @@ -1,14 +1,14 @@ - + tcfail023.hs:1: Duplicate or overlapping instance declarations for `A B' at tcfail023.hs:11 and tcfail023.hs:14 - + tcfail023.hs:11: Couldn't match `B' against `Bool' Expected type: B Inferred type: Bool In the right-hand side of an equation for `op': True - + tcfail023.hs:14: Couldn't match `B' against `Bool' Expected type: B @@ -16,5 +16,6 @@ tcfail023.hs:14: In the right-hand side of an equation for `op': True + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail027.stderr b/ghc/tests/typecheck/should_fail/tcfail027.stderr index 241231c4ec67b6551385f8d4e889f8a9d3d4010b..806100ba36b48fc0eafaa8cc8e3d3727a27425f1 100644 --- a/ghc/tests/typecheck/should_fail/tcfail027.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail027.stderr @@ -1,9 +1,10 @@ - + tcfail027.hs:3: Cycle in class declarations: `B' at tcfail027.hs:7 `A' at tcfail027.hs:4 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail028.stderr b/ghc/tests/typecheck/should_fail/tcfail028.stderr index 3aa6f428a9abbbc7665038fb2087e8583b3385b4..dbede23e2f8bc2a868bab8e01a46cb28fc1d8550 100644 --- a/ghc/tests/typecheck/should_fail/tcfail028.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail028.stderr @@ -1,4 +1,4 @@ - + tcfail028.hs:4: Couldn't match `Type t' against `k -> *' Expected kind: Type t @@ -7,5 +7,6 @@ tcfail028.hs:4: In the newtype declaration for `A' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail029.stderr b/ghc/tests/typecheck/should_fail/tcfail029.stderr index 5b997acdbd32a65f98e4a766abd82b009f80c7aa..3c2874d502cf87cf79eb9b62df359dd3b6400f7c 100644 --- a/ghc/tests/typecheck/should_fail/tcfail029.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail029.stderr @@ -1,7 +1,7 @@ - + tcfail029.hs:6: - No instance for `PrelBase.Ord Foo' - arising from use of `PrelBase.>' at tcfail029.hs:6 + No instance for `Ord Foo' arising from use of `>' at tcfail029.hs:6 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail030.stderr b/ghc/tests/typecheck/should_fail/tcfail030.stderr index 5ad8a2350b6e40d09948e96f5fd1507e490cb30a..88a651b8e22876bce13f1ab053cdda715eea6512 100644 --- a/ghc/tests/typecheck/should_fail/tcfail030.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail030.stderr @@ -1 +1,7 @@ -tcfail030.hs:2:1: parse error on input: <EOF> + +tcfail030.hs:0: Module `Main' must include a definition for `main' + + + +Compilation had errors + diff --git a/ghc/tests/typecheck/should_fail/tcfail031.stderr b/ghc/tests/typecheck/should_fail/tcfail031.stderr index 127c5bda6665177d87c66f0b630dfcd901b9c531..a8d9781dbc3b9de66dc17eb0687d80c5e04e266b 100644 --- a/ghc/tests/typecheck/should_fail/tcfail031.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail031.stderr @@ -1,4 +1,4 @@ - + tcfail031.hs:3: Couldn't match `Bool' against `Char' Expected type: Bool @@ -7,5 +7,6 @@ tcfail031.hs:3: In the right-hand side of an equation for `f': if 'a' then 1 else 2 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail032.stderr b/ghc/tests/typecheck/should_fail/tcfail032.stderr index d693416a5aefc9bcc2bd981c861e722a3a619b98..d8287931ca8246fb480c46aa0743d89c38400199 100644 --- a/ghc/tests/typecheck/should_fail/tcfail032.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail032.stderr @@ -1,17 +1,17 @@ - + tcfail032.hs:14: Inferred type is less polymorphic than expected Quantified type variable `a' escapes It is mentioned in the environment The following variables in the environment mention `a' x :: a -> Int - In an expression with expected type: forall - _97. - {PrelBase.Eq _97} => - _97 -> Int + In an expression with expected type: forall a1. + {Eq a1} => + a1 -> Int In an expression with a type signature: x :: forall a. (Eq a) => a -> Int + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail033.stderr b/ghc/tests/typecheck/should_fail/tcfail033.stderr index 94522fad7b86707332bb8b3b3e4e58673a4f2cee..3bc5fa549e43f866479ccf427640adbf80d26c0e 100644 --- a/ghc/tests/typecheck/should_fail/tcfail033.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail033.stderr @@ -1,10 +1,11 @@ - + tcfail033.hs:4: - Occurs check: cannot construct the infinite type: t = (t, _116) - Expected type: (t, _116) + Occurs check: cannot construct the infinite type: t = (t, t1) + Expected type: (t, t1) Inferred type: t In a list-comprehension qualifier: return x + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail034.stderr b/ghc/tests/typecheck/should_fail/tcfail034.stderr index 2a326aa4d055ff726e2087f5026d16bcc2014c9f..42ed8bfae608b0e865ac97e6d6b5a8b8c8812b72 100644 --- a/ghc/tests/typecheck/should_fail/tcfail034.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail034.stderr @@ -1,12 +1,12 @@ - + tcfail034.hs:17: - Could not deduce `PrelNum.Integral a' - (arising from use of `PrelNum.mod' at tcfail034.hs:17) - from the context: (PrelBase.Num a, PrelBase.Eq a) - Probable cause: missing `PrelNum.Integral a' - in type signature for `test' + Could not deduce `Integral a' + (arising from use of `mod' at tcfail034.hs:17) + from the context: (Num a, Eq a) + Probable cause: missing `Integral a' in type signature for `test' When checking the type signature(s) for `test' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail035.stderr b/ghc/tests/typecheck/should_fail/tcfail035.stderr index 9db43b41495fd13017d7610932b79e1d586ce636..ed219a596bb1c93a3254d4298539a1e6bbc93e6f 100644 --- a/ghc/tests/typecheck/should_fail/tcfail035.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail035.stderr @@ -1,48 +1,50 @@ - -tcfail035.hs:6: Warning: - No explicit method nor default method for `PrelBase.fromInteger' - in an instance declaration for `PrelBase.Num' - -tcfail035.hs:6: Warning: - No explicit method nor default method for `PrelBase.signum' - in an instance declaration for `PrelBase.Num' - -tcfail035.hs:6: Warning: - No explicit method nor default method for `PrelBase.abs' - in an instance declaration for `PrelBase.Num' - -tcfail035.hs:6: Warning: - No explicit method nor default method for `PrelBase.*' - in an instance declaration for `PrelBase.Num' - -tcfail035.hs:6: Warning: - No explicit method nor default method for `PrelBase.+' - in an instance declaration for `PrelBase.Num' - -tcfail035.hs:7: Warning: - No explicit method nor default method for `PrelBase.fromInteger' - in an instance declaration for `PrelBase.Num' - -tcfail035.hs:7: Warning: - No explicit method nor default method for `PrelBase.signum' - in an instance declaration for `PrelBase.Num' - -tcfail035.hs:7: Warning: - No explicit method nor default method for `PrelBase.abs' - in an instance declaration for `PrelBase.Num' - -tcfail035.hs:7: Warning: - No explicit method nor default method for `PrelBase.*' - in an instance declaration for `PrelBase.Num' - -tcfail035.hs:7: Warning: - No explicit method nor default method for `PrelBase.+' - in an instance declaration for `PrelBase.Num' - - + +tcfail035.hs:6: + Warning: No explicit method nor default method for `fromInteger' + in an instance declaration for `Num' + +tcfail035.hs:6: + Warning: No explicit method nor default method for `signum' + in an instance declaration for `Num' + +tcfail035.hs:6: + Warning: No explicit method nor default method for `abs' + in an instance declaration for `Num' + +tcfail035.hs:6: + Warning: No explicit method nor default method for `*' + in an instance declaration for `Num' + +tcfail035.hs:6: + Warning: No explicit method nor default method for `+' + in an instance declaration for `Num' + +tcfail035.hs:7: + Warning: No explicit method nor default method for `fromInteger' + in an instance declaration for `Num' + +tcfail035.hs:7: + Warning: No explicit method nor default method for `signum' + in an instance declaration for `Num' + +tcfail035.hs:7: + Warning: No explicit method nor default method for `abs' + in an instance declaration for `Num' + +tcfail035.hs:7: + Warning: No explicit method nor default method for `*' + in an instance declaration for `Num' + +tcfail035.hs:7: + Warning: No explicit method nor default method for `+' + in an instance declaration for `Num' + + + tcfail035.hs:3: Duplicate or overlapping instance declarations - for `PrelBase.Num NUM' at tcfail035.hs:6 and tcfail035.hs:7 + for `Num NUM' at tcfail035.hs:6 and tcfail035.hs:7 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail036.stderr b/ghc/tests/typecheck/should_fail/tcfail036.stderr index 175e247fa7770c458d1bfdb2885d72321a7299c9..441b9ff6659f9ca5141e7f0ecb24136b8f0c2806 100644 --- a/ghc/tests/typecheck/should_fail/tcfail036.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail036.stderr @@ -1,57 +1,59 @@ - -tcfail036.hs:7: Warning: - No explicit method nor default method for `PrelBase.fromInteger' - in an instance declaration for `PrelBase.Num' - -tcfail036.hs:7: Warning: - No explicit method nor default method for `PrelBase.signum' - in an instance declaration for `PrelBase.Num' - -tcfail036.hs:7: Warning: - No explicit method nor default method for `PrelBase.abs' - in an instance declaration for `PrelBase.Num' - -tcfail036.hs:7: Warning: - No explicit method nor default method for `PrelBase.*' - in an instance declaration for `PrelBase.Num' - -tcfail036.hs:8: Warning: - No explicit method nor default method for `PrelBase.fromInteger' - in an instance declaration for `PrelBase.Num' - -tcfail036.hs:8: Warning: - No explicit method nor default method for `PrelBase.signum' - in an instance declaration for `PrelBase.Num' - -tcfail036.hs:8: Warning: - No explicit method nor default method for `PrelBase.abs' - in an instance declaration for `PrelBase.Num' - -tcfail036.hs:8: Warning: - No explicit method nor default method for `PrelBase.*' - in an instance declaration for `PrelBase.Num' - -tcfail036.hs:8: Warning: - No explicit method nor default method for `PrelBase.+' - in an instance declaration for `PrelBase.Num' - - + +tcfail036.hs:7: + Warning: No explicit method nor default method for `fromInteger' + in an instance declaration for `Num' + +tcfail036.hs:7: + Warning: No explicit method nor default method for `signum' + in an instance declaration for `Num' + +tcfail036.hs:7: + Warning: No explicit method nor default method for `abs' + in an instance declaration for `Num' + +tcfail036.hs:7: + Warning: No explicit method nor default method for `*' + in an instance declaration for `Num' + +tcfail036.hs:8: + Warning: No explicit method nor default method for `fromInteger' + in an instance declaration for `Num' + +tcfail036.hs:8: + Warning: No explicit method nor default method for `signum' + in an instance declaration for `Num' + +tcfail036.hs:8: + Warning: No explicit method nor default method for `abs' + in an instance declaration for `Num' + +tcfail036.hs:8: + Warning: No explicit method nor default method for `*' + in an instance declaration for `Num' + +tcfail036.hs:8: + Warning: No explicit method nor default method for `+' + in an instance declaration for `Num' + + + tcfail036.hs:3: Duplicate or overlapping instance declarations - for `PrelBase.Num NUM' at tcfail036.hs:7 and tcfail036.hs:8 - + for `Num NUM' at tcfail036.hs:7 and tcfail036.hs:8 + tcfail036.hs:7: - No instance for `PrelBase.Show NUM' + No instance for `Show NUM' arising from an instance declaration at tcfail036.hs:7 - + tcfail036.hs:7: - No instance for `PrelBase.Eq NUM' + No instance for `Eq NUM' arising from an instance declaration at tcfail036.hs:7 - + tcfail036.hs:9: Class used as a type constructor: Num When checking kinds in `Eq Num' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail037.stderr b/ghc/tests/typecheck/should_fail/tcfail037.stderr index 8421c3be8585e190013d4824554e652d1131dffe..ab51ba6f74f1fff27e1a6ee133e290db1b1daf4c 100644 --- a/ghc/tests/typecheck/should_fail/tcfail037.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail037.stderr @@ -1,18 +1,9 @@ - -tcfail037.hs:3: - Ambiguous occurrence `+' - It could refer to: +: defined at tcfail037.hs:10 - PrelBase.+: imported from Prelude at tcfail037.hs:3 - + tcfail037.hs:7: Ambiguous occurrence `+' - It could refer to: +: defined at tcfail037.hs:10 - PrelBase.+: imported from Prelude at tcfail037.hs:3 - -tcfail037.hs:10: - Ambiguous occurrence `+' - It could refer to: +: defined at tcfail037.hs:10 - PrelBase.+: imported from Prelude at tcfail037.hs:3 + It could refer to either `+', defined at tcfail037.hs:10 + or `Prelude.+', imported from Prelude at tcfail037.hs:3 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail038.stderr b/ghc/tests/typecheck/should_fail/tcfail038.stderr index dc70bbb72fc1db5070611d69afd50a1716fe00ae..d1ca6fd54623587bde9203aad48a6ba89834760d 100644 --- a/ghc/tests/typecheck/should_fail/tcfail038.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail038.stderr @@ -1,9 +1,12 @@ - + tcfail038.hs:7: - Conflicting definitions for `==' in the bindings in an instance declaration - + Conflicting definitions for `==' + in the bindings in an instance declaration + tcfail038.hs:8: - Conflicting definitions for `/=' in the bindings in an instance declaration + Conflicting definitions for `/=' + in the bindings in an instance declaration + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail040.stderr b/ghc/tests/typecheck/should_fail/tcfail040.stderr index 3ad40d60ee3534dd0eacf3f224d81419a9d80a79..dfcdd4c693b8736a9c023c00561b510011c02cc3 100644 --- a/ghc/tests/typecheck/should_fail/tcfail040.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail040.stderr @@ -1,9 +1,10 @@ - + tcfail040.hs:19: Ambiguous type variable(s) `a' in the constraint `ORD a' arising from use of `<<' at tcfail040.hs:19 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail042.stderr b/ghc/tests/typecheck/should_fail/tcfail042.stderr index e5de9ff538c710283c81947936f7e26fd58e9af2..7e746ccc3662d962516a1f4aa6494cab37dddb93 100644 --- a/ghc/tests/typecheck/should_fail/tcfail042.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail042.stderr @@ -1,12 +1,12 @@ - + tcfail042.hs:18: - Could not deduce `PrelBase.Num a' + Could not deduce `Num a' (arising from an instance declaration at tcfail042.hs:18) - from the context: (PrelBase.Eq a, PrelBase.Show a) - Probable cause: missing `PrelBase.Num a' - in instance declaration context + from the context: (Eq a, Show a) + Probable cause: missing `Num a' in instance declaration context When checking the superclasses of an instance declaration + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail043.stderr b/ghc/tests/typecheck/should_fail/tcfail043.stderr index e93d0b382ea895b7af25348c39b8e2e792f11370..ac63226a6a8f9b9525a92a8ed58e612bec80e4aa 100644 --- a/ghc/tests/typecheck/should_fail/tcfail043.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail043.stderr @@ -1,53 +1,34 @@ - -tcfail043.hs:16: - Ambiguous occurrence `and' - It could refer to: and: defined at tcfail043.hs:42 - PrelList.and: imported from Prelude at tcfail043.hs:16 - -tcfail043.hs:16: - Ambiguous occurrence `null' - It could refer to: null: defined at tcfail043.hs:57 - PrelList.null: imported from Prelude at tcfail043.hs:16 - + tcfail043.hs:24: Ambiguous occurrence `null' - It could refer to: null: defined at tcfail043.hs:57 - PrelList.null: imported from Prelude at tcfail043.hs:16 - + It could refer to either `null', defined at tcfail043.hs:57 + or `Prelude.null', imported from Prelude at tcfail043.hs:16 + tcfail043.hs:24: Ambiguous occurrence `null' - It could refer to: null: defined at tcfail043.hs:57 - PrelList.null: imported from Prelude at tcfail043.hs:16 - + It could refer to either `null', defined at tcfail043.hs:57 + or `Prelude.null', imported from Prelude at tcfail043.hs:16 + tcfail043.hs:26: Ambiguous occurrence `null' - It could refer to: null: defined at tcfail043.hs:57 - PrelList.null: imported from Prelude at tcfail043.hs:16 - + It could refer to either `null', defined at tcfail043.hs:57 + or `Prelude.null', imported from Prelude at tcfail043.hs:16 + tcfail043.hs:26: Ambiguous occurrence `and' - It could refer to: and: defined at tcfail043.hs:42 - PrelList.and: imported from Prelude at tcfail043.hs:16 - + It could refer to either `and', defined at tcfail043.hs:42 + or `Prelude.and', imported from Prelude at tcfail043.hs:16 + tcfail043.hs:41: Ambiguous occurrence `and' - It could refer to: and: defined at tcfail043.hs:42 - PrelList.and: imported from Prelude at tcfail043.hs:16 - -tcfail043.hs:42: - Ambiguous occurrence `and' - It could refer to: and: defined at tcfail043.hs:42 - PrelList.and: imported from Prelude at tcfail043.hs:16 - + It could refer to either `and', defined at tcfail043.hs:42 + or `Prelude.and', imported from Prelude at tcfail043.hs:16 + tcfail043.hs:56: Ambiguous occurrence `null' - It could refer to: null: defined at tcfail043.hs:57 - PrelList.null: imported from Prelude at tcfail043.hs:16 - -tcfail043.hs:57: - Ambiguous occurrence `null' - It could refer to: null: defined at tcfail043.hs:57 - PrelList.null: imported from Prelude at tcfail043.hs:16 + It could refer to either `null', defined at tcfail043.hs:57 + or `Prelude.null', imported from Prelude at tcfail043.hs:16 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail044.stderr b/ghc/tests/typecheck/should_fail/tcfail044.stderr index 5a3633d16bd4cb02c3cea20649b470168f11df1a..f30e605f51080d8c408d1de12a48a7adafdea44e 100644 --- a/ghc/tests/typecheck/should_fail/tcfail044.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail044.stderr @@ -1,23 +1,25 @@ - -tcfail044.hs:12: Warning: - No explicit method nor default method for `PrelBase.signum' - in an instance declaration for `PrelBase.Num' - -tcfail044.hs:12: Warning: - No explicit method nor default method for `PrelBase.abs' - in an instance declaration for `PrelBase.Num' - - + +tcfail044.hs:12: + Warning: No explicit method nor default method for `signum' + in an instance declaration for `Num' + +tcfail044.hs:12: + Warning: No explicit method nor default method for `abs' + in an instance declaration for `Num' + + + tcfail044.hs:5: - Illegal instance declaration for `PrelBase.Eq (a -> a)' + Illegal instance declaration for `Eq (a -> a)' (the instance type must be of form (T a b c) where T is not a synonym, and a,b,c are distinct type variables) - + tcfail044.hs:12: - Illegal instance declaration for `PrelBase.Num (a -> a)' + Illegal instance declaration for `Num (a -> a)' (the instance type must be of form (T a b c) where T is not a synonym, and a,b,c are distinct type variables) + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail045.stderr b/ghc/tests/typecheck/should_fail/tcfail045.stderr index 7f7e5b745627aa2399b23c8024597eb34df8545c..236911e8953216f72e16aad3fdc29a1bcea3c6c7 100644 --- a/ghc/tests/typecheck/should_fail/tcfail045.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail045.stderr @@ -1,7 +1,8 @@ - + tcfail045.hs:10: Unacceptable instance type for ccall-ish class - class PrelGHC.CCallable type Socket + class CCallable type Socket + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail046.stderr b/ghc/tests/typecheck/should_fail/tcfail046.stderr index 27fbf4a4d4027202cb5fe39f59dd949d093abe9b..2f5fe27f2ae39170dca70259cce4708e443e84f0 100644 --- a/ghc/tests/typecheck/should_fail/tcfail046.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail046.stderr @@ -1,8 +1,9 @@ - + tcfail046.hs:4: - No instance for `PrelBase.Eq (Process a)' + No instance for `Eq (Process a)' When deriving classes for `Message' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail047.stderr b/ghc/tests/typecheck/should_fail/tcfail047.stderr index 3d04691330c189ad1af45c1a30c58940fea8531e..4eb3cca94fa316b77250580d80e42442619a7930 100644 --- a/ghc/tests/typecheck/should_fail/tcfail047.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail047.stderr @@ -1,9 +1,10 @@ - + tcfail047.hs:7: Illegal instance declaration for `A (a, (b, c))' (the instance type must be of form (T a b c) where T is not a synonym, and a,b,c are distinct type variables) + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail048.stderr b/ghc/tests/typecheck/should_fail/tcfail048.stderr index d13818260c664a59bb2dbc51945862065b631d06..5b2692450af5f81ee24763df5f7ac33427d70655 100644 --- a/ghc/tests/typecheck/should_fail/tcfail048.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail048.stderr @@ -1,6 +1,7 @@ - + tcfail048.hs:4: Type constructor or class not in scope: `B' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail049.stderr b/ghc/tests/typecheck/should_fail/tcfail049.stderr index 3814659721cac246ae44ab59281f932f49c0fe9e..e2e5992eaea8358b8c108ed700672985a5b0de38 100644 --- a/ghc/tests/typecheck/should_fail/tcfail049.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail049.stderr @@ -1,5 +1,6 @@ - -tcfail049.hs:3: Value not in scope: `g' + +tcfail049.hs:3: Variable not in scope: `g' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail050.stderr b/ghc/tests/typecheck/should_fail/tcfail050.stderr index 164fe3c731a5683fc96d366e709b3d12b64b92ed..f21fbf494f35fdfacf39f74baecd0525e553d886 100644 --- a/ghc/tests/typecheck/should_fail/tcfail050.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail050.stderr @@ -1,6 +1,7 @@ - + tcfail050.hs:3: Data constructor not in scope: `B' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail051.stderr b/ghc/tests/typecheck/should_fail/tcfail051.stderr index 6faa68c3213eb16c4d61a744eec4df457ae5fd52..ead1fa1326b8369c38c8e9d7e9b1d35fee1eec7c 100644 --- a/ghc/tests/typecheck/should_fail/tcfail051.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail051.stderr @@ -1,7 +1,8 @@ - + tcfail051.hs:4: Type constructor or class not in scope: `B' - -tcfail051.hs:4: Value not in scope: `op1' + +tcfail051.hs:4: Variable not in scope: `op1' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail052.stderr b/ghc/tests/typecheck/should_fail/tcfail052.stderr index fb4b63546dad60009903b313d1fd565a15413048..397abcd8cb385af34dd907c2e068c834e7183e53 100644 --- a/ghc/tests/typecheck/should_fail/tcfail052.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail052.stderr @@ -1,6 +1,7 @@ - + tcfail052.hs:4: Type variable not in scope: `c' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail053.stderr b/ghc/tests/typecheck/should_fail/tcfail053.stderr index 39661e67d9b4ed067794cefe42d2bf5911c6841a..baa28f5ef00748aab19e41e0c4c1e66ccdb2244a 100644 --- a/ghc/tests/typecheck/should_fail/tcfail053.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail053.stderr @@ -1,6 +1,7 @@ - + tcfail053.hs:3: Type constructor or class not in scope: `A' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail054.stderr b/ghc/tests/typecheck/should_fail/tcfail054.stderr index 5a22c7f249de293c1ec99b40216291461623dabe..65477564f70d1e5a4bc49c2bf1dd446877c5f45d 100644 --- a/ghc/tests/typecheck/should_fail/tcfail054.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail054.stderr @@ -1,6 +1,7 @@ - + tcfail054.hs:3: Data constructor not in scope: `B' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail055.stderr b/ghc/tests/typecheck/should_fail/tcfail055.stderr index 46f3d649c25b25fb5072c3696dc5bd0940ed7d29..834f6567e40016c4df5df94ecc305276deaf1766 100644 --- a/ghc/tests/typecheck/should_fail/tcfail055.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail055.stderr @@ -1,4 +1,4 @@ - + tcfail055.hs:3: Couldn't match `Int' against `Float' Expected type: Int @@ -6,5 +6,6 @@ tcfail055.hs:3: In an expression with a type signature: x + 1 :: Int + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail056.stderr b/ghc/tests/typecheck/should_fail/tcfail056.stderr index 1bc765d917b93a000a8f80b9e967dc2afeede923..1ac293662ce00bbaf848fecd4c6c3c11f4e11a86 100644 --- a/ghc/tests/typecheck/should_fail/tcfail056.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail056.stderr @@ -1,9 +1,10 @@ - + tcfail056.hs:1: Duplicate or overlapping instance declarations - for `PrelBase.Eq Foo' at tcfail056.hs:6 and tcfail056.hs:10 - -tcfail056.hs:10: Class `PrelBase.Eq' does not have a method `<=' + for `Eq Foo' at tcfail056.hs:6 and tcfail056.hs:10 + +tcfail056.hs:10: Class `Eq' does not have a method `<=' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail057.stderr b/ghc/tests/typecheck/should_fail/tcfail057.stderr index 87aff591e22ab175f66db099ddebd0f5fd89a746..15966fae701c60e02ce072ea5c934c7d0f6c9370 100644 --- a/ghc/tests/typecheck/should_fail/tcfail057.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail057.stderr @@ -1,8 +1,9 @@ - + tcfail057.hs:5: Class used as a type constructor: RealFrac When checking kinds in `RealFrac a' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail058.stderr b/ghc/tests/typecheck/should_fail/tcfail058.stderr index 544e50651946bf6396a0894eb58249d3086d8e38..bab93a7cdc0262961bb4c0088f4b09866b9cf75a 100644 --- a/ghc/tests/typecheck/should_fail/tcfail058.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail058.stderr @@ -1,8 +1,9 @@ - + tcfail058.hs:6: Type constructor used as a class: Array When checking kinds in `Array a' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail061.stderr b/ghc/tests/typecheck/should_fail/tcfail061.stderr index 6375a067c7b0f0c198d194f781618913ebab67ef..362e7a5e88f0c8caf15377a9a6ef6f9ae4aaf2e9 100644 --- a/ghc/tests/typecheck/should_fail/tcfail061.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail061.stderr @@ -1,12 +1,13 @@ - + tcfail061.hs:5: Type variable not in scope: `b' - + tcfail061.hs:5: Type variable not in scope: `b' - + tcfail061.hs:11: Type variable not in scope: `b' - + tcfail061.hs:11: Type variable not in scope: `b' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail062.stderr b/ghc/tests/typecheck/should_fail/tcfail062.stderr index 362a4603dfdf0f28e9f104553ad968691a625a9c..2887b6bbe211b1e38893f27d1fbe77dea26a6f12 100644 --- a/ghc/tests/typecheck/should_fail/tcfail062.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail062.stderr @@ -1,10 +1,11 @@ - + tcfail062.hs:33: Type variable not in scope: `behaviouralExpression' - + tcfail062.hs:33: Type variable not in scope: `behaviouralExpression' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail065.stderr b/ghc/tests/typecheck/should_fail/tcfail065.stderr index a19293a74d0de831da9f2506ea89070f7903e38a..191e08ed5fab75cb80b0a58f9a41bdd695ec3784 100644 --- a/ghc/tests/typecheck/should_fail/tcfail065.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail065.stderr @@ -1,13 +1,14 @@ - + tcfail065.hs:29: Inferred type is less polymorphic than expected Quantified type variable `x' escapes It is mentioned in the environment The following variables in the environment mention `x' When checking the type signature - setX :: forall _1201. _1201 -> X _120 -> X _120 + setX :: forall x2. x2 -> X x1 -> X x1 In the definition for method `setX' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail067.stderr b/ghc/tests/typecheck/should_fail/tcfail067.stderr index b243791c35ea7d40ed29b9bf6c387dc3ac027767..fca214ae220de5b4dc024a951d0aa7c4da90c009 100644 --- a/ghc/tests/typecheck/should_fail/tcfail067.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail067.stderr @@ -1,38 +1,39 @@ - -tcfail067.hs:65: Warning: - No explicit method nor default method for `PrelBase.signum' - in an instance declaration for `PrelBase.Num' - -tcfail067.hs:65: Warning: - No explicit method nor default method for `PrelBase.abs' - in an instance declaration for `PrelBase.Num' - - + +tcfail067.hs:65: + Warning: No explicit method nor default method for `signum' + in an instance declaration for `Num' + tcfail067.hs:65: - Could not deduce `PrelBase.Ord a' + Warning: No explicit method nor default method for `abs' + in an instance declaration for `Num' + + + +tcfail067.hs:65: + Could not deduce `Ord a' (arising from use of `SubRange' at tcfail067.hs:65) - from the context: (PrelBase.Num (SubRange _97), PrelBase.Num _97, PrelBase.Eq (SubRange _97), PrelBase.Show (SubRange _97), PrelBase.Eq (SubRange _97), PrelBase.Show (SubRange _97)) - Probable cause: missing `PrelBase.Ord a' - in instance declaration context + from the context: (Num (SubRange a1), Num a1, Eq (SubRange a1), Show (SubRange a1), Eq (SubRange a1), Show (SubRange a1)) + Probable cause: missing `Ord a' in instance declaration context When checking the methods of an instance declaration - + tcfail067.hs:65: - Could not deduce `PrelBase.Show (SubRange a)' + Could not deduce `Show (SubRange a)' (arising from an instance declaration at tcfail067.hs:65) - from the context: (PrelBase.Num _97) - Probable cause: missing `PrelBase.Show (SubRange a)' + from the context: (Num a1) + Probable cause: missing `Show (SubRange a)' in instance declaration context - or missing instance declaration for `PrelBase.Show (SubRange a)' + or missing instance declaration for `Show (SubRange a)' When checking the superclasses of an instance declaration - + tcfail067.hs:74: - Could not deduce `PrelBase.Ord a' + Could not deduce `Ord a' (arising from use of `SubRange' at tcfail067.hs:74) - from the context: (PrelBase.Num a) - Probable cause: missing `PrelBase.Ord a' + from the context: (Num a) + Probable cause: missing `Ord a' in type signature for `numSubRangeBinOp' When checking the type signature(s) for `numSubRangeBinOp' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail068.stderr b/ghc/tests/typecheck/should_fail/tcfail068.stderr index ebd2b1a3473d6de97266fd45cca2fbb1ffe8edc2..4fea13ff31570ae15565e0f4b7b6593b2011298e 100644 --- a/ghc/tests/typecheck/should_fail/tcfail068.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail068.stderr @@ -1,68 +1,55 @@ - + tcfail068.hs:12: Inferred type is less polymorphic than expected Quantified type variable `s' escapes - It unifies with `_115', which is mentioned in the environment - The following variables in the environment mention `_115' - In an expression with expected type: forall - _1151. - PrelST.ST _1151 a + It unifies with `s1', which is mentioned in the environment + The following variables in the environment mention `s1' + In an expression with expected type: forall s2. ST s2 a In the first argument of `runST', namely `(newArray ((1, 1), n) x)' In the right-hand side of an equation for `itgen': runST (newArray ((1, 1), n) x) - + tcfail068.hs:17: Inferred type is less polymorphic than expected Quantified type variable `s' escapes - It unifies with `_115', which is mentioned in the environment - The following variables in the environment mention `_115' - arr :: IndTree _115 a - In an expression with expected type: forall - _1151. - PrelST.ST _1151 _97 + It unifies with `s1', which is mentioned in the environment + The following variables in the environment mention `s1' + arr :: IndTree s1 a + In an expression with expected type: forall s2. ST s2 a1 In the first argument of `runST', namely `((readArray arr i) >>= (\ val -> (writeArray arr i (f val)) >> (return arr)))' In the right-hand side of an equation for `itiap': runST ((readArray arr i) >>= (\ val -> (writeArray arr i (f val)) >> (return arr))) - + tcfail068.hs:24: Inferred type is less polymorphic than expected Quantified type variable `s' escapes - It unifies with `_115', which is mentioned in the environment - The following variables in the environment mention `_115' - arr :: IndTree _115 a - itrap' :: Int -> Int -> PrelST.ST _115 (IndTree _115 a) - itrapsnd :: Int -> Int -> PrelST.ST _115 (IndTree _115 a) - In an expression with expected type: forall - _1151. - PrelST.ST _1151 _97 + It unifies with `s1', which is mentioned in the environment + The following variables in the environment mention `s1' + arr :: IndTree s1 a + itrap' :: Int -> Int -> ST s1 (IndTree s1 a) + itrapsnd :: Int -> Int -> ST s1 (IndTree s1 a) + In an expression with expected type: forall s2. ST s2 a1 In the first argument of `runST', namely `(itrap' i k)' In the right-hand side of an equation for `itrap': runST (itrap' i k) - + tcfail068.hs:36: Inferred type is less polymorphic than expected Quantified type variable `s' escapes - It unifies with `_115', which is mentioned in the environment - The following variables in the environment mention `_115' - arr :: IndTree _115 b - itrapstate' :: Int - -> Int - -> c - -> PrelST.ST _115 (c, IndTree _115 b) - itrapstatesnd :: Int - -> Int - -> c - -> PrelST.ST _115 (c, IndTree _115 b) - In an expression with expected type: forall - _1151. - PrelST.ST _1151 a + It unifies with `s1', which is mentioned in the environment + The following variables in the environment mention `s1' + arr :: IndTree s1 b + itrapstate' :: Int -> Int -> c -> ST s1 (c, IndTree s1 b) + itrapstatesnd :: Int -> Int -> c -> ST s1 (c, IndTree s1 b) + In an expression with expected type: forall s2. ST s2 a In the first argument of `runST', namely `(itrapstate' i k s)' In the right-hand side of an equation for `itrapstate': runST (itrapstate' i k s) + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail069.stderr b/ghc/tests/typecheck/should_fail/tcfail069.stderr index ed4c38343cfdc2da816d1eaf0d386d7d9e90860d..3ca0c5f8296487b9fc2f40062f9198cb2f9b03bd 100644 --- a/ghc/tests/typecheck/should_fail/tcfail069.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail069.stderr @@ -1,11 +1,12 @@ - + tcfail069.hs:20: - Couldn't match `[t]' against `(_116, _1161)' + Couldn't match `[t]' against `(t1, t2)' Expected type: [t] - Inferred type: (_116, _1161) + Inferred type: (t1, t2) In the scrutinee of a case expression: (list1, list2) In the case expression: case (list1, list2) of [] -> error "foo" + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail070.stderr b/ghc/tests/typecheck/should_fail/tcfail070.stderr index e38c186d84aeba4d2a91713d2667df1a8f7bcfcc..e0736b83fd7cf0b40c55bb69564f640d0ebe095e 100644 --- a/ghc/tests/typecheck/should_fail/tcfail070.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail070.stderr @@ -1,4 +1,4 @@ - + tcfail070.hs:13: Couldn't match `*' against `* -> k' Expected kind: * @@ -7,5 +7,6 @@ tcfail070.hs:13: In the type synonym declaration for `State' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail071.stderr b/ghc/tests/typecheck/should_fail/tcfail071.stderr index ac174a7c37e2a0c4a1be94d6f3b9881127b6a2cc..018379f8257be01ad4e96f220513f7176fcc71d4 100644 --- a/ghc/tests/typecheck/should_fail/tcfail071.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail071.stderr @@ -1,8 +1,9 @@ - + tcfail071.hs:8: Inferred type is less polymorphic than expected Quantified type variable `c' is unified with `a -> [t] -> [t]' - When checking the type signature g :: forall _99. _99 -> _99 + When checking the type signature g :: forall c1. c1 -> c1 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail072.stderr b/ghc/tests/typecheck/should_fail/tcfail072.stderr index d64a33fb52ba1359f23ba9e3c28d42cae1fa9ccd..ea214e1c4909125577730bf0f0445482edaf3770 100644 --- a/ghc/tests/typecheck/should_fail/tcfail072.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail072.stderr @@ -1,14 +1,15 @@ - + tcfail072.hs:23: Ambiguous type variable(s) `p' - in the constraint `PrelBase.Ord p' + in the constraint `Ord p' arising from use of `g' at tcfail072.hs:23 - + tcfail072.hs:23: Ambiguous type variable(s) `q' - in the constraint `PrelBase.Ord q' + in the constraint `Ord q' arising from use of `g' at tcfail072.hs:23 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail073.stderr b/ghc/tests/typecheck/should_fail/tcfail073.stderr index 52038da2008e1623d148989d55c3fb26627aa309..a51978510e8100926a5bd5fe3d7960144b30e528 100644 --- a/ghc/tests/typecheck/should_fail/tcfail073.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail073.stderr @@ -1,16 +1,16 @@ - + tcfail073.hs:3: Duplicate or overlapping instance declarations - for `PrelBase.Eq (a, b)' at PrelTup.hi:14 and tcfail073.hs:8 - + for `Eq (a, b)' at PrelTup.hi:10 and tcfail073.hs:8 + tcfail073.hs:8: - Could not deduce `PrelBase.Eq a' - (arising from use of `PrelBase.==' at tcfail073.hs:8) - from the context: (PrelBase.Eq (a, b)) - Probable cause: missing `PrelBase.Eq a' - in instance declaration context + Could not deduce `Eq a' + (arising from use of `==' at tcfail073.hs:8) + from the context: (Eq (a, b)) + Probable cause: missing `Eq a' in instance declaration context When checking the methods of an instance declaration + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail074.stderr b/ghc/tests/typecheck/should_fail/tcfail074.stderr index 9456d4eb3a50f1d48c4f1287cb25e7e39fefb96e..9e85e923b6ec3db94894f75999dc27419c38636b 100644 --- a/ghc/tests/typecheck/should_fail/tcfail074.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail074.stderr @@ -1,9 +1,10 @@ - + tcfail074.hs:7: Multiple declarations of `main' defined at tcfail074.hs:7 defined at tcfail074.hs:8 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail076.stderr b/ghc/tests/typecheck/should_fail/tcfail076.stderr index ae09933be67d0729ef4b765e39f63003ecaf7fe9..c715384aafbd15622b2332a19df85698e7a6b0a2 100644 --- a/ghc/tests/typecheck/should_fail/tcfail076.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail076.stderr @@ -1,17 +1,17 @@ - + tcfail076.hs:18: Inferred type is less polymorphic than expected Quantified type variable `res' escapes - It unifies with `_114_101_115', which is mentioned in the environment - The following variables in the environment mention `_114_101_115' - cont :: a -> m _114_101_115 - In an expression with expected type: forall - _114_101_1151. - (_97 -> m _114_101_1151) -> m _114_101_1151 + It unifies with `res1', which is mentioned in the environment + The following variables in the environment mention `res1' + cont :: a -> m res1 + In an expression with expected type: forall res2. + (a1 -> m res2) -> m res2 In the first argument of `KContT', namely `(\ cont' -> cont a)' In the right-hand side of a lambda abstraction: KContT (\ cont' -> cont a) + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail077.stderr b/ghc/tests/typecheck/should_fail/tcfail077.stderr index 7a3a74dee8f8c139c21da7c80699322c806f9532..376d1bfe13d838925cad6a65393d508324faf9f4 100644 --- a/ghc/tests/typecheck/should_fail/tcfail077.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail077.stderr @@ -1,5 +1,6 @@ - -tcfail077.hs:8: Value not in scope: `op2' + +tcfail077.hs:8: Variable not in scope: `op2' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail078.stderr b/ghc/tests/typecheck/should_fail/tcfail078.stderr index cb15a3a86426ee168f3b83c4f1270863589557c5..ffae1f07c3366c93c0372eecb41d7650faa1ba69 100644 --- a/ghc/tests/typecheck/should_fail/tcfail078.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail078.stderr @@ -1,8 +1,9 @@ - + tcfail078.hs:5: Type constructor used as a class: Integer When checking kinds in `Integer i' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail079.stderr b/ghc/tests/typecheck/should_fail/tcfail079.stderr index 963dafb70857cff74923842709f912ca03455b72..bf3afb46360e35195325429e92d0c32636b03c6d 100644 --- a/ghc/tests/typecheck/should_fail/tcfail079.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail079.stderr @@ -1,4 +1,4 @@ - + tcfail079.hs:9: Couldn't match `*' against `#' Expected kind: * @@ -7,5 +7,6 @@ tcfail079.hs:9: In the data type declaration for `Unboxed' + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail080.stderr b/ghc/tests/typecheck/should_fail/tcfail080.stderr index 714b14f538130d67cf9e029d28a7dcf049857dfc..e4d8be979807fd8b1784c02a2a663054d94e9dea 100644 --- a/ghc/tests/typecheck/should_fail/tcfail080.stderr +++ b/ghc/tests/typecheck/should_fail/tcfail080.stderr @@ -1,9 +1,10 @@ - + tcfail080.hs:11: Ambiguous type variable(s) `c' in the constraint `Collection c a' arising from use of `isempty' at tcfail080.hs:11 + Compilation had errors diff --git a/ghc/tests/typecheck/should_fail/tcfail081.hs b/ghc/tests/typecheck/should_fail/tcfail081.hs new file mode 100644 index 0000000000000000000000000000000000000000..95e0bfef42ca3d998b7b46135cc979332227d06a --- /dev/null +++ b/ghc/tests/typecheck/should_fail/tcfail081.hs @@ -0,0 +1,5 @@ +-- !!! Catch an invalid Main.main type +module Main(main) where + +main :: a +main = error "not much luck" diff --git a/ghc/tests/typecheck/should_fail/tcfail081.stderr b/ghc/tests/typecheck/should_fail/tcfail081.stderr new file mode 100644 index 0000000000000000000000000000000000000000..c0bbc90c8e4180288c4194903eeed573f9faead7 --- /dev/null +++ b/ghc/tests/typecheck/should_fail/tcfail081.stderr @@ -0,0 +1,10 @@ + +tcfail081.hs:4: + Inferred type is less polymorphic than expected + Quantified type variable `a' is unified with `IO t' + When checking the type signature main :: forall a1. a1 + + + +Compilation had errors + diff --git a/ghc/tests/typecheck/should_run/Makefile b/ghc/tests/typecheck/should_run/Makefile index 91428646c86acc7194b4ef390758cb9b6e4f9be9..52a3fbab85f4db0475d83e5462e83ffb8bfa570b 100644 --- a/ghc/tests/typecheck/should_run/Makefile +++ b/ghc/tests/typecheck/should_run/Makefile @@ -4,4 +4,6 @@ include $(TOP)/mk/should_run.mk SRC_HC_OPTS += -dcore-lint +tcrun003_HC_OPTS += -fglasgow-exts + include $(TOP)/mk/target.mk diff --git a/ghc/tests/typecheck/should_run/tcrun003.hs b/ghc/tests/typecheck/should_run/tcrun003.hs index 86eb318f1b9a3487de8e00862c415189321fe952..fae88c7245e4c48f78e2a861a3c65e14e3491e99 100644 --- a/ghc/tests/typecheck/should_run/tcrun003.hs +++ b/ghc/tests/typecheck/should_run/tcrun003.hs @@ -1,5 +1,5 @@ ---!!! One method class from Sergey Mechveliani --- showed up problematic newtype dict rep. +-- !!! One method class from Sergey Mechveliani +-- showed up problematic newtype dict rep. module Main where import Ratio diff --git a/ghc/tests/typecheck/should_run/tcrun004.hs b/ghc/tests/typecheck/should_run/tcrun004.hs index d2047588670693e1fa672c8f15cee89a5a41bd42..3511cdd2557d3d9aede0a4f1d6427e45b10eaf13 100644 --- a/ghc/tests/typecheck/should_run/tcrun004.hs +++ b/ghc/tests/typecheck/should_run/tcrun004.hs @@ -1,7 +1,6 @@ --- Originally from Kevin Glynn --- Tests existential data types - -module Main where +-- !!! Tests existential data types +-- Originally from Kevin Glynn +module Main(main) where data Coordinate3D = Coord3D {cx, cy, cz::Double} deriving (Eq, Show) @@ -66,7 +65,7 @@ putName x = putStr $ getPictureName x main :: IO () -main = do { sequence $ map put_it obj_list } +main = do { sequence_ $ map put_it obj_list } where - put_it (MkGenPic s) = putStr (getPictureName s) + put_it (MkGenPic s) = putStrLn (getPictureName s)