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.
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:
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)
20 instance Eq_
Int where
23 instance (Eq_ a
) => Eq_
[a
] where
29 else (&&) (eq
(hd xs
) (hd ys
)) (eq
(tl xs
) (tl ys
))
31 class (Eq_ a
) => Ord_ a
where
34 instance Ord_
Int where
38 = \ a bs
-> if gt
(hd bs
) a
40 else if eq a
(hd bs
) then True else search a
(tl bs
)
49 ordIntGt
:: Int -> Int -> Bool
52 eqIntEq
:: Int -> Int -> Bool
60 ===============================================
61 Main.Eq__INST_PreludeBuiltin.Int =
63 AbsBinds [] [] [(eq, eq)]
65 {-# LINE 2 "test3.hs" -}
67 eq
:: PreludeBuiltin
.Int -> PreludeBuiltin
.Int -> PreludeCore
.Bool
71 Main
.Eq__INST_PreludeBuiltin
.List
=
76 _dict136
= {-singleDict-} _dict138
78 _dict129
= {-singleDict-} _dict136
79 AbsBinds
[] [] [(eq
, eq
)]
83 Main
.Eq__INST_PreludeBuiltin
.List
84 [t135
] [{-singleDict-} _dict136
]
86 {-# LINE 5 "test3.hs" -}
88 eq
:: [t135
] -> [t135
] -> PreludeCore
.Bool
91 if (Main
.null t135
) xs
then
95 if (Main
.null t135
) ys
then
102 ((Main
.Eq_
.eq t135 _dict129
)
113 (Main
.Eq_
.eq
[t135
] _dict133
)
119 in ({-dict-} [] [eq
])
120 Main
.Ord__INST_PreludeBuiltin
.Int =
123 _dict142
= Main
.Eq__INST_PreludeBuiltin
.Int [] []
124 AbsBinds
[] [] [(gt
, gt
)]
126 {-# LINE 16 "test3.hs" -}
128 gt
:: PreludeBuiltin
.Int -> PreludeBuiltin
.Int -> PreludeCore
.Bool
130 in ({-dict-} [_dict142
] [gt
])
132 Main
.Eq_
.eq
= /\ a
-> \{-classdict-} [] [eq
] -> eq
134 Main
.Ord_
.gt
= /\ a
-> \{-classdict-} [_dict56
] [gt
] -> gt
136 Main
.Ord__TO_Main
.Eq_
= /\ a
-> \{-classdict-} [_dict58
] [gt
] -> ???_dict58???
138 AbsBinds
[t60
] [] [(hd
, Main
.hd
)]
144 hd
(a PreludeBuiltin
.: as)
147 AbsBinds
[t68
] [] [(tl
, Main
.tl
)]
154 tl
(a PreludeBuiltin
.: as)
158 AbsBinds
[t91
] [_dict85
, _dict88
] [(search
, Main
.search
)]
160 {-# LINE 19 "test3.hs" -}
163 search
:: t91
-> [t91
] -> PreludeCore
.Bool
168 if (Main
.Ord_
.gt t91 _dict85
) ((Main
.hd t91
) bs
) a
then
172 if (Main
.Eq_
.eq t91 _dict88
) a
((Main
.hd t91
) bs
) then
176 search a
((Main
.tl t91
) bs
)
177 AbsBinds
[] [] [(and, Main
.and)]
179 and :: PreludeCore
.Bool -> PreludeCore
.Bool -> PreludeCore
.Bool
180 and PreludeCore
.True PreludeCore
.True
182 AbsBinds
[] [] [(ordIntGt
, Main
.ordIntGt
)]
184 _dict97
= PreludeCore
.Num_INST_PreludeBuiltin
.Int [] []
186 _dict98
= PreludeCore
.Eq_INST_PreludeBuiltin
.Int [] []
188 _dict100
= PreludeCore
.Num_INST_PreludeBuiltin
.Int [] []
190 _dict101
= PreludeCore
.Eq_INST_PreludeBuiltin
.Int [] []
195 ordIntGt
:: PreludeBuiltin
.Int -> PreludeBuiltin
.Int -> PreludeCore
.Bool
197 2 3 = PreludeCore
.True
198 AbsBinds
[] [] [(eqIntEq
, Main
.eqIntEq
)]
200 _dict105
= PreludeCore
.Num_INST_PreludeBuiltin
.Int [] []
202 _dict106
= PreludeCore
.Eq_INST_PreludeBuiltin
.Int [] []
204 _dict108
= PreludeCore
.Num_INST_PreludeBuiltin
.Int [] []
206 _dict109
= PreludeCore
.Eq_INST_PreludeBuiltin
.Int [] []
209 eqIntEq
:: PreludeBuiltin
.Int -> PreludeBuiltin
.Int -> PreludeCore
.Bool
211 2 3 = PreludeCore
.True
214 AbsBinds
[t112
] [] [(null, Main
.null)]
217 null :: [t112
] -> PreludeCore
.Bool
218 null [] = PreludeCore
.True