Skip to content
Snippets Groups Projects
Commit a0953bd3 authored by Reuben Thomas's avatar Reuben Thomas
Browse files

[project @ 2000-05-16 14:03:14 by rrt]

Now that -ddump-* dumps to stdout, the stderr/out files need
reorganising.
parent bf0c937e
No related merge requests found
==================== Parser ====================
module OneOfEverything (
module OneOfEverything, module OneC, OrdClass(orda, ordb),
EqClass(..), EqTree(EqLeaf, EqBranch), FooDataC(..), FooDataB(..),
FooData, fixn
) where
import Prelude
import IO (putStr)
import System hiding (getArgs)
import Monad
bindwith ::
{- implicit forall -} (OrdClass a, OrdClass b) => a -> b -> b
g ::
{- implicit forall -}
(Num a, Eq b) =>
Foo a -> [b] -> (a, a, a) -> b
g x y z = head y
f _
x
1
1.93
'c'
"dog"
~y
(z@(Foo a b))
(c Bar d)
[1, 2]
(3, 4)
((n+42))
= y
expr a b c d
= ((((((((a + (: a b)) + (a : b)) + (((1 - 'c') - "abc") - 1.293))
+ ((\ x y z -> x) 42))
+ ((9 *)))
+ ((* 8)))
+ (case x of
Prelude.[]
| null x -> 99
| otherwise -> 98
| True -> 97
where
null x = False))
+ ([z | z <- c, isSpace z]))
+ (let y = foo
in
(((((((y + [1, 2, 3, 4]) + (4, 3, 2, 1))
+ (4 :: {- implicit forall -} (Num a) => a))
+ (if 42 == 42.0 then 1 else 4))
+ ([1 .. ]))
+ ([2, 4 .. ]))
+ ([3 .. 5]))
+ ([4, 8 .. 999]))
mat a b c d
| foof a b = d
| foof a c = d
| foof b c = d
where
foof a b = a == b
(~(a, b, c))
| nullity b = a
| nullity c = a
| otherwise = a
where
nullity = null
recb a = reca a
reca a = recb a
bindwith a b = b
singlebind x = x
fixr x y = x
fixl x y = x
fixn x y = x
infix 6 fixn
infixl 7 +#
infixr 8 fixr
type Pair a b = (a, b)
data FooData = forall. FooCon Int
data FooDataB = forall. FooConB Double
data (Eq a) => EqTree a =
forall. EqLeaf a | forall. EqBranch (EqLeaf a) (EqLeaf a)
class (Eq a) => EqClass a where {
eqc :: {- implicit forall -} a -> Char;
eqc x = '?'
}
class (Ord a) => OrdClass a where {
orda :: {- implicit forall -} a -> Char;
ordb :: {- implicit forall -} a -> Char;
ordc :: {- implicit forall -} a -> Char;
}
instance {- implicit forall -} (Eq a) => EqClass (EqTree a) where
[]
eqc x = 'a'
default (Rational, Integer)
read001.hs:5: Unknown module in export list: module `OneC'
read001.hs:5: Type constructor or class not in scope: `FooDataC'
......
==================== Parser ====================
module OneOfEverything (
module OneOfEverything, module OneC, OrdClass(orda, ordb),
EqClass(..), EqTree(EqLeaf, EqBranch), FooDataC(..), FooDataB(..),
FooData, fixn
) where
import Prelude
import IO (putStr)
import System hiding (getArgs)
import Monad
bindwith ::
{- implicit forall -} (OrdClass a, OrdClass b) => a -> b -> b
g ::
{- implicit forall -}
(Num a, Eq b) =>
Foo a -> [b] -> (a, a, a) -> b
g x y z = head y
f _
x
1
1.93
'c'
"dog"
~y
(z@(Foo a b))
(c Bar d)
[1, 2]
(3, 4)
((n+42))
= y
expr a b c d
= ((((((((a + (: a b)) + (a : b)) + (((1 - 'c') - "abc") - 1.293))
+ ((\ x y z -> x) 42))
+ ((9 *)))
+ ((* 8)))
+ (case x of
Prelude.[]
| null x -> 99
| otherwise -> 98
| True -> 97
where
null x = False))
+ ([z | z <- c, isSpace z]))
+ (let y = foo
in
(((((((y + [1, 2, 3, 4]) + (4, 3, 2, 1))
+ (4 :: {- implicit forall -} (Num a) => a))
+ (if 42 == 42.0 then 1 else 4))
+ ([1 .. ]))
+ ([2, 4 .. ]))
+ ([3 .. 5]))
+ ([4, 8 .. 999]))
mat a b c d
| foof a b = d
| foof a c = d
| foof b c = d
where
foof a b = a == b
(~(a, b, c))
| nullity b = a
| nullity c = a
| otherwise = a
where
nullity = null
recb a = reca a
reca a = recb a
bindwith a b = b
singlebind x = x
fixr x y = x
fixl x y = x
fixn x y = x
infix 6 fixn
infixl 7 +#
infixr 8 fixr
type Pair a b = {- implicit forall -} (a, b)
data FooData = forall. FooCon Int
data FooDataB = forall. FooConB Double
data (Eq a) => EqTree a =
forall. EqLeaf a | forall. EqBranch (EqLeaf a) (EqLeaf a)
class (Eq a) => EqClass a where {
eqc :: {- implicit forall -} a -> Char;
eqc x = '?'
}
class (Ord a) => OrdClass a where {
orda :: {- implicit forall -} a -> Char;
ordb :: {- implicit forall -} a -> Char;
ordc :: {- implicit forall -} a -> Char;
}
instance {- implicit forall -} (Eq a) => EqClass (EqTree a) where
[]
eqc x = 'a'
default (Rational, Integer)
==================== Parser ====================
module Read003 where
~(a, b, c)
| nullity b = a
| nullity c = a
| otherwise = a
where
nullity = null
read003.hs:4:
Occurs check: cannot construct the infinite type: t = (t, [a], t1)
Expected type: (t, [a], t1)
......
==================== Parser ====================
module Read003 where
~(a, b, c)
| nullity b = a
| nullity c = a
| otherwise = a
where
nullity = null
==================== Parser ====================
module ShouldFail where
f :: {- implicit forall -} Int -> IO Int
f x = do
(2 + 2) <- 2
return x
read007.hs:6:
`+' is not a data constructor
In the pattern: 2 + 2
......
==================== Parser ====================
module ShouldFail where
f :: {- implicit forall -} Int -> IO Int
f x = do
(2 + 2) <- 2
return x
==================== Parser ====================
module ShouldFail where
h x = x
foo = do let foo = True
read009.hs:5:
`do' statements must end in expression: do let foo = True
......
==================== Parser ====================
module ShouldFail where
h x = x
foo = do let foo = True
==================== Parser ====================
module ShouldFail where
import qualified List as L (intersperse)
y = intersperse
x = L.intersperse
read010.hs:8: Variable not in scope: `intersperse'
Compilation had errors
......
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