Difference between revisions of "Multiplate"

From HaskellWiki
Jump to navigation Jump to search
(An example of how to make Multiplate instaces.)
(Using monoid to sumerize data from structures)
Line 1: Line 1:
 
== Making a Multiplate instance ==
 
== Making a Multiplate instance ==
   
The easiest way to understand how to use Multiplate is to look at a simple example.
+
The easiest way to understand how to use Multiplate is to look at a simple example. We assume you have the transformers library installed.
   
 
<pre>
 
<pre>
   
 
> import Data.Generics.Multiplate
 
> import Data.Generics.Multiplate
  +
> import Data.Functor.Constant
   
 
</pre>
 
</pre>
Line 76: Line 77:
 
</pre>
 
</pre>
   
That's it. Now we are ready to use out generic library to process our mutually recursive data structure without using any more boilerplate
+
That's it. Now we are ready to use out generic library to process our mutually recursive data structure without using any more boilerplate.
   
 
== Generic Programing with Multiplate ==
 
== Generic Programing with Multiplate ==
  +
  +
=== Monoids ===
  +
  +
Suppose we we want to get a list of all variables used in an expression. To do this we would use <code>preorderFold</code> with the list monoid. The first step is to build a <code>Plate</code> that handles the cases we care about. What we can do is use the default <code>purePlate</code> which does nothing, and modify it to handle the cases we care about.
  +
  +
<pre>
  +
getVariablesPlate :: Plate (Constant [Var])
  +
getVariablesPlate = purePlate { exprPlate = exprVars }
  +
where
  +
exprVars (EVar v) = Constant [v]
  +
exprVars x = pure x
  +
</pre>
  +
  +
This can be written alternatively using some list comprehension tricks
  +
  +
<pre>
  +
getVariablesPlate = purePlate {expr = \x -> Constant [s|EVar s <- [x]]}
  +
</pre>
  +
  +
Now we can can build a plate that will get variables from all subexpressions and concatenate them together into one big list
  +
  +
<pre>
  +
variablesPlate = preorderFold getVariablesPlate
  +
</pre>
  +
  +
In a real program we would either put <code>getVariablesPlate</code> into <code>variablesPlates</code>'s <code>where</code> clause or else simply inline
  +
the definition.
  +
  +
<code>variablesPlate</code> is a record of functions that will give a list of variables for each type in our mutually recursive record. Say we have an <code>Expr</code> we want to apply this to.
  +
  +
<pre>
  +
e1 :: Expr
  +
e1 = Let ("x" := Con 42) (Add (EVar "x") (EVar "x"))
  +
</pre>
  +
  +
We can project out the function for <code>Expr</code>'s from our plate apply it to <code>e1</code> and then unwrap the <code>Constant</code> wrapper. There is a little helper function, called <code>foldFor</code>, that will upgrade of projection function to remove the <code>Constant</code> wrapper for us.
  +
  +
<pre>
  +
>>> foldFor expr variablesPlate e1
  +
  +
["x","x"]
  +
</pre>
  +
  +
=== Traversing ===
   
 
Coming Soon.
 
Coming Soon.

Revision as of 22:35, 19 November 2010

Making a Multiplate instance

The easiest way to understand how to use Multiplate is to look at a simple example. We assume you have the transformers library installed.


> import Data.Generics.Multiplate
> import Data.Functor.Constant

Suppose you defined the follow set of mutually recursive data types for a simple language.


> data Expr = Con Int
>           | Add Expr Expr
>           | Mul Expr Expr
>           | EVar Var
>           | Let Decl Expr
>           deriving (Eq, Show)
> 
> data Decl = Var := Expr
>           | Seq Decl Decl
>           deriving (Eq, Show)
> 
> type Var = String

The first thing we are going to define is a 'plate' for this language.


> data Plate f = Plate
>            { expr :: Expr -> f Expr
>            , decl :: Decl -> f Decl
>            }

A plate is a record type that is parametrized by a functor f. There is one field for each type in the mutually recursive structure we want to write generic functions for. Each field has type A -> f A where A is one of the data types.

To use the Multiplate library we have to make Plate and instance of the Multiplate class. The instance requires that we write two functions: multiplate and mkPlate. Let's define each of these functions in turn.


> instance Multiplate Plate where

We have to write one piece of boilerplate code for multiplate. However, once this is implemented, no further boilerplate code need be written. multiplate takes a Plate as a parameter. The idea is that for each expression in our language we will call this a function from this Plate parameter on the children of our expression and then combine the results.


>  multiplate plate = Plate buildExpr buildDecl
>   where
>    buildExpr (Add e1 e2) = Add <$> expr plate e1 <*> expr plate e2
>    buildExpr (Mul e1 e2) = Mul <$> expr plate e1 <*> expr plate e2
>    buildExpr (Let d e) = Let <$> decl plate d <*> expr plate e
>    buildExpr e = pure e
>    buildDecl (v := e) = (:=) <$> pure v <*> expr plate e
>    buildDecl (Seq d1 d2) = Seq <$> decl plate d1 <*> decl plate d2

Notice that when an expression has no children, as in the case of v in v := e, we simply use pure v. pure is used to handle the default case in buildExpr, also have no subexpressions.

Next we have to define mkPlate. mkPlate is a function that builds a Plate given a generic builder function that produces values of type a -> f a. However these generic builder functions require a bit of help. The need to know what the projection function for the field that they are building is, so we pass that as a parameter to them.


>  mkPlate build = Plate (build expr) (build decl)

That's it. Now we are ready to use out generic library to process our mutually recursive data structure without using any more boilerplate.

Generic Programing with Multiplate

Monoids

Suppose we we want to get a list of all variables used in an expression. To do this we would use preorderFold with the list monoid. The first step is to build a Plate that handles the cases we care about. What we can do is use the default purePlate which does nothing, and modify it to handle the cases we care about.

getVariablesPlate :: Plate (Constant [Var])
getVariablesPlate = purePlate { exprPlate = exprVars }
 where
  exprVars (EVar v) = Constant [v]
  exprVars x = pure x

This can be written alternatively using some list comprehension tricks

getVariablesPlate = purePlate {expr = \x -> Constant [s|EVar s <- [x]]}

Now we can can build a plate that will get variables from all subexpressions and concatenate them together into one big list

variablesPlate = preorderFold getVariablesPlate

In a real program we would either put getVariablesPlate into variablesPlates's where clause or else simply inline the definition.

variablesPlate is a record of functions that will give a list of variables for each type in our mutually recursive record. Say we have an Expr we want to apply this to.

e1 :: Expr
e1 = Let ("x" := Con 42) (Add (EVar "x") (EVar "x"))

We can project out the function for Expr's from our plate apply it to e1 and then unwrap the Constant wrapper. There is a little helper function, called foldFor, that will upgrade of projection function to remove the Constant wrapper for us.

>>> foldFor expr variablesPlate e1

["x","x"]

Traversing

Coming Soon.