
Hi Everyone, I am trying to build a function to rewrite and AST. I have and AST which is designed to represent a computation graph. I will present a simplified version here designed to illustrate the problem. I have tried numerous ways of rewriting it including uniplate, recursion and Edward Kmett's implementation of plate in his lens package. My AST is defined using GADTs as follows: class (ReflectDescriptor a, Typeable a, Wire a) => ProtoBuf a data Expression a b where OpenTable :: (ProtoBuf b) => Int -> Table -> Expression () b OpenFile :: (ProtoBuf b) => Int -> String -> Expression () b WriteFile :: (Typeable a, ProtoBuf b) => Int -> String -> Expression a b -> Expression b () WriteTable :: (Typeable a, ProtoBuf b) => Int -> Table -> Expression a b -> Expression b () Map :: (ProtoBuf a, ProtoBuf b, ProtoBuf c) => Int -> (a -> b) -> Expression c a -> Expression a b LocalMerge :: (ProtoBuf a) => Int -> [Expression c a] -> Expression c a The user can create code inside a Monad Transformer like so: q <- query $ do table <- openTable myTable transform <- map someFunc table writeTable otherTable transform As part of this language the compiler I am building would need to for instance transform OpenTable into a series OpenFile nodes with a LocalMerge to merge the results together. So uniplate cannot work over GADTs if I recall correctly. I exchanged emails with Edward and he explained that for the lens case I would need something like an indexed lens family from his indexed package which is not implemented yet but which may be in the future. The issue with recursion is that as you recurse through the AST the a b on the Expression change and GHC cannot compile it because it wants the a b to be the same on each recursive call. My question to the Haskell community is how might one develop AST rewriting functionality. One possible solution is stripping the types away from GHC and doing all the type checking myself. That doesn't seem very good. Another possibility that I have looked at was using hoopl. It seems very compatible given that it is built for describing and optimizing data flow which I am doing however the learning curve looks quite steep. I have been reluctant so far to invest the time in it. Has anyone developed something similar? What recommendations do you have? Thanks. Steve

Have you read "Data types a la carte"? The 'syntactic' package implements
the ideas, but it was a little dense for my purposes when I looked (I just
wanted data types, a la carte; it focuses on manipulating ASTs defined a la
carte). It might be what you need, or you can roll your own based on the
paper.
On Tue, Nov 20, 2012 at 3:21 PM, Steve Severance
Hi Everyone,
I am trying to build a function to rewrite and AST. I have and AST which is designed to represent a computation graph. I will present a simplified version here designed to illustrate the problem. I have tried numerous ways of rewriting it including uniplate, recursion and Edward Kmett's implementation of plate in his lens package.
My AST is defined using GADTs as follows:
class (ReflectDescriptor a, Typeable a, Wire a) => ProtoBuf a
data Expression a b where OpenTable :: (ProtoBuf b) => Int -> Table -> Expression () b OpenFile :: (ProtoBuf b) => Int -> String -> Expression () b WriteFile :: (Typeable a, ProtoBuf b) => Int -> String -> Expression a b -> Expression b () WriteTable :: (Typeable a, ProtoBuf b) => Int -> Table -> Expression a b -> Expression b () Map :: (ProtoBuf a, ProtoBuf b, ProtoBuf c) => Int -> (a -> b) -> Expression c a -> Expression a b LocalMerge :: (ProtoBuf a) => Int -> [Expression c a] -> Expression c a
The user can create code inside a Monad Transformer like so:
q <- query $ do table <- openTable myTable transform <- map someFunc table writeTable otherTable transform
As part of this language the compiler I am building would need to for instance transform OpenTable into a series OpenFile nodes with a LocalMerge to merge the results together.
So uniplate cannot work over GADTs if I recall correctly.
I exchanged emails with Edward and he explained that for the lens case I would need something like an indexed lens family from his indexed package which is not implemented yet but which may be in the future.
The issue with recursion is that as you recurse through the AST the a b on the Expression change and GHC cannot compile it because it wants the a b to be the same on each recursive call.
My question to the Haskell community is how might one develop AST rewriting functionality. One possible solution is stripping the types away from GHC and doing all the type checking myself. That doesn't seem very good.
Another possibility that I have looked at was using hoopl. It seems very compatible given that it is built for describing and optimizing data flow which I am doing however the learning curve looks quite steep. I have been reluctant so far to invest the time in it.
Has anyone developed something similar? What recommendations do you have?
Thanks.
Steve
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

This is one of the problem Syntactic aims to solve, but it requires you to use a different representation of expressions (for good or bad). If you want to keep your existing representation, then you have to use a generic programming library that supports GADTs. I know at least the Spine approach supports GADTs, but the library on Hackage seems too incomplete to be useful: http://hackage.haskell.org/package/spine I don't know if there are other libraries that support GADTs. You can also have a look at CompData: http://hackage.haskell.org/package/compdata It is similar to Syntactic (i.e. requires a different representation), but it has a richer library of generic traversals. / Emil 2012-11-21 04:20, Alexander Solla skrev:
Have you read "Data types a la carte"? The 'syntactic' package implements the ideas, but it was a little dense for my purposes when I looked (I just wanted data types, a la carte; it focuses on manipulating ASTs defined a la carte). It might be what you need, or you can roll your own based on the paper.
On Tue, Nov 20, 2012 at 3:21 PM, Steve Severance
mailto:sseverance@alphaheavy.com> wrote: Hi Everyone,
I am trying to build a function to rewrite and AST. I have and AST which is designed to represent a computation graph. I will present a simplified version here designed to illustrate the problem. I have tried numerous ways of rewriting it including uniplate, recursion and Edward Kmett's implementation of plate in his lens package.
My AST is defined using GADTs as follows:
class (ReflectDescriptor a, Typeable a, Wire a) => ProtoBuf a
data Expression a b where OpenTable :: (ProtoBuf b) => Int -> Table -> Expression () b OpenFile :: (ProtoBuf b) => Int -> String -> Expression () b WriteFile :: (Typeable a, ProtoBuf b) => Int -> String -> Expression a b -> Expression b () WriteTable :: (Typeable a, ProtoBuf b) => Int -> Table -> Expression a b -> Expression b () Map :: (ProtoBuf a, ProtoBuf b, ProtoBuf c) => Int -> (a -> b) -> Expression c a -> Expression a b LocalMerge :: (ProtoBuf a) => Int -> [Expression c a] -> Expression c a
The user can create code inside a Monad Transformer like so:
q <- query $ do table <- openTable myTable transform <- map someFunc table writeTable otherTable transform
As part of this language the compiler I am building would need to for instance transform OpenTable into a series OpenFile nodes with a LocalMerge to merge the results together.
So uniplate cannot work over GADTs if I recall correctly.
I exchanged emails with Edward and he explained that for the lens case I would need something like an indexed lens family from his indexed package which is not implemented yet but which may be in the future.
The issue with recursion is that as you recurse through the AST the a b on the Expression change and GHC cannot compile it because it wants the a b to be the same on each recursive call.
My question to the Haskell community is how might one develop AST rewriting functionality. One possible solution is stripping the types away from GHC and doing all the type checking myself. That doesn't seem very good.
Another possibility that I have looked at was using hoopl. It seems very compatible given that it is built for describing and optimizing data flow which I am doing however the learning curve looks quite steep. I have been reluctant so far to invest the time in it.
Has anyone developed something similar? What recommendations do you have?
Thanks.
Steve
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org mailto: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

On Wed, Nov 21, 2012 at 2:56 PM, Emil Axelsson wrote:
This is one of the problem Syntactic aims to solve, but it requires you to use a different representation of expressions (for good or bad). If you want to keep your existing representation, then you have to use a generic programming library that supports GADTs. I know at least the Spine approach supports GADTs, but the library on Hackage seems too incomplete to be useful:
http://hackage.haskell.org/**package/spinehttp://hackage.haskell.org/package/spine
Just a comment on this library (since I put it up there). Yes, it is incomplete. It's only been used for students in a course. It is not intended for practical use. Even if it were complete, the Type datatype is closed, meaning the library cannot be extended to support new types, which probably won't necessarily be that useful to you. The spine view works nicely as a model of SYB but not so nicely as a library for generic programming. Regards, Sean

Thanks everyone for your replies.
I am not wedded to GADTs or really anything else. I am going to give the
syntactic library a shot over the next few days and see if I can hack
something together.
Thanks again for the papers and libraries.
Steve
On Wed, Nov 21, 2012 at 6:10 AM, Sean Leather
On Wed, Nov 21, 2012 at 2:56 PM, Emil Axelsson wrote:
This is one of the problem Syntactic aims to solve, but it requires you to
use a different representation of expressions (for good or bad). If you want to keep your existing representation, then you have to use a generic programming library that supports GADTs. I know at least the Spine approach supports GADTs, but the library on Hackage seems too incomplete to be useful:
http://hackage.haskell.org/**package/spinehttp://hackage.haskell.org/package/spine
Just a comment on this library (since I put it up there). Yes, it is incomplete. It's only been used for students in a course. It is not intended for practical use.
Even if it were complete, the Type datatype is closed, meaning the library cannot be extended to support new types, which probably won't necessarily be that useful to you. The spine view works nicely as a model of SYB but not so nicely as a library for generic programming.
Regards, Sean
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 11/20/12 6:21 PM, Steve Severance wrote:
class (ReflectDescriptor a, Typeable a, Wire a) => ProtoBuf a
data Expression a b where OpenTable :: (ProtoBuf b) => Int -> Table -> Expression () b OpenFile :: (ProtoBuf b) => Int -> String -> Expression () b WriteFile :: (Typeable a, ProtoBuf b) => Int -> String -> Expression a b -> Expression b () WriteTable :: (Typeable a, ProtoBuf b) => Int -> Table -> Expression a b -> Expression b () Map :: (ProtoBuf a, ProtoBuf b, ProtoBuf c) => Int -> (a -> b) -> Expression c a -> Expression a b LocalMerge :: (ProtoBuf a) => Int -> [Expression c a] -> Expression c a We can implement a version of the compos operator like so:
compos :: forall m c d. (forall a. a -> m a) -> (forall a b. m (a -> b) -> m a -> m b) -> (forall e f. Expression e f -> m (Expression e f)) -> Expression c d -> m (Expression c d) compos ret app f v = case v of OpenTable i t -> ret (OpenTable i t) OpenFile i s -> ret (OpenFile i s) Map i g e -> ret (Map i g) `app` f e WriteFile i s e -> ret (WriteFile i s) `app` f e WriteTable i t e -> ret (WriteTable i t) `app` f e LocalMerge i es -> ret (LocalMerge i) `app` mapm f es where mapm :: forall g h. (Expression g h -> m (Expression g h)) -> [Expression g h] -> m [Expression g h] mapm g = foldr (app . app (ret (:)) . g) (ret []) Then, with this in hand, we get all the usual compos variants: composOp :: (forall a b. Expression a b -> Expression a b) -> Expression c d -> Expression c d composOp f = runIdentity . composOpM (Identity . f) composOpM :: (Monad m) => (forall a b. Expression a b -> m (Expression a b)) -> Expression c d -> m (Expression c d) composOpM = compos return ap composOpM_ :: (Monad m) => (forall a b. Expression a b -> m ()) -> Expression c d -> m () composOpM_ = composOpFold (return ()) (>>) composOpFold :: b -> (b -> b -> b) -> (forall c d. Expression c d -> b) -> Expression e f -> b composOpFold z c f = unC . compos (\_ -> C z) (\(C x) (C y) -> C (c x y)) (C . f) newtype C b a = C { unC :: b } See Bringert and Ranta's "A Pattern for Almost Compositional Functions" for more details: http://publications.lib.chalmers.se/records/fulltext/local_75172.pdf In my experience, compos requires a little work, but it can handle just about any data type or family of data types you throw at it. (note the twist on compos is just an extra rank 2 type to quantify over the "a" and "b" in "Expression a b". The same rank 2 type lets you write the recursive code almost directly as well [using polymorphic recursion] -- compos is just a nice generic way to avoid writing the boilerplate traversal repeatedly). Cheers, Gershom
participants (5)
-
Alexander Solla
-
Emil Axelsson
-
Gershom Bazerman
-
Sean Leather
-
Steve Severance