Skip to content
Snippets Groups Projects
Commit 7c200a0f authored by sof's avatar sof
Browse files

[project @ 1999-02-09 10:12:24 by sof]

Updated + added Main.main regression test.
parent cd10502b
No related merge requests found
Showing
with 66 additions and 66 deletions
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 ;
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 ;
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 ;
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 ;
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 ;
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 ;
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 ;
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) ;
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]} ;
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} ;
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 ;
......
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]} ;
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 ;
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]} ;
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] ;
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 ;
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} ;
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} ;
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]} ;
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} ;
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment