184a4e23bf32464cb2d66f4a13dbe83a91180c45
[ghc-hetmet.git] / ghc / tests / typecheck / should_fail / tcfail043.hs
1 -- The translation of this program should assign only one dictionary to
2 -- the function search (an Ord dictionary). Instead, it assigns two.
3 -- The output produced currently displays this.
4
5 -- 10/12/92:  This program is actually erroneous.  The pattern-binding for
6 -- search falls under the monomorphism restriction, and there is no
7 -- call to search which might fix its type.  So there should be a complaint.
8 -- But the actual error message is horrible:
9 -- 
10 -- "bug001.hs", line 26: Ambiguous overloading:
11 --     class "Ord_", type "a" (at a use of an overloaded identifier: gt)
12 --     class "Eq_", type "a" (at a use of an overloaded identifier: eq)
13
14
15 module TcFail where
16
17 class Eq_ a where
18  eq :: a -> a -> Bool
19
20 instance Eq_ Int where
21  eq = eqIntEq
22
23 instance (Eq_ a) => Eq_ [a] where
24  eq = \ xs ys -> 
25      if (null xs) 
26         then (null ys)
27         else if (null ys) 
28                 then False
29                 else (&&) (eq (hd xs) (hd ys)) (eq (tl xs) (tl ys))
30
31 class (Eq_ a) => Ord_ a where
32  gt :: a -> a -> Bool
33
34 instance Ord_ Int where
35  gt = ordIntGt
36
37 search 
38  = \ a bs -> if gt (hd bs) a
39                 then False 
40                 else if eq a (hd bs) then True else search a (tl bs)
41
42
43 hd :: [a] -> a
44 hd (a:as) = a
45
46 tl :: [a] -> [a]
47 tl (a:as) = as
48
49 ordIntGt :: Int -> Int -> Bool
50 ordIntGt 2 3 = True
51
52 eqIntEq :: Int -> Int -> Bool
53 eqIntEq  2 3 = True
54
55
56
57
58 {-
59
60 ===============================================
61 Main.Eq__INST_PreludeBuiltin.Int =
62     let
63       AbsBinds [] [] [(eq, eq)]
64           {- nonrec -}
65           {-# LINE 2 "test3.hs" -}
66
67           eq :: PreludeBuiltin.Int -> PreludeBuiltin.Int -> PreludeCore.Bool
68           eq = Main.eqIntEq
69     in ({-dict-} [] [eq])
70
71 Main.Eq__INST_PreludeBuiltin.List =
72     /\ t135 ->
73         \{-dict-} _dict138 ->
74             let
75               {- nonrec -}
76               _dict136 = {-singleDict-} _dict138
77               {- nonrec -}
78               _dict129 = {-singleDict-} _dict136
79               AbsBinds [] [] [(eq, eq)]
80                   {- nonrec -}
81
82                   _dict133 =
83                       Main.Eq__INST_PreludeBuiltin.List
84                           [t135] [{-singleDict-} _dict136]
85                   {- nonrec -}
86                   {-# LINE 5 "test3.hs" -}
87
88                   eq :: [t135] -> [t135] -> PreludeCore.Bool
89                   eq = \ xs ys -> 
90
91 if (Main.null t135) xs then
92                                       (Main.null t135) ys
93                                   else
94
95                                       if (Main.null t135) ys then
96                                           PreludeCore.False
97                                       else
98
99                                           Main.and
100
101
102                                               ((Main.Eq_.eq t135 _dict129)
103
104
105                                                    ((Main.hd t135) xs)
106                                                    ((Main.hd t135) ys))
107                                               
108
109
110
111
112
113 (Main.Eq_.eq [t135] _dict133)
114
115
116
117                                                    ((Main.tl t135) xs)
118                                                    ((Main.tl t135) ys))
119             in ({-dict-} [] [eq])
120 Main.Ord__INST_PreludeBuiltin.Int =
121     let
122       {- nonrec -}
123       _dict142 = Main.Eq__INST_PreludeBuiltin.Int [] []
124       AbsBinds [] [] [(gt, gt)]
125           {- nonrec -}
126           {-# LINE 16 "test3.hs" -}
127
128           gt :: PreludeBuiltin.Int -> PreludeBuiltin.Int -> PreludeCore.Bool
129           gt = Main.ordIntGt
130     in ({-dict-} [_dict142] [gt])
131
132 Main.Eq_.eq = /\ a -> \{-classdict-} [] [eq] -> eq
133
134 Main.Ord_.gt = /\ a -> \{-classdict-} [_dict56] [gt] -> gt
135
136 Main.Ord__TO_Main.Eq_ = /\ a -> \{-classdict-} [_dict58] [gt] -> ???_dict58???
137
138 AbsBinds [t60] [] [(hd, Main.hd)]
139     {- nonrec -}
140
141
142
143     hd :: [t60] -> t60
144     hd (a PreludeBuiltin.: as)
145                = a
146
147 AbsBinds [t68] [] [(tl, Main.tl)]
148     {- nonrec -}
149
150
151
152
153     tl :: [t68] -> [t68]
154     tl (a PreludeBuiltin.: as)
155                = as
156
157
158 AbsBinds [t91] [_dict85, _dict88] [(search, Main.search)]
159     {- rec -}
160     {-# LINE 19 "test3.hs" -}
161
162
163     search :: t91 -> [t91] -> PreludeCore.Bool
164     search
165         = \ a bs -> 
166
167
168 if (Main.Ord_.gt t91 _dict85) ((Main.hd t91) bs) a then
169                         PreludeCore.False
170                     else
171
172                         if (Main.Eq_.eq t91 _dict88) a ((Main.hd t91) bs) then
173                             PreludeCore.True
174                         else
175
176                             search a ((Main.tl t91) bs)
177 AbsBinds [] [] [(and, Main.and)]
178     {- nonrec -}
179     and :: PreludeCore.Bool -> PreludeCore.Bool -> PreludeCore.Bool
180     and PreludeCore.True PreludeCore.True
181                 = PreludeCore.True
182 AbsBinds [] [] [(ordIntGt, Main.ordIntGt)]
183     {- nonrec -}
184     _dict97 = PreludeCore.Num_INST_PreludeBuiltin.Int [] []
185     {- nonrec -}
186     _dict98 = PreludeCore.Eq_INST_PreludeBuiltin.Int [] []
187     {- nonrec -}
188     _dict100 = PreludeCore.Num_INST_PreludeBuiltin.Int [] []
189     {- nonrec -}
190     _dict101 = PreludeCore.Eq_INST_PreludeBuiltin.Int [] []
191     {- nonrec -}
192
193
194
195     ordIntGt :: PreludeBuiltin.Int -> PreludeBuiltin.Int -> PreludeCore.Bool
196     ordIntGt
197         2 3 = PreludeCore.True
198 AbsBinds [] [] [(eqIntEq, Main.eqIntEq)]
199     {- nonrec -}
200     _dict105 = PreludeCore.Num_INST_PreludeBuiltin.Int [] []
201     {- nonrec -}
202     _dict106 = PreludeCore.Eq_INST_PreludeBuiltin.Int [] []
203     {- nonrec -}
204     _dict108 = PreludeCore.Num_INST_PreludeBuiltin.Int [] []
205     {- nonrec -}
206     _dict109 = PreludeCore.Eq_INST_PreludeBuiltin.Int [] []
207     {- nonrec -}
208
209     eqIntEq :: PreludeBuiltin.Int -> PreludeBuiltin.Int -> PreludeCore.Bool
210     eqIntEq
211         2 3 = PreludeCore.True
212
213
214 AbsBinds [t112] [] [(null, Main.null)]
215     {- nonrec -}
216
217     null :: [t112] -> PreludeCore.Bool
218     null [] = PreludeCore.True
219 -}