Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-13 Thread Alberto G. Corona
even at the level of expressions you can be sure that inequalities hold. So
you can create an instance of Ord. for example:
(Sum x z) <  y | x== y && z>0 = True
  | 

here x and y can be expressions and == can have its own rules

with this you can compute symbolically, because you don´t need to reduce the
expression to a numerical value. It´s a matter of finding rules.

2009/3/13 Alberto G. Corona 

> >(<) :: (Ord a) => a -> a -> Bool
>
> what´s the problem?
>
> make your Expr an instance of Ord.
>
> By the way
>
> > instance Num Expr where
> > fromInterger = Const
> > (+) = Plus
> > (*) = Times
>
> does not work. you have not defined (+) and (*) for Const Integer.
>
> (+) (Const a) (Const b)= Const (a+b)
>
> With this you have an evaluator.
>
> In the same way:
>
> (Const a) < (Const b) = Const (a < b)
>
>
>
>
> 2009/3/12 Adam Vogt 
>
> This seems to be in ghc for those reasons:
>> http://www.haskell.org/haskellwiki/Quasiquotation
>>
>> * On Monday, March 02 2009, Andrew Hunter 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


Fwd: [Haskell-cafe] DSLs with {in,}equalities

2009-03-13 Thread Alberto G. Corona
-- Forwarded message --
From: Alberto G. Corona 
Date: 2009/3/13
Subject: Re: [Haskell-cafe] DSLs with {in,}equalities
To: Adam Vogt 


You need an expression evaluator:

with
(+) (Const a) (Const b)= Const (a+b)
(*) (Const a) (Const b)= Const (a*b)

eval :: Exp -> Integer

eval (Const i)= i
eval ( Plus e1 e2)= eval e1 + eval e2 ..
eval( Mul 

and

instance Ord Expr where
 (<) expr1 expr2 = eval expr1 < eval expr2


by the way:

simplify expr= Const (eval expr)



..

2009/3/13 Alberto G. Corona 

> Sorry(Const a) < (Const b) = a < b
>
> also
>
> (*) (Const a) (Const b)= Const (a*b)
>
>
> 2009/3/13 Alberto G. Corona 
>
> >(<) :: (Ord a) => a -> a -> Bool
>>
>> what´s the problem?
>>
>> make your Expr an instance of Ord.
>>
>> By the way
>>
>> > instance Num Expr where
>> > fromInterger = Const
>> > (+) = Plus
>> > (*) = Times
>>
>> does not work. you have not defined (+) and (*) for Const Integer.
>>
>> (+) (Const a) (Const b)= Const (a+b)
>>
>> With this you have an evaluator.
>>
>> In the same way:
>>
>> (Const a) < (Const b) = Const (a < b)
>>
>>
>>
>>
>> 2009/3/12 Adam Vogt 
>>
>> This seems to be in ghc for those reasons:
>>> http://www.haskell.org/haskellwiki/Quasiquotation
>>>
>>> * On Monday, March 02 2009, Andrew Hunter 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


Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-12 Thread Adam Vogt
This seems to be in ghc for those reasons:
http://www.haskell.org/haskellwiki/Quasiquotation

* On Monday, March 02 2009, Andrew Hunter 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


Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-03 Thread Henning Thielemann


On Tue, 3 Mar 2009, Brandon S. Allbery KF8NH wrote:


On 2009 Mar 2, at 23:13, Andrew Hunter wrote:

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.


I guess aesthetics differ; I'd use e.g. $<$, where the $ (to me, from other 
contexts) means "symbolic".


... like escaping '<' in LaTeX. Funny!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-03 Thread Andrew Wagner
Err, I was actually talking about the thread subject, where he actually has
the word "{in,}equalities", short for "inequalities and equalities" (more or
less). AFAIK, that's unix notation.

On Tue, Mar 3, 2009 at 12:36 PM, Brandon S. Allbery KF8NH <
allb...@ece.cmu.edu> wrote:

> On 2009 Mar 3, at 12:25, Andrew Wagner wrote:
>
> Not to hijack the thread, but I thought I was the only one that used unix
> notation for statements like {in,}equalities. I like it!
>
>
> It's actually closer to Windows notation with the bracket on both sides
> (and I actually considered making it %<% but to me that looks more
> cluttered, plus the S-curve in $ can be a mnemonic for "symbolic" for those
> who don't live their lives on Unix).
>
> --
> brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
> system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
> electrical and computer engineering, carnegie mellon universityKF8NH
>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-03 Thread Brandon S. Allbery KF8NH

On 2009 Mar 3, at 12:25, Andrew Wagner wrote:
Not to hijack the thread, but I thought I was the only one that used  
unix notation for statements like {in,}equalities. I like it!


It's actually closer to Windows notation with the bracket on both  
sides (and I actually considered making it %<% but to me that looks  
more cluttered, plus the S-curve in $ can be a mnemonic for "symbolic"  
for those who don't live their lives on Unix).


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-03 Thread Andrew Wagner
Not to hijack the thread, but I thought I was the only one that used unix
notation for statements like {in,}equalities. I like it!

On Mon, Mar 2, 2009 at 11:13 PM, Andrew Hunter  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


Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-03 Thread Brandon S. Allbery KF8NH

On 2009 Mar 2, at 23:13, Andrew Hunter wrote:
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.


I guess aesthetics differ; I'd use e.g. $<$, where the $ (to me, from  
other contexts) means "symbolic".


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH




PGP.sig
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-03 Thread John A. De Goes


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   
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


Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-02 Thread Lennart Augustsson
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  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


Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-02 Thread Andrew Hunter
On Tue, Mar 03, 2009 at 01:53:44AM -0500, wren ng thornton wrote:
> If you're just wanting to build Exprs, then the canonical solution is to 
> use ':' as in (:>), (:>=), (:==), (:/=), (:<=), (:<). The colon is 
> considered a "capital symbol" and so it's what you use as the first letter 
> of symbolic constructors. For symmetry, many folks will ad another colon at 
> the end as well.
>
>   > data Expr = Const Integer | Expr :+: Expr | Expr :*: Expr | Expr :>: 
> Expr | ...
>

Alas, in several instances (too long to give here) it's impractical to
write the DSL just as constructors--several of the operators have to
do nontrivial computation.  (Plus, I'd still call the :*: solution
ugly, personally.) Is it possible to do better?

AHH

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


Re: [Haskell-cafe] DSLs with {in,}equalities

2009-03-02 Thread wren ng thornton

Andrew Hunter 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

>

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?



If you're just wanting to build Exprs, then the canonical solution is to 
use ':' as in (:>), (:>=), (:==), (:/=), (:<=), (:<). The colon is 
considered a "capital symbol" and so it's what you use as the first 
letter of symbolic constructors. For symmetry, many folks will ad 
another colon at the end as well.


  > data Expr = Const Integer | Expr :+: Expr | Expr :*: Expr | Expr 
:>: Expr | ...


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] DSLs with {in,}equalities

2009-03-02 Thread Andrew Hunter
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