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

[project @ 1998-03-16 17:53:54 by sof]

New layout test
parent e509fc9e
No related merge requests found
......@@ -5,6 +5,5 @@ include $(TOP)/mk/should_compile.mk
SRC_HC_OPTS += -noC -dcore-lint
read004_HC_OPTS = -fno-implicit-prelude
read006_HC_OPTS = -hi
include $(TOP)/mk/target.mk
_interface_ MyList 1
_interface_ MyList 1 302
_instance_modules_
IO PrelAddr PrelArr PrelBounded PrelCCall PrelForeign PrelNum
_usages_
PrelBase 1 :: $d2 1 $d29 1 $d31 1 $d33 1 $d38 1 Eval 1;
PrelBase 3 :: $dEval0 1 $dEval2 1 $dEvalBool0 1 $dEvalDouble0 1 $dEvalInt0 1 Eval 1;
_exports_
MyList MyList(Empty :::);
_instances_
instance _forall_ [a] => {PrelBase.Eval (MyList a)} = $d1;
instance _forall_ [a] => {PrelBase.Eval (MyList a)} = $dEvalMyList0;
_declarations_
1 $d1 _:_ _forall_ [a] => {PrelBase.Eval (MyList a)} ;;
1 $dEvalMyList0 _:_ _forall_ [a] => {PrelBase.Eval (MyList a)} ;;
1 data MyList a = Empty | ::: (MyList a) (MyList a) ;
--!!! Testing layout rule
module Layout where
l1 :: IO ()
l1 = do
return a
where
a = ()
l2 :: IO ()
l2 = do
return a
where
a = ()
l3 :: IO ()
l3 = do
return a
where
a = ()
--!!! Testing handling of troublesome constructor name (:::)
module MyList (MyList(Empty, (:::))) where
data MyList a = Empty
......
ghc: module version unchanged at 1
_interface_ MyList 1
_instance_modules_
IO PrelAddr PrelArr PrelBounded PrelCCall PrelForeign PrelNum
_usages_
PrelBase 1 :: $d2 1 $d29 1 $d31 1 $d33 1 $d38 1 Eval 1;
_exports_
MyList MyList(Empty :::);
_instances_
instance _forall_ [a] => {PrelBase.Eval (MyList a)} = $d1;
_declarations_
1 $d1 _:_ _forall_ [a] => {PrelBase.Eval (MyList a)} ;;
1 data MyList a = Empty | ::: (MyList a) (MyList a) ;
module ShouldSucceed where
--!!! combining undeclared infix operators
module ShouldSucceed where
-- should default to 'infixl 9'
......
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