Update:
toAST
/fromAST
have been rewritten using catamorphisms.
Syntactic and CompData are two packages for modeling compositional data types. Both packages use the technique from Data Types à la Carte to model polymorphic variants, but they model recursion quite differently: Syntactic uses an application tree, while CompData uses a type-level fixed-point.
This post demonstrates the relation between the two approaches by showing how to translate one to the other. As a side effect, I also show how to obtain pattern functors for free, avoiding the need to derive instances for various type classes in CompData.
To remain focused on the matter at hand, I will only introduce Syntactic briefly. For more information, see this paper. I will also assume some familiarity with CompData.
Preliminaries
We start by importing the necessary stuff from Syntactic:
import Language.Syntactic
( AST (..)
, Full
, (:->)
, DenResult
, Args (..)
, mapArgs
, appArgs
, fold
)
Data types in Syntactic correspond to Generalised Compositional Data Types in CompData. These are found under Data.Comp.Multi
in the module hierarchy:
import Data.Comp.Multi
( Cxt (Term)
, Term
, HFunctor (..)
, cata
)
import Data.Comp.Multi.HFoldable (HFoldable (..))
Cxt
is the type-level fixed-point operator, which I will use by its alias Term
. The type classes HFunctor
and HFoldable
are used for traversing terms.
Our example will also make use of the Monoid
class.
import Data.Monoid
Syntactic
The idea behind Syntactic is to model a GADT such as the following
data Expr a
where
Int :: Int -> Expr Int
Add :: Expr Int -> Expr Int -> Expr Int
as a simpler non-recursive data type:
data ExprSym a
where
IntSym :: Int -> ExprSym (Full Int)
AddSym :: ExprSym (Int :-> Int :-> Full Int)
If we think of Expr
as an AST, then ExprSym
defines the symbols in this tree, but not the tree itself. The type parameter of each symbol is called the symbol signature. The signature for Add
– (Int :-> Int :-> Full Int)
– should be read as saying that Add
expects two integer sub-expressions and produces an integer result. In general, an ordinary constructor of the type
C :: T a -> T b -> ... -> T x
is modeled as a symbol of the type
CSym :: TSym (a :-> b :-> ... :-> Full x)
The AST
type can be used to make an actual AST from the symbols:
type Expr' a = AST ExprSym (Full a)
This type is isomorphic to Expr
. So, in what way is Expr'
better than Expr
? The answer is that Expr'
can be traversed generically by matching only on the constructors of AST
. For example, to compute the size of an AST, we only need two cases:
size :: AST sym sig -> Int
size (Sym _) = 1
size (s :$ a) = size s + size a
The first case says that a symbol has size 1, and the second says how to join the sizes of a symbol and a sub-expression. (Note that s
can contain nested uses of (:$)
.) Another advantage of using AST
is that it supports composable data types.
Listing arguments
The size
function is a bit special in that it operates on every symbol application in a compositional way. For more complex generic traversals, it is often needed to operate on a symbol and all its arguments at once. For example, Syntactic provides the following function for folding an AST
:
fold :: (forall sig . sym sig -> Args c sig -> c (Full (DenResult sig)))
-> AST sym (Full a)
-> c (Full a)
The caller provides a function that, given a symbol and a list of results for its sub-expressions, produces a result for the combined expression. fold
uses this function to compute a result for the whole AST. The type of fold
requires some explanation. The c
type (the folded result) is indexed by the type of the corresponding sub-expression; i.e. folding a sub-expression of type AST sym (Full a)
results in a value type c (Full a)
. The type function DenResult
gives the result type of a symbol signature; e.g. DenResult (Int :-> Full Bool) = Bool
.
For our current purposes, the most important part of the type is the argument list. Args c sig
is a list of results, each one corresponding to an argument in the signature sig
(again, more information is found in the Syntactic paper). Args
is defined so as to ensure that the length of the list is the same as the number of arguments in the signature. For example, Args c (Int :-> Int :-> Full Int)
is a list of two elements, each one of type c (Full Int)
.
Pattern functors for free
Now to the gist of this post. Using Args
, we can easily define a pattern functor (actually a higher-order functor) corresponding to a symbol:
data PF sym f a
where
PF :: sym sig -> Args f sig -> PF sym f (Full (DenResult sig))
A pattern functor here is simply a symbol paired with an argument list. Each argument is of type f (Full b)
, where b
is the type of the corresponding sub-expression. The HFunctor
instance is straightforward (mapArgs
is provided by Syntactic):
instance HFunctor (PF sym)
where
hfmap f (PF s as) = PF s (mapArgs f as)
Now we can actually use the symbols defined earlier to make an expression type using CompData’s fixed-point operator:
type Expr'' = Term (PF ExprSym)
The correspondence between expressions based on AST
and expressions based on Term
can be seen by the following functions mapping back and forth between them (appArgs
is provided by Syntactic):1
toAST :: Term (PF sym) (Full a) -> AST sym (Full a)
toAST = cata (\(PF s as) -> appArgs (Sym s) as)
fromAST :: AST sym (Full a) -> Term (PF sym) (Full a)
fromAST = fold (\s as -> Term (PF s as))
The translations are simply defined using catamorphisms; cata
for CompData terms and fold
for Syntactic terms.
To make the experiment a bit more complete, we also give an instance of HFoldable
. For this, we need a helper function which is currently not included in Syntactic:
foldrArgs
:: (forall a . c (Full a) -> b -> b)
-> b
-> (forall sig . Args c sig -> b)
foldrArgs f b Nil = b
foldrArgs f b (a :* as) = f a (foldrArgs f b as)
After this, the instance follows naturally:
instance HFoldable (PF sym)
where
hfoldr f b (PF s as) = foldrArgs f b as
Testing
To try out the code, we define a small expression using the Expr'
representation:
expr1 :: Expr' Int
expr1 = int 2 <+> int 3 <+> int 4
int :: Int -> Expr' Int
int i = Sym (IntSym i)
(<+>) :: Expr' Int -> Expr' Int -> Expr' Int
a <+> b = Sym AddSym :$ a :$ b
Next, we define the size
function for expressions based on CompData’s Term
(Sum
is provided by Data.Monoid
):
size' :: HFoldable f => Term f a -> Sum Int
size' (Term f) = Sum 1 `mappend` hfoldMap size' f
And, finally, the test:
*Main> size expr1
5
*Main> size' $ fromAST expr1
Sum {getSum = 5}
Summary
Hopefully, this post has provided some insights into the relation between Syntactic and CompData. The key observation is that symbol types defined for Syntactic give rise to free pattern functors that can be used to define terms in CompData. As we can translate freely between the two representations, there doesn’t appear to be any fundamental differences between them. A practical difference is that CompData uses type classes like HFunctor
and HFoldable
for generic traversals, while syntactic provides more direct access to the tree structure. As an interesting aside, the free pattern functors defined in this post avoids the need to use TemplateHaskell to derive instances for higher-order functor type classes in CompData.
The code in this post is available has been tested with GHC 7.6.1, syntactic-1.5.1 and compdata-0.6.1.
Download the source code (literate Haskell).
As noted by Patrick Bahr, the
toAST
/fromAST
translations destroy compositionality since a compound domain(S1 :+: S2)
in Syntactic is mapped to a monolithic functorPF (S1 :+: S2)
in CompData. However, with suitable type-level programming it should be possible to make the mapping to the compound type(PF S1 :+: PF S2)
instead.↩