Skip to content
Snippets Groups Projects
Commit b799e5ca authored by sven.panne@aedion.de's avatar sven.panne@aedion.de
Browse files

[project @ 2000-07-03 21:04:44 by panne]

Removed foralls in expected output
parent d2e67f30
No related merge requests found
......@@ -9,12 +9,8 @@ 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
bindwith :: (OrdClass a, OrdClass b) => a -> b -> b
g :: (Num a, Eq b) => Foo a -> [b] -> (a, a, a) -> b
g x y z = head y
f _
x
......@@ -44,8 +40,7 @@ expr a b c d
+ ([z | z <- c, isSpace z]))
+ (let y = foo
in
(((((((y + [1, 2, 3, 4]) + (4, 3, 2, 1))
+ (4 :: {- implicit forall -} (Num a) => a))
(((((((y + [1, 2, 3, 4]) + (4, 3, 2, 1)) + (4 :: (Num a) => a))
+ (if 42 == 42.0 then 1 else 4))
+ ([1 .. ]))
+ ([2, 4 .. ]))
......@@ -73,21 +68,14 @@ 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 = '?'
}
type Pair a b = (a, b)
data FooData = FooCon Int
data FooDataB = FooConB Double
data (Eq a) => EqTree a = EqLeaf a | EqBranch (EqLeaf a) (EqLeaf a)
class (Eq a) => EqClass a where { eqc :: 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
orda :: a -> Char; ordb :: a -> Char; ordc :: a -> Char; }
instance (Eq a) => {EqClass (EqTree a)} where
[]
eqc x = 'a'
default (Rational, Integer)
......
==================== Parser ====================
module ShouldFail where
f :: {- implicit forall -} Int -> IO Int
f :: Int -> IO Int
f x = do
(2 + 2) <- 2
return x
......
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