Workarounds for the lack of linguistic overloading. :-)

Regards,

John A. De Goes
N-BRAIN, Inc.
The Evolution of Collaboration

http://www.n-brain.net    |    877-376-2724 x 101

On Mar 3, 2009, at 12:52 AM, Lennart Augustsson wrote:

I often hide the Prelude and import my own Prelude which reexports the
old Prelude, but with these changes.
It's still not ideal, by far.

 -- Lennart

class Boolean b where
   false, true :: b
   (&&), (||) :: b -> b -> b
   not :: b -> b

instance Boolean Bool where
   false = False
   true = True
   (&&) = (P.&&)
   (||) = (P.||)
   not = P.not

class (Boolean b) => Eq a b where
   (==), (/=) :: a -> a -> b
   x /= y  =  not (x == y)

instance (P.Eq a) => Eq a Bool where
   (==) = (P.==)
   (/=) = (P./=)

class (Eq a b) => Ord a b where
   (<), (<=), (>), (>=) :: a -> a -> b

instance (P.Ord a) => Ord a Bool where
   (<)  = (P.<)
   (<=) = (P.<=)
   (>)  = (P.>)
   (>=) = (P.>=)

class (Boolean b) => Conditional a b where
   (?) :: b -> (a, a) -> a

instance Conditional a Bool where
   c ? (t, e) = if c then t else e


On Tue, Mar 3, 2009 at 4:13 AM, Andrew Hunter <ahun...@cs.hmc.edu> wrote:
Several times now I've had to define an EDSL for working with
(vaguely) numeric expressions.  For stuff like 2*X+Y, this is easy,
looking pretty much like:

data Expr = Const Integer | Plus Expr Expr | Times Expr Expr

instance Num Expr where
fromInterger = Const
(+) = Plus
(*) = Times

&c.  This lets me get a perfectly nice AST, which is what I want.
When I want to be able to express and work with inequalities and
equalities, this breaks.  Suppose I want to write 2*X + Y < 3.  I
either have to:

a) Hide Prelude.(<) and define a simple < that builds the AST term I want.
b) Come up with a new symbol for it that doesn't look totally awful.

Neither of these work decently well.  Hiding Eq and Ord operators,
which is what I effectively have to do for a), is pretty much a
nonstarter--we'll have to use them too much for that to be practical.

On the other hand, b) works...but is about as ugly as it gets.  We
have lots and lots of symbols that are already taken for important
purposes that are syntactically "near" <,<=,==, and the like: << and
and >>= for monads, >>> for arrows, etc.  There...are not good
choices that I know of for the symbols that don't defeat the purpose
of making a nice clean EDSL for expressions; I might as well use 3*X +
Y `lessthan` 3, which is just not cool.

Does anyone know of a good solution, here?  Are there good
substitutions for all the six operators that are important
(<,>,>=,<=,==,/=), that are close enough to be pretty-looking but not
used for other important modules?

Better yet, though a little harder, is there a nice type trick I'm not
thinking of?  This works for Num methods but not for Ord methods
because:

(+) :: (Num a) => a -> a -> a
(<) :: (Ord a) => a -> a -> Bool

i.e. the return type of comparisons is totally fixed. I don't suppose there's a good way to...well, I don't know what the *right* answer is,
but maybe define a new typeclass with a more flexible type for < that
lets both standard types return Bool and my expressions return Expr?
Any good solution would be appreciated.

Thanks,
AHH
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to