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

2009-12-05 Thread Martijn van Steenbergen

Radek Micek wrote:

Hi,

thank you for your reply but your MulExpr
does not support expressions like

(2*3)+5


Oh! You're right, how silly of me.

Martijn.

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


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

2009-12-04 Thread Radek Micek
Hi,

thank you for your reply but your MulExpr
does not support expressions like

(2*3)+5

Radek

On Dec 5, 12:48 am, Martijn van Steenbergen
 wrote:
> 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-c...@haskell.orghttp://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] Re: From function over expression (+, *) derive function over expression (+)

2009-12-04 Thread Radek Micek
Thank you for your reply. If I understand this correctly
I can use your solution to have functions which work on any
subsets of constructors like in this example:

{-# LANGUAGE GADTs, EmptyDataDecls #-}

data Yes
data No

data AnyType a b c where
  A :: AnyType Yes b c
  B :: AnyType a Yes c
  C :: AnyType a b Yes

func :: AnyType a b No -> String
func A = "A"
func B = "B"

func2 :: AnyType No No c -> String
func2 C = "C"

On Dec 4, 7:14 pm, Reid Barton  wrote:
> On Fri, Dec 04, 2009 at 11:52:35AM -0600, Derek Elkins wrote:
> > On Fri, Dec 4, 2009 at 11:26 AM, Radek Micek  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-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe