Re: [Haskell-cafe] Transformation sequence

2007-10-22 Thread R Hayes


I know that this is a resolved question, but wouldn't Huet's Zipper  
also work for this



On Oct 20, 2007, at 5:26 PM, Alfonso Acosta wrote:


On 10/20/07, Mads Lindstrøm [EMAIL PROTECTED] wrote:

I am not a monad-expect, so I may be wrong, but wouldn't a writer  
monad

be more appropriate?


You are at least more monad-expert than myself . I knew the existence
of the writer monad but not really how it works. After checking its
documentation I must say you and Brandon are right. Using the Writer
Monad makes sense.
___
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] Transformation sequence

2007-10-20 Thread Andrew Coppin
I'm writing some code where I take an expression tree and transform it 
into another equivilent one.


Now it's moderately easy to write the code that does the transformation. 
But what I *really* want is to print out the transformation *sequence*. 
This appears to be much more awkward.


What I have is a function like this:

 transform :: Expression - [Expression]

The trouble is, if you want to apply the transformation recursively, 
things get very messy. Oh, it *works* and everything. It's just really 
messy and verbose. In Haskell, this is usually a sign that you want to 
start applying some ingenious trickery... but I'm having an ingeniety 
failure here.


Suppose, for example, that in one case you want to recursively transform 
two subexpressions. I end up writing something like


 transform (...sub1...sub2...) =
   let
 sub1s = transform sub1
 sub2s = transform sub2
   in map (\sub1' - put sub1' back into main expression) sub1s ++ map 
(\sub2' - put sub2' back into main expression) sub2s


After you've typed that a few times, it becomes *very* boring! But I 
can't think of a clean way to abstract it. :-(


It's *almost* like you want to use the list monad:

 transform (...sub1...sub2...) = do
   sub1' - transform sub1
   sub2' - transform sub2
   return (put sub1' and sub2' back into the main expression)

Except that that doesn't quite work properly. As shown above, I actually 
want to go through all the transformation steps for the first branch, 
and *then* all the steps for the second branch.


Any hints?

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


Re: [Haskell-cafe] Transformation sequence

2007-10-20 Thread Alfonso Acosta
How about using a state monad as a logger?

You store the transformation sequence in the state while processing
the tree, then you simply retrieve the state and print it out.

Your transformation function should change to

 import Control.Monad.State

 data Log = ... -- to be defined

 type LogMonad a = State Log a

 transform :: LogMonad Expression - LogMonad [Expression]



On 10/20/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 I'm writing some code where I take an expression tree and transform it
 into another equivilent one.

 Now it's moderately easy to write the code that does the transformation.
 But what I *really* want is to print out the transformation *sequence*.
 This appears to be much more awkward.

 What I have is a function like this:

   transform :: Expression - [Expression]

 The trouble is, if you want to apply the transformation recursively,
 things get very messy. Oh, it *works* and everything. It's just really
 messy and verbose. In Haskell, this is usually a sign that you want to
 start applying some ingenious trickery... but I'm having an ingeniety
 failure here.

 Suppose, for example, that in one case you want to recursively transform
 two subexpressions. I end up writing something like

   transform (...sub1...sub2...) =
 let
   sub1s = transform sub1
   sub2s = transform sub2
 in map (\sub1' - put sub1' back into main expression) sub1s ++ map
 (\sub2' - put sub2' back into main expression) sub2s

 After you've typed that a few times, it becomes *very* boring! But I
 can't think of a clean way to abstract it. :-(

 It's *almost* like you want to use the list monad:

   transform (...sub1...sub2...) = do
 sub1' - transform sub1
 sub2' - transform sub2
 return (put sub1' and sub2' back into the main expression)

 Except that that doesn't quite work properly. As shown above, I actually
 want to go through all the transformation steps for the first branch,
 and *then* all the steps for the second branch.

 Any hints?

 ___
 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] Transformation sequence

2007-10-20 Thread Andrew Coppin

Alfonso Acosta wrote:

How about using a state monad as a logger?

You store the transformation sequence in the state while processing
the tree, then you simply retrieve the state and print it out.
  


Mmm... that could work... I'll investigate.

Thanks.

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


Re: [Haskell-cafe] Transformation sequence

2007-10-20 Thread Twan van Laarhoven

Andrew Coppin wrote:
I'm writing some code where I take an expression tree and transform it 
into another equivilent one.


Now it's moderately easy to write the code that does the transformation. 
But what I *really* want is to print out the transformation *sequence*. 
This appears to be much more awkward.


What I have is a function like this:

 transform :: Expression - [Expression]

The trouble is, if you want to apply the transformation recursively, 
things get very messy. Oh, it *works* and everything. It's just really 
messy and verbose. In Haskell, this is usually a sign that you want to 
start applying some ingenious trickery... but I'm having an ingeniety 
failure here.


Suppose, for example, that in one case you want to recursively transform 
two subexpressions. I end up writing something like


 transform (...sub1...sub2...) =
   let
 sub1s = transform sub1
 sub2s = transform sub2
   in map (\sub1' - put sub1' back into main expression) sub1s ++ map 
(\sub2' - put sub2' back into main expression) sub2s


After you've typed that a few times, it becomes *very* boring! But I 
can't think of a clean way to abstract it. :-(


It's *almost* like you want to use the list monad:

 transform (...sub1...sub2...) = do
   sub1' - transform sub1
   sub2' - transform sub2
   return (put sub1' and sub2' back into the main expression)


How about:

   transform ... =
 (transform sub1 = put back into main expression)
  ++ (transform sub2 = put back into main expression)

Or something to that effect? Or maybe

   transform ... = do
  sub' - transform sub1 ++ transform sub2
  put back into main expression)

It would help if you gave some more information on what 'put back into 
main expression' actually looks like.



A trick I often find useful when working with transformations is to have 
a function


   step :: Expression - Maybe Expression

that applies a single transformation step, and returns Nothing if no 
further transformations are possible. You then use the maybe monad, and 
run steps with:


   runSteps :: (a - Maybe a) - a - a

Alternatively, the intermediate results could be remebered, then the 
function would return a list instead.


For combining alternatives you can define

   orElse :: (a - Maybe a) - (a - Maybe a) - (a - Maybe a)

Again, I am not sure if any of this applies to your problem, but it 
might help.


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


Re: [Haskell-cafe] Transformation sequence

2007-10-20 Thread Mads Lindstrøm
Hi Alfonso  Andrew

Alfonso Acosta wrote:
 How about using a state monad as a logger?

I am not a monad-expect, so I may be wrong, but wouldn't a writer monad
be more appropriate? After all, it is just used for logging the
intermediate results, not to keep read/write state. In other words, we
just need to read the logged values when the transformation has
occurred, not while it is occurring.


Greetings,

Mads Lindstrøm


 You store the transformation sequence in the state while processing
 the tree, then you simply retrieve the state and print it out.
 
 Your transformation function should change to
 
  import Control.Monad.State
 
  data Log = ... -- to be defined
 
  type LogMonad a = State Log a
 
  transform :: LogMonad Expression - LogMonad [Expression]
 
 
 
 On 10/20/07, Andrew Coppin [EMAIL PROTECTED] wrote:
  I'm writing some code where I take an expression tree and transform it
  into another equivilent one.
 
  Now it's moderately easy to write the code that does the transformation.
  But what I *really* want is to print out the transformation *sequence*.
  This appears to be much more awkward.
 
  What I have is a function like this:
 
transform :: Expression - [Expression]
 
  The trouble is, if you want to apply the transformation recursively,
  things get very messy. Oh, it *works* and everything. It's just really
  messy and verbose. In Haskell, this is usually a sign that you want to
  start applying some ingenious trickery... but I'm having an ingeniety
  failure here.
 
  Suppose, for example, that in one case you want to recursively transform
  two subexpressions. I end up writing something like
 
transform (...sub1...sub2...) =
  let
sub1s = transform sub1
sub2s = transform sub2
  in map (\sub1' - put sub1' back into main expression) sub1s ++ map
  (\sub2' - put sub2' back into main expression) sub2s
 
  After you've typed that a few times, it becomes *very* boring! But I
  can't think of a clean way to abstract it. :-(
 
  It's *almost* like you want to use the list monad:
 
transform (...sub1...sub2...) = do
  sub1' - transform sub1
  sub2' - transform sub2
  return (put sub1' and sub2' back into the main expression)
 
  Except that that doesn't quite work properly. As shown above, I actually
  want to go through all the transformation steps for the first branch,
  and *then* all the steps for the second branch.
 
  Any hints?
 
  ___
  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] Transformation sequence

2007-10-20 Thread Brent Yorgey
On 10/20/07, Andrew Coppin [EMAIL PROTECTED] wrote:

 I'm writing some code where I take an expression tree and transform it
 into another equivilent one.

 Now it's moderately easy to write the code that does the transformation.
 But what I *really* want is to print out the transformation *sequence*.
 This appears to be much more awkward.

 What I have is a function like this:

   transform :: Expression - [Expression]

 The trouble is, if you want to apply the transformation recursively,
 things get very messy. Oh, it *works* and everything. It's just really
 messy and verbose. In Haskell, this is usually a sign that you want to
 start applying some ingenious trickery... but I'm having an ingeniety
 failure here.

 Suppose, for example, that in one case you want to recursively transform
 two subexpressions. I end up writing something like

   transform (...sub1...sub2...) =
 let
   sub1s = transform sub1
   sub2s = transform sub2
 in map (\sub1' - put sub1' back into main expression) sub1s ++ map
 (\sub2' - put sub2' back into main expression) sub2s

 After you've typed that a few times, it becomes *very* boring! But I
 can't think of a clean way to abstract it. :-(

 It's *almost* like you want to use the list monad:

   transform (...sub1...sub2...) = do
 sub1' - transform sub1
 sub2' - transform sub2
 return (put sub1' and sub2' back into the main expression)

 Except that that doesn't quite work properly. As shown above, I actually
 want to go through all the transformation steps for the first branch,
 and *then* all the steps for the second branch.

 Any hints?


Hmm... I'm having trouble understanding exactly what you want.  In
particular, I don't understand what this statement:

But what I *really* want is to print out the transformation *sequence*.

has to do with the pseudocode that you exhibit later.  Could you perhaps
clarify a bit more, or give a specific example?

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


Re: [Haskell-cafe] Transformation sequence

2007-10-20 Thread Andrew Coppin

Twan van Laarhoven wrote:


How about:

   transform ... =
 (transform sub1 = put back into main expression)
  ++ (transform sub2 = put back into main expression)

Or something to that effect? Or maybe

   transform ... = do
  sub' - transform sub1 ++ transform sub2
  put back into main expression)


Ooo... that's a tad neater.

It would help if you gave some more information on what 'put back into 
main expression' actually looks like.


It changes for each case. Basically transform does a case analysis on 
the form of the expression, and decides how to transform it. In some 
cases, that involves simply calling itself recursively. But that's where 
trying to keep records of the process gets rather tangled.


A trick I often find useful when working with transformations is to 
have a function


   step :: Expression - Maybe Expression

that applies a single transformation step, and returns Nothing if no 
further transformations are possible. You then use the maybe monad, 
and run steps with:


   runSteps :: (a - Maybe a) - a - a

Alternatively, the intermediate results could be remebered, then the 
function would return a list instead.


For combining alternatives you can define

   orElse :: (a - Maybe a) - (a - Maybe a) - (a - Maybe a)

Again, I am not sure if any of this applies to your problem, but it 
might help.


Yeah, this is the approach I took with one of the earlier transforms. 
You start at the top of expressions, look for transformations to apply, 
in necessary recurse down the tree, until eventually a transformation is 
applied. Then you go right back to the top and start again. Repeat until 
no available transforms remain. It basically looks like this:


 go1 :: Expression - Maybe Expression
 go = unfoldr (\e - do e' - go1 e; return (e,e))

Very simple, very neat.

This new transformation I'm trying to implement works in a different 
order. It works from the bottom up, rather than from the top down... if 
that makes sense.


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


Re: [Haskell-cafe] Transformation sequence

2007-10-20 Thread Andrew Coppin

Brent Yorgey wrote:


Hmm... I'm having trouble understanding exactly what you want.  In 
particular, I don't understand what this statement:


But what I *really* want is to print out the transformation *sequence*.

has to do with the pseudocode that you exhibit later.  Could you 
perhaps clarify a bit more, or give a specific example?


I want to construct a program that prints out something like this:

[\fx - f(fx)]
[\f - [\x - f(fx)]]
[\f - S[\x - f][\x - fx]]
[\f - S(Kf)[\x - fx]]
[\f - S(Kf)f]
S[\f - S(Kf)][\f - f]
S(S[\f - S][\f - Kf])[\f - f]
S(S(KS)[\f - Kf])[\f - f]
S(S(KS)K)[\f - f]
S(S(KS)K)I

I can quite happily construct a program which, given the first line, 
yields the last line. But getting it to print all the intermediate steps 
is harder. And, like I said, when something is hard in Haskell, it 
usually means you're doing it the wrong way... ;-)


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


Re: [Haskell-cafe] Transformation sequence

2007-10-20 Thread Brandon S. Allbery KF8NH


On Oct 20, 2007, at 15:05 , Andrew Coppin wrote:

I can quite happily construct a program which, given the first  
line, yields the last line. But getting it to print all the  
intermediate steps is harder. And, like I said, when something is  
hard in Haskell, it usually means you're doing it the wrong  
way... ;-)


This is the Writer monad.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
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] Transformation sequence

2007-10-20 Thread Stefan O'Rear
On Sat, Oct 20, 2007 at 08:05:37PM +0100, Andrew Coppin wrote:
 Brent Yorgey wrote:

 Hmm... I'm having trouble understanding exactly what you want.  In 
 particular, I don't understand what this statement:

 But what I *really* want is to print out the transformation *sequence*.

 has to do with the pseudocode that you exhibit later.  Could you perhaps 
 clarify a bit more, or give a specific example?

 I want to construct a program that prints out something like this:

 [\fx - f(fx)]
 [\f - [\x - f(fx)]]
 [\f - S[\x - f][\x - fx]]
 [\f - S(Kf)[\x - fx]]
 [\f - S(Kf)f]
 S[\f - S(Kf)][\f - f]
 S(S[\f - S][\f - Kf])[\f - f]
 S(S(KS)[\f - Kf])[\f - f]
 S(S(KS)K)[\f - f]
 S(S(KS)K)I

 I can quite happily construct a program which, given the first line, yields 
 the last line. But getting it to print all the intermediate steps is 
 harder. And, like I said, when something is hard in Haskell, it usually 
 means you're doing it the wrong way... ;-)

Thought it sounded fun, so I did it:


data Term = Lam String Term | Term :$ Term | Var String

paren act = if act then \ a - ('(':) . a . (')':) else id

ppr i (Lam s t) = paren (i  0) $ (:) '\\' . (++) s . (++) .  . ppr 0 t
ppr i (a :$ b)  = paren (i  1) $ ppr 1 a . (:) ' ' . ppr 2 b
ppr i (Var s)   = paren (i  2) $ (++) s

reduce (Lam nm bd :$ obj) = Just (subst bd) where
subst (Lam nm' bd') = Lam nm' (if nm == nm' then bd' else subst bd')
subst (a :$ b)  = subst a :$ subst b
subst (Var nm') = if nm == nm' then obj else Var nm'
reduce (left :$ right)= fmap (:$ right) (reduce left)
reduce other  = Nothing

trail' ob = ppr 0 ob \n : maybe [] trail' (reduce ob)
trail = concat . trail'

The important part is the co-recursive trail, which produces a value
using (:) before calling itself.  No monads necessary.

Stefan


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


Re: [Haskell-cafe] Transformation sequence

2007-10-20 Thread Andrew Coppin

Stefan O'Rear wrote:

On Sat, Oct 20, 2007 at 08:05:37PM +0100, Andrew Coppin wrote:
  

I want to construct a program that prints out something like this:

[\fx - f(fx)]
[\f - [\x - f(fx)]]
[\f - S[\x - f][\x - fx]]
[\f - S(Kf)[\x - fx]]
[\f - S(Kf)f]
S[\f - S(Kf)][\f - f]
S(S[\f - S][\f - Kf])[\f - f]
S(S(KS)[\f - Kf])[\f - f]
S(S(KS)K)[\f - f]
S(S(KS)K)I

I can quite happily construct a program which, given the first line, yields 
the last line. But getting it to print all the intermediate steps is 
harder. And, like I said, when something is hard in Haskell, it usually 
means you're doing it the wrong way... ;-)



Thought it sounded fun, so I did it:


data Term = Lam String Term | Term :$ Term | Var String

paren act = if act then \ a - ('(':) . a . (')':) else id

ppr i (Lam s t) = paren (i  0) $ (:) '\\' . (++) s . (++) .  . ppr 0 t
ppr i (a :$ b)  = paren (i  1) $ ppr 1 a . (:) ' ' . ppr 2 b
ppr i (Var s)   = paren (i  2) $ (++) s

reduce (Lam nm bd :$ obj) = Just (subst bd) where
subst (Lam nm' bd') = Lam nm' (if nm == nm' then bd' else subst bd')
subst (a :$ b)  = subst a :$ subst b
subst (Var nm') = if nm == nm' then obj else Var nm'
reduce (left :$ right)= fmap (:$ right) (reduce left)
reduce other  = Nothing

trail' ob = ppr 0 ob \n : maybe [] trail' (reduce ob)
trail = concat . trail'

The important part is the co-recursive trail, which produces a value
using (:) before calling itself.  No monads necessary.
  


Unbelievable... I spend an entire day coding something, and somebody 
else manages to write a complete working solution in under 20 minutes. 
Heh. 8^)


I feel it might take me another 20 minutes just to figure out how this 
works...


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


Re: [Haskell-cafe] Transformation sequence

2007-10-20 Thread Alfonso Acosta
On 10/20/07, Mads Lindstrøm [EMAIL PROTECTED] wrote:

 I am not a monad-expect, so I may be wrong, but wouldn't a writer monad
 be more appropriate?

You are at least more monad-expert than myself . I knew the existence
of the writer monad but not really how it works. After checking its
documentation I must say you and Brandon are right. Using the Writer
Monad makes sense.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe