GHC 3.02, outa-tha-box.  In the program given below, compiled by:

% ghc  -fglasgow-exts  -c tt.hs -o tt.o

I get the complaint:

tt.hs:22:
    No instance for `Conditional Bool [Bool]'
        (arising from use of `ifc' at tt.hs:22)

I say there is an instance, given by the last instance decl in the
file.  In fact, if I try to add the following, unconditional instance
decl:

instance Conditional Bool [Bool] where
    ifc c x y = map (uncurry (ifb c)) (dist2 x y)

then it gives me the additional complaint:

tt.hs:1:
    Duplicate or overlapping instance declarations
        for `Conditional Bool [Bool]' at tt.hs:23 and tt.hs:20

Oi!  There's either no instances, or there's too many -- what's it going
to be! ;-)

--Jeff

------------------

module Buggo where

class Boolean b where
    ifb :: b -> b -> b -> b

instance Boolean Bool where
    ifb x y z = if x then y else z

class Conditional c a where
    ifc :: c -> a -> a -> a
    ifc_bogus :: c -> a

class Dist2 f where
    dist2 :: f a -> f b -> f (a, b)

instance Dist2 [] where
    dist2 = zip

instance (Boolean b, Dist2 f, Functor f) => Conditional b (f b) where
    ifc c x y = map (uncurry (ifb c)) (dist2 x y)

t x y z = ifc (x :: Bool) (y :: [Bool]) z

Reply via email to