defining (-> Bool) as a set

Jorge Adriano jadrian@mat.uc.pt
Tue, 23 Apr 2002 00:53:52 +0100


On Monday 22 April 2002 23:31, Hal Daume III wrote:
> I'd like to be able to define something like
>
> instance Eq a =3D> Coll (-> Bool) a where
>   empty    =3D \_ -> False
>   single x =3D \y -> if x =3D=3D y then True else False
>   union a b =3D \x -> a x || b x
>   insert s x =3D \y -> x =3D=3D y || s y
>
> and the like
>
> However, this seems to be impossible.  Is this the type lambda restrict=
ion
> that's been discussed recently on the mailing list?
>
>  - Hal

Hi Hal,=20
I'd do it like this, hope it helps.
----------------------------------
module Test where

newtype  BinClass a =3D BC (a->Bool)


class  Coll c a where
  empty  :: c a
  single :: a->c a
  union  :: c a->c a->c a
  insert :: c a->a->c a

instance Eq a =3D> Coll BinClass a where
    empty    =3D BC(\_->True)
    single x =3D BC(\y -> if x =3D=3D y then True else False)
    union  (BC a) (BC b) =3D BC(\x -> a x || b x)
    insert (BC s) x      =3D BC(\y -> x =3D=3D y || s y)