Multiplate: Difference between revisions
(Dibbs on this page.) |
(An example of how to make Multiplate instaces.) |
||
Line 1: | Line 1: | ||
== Making a Multiplate instance == | |||
The easiest way to understand how to use Multiplate is to look at a simple example. | |||
<pre> | |||
> import Data.Generics.Multiplate | |||
</pre> | |||
Suppose you defined the follow set of mutually recursive data types for a simple language. | |||
<pre> | |||
> 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 | |||
</pre> | |||
The first thing we are going to define is a 'plate' for this language. | |||
<pre> | |||
> data Plate f = Plate | |||
> { expr :: Expr -> f Expr | |||
> , decl :: Decl -> f Decl | |||
> } | |||
</pre> | |||
A plate is a record type that is parametrized by a functor <code>f</code>. There is one field for each type in the mutually recursive structure we want to write generic functions for. Each field has type <code>A -> f A</code> where <code>A</code> is one of the data types. | |||
To use the Multiplate library we have to make <code>Plate</code> and instance of the <code>Multiplate</code> class. The instance requires that we write two functions: <code>multiplate</code> and <code>mkPlate</code>. Let's define each of these functions in turn. | |||
<pre> | |||
> instance Multiplate Plate where | |||
</pre> | |||
We have to write one piece of boilerplate code for <code>multiplate</code>. However, once this is implemented, no further boilerplate code need be written. | |||
<code>multiplate</code> takes a <code>Plate</code> as a parameter. The idea is that for each expression in our language we will call this a function from this <code>Plate</code> parameter on the children of our expression and then combine the results. | |||
<pre> | |||
> 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 | |||
</pre> | |||
Notice that when an expression has no children, as in the case of <code>v</code> in <code>v := e</code>, we simply use <code>pure v</code>. | |||
<code>pure</code> is used to handle the default case in <code>buildExpr</code>, also have no subexpressions. | |||
Next we have to define <code>mkPlate</code>. <code>mkPlate</code> is a function that builds a <code>Plate</code> given a generic builder function that produces values of type <code>a -> f a</code>. 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. | |||
<pre> | |||
> mkPlate build = Plate (build expr) (build decl) | |||
</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 | |||
== Generic Programing with Multiplate == | |||
Coming Soon. | Coming Soon. |
Revision as of 22:11, 19 November 2010
Making a Multiplate instance
The easiest way to understand how to use Multiplate is to look at a simple example.
> import Data.Generics.Multiplate
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
Coming Soon.