Skip to content
Snippets Groups Projects
Commit cedd20d4 authored by Simon Peyton Jones's avatar Simon Peyton Jones
Browse files

[project @ 1999-02-10 15:45:52 by simonpj]

Misc tests fixes, and activate the programs directory
parent 24bcd8b0
No related merge requests found
Showing
with 98 additions and 91 deletions
......@@ -13,11 +13,11 @@ SUBDIRS = \
rename \
simplCore \
stranal \
typecheck
typecheck \
programs
# printing \
# io \
# programs
include $(TOP)/mk/target.mk
......
TOP = .
include $(TOP)/mk/boilerplate.mk
NOT_THESE = Makefile ipoole_spec_class areid_pass
NOT_THESE = CVS mk Makefile \
NOT_THESE += hill_stk_oflow
# Correctly fails to terminate
NOT_THESE += ipoole_spec_class
# Dialogue style IO
# areid_pass
SUBDIRS = $(filter-out $(NOT_THESE), $(wildcard *))
......
......@@ -6,7 +6,8 @@
land_i, lnot_i, lor_i, lshift_i, rshift_i,
descr,
destr_update, indassoc, lowbound, tabulate, upbound, update, valassoc) where {
import Word2;
import Bits;
import Word;
import Complex; -- 1.3
import Array; -- 1.3
type Complex_type = Complex Double;
......@@ -19,23 +20,22 @@
force x = x; -- error "force not implemented";
iff b x y = if b then x else y;
iffrev y x b = if b then x else y;
seQ x y = seq_const y (x{-#STRICT-});
seq_const x y = x ;
seQ x y = x `seq` y;
pair [] = False;
pair x = True;
strcmp :: [Char] -> [Char] -> Bool;
strcmp x y = x == y;
entier x = fromIntegral (floor x);
land_i :: Int -> Int -> Int;
land_i x y = wordToInt (bitAnd (fromInt x) (fromInt y));
land_i x y = wordToInt (fromInt x .&. fromInt y);
lnot_i :: Int -> Int;
lnot_i x = wordToInt (bitCompl (fromInt x));
lnot_i x = wordToInt (complement (fromInt x));
lor_i :: Int -> Int -> Int;
lor_i x y = wordToInt (bitOr (fromInt x) (fromInt y));
lor_i x y = wordToInt (fromInt x .|. fromInt y);
lshift_i :: Int -> Int -> Int;
lshift_i x y = wordToInt (bitLsh (fromInt x) y);
lshift_i x y = wordToInt (fromInt x `shiftL` y);
rshift_i :: Int -> Int -> Int;
rshift_i x y = wordToInt (bitRsh (fromInt x) y);
rshift_i x y = wordToInt (fromInt x `shiftR` y);
write x = abortstr "write not implemented";
descr l u = (l,u);
destr_update ar i x = ar // [(i,x)];
......
......@@ -49,7 +49,7 @@ Likewise if you change the type of LinearCode to Int!
> getRepInterp (RepInterp a ) = a
> instance Functor Interpreter where
> map f (RepInterp intp )
> fmap f (RepInterp intp )
> = RepInterp (\s -> case intp s of
> g -> g >>= \q ->
> case q of
......@@ -81,4 +81,4 @@ Likewise if you change the type of LinearCode to Int!
> class Monad m => OutputMonad m where
> out :: String -> m ()
> instance OutputMonad IO where
> out s = catch (putStr s) (\_ -> fail $userError "Oh MY")
> out s = catch (putStr s) (\_ -> ioError $ userError "Oh MY")
......@@ -2,13 +2,12 @@
==================== Reader ====================
module Main where
{- rec -}
f x = x + (if c then 1 else 2)
f x = x + 1 :: Int
f x = x zp (if c then 1 else 2)
f x = x zp 1 :: Int
expr001.hs:10: Value not in scope: `c'
expr001.hs:10: Variable not in scope: `c'
Compilation had errors
==================== Reader ====================
module OneOfEverything (
fixn, FooData, FooDataB(..), FooDataC(..), EqTree(EqLeaf,
EqBranch), EqClass(..), OrdClass(orda,
ordb), module OneC, module OneOfEverything
fixn, FooData, FooDataB(..), FooDataC(..),
EqTree(EqLeaf, EqBranch), EqClass(..), OrdClass(orda, ordb),
module OneC, module OneOfEverything
) where
import Prelude
import IO (putStr)
......@@ -32,31 +32,32 @@ mat a b c d
| foof b c = d
where
{- rec -}
foof a b = a == b
foof a b = a zeze b
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
{- rec -}
null x = False))
+ ([z | z <- c, isSpace z]))
+ (let
{- rec -}
y = foo
in
(((((((y + [1, 2, 3, 4]) + (4, 3, 2, 1)) + (4 :: (Num a) => a))
+ (if 42 == 42.0 then 1 else 4))
+ ([1 .. ]))
+ ([2, 4 .. ]))
+ ([3 .. 5]))
+ ([4, 8 .. 999]))
= ((((((((a zp (ZC a b)) zp (a ZC b))
zp (((1 zm 'c') zm "abc") zm 1.293))
zp ((\ x y zz -> x) 42))
zp ((9 zt)))
zp ((zt 8)))
zp (case x of
Prelude.ZMZN
| null x -> 99
| otherwise -> 98
| True -> 97
where
{- rec -}
null x = False))
zp ([zz | zz <- c, isSpace zz]))
zp (let
{- rec -}
y = foo
in
(((((((y zp [1, 2, 3, 4]) zp (4, 3, 2, 1)) zp (4 :: (Num a) => a))
zp (if 42 zeze 42.0 then 1 else 4))
zp ([1 .. ]))
zp ([2, 4 .. ]))
zp ([3 .. 5]))
zp ([4, 8 .. 999]))
f _
x
1
......@@ -64,13 +65,13 @@ f _
'c'
"dog"
~y
(z@(Foo a b))
(zz@(Foo a b))
(c Bar d)
[1, 2]
(3, 4)
((n+42))
= y
g x y z = head y
g x y zz = head y
default (Integer, Rational)
instance (Eq a) => EqClass (EqTree a) where
[]
......@@ -87,36 +88,32 @@ data FooDataB = FooConB Double
data FooData = FooCon Int
type Pair a b = (a, b)
infixr 8 fixr
infixl 7 +#
infixl 7 zpzh
infix 6 fixn
read001.hs:20: Warning: Unused fixity declaration for `+#'
read001.hs:5: Type constructor or class not in scope: `FooDataC'
read001.hs:5: Unknown module in export list: module `OneC'
read001.hs:40: Type constructor or class not in scope: `EqLeaf'
read001.hs:40: Type constructor or class not in scope: `EqLeaf'
read001.hs:80: Value not in scope: `isSpace'
read001.hs:87: Value not in scope: `x'
read001.hs:87: Value not in scope: `x'
read001.hs:95: Value not in scope: `foo'
read001.hs:80: Variable not in scope: `isSpace'
read001.hs:87: Variable not in scope: `x'
read001.hs:87: Variable not in scope: `x'
read001.hs:95: Variable not in scope: `foo'
read001.hs:107: Data constructor not in scope: `Foo'
read001.hs:107: Data constructor not in scope: `Bar'
read001.hs:112: Type constructor or class not in scope: `Foo'
read001.hs:112: Type constructor or class not in scope: `Foo'
Compilation had errors
......@@ -11,14 +11,12 @@ module Read003 where
nullity = null
read003.hs:4:
Occurs check: cannot construct the infinite type:
t = (t, [a], _116)
Expected type: (t, [a], _116)
Occurs check: cannot construct the infinite type: t = (t, [a], t1)
Expected type: (t, [a], t1)
Inferred type: t
In the right-hand side of a pattern binding: a
Compilation had errors
read006.hs:5:7: pattern syntax used in expression on input: "_"
read006.hs:8:12: parse error on input: "@"
ghc: module version changed to 1; reason: no old .hi file
__export Rn017 a b c Wibble{MkWibble} Wobble;
__export Test f FOO{op} Foo{MkFoo};
__export Rn017 Wibble{MkWibble} Wobble a b c;
__export Test FOO{op} Foo{MkFoo} f;
rnfail001.hs:3: Conflicting definitions for `x' in pattern
rnfail001.hs:3:
Conflicting definitions for `x'
in a pattern
Compilation had errors
......
rnfail002.hs:4:
Multiple declarations of `y'
defined at rnfail002.hs:5
......
rnfail003.hs:2:
Multiple declarations of `f'
defined at rnfail003.hs:2
......
rnfail004.hs:6: Conflicting definitions for `a' in binding group
rnfail004.hs:7: Conflicting definitions for `b' in binding group
rnfail004.hs:6:
Conflicting definitions for `a'
in a binding group
rnfail004.hs:7:
Conflicting definitions for `b'
in a binding group
Compilation had errors
......
rnfail007.hs:3:
Module `Main' must include a definition for `Main.main'
rnfail007.hs:3: Module `Main' must include a definition for `main'
Compilation had errors
......
rnfail008.hs:18: Value not in scope: `op3'
rnfail008.hs:18: Variable not in scope: `op3'
Compilation had errors
......
rnfail009.hs:1:
Multiple declarations of `A'
defined at rnfail009.hs:3
......
rnfail010.hs:2:
Multiple declarations of `f'
defined at rnfail010.hs:2
......
rnfail011.hs:2:
Multiple declarations of `A'
defined at rnfail011.hs:2
......
rnfail012.hs:2:
Multiple declarations of `A'
defined at rnfail012.hs:3
......
rnfail013.hs:3:
Multiple declarations of `MkT'
defined at rnfail013.hs:7
......
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