summaryrefslogtreecommitdiff
path: root/ghc/compiler/tests/reader/read001.hs
blob: 4a97768a78d9e4712169a40cc994811d5ec97034 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
-- 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