Multiplate

From HaskellWiki
Revision as of 00:59, 4 December 2010 by Roconnor (talk | contribs) (spelling)
Jump to navigation Jump to search

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
> import Data.Functor.Identity

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 an applicative 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 child = Plate buildExpr buildDecl
>   where
>    buildExpr (Add e1 e2) = Add <$> expr child e1 <*> expr child e2
>    buildExpr (Mul e1 e2) = Mul <$> expr child e1 <*> expr child e2
>    buildExpr (Let d e) = Let <$> decl child d <*> expr child e
>    buildExpr e = pure e
>    buildDecl (v := e) = (:=) <$> pure v <*> expr child e
>    buildDecl (Seq d1 d2) = Seq <$> decl child d1 <*> decl child 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

Suppose we want to recursively evaluate constant expressions in the language. We can use mapFamily for this. We define a Plate Identity for the functionality we care about.

doConstFold :: Plate Identity
doConstFold = purePlate { expr = exprConst }
 where
  expr (Add (Con x) (Con y)) = return (Con (x + y))
  expr (Mul (Con x) (Con y)) = return (Con (x * y))
  expr x = pure x

Now we can can build a plate that will repeatedly apply this transformation from bottom up.

constFoldPlate = mapFamily doConstFold

Let's build an declaration to test.

d1 :: Decl
d1 = "x" := (Add (Mul (Con 42) (Con 68)) (Con 7))

We can project out the function for Decl's from our plate apply it to d1 and then unwrap the Identity wrapper. Again, there is a little helper function, called traverseFor, that will upgrade of projection function to remove the Identity wrapper for us.

>>> traverseFor decl constFoldPlate d1

"x" := Con 2863

Alternative Plates

Multiplate does not have to be used in the above way. Any structure can be made an instance of Multiplate as long as the following two Multiplate laws are satisfied:

  1. multiplate purePlate = purePlate
  2. multiplate (composePlate p1 p2) = composePlate (multiplate p1) (multiplate p2)

For example, sjoerd_visscher gives an example of a plate where each constructor of each data type has its own field in a record structure.

Links

Multiplate on Hackage