On Sat, Oct 09, 1999 at 04:52:20PM +0100, [EMAIL PROTECTED] wrote:
> I'd include composition, function products (as in Joe English's
> message) and operations on boolean predicates:
>> (f &&& g) x = f x && g x
>> (f ||| g) x = f x || g x
>> notF f x = not (f x)

One way to get around this would be to make a class Boolean (or, better
yet, Lattice) with not too many constraints and then have something on
the order of

module Lattice where
-- it's important that there isn't an Eq a => Lattice a constraint
-- because functions aren't of observable type; unless you want to
-- define functions as a trivial instance of Eq, like I had to for
-- arithmetic operations
        class Lattice a where
                (&&&), (|||)    :: a -> a -> a

        instance Lattice Bool where
                (&&&)   = (&&)
                (|||)   = (||)

        instance Lattice b => Lattice (a->b) where
                f &&& g = \x -> (f x) &&& (g x)
                f ||| g = \x -> (f x) ||| (g x)

-- the end of the code

and this would allow things like
        let     f True  = False ;
                f False = True ;
                g _             = False
        in
                (f ||| g) False

and

        let     f True  = False ;
                f False = True ;
                g _             = False
        in
                (f &&& g) True

to be interpreted naturally. There is no class corresponding to && and ||
in the Prelude, which is why I had to do it this way.


Bill



Reply via email to