[project @ 1997-07-27 00:11:16 by sof]
[ghc-hetmet.git] / ghc / tests / codeGen / cg013.hs
1 {-
2 From: Kevin Hammond <kh>
3 To: partain
4 Subject: Nasty Overloading
5 Date: Wed, 23 Oct 91 16:19:46 BST
6 -}
7 module Main where
8
9 class Foo a where
10         o1 :: a -> a -> Bool
11         o2 :: a -> Int
12
13 --      o2 :: Int
14     -- Lennart: The type of method o2 does not contain the variable a
15     -- (and it must according to line 1 page 29 of the manual).
16
17 class Foo tyvar => Bar tyvar where
18         o3 :: a -> tyvar -> tyvar
19
20 -- class (Eq a, Foo a) => Baz a where
21 class (Ord a, Foo a) => Baz a where
22         o4 :: a -> a -> (String,String,String,a)
23
24 instance (Ord a, Foo a) =>  Foo [a] where
25         o2 x = 100
26         o1 a b = a < b || o1 (head a) (head b)
27
28 -- instance Bar [a] where
29 instance (Ord a, Foo a) => Bar [a] where
30         o3 x l = []
31     --
32     -- Lennart: I guess the instance declaration 
33     --  instance Bar [w] where
34     --          o3 x l = []
35     -- is wrong because to be a Bar you have to be a Foo.  For [w] to
36     -- be a Foo, w has to be Ord and Foo.  But w is not Ord or Foo in
37     -- this instance declaration so it must be wrong.  (Page 31, line
38     -- 7: The context c' must imply ...)
39
40 instance Baz a => Baz [a] where
41         o4 [] [] = ("Nil", "Nil", "Nil", [])
42         o4 l1 l2 = 
43                 (if o1 l1 l2 then "Y" else "N",
44                  if l1 == l2 then "Y" else "N",
45 --               if o4 (head l1) (head l2) then "Y" else "N",
46                  case o4 (head l1) (head l2) of
47                         (_,_,_,l3) -> if (o1 (head l1) l3) then "Y" else "N",
48                  l1 ++ l2 )
49
50 instance Foo Int where
51         o2 x = x
52         o1 i j = i == j
53
54 instance Bar Int where
55         o3 _ j = j + 1
56
57 instance Baz Int where
58 --      o4 i j = i > j
59         o4 i j = (if i>j then "Y" else "Z", "p", "q", i+j)
60 --simpl:o4 i j = ("Z", "p", "q", i+j)
61
62 {- also works w/ glhc! -}
63
64 main =  if o4 [1,2,3] [1,3,2::Int] /= ("Y","N","Y",[1,2,3,1,3,2]) then
65                 (print "43\n") 
66         else    (print "144\n")
67
68 {- works: glhc
69 main =  case o4 [1,2,3] [1,3,2::Int] of
70                 (s1,s2,s3,x) -> print s1
71
72 main =  case o4 ([]::[Int]) ([]::[Int]) of
73                 (s1,s2,s3,x) -> print s1
74 -}
75
76 {- simple main: breaks nhc, works w/ glhc 
77 main = case o4 (3::Int) (4::Int) of (s1,s2,s3,x) -> print s1
78 -}