[Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Radek Micek
Hello.

I have two types for expression:

data Expr = Add Expr Expr | Mul Expr Expr | Const Int

data AExpr = AAdd AExpr AExpr | AConst Int

The first one supports addition and multiplication and the second
only addition.

I can write a function to simplify the first expression:

simplify :: Expr - Expr
simplify = {- replaces:
a*1 and 1*a by a,
a+0 and 0+a by a -}

And I would like to use the function simplify for the second type
AExpr. What can I do is to convert AExpr to Expr, simplify it and
convert it back. But I don't like this solution because
conversions take some time.

I would prefer following: I say to the compiler that AAdd is like Add
and AConst is like Const and the compiler derives function
asimplify for AExpr.

Is it possible to do this? In fact I want to have two distinct types
where one is extension of the second (Expr is extension of AExpr)
and I want to define a function for the extended type (Expr) and
use it for the original type (AExpr). I assume that the function won't
introduce Mul to the expression which had no Mul.

Thanks in advance

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


Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Eugene Kirpichov
It is possible to do this automatically, but you'll have to program
the automation yourself with Template Haskell.

2009/12/4 Radek Micek radek.mi...@gmail.com:
 Hello.

 I have two types for expression:

 data Expr = Add Expr Expr | Mul Expr Expr | Const Int

 data AExpr = AAdd AExpr AExpr | AConst Int

 The first one supports addition and multiplication and the second
 only addition.

 I can write a function to simplify the first expression:

 simplify :: Expr - Expr
 simplify = {- replaces:
 a*1 and 1*a by a,
 a+0 and 0+a by a -}

 And I would like to use the function simplify for the second type
 AExpr. What can I do is to convert AExpr to Expr, simplify it and
 convert it back. But I don't like this solution because
 conversions take some time.

 I would prefer following: I say to the compiler that AAdd is like Add
 and AConst is like Const and the compiler derives function
 asimplify for AExpr.

 Is it possible to do this? In fact I want to have two distinct types
 where one is extension of the second (Expr is extension of AExpr)
 and I want to define a function for the extended type (Expr) and
 use it for the original type (AExpr). I assume that the function won't
 introduce Mul to the expression which had no Mul.

 Thanks in advance

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




-- 
Eugene Kirpichov
Web IR developer, market.yandex.ru
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Luke Palmer
On Fri, Dec 4, 2009 at 10:26 AM, Radek Micek radek.mi...@gmail.com wrote:
 Hello.

 I have two types for expression:

 data Expr = Add Expr Expr | Mul Expr Expr | Const Int

 data AExpr = AAdd AExpr AExpr | AConst Int

 The first one supports addition and multiplication and the second
 only addition.

 I can write a function to simplify the first expression:

 simplify :: Expr - Expr
 simplify = {- replaces:
 a*1 and 1*a by a,
 a+0 and 0+a by a -}

 And I would like to use the function simplify for the second type
 AExpr. What can I do is to convert AExpr to Expr, simplify it and
 convert it back. But I don't like this solution because
 conversions take some time.

Well there are more involved reasons than simply the conversion taking
time.  If you would like the type system on your side, you have a
decent modeling problem on your hands.  How can you guarantee that
simplify will return a type that will fit in AExpr?  Simplify might
turn a+a into 2*a, and then your trick no longer works.  It would
seem that you need to typecheck the function twice.

You could attempt to go the other way, i.e. define a simplify on AExpr
and map to and from Expr, but that will have trouble with expressions
like 0+(2*a), because 2*a has no representation in AExpr.

My hunch is that to do this properly, you need to use some of the
fixed point modeling that I can't find the paper about (!)  (It's
popular, someone please chime in :-).  I.e. define a data type which,
directed by type classes, may or may not support multiplication.  Then
define separately an additive simplifier and a multiplicative
simplifier on that.

There is some ugly bookkeeping involved, so that the code *locally* is
not that pretty, but it has good large-scale engineering properties.

And in the grand scheme of things, the conversions will not take that
much time.  The equivalent of a pointer indirection per node (+ some
GC).  And there is no difference in memory usage because of laziness.
This is not the level at which you worry about speed in Haskell -- at
least in my experience.

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


Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Derek Elkins
On Fri, Dec 4, 2009 at 11:26 AM, Radek Micek radek.mi...@gmail.com wrote:
 Hello.

 I have two types for expression:

 data Expr = Add Expr Expr | Mul Expr Expr | Const Int

 data AExpr = AAdd AExpr AExpr | AConst Int

 The first one supports addition and multiplication and the second
 only addition.

 I can write a function to simplify the first expression:

 simplify :: Expr - Expr
 simplify = {- replaces:
 a*1 and 1*a by a,
 a+0 and 0+a by a -}

 And I would like to use the function simplify for the second type
 AExpr. What can I do is to convert AExpr to Expr, simplify it and
 convert it back. But I don't like this solution because
 conversions take some time.

 I would prefer following: I say to the compiler that AAdd is like Add
 and AConst is like Const and the compiler derives function
 asimplify for AExpr.

 Is it possible to do this? In fact I want to have two distinct types
 where one is extension of the second (Expr is extension of AExpr)
 and I want to define a function for the extended type (Expr) and
 use it for the original type (AExpr). I assume that the function won't
 introduce Mul to the expression which had no Mul.

What you'd ideally want is called refinement types which Haskell, and
as far as I know, no practical language has.  There is a paper about a
way to encode these, but it is fairly heavy-weight.  You could use
phantom type trickery to combine the data types into one type but
still statically check that only additive expressions are passed to
certain functions, but that too is also probably more trouble than
it's worth.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Reid Barton
On Fri, Dec 04, 2009 at 11:52:35AM -0600, Derek Elkins wrote:
 On Fri, Dec 4, 2009 at 11:26 AM, Radek Micek radek.mi...@gmail.com wrote:
  Hello.
 
  I have two types for expression:
 
  data Expr = Add Expr Expr | Mul Expr Expr | Const Int
 
  data AExpr = AAdd AExpr AExpr | AConst Int
 
  The first one supports addition and multiplication and the second
  only addition.
 
  I can write a function to simplify the first expression:
 
  simplify :: Expr - Expr
  simplify = {- replaces:
  a*1 and 1*a by a,
  a+0 and 0+a by a -}
 
  And I would like to use the function simplify for the second type
  AExpr. What can I do is to convert AExpr to Expr, simplify it and
  convert it back. But I don't like this solution because
  conversions take some time.
 
  I would prefer following: I say to the compiler that AAdd is like Add
  and AConst is like Const and the compiler derives function
  asimplify for AExpr.
 
  Is it possible to do this? In fact I want to have two distinct types
  where one is extension of the second (Expr is extension of AExpr)
  and I want to define a function for the extended type (Expr) and
  use it for the original type (AExpr). I assume that the function won't
  introduce Mul to the expression which had no Mul.
 
 What you'd ideally want is called refinement types which Haskell, and
 as far as I know, no practical language has.  There is a paper about a
 way to encode these, but it is fairly heavy-weight.  You could use
 phantom type trickery to combine the data types into one type but
 still statically check that only additive expressions are passed to
 certain functions, but that too is also probably more trouble than
 it's worth.

In this particular case, with only two types Expr and AExpr, the
encoding is not particularly onerous.

{-# LANGUAGE GADTs, EmptyDataDecls, ViewPatterns #-}

data M
data Blah

-- A value of type 'E a' can only involve multiplication when a is M
data E a where
  Const :: Int - E a
  Add :: E a - E a - E a
  Mul :: E M - E M - E M

type Expr = E M
type AExpr = E Blah

-- The same simplify function we would write for the original Expr,
-- with a different type
simplify :: E a - E a
simplify (Const x) = Const x
simplify (Add (simplify - a) (simplify - b)) = case (a, b) of
  (Const 0, _) - b
  (_, Const 0) - a
  _ - Add a b
simplify (Mul (simplify - a) (simplify - b)) = case (a, b) of
  (Const 1, _) - b
  (_, Const 1) - a
  _ - Mul a b

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


Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Martijn van Steenbergen

Luke Palmer wrote:

On Fri, Dec 4, 2009 at 10:26 AM, Radek Micek radek.mi...@gmail.com wrote:

Hello.

I have two types for expression:

data Expr = Add Expr Expr | Mul Expr Expr | Const Int

data AExpr = AAdd AExpr AExpr | AConst Int

The first one supports addition and multiplication and the second
only addition.

I can write a function to simplify the first expression:

simplify :: Expr - Expr
simplify = {- replaces:
a*1 and 1*a by a,
a+0 and 0+a by a -}

And I would like to use the function simplify for the second type
AExpr. What can I do is to convert AExpr to Expr, simplify it and
convert it back. But I don't like this solution because
conversions take some time.


Well there are more involved reasons than simply the conversion taking
time.  If you would like the type system on your side, you have a
decent modeling problem on your hands.  How can you guarantee that
simplify will return a type that will fit in AExpr?  Simplify might
turn a+a into 2*a, and then your trick no longer works.  It would
seem that you need to typecheck the function twice.

You could attempt to go the other way, i.e. define a simplify on AExpr
and map to and from Expr, but that will have trouble with expressions
like 0+(2*a), because 2*a has no representation in AExpr.

My hunch is that to do this properly, you need to use some of the
fixed point modeling that I can't find the paper about (!)  (It's
popular, someone please chime in :-).  I.e. define a data type which,
directed by type classes, may or may not support multiplication.  Then
define separately an additive simplifier and a multiplicative
simplifier on that.


Perhaps you're looking for:

Wouter Swierstra
Data types à la carte
http://www.cse.chalmers.se/~wouter/Publications/DataTypesALaCarte.pdf

Groetjes,

Martijn.

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


Re: [Haskell-cafe] From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Martijn van Steenbergen

Hi Radek,

Radek Micek wrote:

I can write a function to simplify the first expression:

simplify :: Expr - Expr
simplify = {- replaces:
a*1 and 1*a by a,
a+0 and 0+a by a -}

And I would like to use the function simplify for the second type
AExpr. What can I do is to convert AExpr to Expr, simplify it and
convert it back. But I don't like this solution because
conversions take some time.


Like Luke said, you can probably work out something using explicit fixed 
points.


Or you can cheat a little and use generic programming:


{-# LANGUAGE DeriveDataTypeable #-}

import Data.Generics

data AddExpr = Const Int | Add AddExpr AddExpr
  deriving (Eq, Show, Typeable, Data)

data MulExpr = AddMul AddExpr | Mul MulExpr MulExpr
  deriving (Eq, Show, Typeable, Data)


Here you have explicitly encoded MulExpr as an extension of AddExpr 
through the constructor AddMul, just like you asked.


Now we define the simplification steps you mentioned, one for each 
datatype. They perform only one simplification step instead of calling 
themselves recursively. The type of simplifyAddStep ensures that it 
doesn't accidentally introduce multiplications:



simplifyAddStep :: AddExpr - AddExpr
simplifyAddStep expr = case expr of
  Add (Const 0) y - y
  Add x (Const 0) - x
  _   - expr

simplifyMulStep :: MulExpr - MulExpr
simplifyMulStep expr = case expr of
  Mul (AddMul (Const 1)) x - x
  Mul x (AddMul (Const 1)) - x
  _ - expr


Using generic programming, we can combine these two steps and apply them 
recursively on entire trees, bottom-up:



simplify :: Data a = a - a
simplify = everywhere (id `extT` simplifyAddStep `extT` simplifyMulStep)


An example invocation:


*Main simplify (AddMul (Const 1) `Mul` (AddMul (Const 2 `Add` Const 0)))
AddMul (Const 2)


Hope this helps,

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