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

[project @ 1997-07-26 23:25:57 by sof]

parent cdde4b94
No related merge requests found
Showing
with 281 additions and 0 deletions
TOP = ../../..
include $(TOP)/mk/boilerplate.mk
HS_SRCS = $(wildcard *.hs)
SRC_RUNTEST_OPTS += -accept-output -o1 $*.stdout -o2 $*.stderr -x 1
HC_OPTS += -noC -dcore-lint
read002_RUNTEST_OPTS = -x 0
%.o : %.hs
%.o : %.hs
$(RUNTEST) $(HC) $(RUNTEST_OPTS) $(HC_OPTS) -c $< -o $@ -osuf $(subst .,,$(suffix $@))
all :: $(HS_OBJS)
read001_HC_OPTS = -noC -ddump-rdr
read002_HC_OPTS = -noC -ddump-rdr
read004_HC_OPTS = -noC -fno-implicit-prelude -ddump-rdr
include $(TOP)/mk/target.mk
interface OneA where
import OneB ( fB ) renaming ( fB to fBa )
type SynA = Float
data DataAA
data (Ord a) => DataAB a = ConAB1 a | ConAB2 deriving Text
class (Ord a) => ClassA a where
clsA :: a -> String
instance ClassA Int
fA :: a -> a
interface OneB where
fB :: a -> a
interface OneC where
fC :: a -> a
{-
From: Kevin Hammond <kh>
To: partain
Subject: Re: parsing problem w/ queens
Date: Wed, 9 Oct 91 17:31:46 BST
OK, I've fixed that little problem by disallowing,
-}
f x = x + if c then 1 else 2
f x = x + 1::Int
-- (the conditional/sig need to be parenthesised). If this is
-- problematic, let me know!
expr001.hs:10:
Value not in scope: `c'
Compilation had errors
--!!! this module supposedly includes one of each Haskell construct
-- HsImpExp stuff
module OneOfEverything (
fixn,
FooData,
FooDataB(..),
FooDataC( .. ),
EqTree(EqLeaf, EqBranch),
EqClass(..),
OrdClass(orda, ordb),
OneC.. ,
OneOfEverything..
) where
import OneA renaming ( fA to renamedA )
import OneB ( fB )
import OneC hiding ( fC )
import OneC hiding ( fC ) renaming ( fc to renamedC )
-- HsDecls stuff
infix 6 `fixn`
infixl 7 +#
infixr 8 `fixr`
fixn x y = x
fixl x y = x
fixr x y = 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 :: a -> Char
ordb :: a -> Char
ordc :: a -> Char
instance (Eq a) => EqClass (EqTree a) where
eqc x = 'a'
default (Integer, Rational)
-- HsBinds stuff
singlebind x = x
bindwith :: (OrdClass a, OrdClass b) => a -> b -> b
bindwith a b = b
reca a = recb a
recb a = reca a
(~(a,b,c)) | nullity b = a
| nullity c = a
| otherwise = a
where
nullity = null
-- HsMatches stuff
mat a b c d | foof a b = d
| foof a c = d
| foof b c = d
where
foof a b = a == b
-- HsExpr stuff
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
[] | 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 :: Num a => a)
+ (if 42 == 42.0 then 1 else 4)
+ [1..]
+ [2,4..]
+ [3..5]
+ [4,8..999]
-- HsPat stuff
f _ x 1 1.93 'c' "dog" ~y z@(Foo a b) (c `Bar` d) [1,2] (3,4) (n+42) = y
-- HsLit stuff -- done above
-- HsTypes stuff
g :: (Num a, Eq b) => Foo a -> [b] -> (a,a,a) -> b
g x y z = head y
read001.hs:13:9: parse error on input: "OneC.."
--!!! tests fixity reading and printing
module Reader where
infixl 1 `f`
infixr 2 \\\
infix 3 :==>
infix 4 `MkFoo`
data Foo = MkFoo Int | Float :==> Double
x `f` y = x
(\\\) :: (Eq a) => [a] -> [a] -> [a]
(\\\) xs ys = xs
================================================================================
Reader:
module Reader where
infixl 1 f
infixr 2 \\\
infix 3 :==>
infix 4 MkFoo
{- rec -}
\\\ ::
_forall_ [] {Eq a} => [a] -> [a] -> [a]
f x y = x
\\\ xs ys = xs
data Foo =
MkFoo Int | Float :==> Double
--!!! Irrefutable patterns + guards
module Read003 where
~(a,b,c) | nullity b = a
| nullity c = a
| otherwise = a
where
nullity = null
read003.hs:8: Cannot construct the infinite type (occur check)
`t{-aK8-}' = `(t{-aK8-}, t{-aKb-}, t{-aKe-})'
Expected: `(t{-aK8-}, [a{-aKm-}], [a{-aKo-}])'
Inferred: `t{-aK8-}'
In a pattern binding:
~(`a', `b', `c')
| [`nullity
b'] =
`a'
| [`nullity
c'] =
`a'
| [`PrelBase.otherwise'] =
`a'
where
`nullity'
= `PrelList.null'
Compilation had errors
--!!! string gaps
--!!!
module Main(main) where
-----------
main = putStr "\
\Some girls give me money\n\
\Some girls buy me clothes\n\
\..."
-----------
main2 = putStr "\
\ \
..."
-----------
main3 = putStr "\
\Some girls give me money\n\
-- and here is a comment
\Some girls buy me clothes\n\
\..."
-----------
main3 = putStr "\
{-
and here is a nested {- comment -}
-}
\Some girls give me money\n\
\Some girls buy me clothes\n\
\..."
read004.hs:19:1: Illegal character: `.' in a string gap
read004.hs:19:1: on input: "."
--!!! Empty comments terminating a file..
main = print "Hello" --
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