clowns to the left of me, jokers to the right

Upload: lucius-gregory-meredith

Post on 09-Apr-2018

218 views

Category:

Documents


0 download

TRANSCRIPT

  • 8/8/2019 Clowns to the left of me, Jokers to the right

    1/8

    A POPL Pearl Submission

    Clowns to the Left of me, Jokers to the Right

    Dissecting Data Structures

    Conor McBride

    University of Nottingham

    [email protected]

    Abstract

    This paper, submitted as a pearl, introduces a small but usefulgeneralisation to the derivative operation on datatypes underly-ing Huets notion of zipper (Huet 1997; McBride 2001; Abbottet al. 2005b), giving a concrete representation to one-hole contextsin data which is in mid-transformation. This operator, dissection,turns a container-like functor into a bifunctor representing a one-

    hole context in which elements to the left of the hole are distin-guished in type from elements to its right.

    I present dissection for polynomial functors, although it is cer-tainly more general, preferring to concentrate here on its diverseapplications. For a start, map-like operations over the functor andfold-like operations over the recursive data structure it induces canbe expressed by tail recursion alone. Moreover, the derivative isreadily recovered from the dissection, along with Huets navigationoperations. A further special case of dissection, division, capturesthe notion of leftmost hole, canonically distinguishing values withno elements from those with at least one. By way of a more prac-tical example, division and dissection are exploited to give a rela-tively efficient generic algorithm for abstracting all occurrences ofone term from another in a first-order syntax.

    The source code for the paper is available online1 and compileswith recent extensions to the Glasgow Haskell Compiler.

    1. Introduction

    Theres an old Stealers Wheel song with the memorable chorus:

    Clowns to the left of me, jokers to the right,Here I am, stuck in the middle with you.

    Joe Egan, Gerry Rafferty

    In this paper, I examine what its like to be stuck in the middleof traversing and transforming a data structure. Ill show both youand the Glasgow Haskell Compiler how to calculate the datatype ofa freezeframe in a map- or fold-like operation from the datatypebeing operated on. That is, Ill explain how to compute a first-classdata representation of the control structure underlying map and fold

    traversals, via an operator which I call dissection. Dissection turnsout to generalise both the derivative operator underlying Huets

    1 http://www.cs.nott.ac.uk/ctm/CloJo/CJ.lhs

    [Copyright notice will appear here once preprint option is removed.]

    zippers (Huet 1997; McBride 2001) and the notion of divisionused to calculate the non-constant part of a polynomial. Let metake you on a journey into the algebra and differential calculus ofdata, in search of functionality from structure.

    Heres an example traversalevaluating a very simple languageof expressions:

    data Expr = Val Int|

    Add Expr Expr

    eval :: Expr Inteval (Val i) = ieval (Add e1 e2) = eval e1 + eval e2

    What happens if we freeze a traversal? Typically, we shall haveone piece of data in focus, with unprocessed data ahead of usand processed data behind. We should expect something a bit likeHuets zipper representation of one-hole contexts (Huet 1997),but with different sorts of stuff either side of the hole.

    In the case of our evaluator, suppose we proceed left-to-right.Whenever we face an Add, we must first go left into the firstoperand, recording the second Expr to process later; once we havefinished with the former, we must go right into the second operand,recording the Int returned from the first; as soon as we have both

    values, we can add. Correspondingly, a Stack of these direction-with-cache choices completely determined where we are in the

    evaluation process. Lets make this structure explicit:2

    type Stack = [ Expr + Int]

    Now we can implement an eval machinea tail recursion, at eachstage stuck in the middle with an expression to decompose, loadingthe stack by going left, or a value to use, unloading the stack andmoving right.

    eval :: Expr Inteval e = load e [ ]

    load :: Expr Stack Intload (Val i) stk = unload i stkload (Add e1 e2) stk = load e1 (L e2 : stk)

    unload :: Int Stack Intunload v [ ] = vunload v1 (L e2 : stk) = load e2 (R v1 : stk)unload v2 (R v1 : stk) = unload (v1 + v2) stk

    Each layer of this Stack structure is a dissection ofExprs recursionpattern. We have two ways to be stuck in the middle: were eitherL e2, on the left with an Exprs waiting to the right of us, or R v1, onthe right with an Int cached to the left of us. Lets find out how todo this in general, calculating the machine corresponding to anyold fold over finite first-order data.

    2 For brevity, I write + for Either, L for Left and R for Right

    Clowns and Jokers 1 2007/7/17

  • 8/8/2019 Clowns to the left of me, Jokers to the right

    2/8

    2. Polynomial Functors and Bifunctors

    This section briefly recapitulates material which is quite standard. Ihope to gain some generic leverage by exploiting the characterisa-tion of recursive datatypes as fixpoints of polynomial functors. Formore depth and detail, I refer the reader to the excellent Algebraof Programming (Bird and de Moor 1997).

    If we are to work in a generic way with data structures, we need

    to present them in a generic way. Rather than giving an individualdata declaration for each type we want, let us see how to buildthem from a fixed repertoire of components. Ill begin with thepolynomial type constructors in one parameter. These are generatedby constants, the identity, sum and product. I label them with a 1subscript to distinguish them their bifunctorial cousins.

    data K1 a x = K1 a -- constantdata Id x = Id x -- elementdata (p +1 q) x = L1 (p x) | R1 (q x) -- choicedata (p 1 q) x = (p x ,1 q x) -- pairing

    Allow me to abbreviate one of my favourite constant functors, atthe same time bringing it into line with our algebraic style.

    type 11 = K1 ()

    Some very basic container type constructors can be expressedas polynomials, with the parameter giving the type of elements.For example, the Maybe type constructor gives a choice betweenNothing, a constant, and Just, embedding an element.

    type Maybe = 11 +1 Id

    Nothing = L1 (K1 ())Just x = R1 (Id x)

    Whenever I reconstruct a datatype from this kit, I shall makea habit of defining its constructors linearly in terms of the kitconstructors. To aid clarity, I use these pattern synonyms on eitherside of a functional equation, so that the coded type acquires thesame programming interface as the original. This is not standardHaskell, but these definitions may readily be expanded to code

    which is fully compliant, if less readable.The kit approach allows us to establish properties of whole

    classes of datatype at once. For example, the polynomials are allfunctorial: we can make the standard Functor class

    class Functor p wherefmap :: (s t) p s p t

    respect the polynomial constructs.

    instance Functor (K1 a) wherefmap f (K1 a) = K1 a

    instance Functor Id wherefmap f (Id s) = Id (f s)

    instance (Functor p, Functor q) Functor (p +1 q) wherefmap f (L1 p) = L1 (fmap f p)

    fmap f (R1 q) = R1 (fmap f q)instance (Functor p, Functor q) Functor (p 1 q) where

    fmap f (p ,1 q) = (fmap f p ,1 fmap f q)

    Our reconstructed Maybe is functorial without further ado.

    2.1 Datatypes as Fixpoints of Polynomial Functors

    The Expr type is not itself a polynomial, but its branching structureis readily described by a polynomial. Think of each node of an Expras a container whose elements are the immediate sub- Exprs:

    type ExprP = K1 Int +1 Id 1 Id

    ValP i = L1 (K1 i)AddP e1 e2 = R1 (Id e1 ,1 Id e2)

    Correspondingly, we should hope to establish the isomorphism

    Expr = ExprP Expr

    but we cannot achieve this just by writing

    type Expr = ExprP Expr

    for this creates an infinite type expression, rather than an infinitetype. Rather, we must define a recursive datatype which ties theknot: p instantiates ps element type with p itself.

    data p = In (p (p))

    Now we may complete our reconstruction of Expr

    type Expr = ExprP

    Val i = In (ValP i)Add e1 e2 = In (AddP e1 e2)

    Now, the container-like quality of polynomials allows us todefine a fold-like recursion operator for them, sometimes called

    the iterator or the catamorphism.3 How can we compute a t froma p? Well, we can expand a p tree as a p (p) container of

    subtrees, use ps fmap to compute ts recursively for each subtree,then post-process the p t result container to produce a final resultin t. The behaviour of the recursion is thus uniquely determined bythe p-algebra :: p v v which does the post-processing.

    (| |) :: Functor p (p v v) p v(||) (In p) = (fmap (||) p)

    For example, we can write our evaluator as a catamorphism, withan algebra which implements each construct of our language forvalues rather than expressions. The pattern synonyms for ExprPhelp us to see what is going on:

    eval :: ExprP Inteval = (||) where

    (ValP i) = i

    (AddP v1 v2) = v1 + v2

    Catamorphism may appear to have a complex higher-order re-cursive structure, but we shall soon see how to turn it into a first-order tail-recursion whenever p is polynomial. We shall do this bydissecting p, distinguishing the clown elements left of a chosenposition from the joker elements to the right.

    2.2 Polynomial Bifunctors

    Before we can start dissecting, however, we shall need to be able tomanage two sorts of element. To this end, we shall need to introducethe polynomial bifunctors, which are just like the functors, but withtwo parameters.

    data K2 a x y = K2 adata Fst x y = Fst xdata Snd x y = Snd ydata (p +2 q) x y = L2 (p x y) | R2 (q x y)data (p 2 q) x y = (p x y,2 q x y)

    type 12 = K2 ()

    We have the analogous notion of mapping, except that we mustsupply one function for each parameter.

    3 Terminology is a minefield here: some people think of fold as threadinga binary operator through the elements of a container, others as replacingthe constructors with an alternative algebra. The confusion arises becausethe two coincide for lists. There is no resolution in sight.

    Clowns and Jokers 2 2007/7/17

  • 8/8/2019 Clowns to the left of me, Jokers to the right

    3/8

    class Bifunctor p wherebimap :: (s1 t1) (s2 t2) p s1 s2 p t1 t2

    instance Bifunctor (K2 a) wherebimap f g (K2 a) = K2 a

    instance Bifunctor Fst wherebimap f g (Fst x) = Fst (f x)

    instance Bifunctor Snd wherebimap f g (Snd y) = Snd (g y)

    instance (Bifunctor p, Bifunctor q) Bifunctor (p +2 q) where

    bimap f g (L2 p) = L2 (bimap f g p)bimap f g (R2 q) = R2 (bimap f g q)

    instance (Bifunctor p, Bifunctor q) Bifunctor (p 2 q) where

    bimap f g (p ,2 q) = (bimap f g p ,2 bimap f g q)

    Its certainly possible to take fixpoints of bifunctors to obtain re-cursively constructed container-like data: one parameter stands forelements, the other for recursive sub-containers. These structuressupport both fmap and a suitable notion of catamorphism. I canrecommend (Gibbons 2007) as a useful tutorial for this origami

    style of programming.

    2.3 Nothing is Missing

    We are still short of one basic component: Nothing. We shall beconstructing types which organise the ways to split at a position,but what if there are no ways to split at a position (because thereare no positions)? We need a datatype to represent impossibilityand here it is:

    data Zero

    Elements ofZero are hard to come byelements worth speak-ing of, that is. Correspondingly, if you have one, you can exchangeit for anything you want.

    magic :: Zero a

    magic x = x seq error "we never get this far"

    I have used Haskells seq operator to insist that magic evaluate itsargument. This is necessarily , hence the error clause can neverbe executed. In effect magic refutes its input.

    We can use p Zero to represent ps with no elements. For ex-ample, the only inhabitant of [Zero ] mentionable in polite societyis [ ]. Zero gives us a convenient way to get our hands on exactly theconstants, common to every instance ofp. Accordingly, we shouldbe able to embed these constants into any other instance:

    inflate :: Functor p p Zero p xinflate = fmap magic

    However, its rather a lot of work traversing a container just totransform all of its nonexistent elements. If we cheat a little, we

    can do nothing much more quickly, and just as safely!inflate :: Functor p p Zero p xinflate = unsafeCoerce

    This unsafeCoerce function behaves operationally like x x,but its type, a b, allows the programmer to intimidate thetypechecker into submission. It is usually present but well hidden inthe libraries distributed with Haskell compilers, and its use requiresextreme caution. Here we are sure that the only Zero computationsmistaken for xs will fail to evaluate, so our optimisation is safe.

    Now that we have Zero, allow me to abbreviate

    type 01 = K1 Zerotype 02 = K2 Zero

    3. Clowns, Jokers and Dissection

    We shall need three operators which take polynomial functors tobifunctors. Let me illustrate them: consider functors parametrisedby elements (depicted ) and bifunctors are parametrised by clowns() to the left and jokers () to the right. I show a typical p x as acontainer ofs

    {}

    Firstly, all clowns p lifts p uniformly to the bifunctor whichuses its left parameter for the elements of p.

    {}

    We can define this uniformly:

    data p c j = (p c)

    instance Functor f Bifunctor ( f) wherebimap f g ( pc) = (fmap f pc)

    Note that Id = Fst.Secondly, all jokers p is the analogue for the right parameter.

    {}

    data p c j = (p j)

    instance Functor f Bifunctor ( f) wherebimap f g ( pj) = (fmap g pj)

    Note that Id = Snd.Thirdly, dissected p takes p to the bifunctor which chooses

    a position in a p and stores clowns to the left of it and jokers to theright.

    {}

    We must clearly define this case by case. Let us work informallyand think through what to do each polynomial type constructor.Constants have no positions for elements,

    {}

    so there is no way to dissect them:

    (K1 a) = 02

    The Id functor has just one position, so there is just one way todissect it, and no room for clowns or jokers, left or right.

    {} {}

    Id = 12

    Dissecting a p +1 q, we get either a dissected p or a dissected q.

    L1 {} L2 {}R1 {} R2 {}

    (p +1 q) = p +2 q

    So far, these have just followed Leibnizs rules for the derivative,

    but for pairs p 1

    q we see the new twist. When dissecting a pair, wechoose to dissect either the left component (in which case the rightcomponent is all jokers) or the right component (in which case theleft component is all clowns).

    ({},1 {})

    L2 ({},2 {})R2 ({},2 {})

    (p 1 q) = p 2 q +2 p 2 q

    Now, in Haskell, this kind of type-directed definition can be donewith type-class programming (Hallgren 2001; McBride 2002). Al-low me to abuse notation very slightly, giving dissection constraintsa slightly more functional notation, after the manner of (Neubaueret al. 2001):

    Clowns and Jokers 3 2007/7/17

  • 8/8/2019 Clowns to the left of me, Jokers to the right

    4/8

    class (Functor p, Bifunctor p) p p | p p where-- methods to follow

    In ASCII, p p is rendered relationally as Diss p p, butthe annotation |p p is a functional dependency, indicating thatp determines p, so it is appropriate to think of as a functionaloperator, even if we cant quite treat it as such in practice.

    I shall extend this definition and its instances with operations

    shortly, but lets start by translating our informal program into type-class Prolog:

    instance (K1 a) 02

    instance Id 12

    instance ( p p, q q) p +1 q p +2 q

    instance ( p p, q q) p 1 q p 2 q +2 p 2 q

    Before we move on, let us just check that we get the answer weexpect for our expression example.

    K1 Int +1 Id 1 Id 02 +2 12 2 Id +2 Id 2 12

    A bit of simplification tells us:ExprP Int Expr = Expr + Int

    Dissection (with values to the left and expressions to the right) hascalculated the type of layers of our stack!

    4. How to Creep Gradually to the Right

    If were serious about representing the state of a traversal by adissection, we had better make sure that we have some means tomove from one position to the next. In this section, well developa method for the p p class which lets us move rightward oneposition at a time. I encourage you to move leftward yourselves.

    What should be the type of this operation? Consider, firstly,where our step might start. If we follow the usual trajectory, wellstart at the far leftand to our right, all jokers.

    {}

    Once weve started our traversal, well be in a dissection. To beready to move, we we must have a clown to put into the hole.

    {}

    Now, think about where our step might take us. If we end up atthe next position, out will pop the next joker, leaving the new hole.

    {}

    But if there are no more positions, well emerge at the far right, allclowns.

    {}

    Putting this together, we add to class p p the method

    right :: p j + ( p c j, c) (j, p c j) + p c

    Let me show you how to implement the instances by pretendingto write a polytypic function after the manner of (Jansson andJeuring 1997), showing the operative functor in a comment.

    right{-p -} :: p j + ( p c j, c) (j, p c j) + p c

    You can paste each clause of right {-p-} into the correspondingp instance.

    For constants, we jump all the way from far left to far right inone go; we cannot be in the middle, so we refute that case.

    right{-K1 a-} x = case x ofL (K1 a) R (K1 a)R (K2 z, c) magic z

    We can step into a single element, or step out.

    right{-Id x-} x = case x ofL (Id j) L (j, K2 ())

    R (K2 (), c) R (Id c)For sums, we make use of the instance for whichever branch is

    appropriate, being careful to strip tags beforehand and replace themafterwards.

    right{-p +1 q-} x = case x ofL (L1 pj) mindp (right{-p -} (L pj))L (R1 qj) mindq (right{-q-} (L qj))R (L2 pd, c) mindp (right{-p -} (R (pd, c)))R (R2 qd, c) mindq (right{-q-} (R (qd, c)))where

    mindp (L (j, pd)) = L (j, L2 pd)mindp (R pc) = R (L1 pc)mindq (L (j, qd)) = L (j, R2 qd)mindq (R qc) = R (R1 qc)

    For products, we must start at the left of the first component andend at the right of the second, but we also need to make things join up in the middle. When we reach the far right of the firstcomponent, we must continue from the far left of the second.

    right{-p 1 q-} x = case x ofL (pj ,1 qj) mindp (right{-p -} (L pj)) qjR (L2 (pd,2 qj), c) mindp (right{-p -} (R (pd, c))) qjR (R2 ( pc ,2 qd), c) mindq pc (right{-q-} (R (qd, c)))where

    mindp (L (j, pd)) qj = L (j, L2 (pd,2 qj))mindp (R pc) qj = mindq pc (right{-q-} (L qj))mindq pc (L (j, qd)) = L (j, R2 ( pc ,2 qd))mindq pc (R qc) = R (pc ,1 qc)

    Lets put this operation straight to work. If we can dissect p,

    then we can make its fmap operation tail recursive. Here, the jokersare the source elements and the clowns are the target elements.

    tmap :: p p (s t) p s p ttmap f ps = continue (right{-p -} (L ps)) where

    continue (L (s, pd)) = continue (right{-p -} (R (pd,f s)))continue (R pt) = pt

    4.1 Tail-Recursive Catamorphism

    If we want to define the catamorphism via dissection, we could justreplace fmap by tmap in the definition of (| |), but that wouldbe cheating! The point, after all, is to turn a higher-order recursiveprogram into a tail-recursive machine. We need some kind of stack.

    Suppose we have a p-algebra, ::p v v, and were traversinga p depth-first, left-to-right, in order to compute a value in v. At

    any given stage, well be processing a given node, in the middle oftraversing her mother, in the middle of traversing her grandmother,and so on in a maternal line back to the root. Well have visitedall the nodes left of this line and thus have computed vs for them;right of the line, each node will contain a p waiting for her turn.Correspondingly, our stack is a list of dissections:

    [ p v (p)]

    We start, ready to load a tree, with an empty stack.

    tcata :: p p (p v v) p vtcata t = load t [ ]

    To load a node, we unpack her container of subnodes and step infrom the far left.

    Clowns and Jokers 4 2007/7/17

  • 8/8/2019 Clowns to the left of me, Jokers to the right

    5/8

    load :: p p (p v v) p [ p v (p)] vload (In pt) stk = next (right{-p -} (L pt)) stk

    After a step, we might arrive at another subnode, in which casewe had better load her, suspending our traversal of her mother bypushing the dissection on the stack.

    next :: p p (p v v)

    (p, p v (p)) + p v [ p v (p)] vnext (L (t, pd)) stk = load t (pd: stk)next (R pv) stk = unload ( pv) stk

    Alternatively, our step might have taken us to the far right of a node,in which case we have all her subnodes values: we are ready toapply the algebra to get her own value, and start unloading.

    Once we have a subnodes value, we may resume the traversalof her mother, pushing the value into her place and moving on.

    unload :: p p (p v v) v [ p v (p)] vunload v (pd: stk) = next (right{-p -} (R (pd, v))) stkunload v [ ] = v

    On the other hand, if the stack is empty, then were holding thevalue for the root node, so were done! As we might expect:

    eval :: ExprP

    Inteval = tcata where

    (ValP i) = i (AddP v1 v2) = v1 + v2

    5. Derivative Derived by Diagonal Dissection

    The dissection of a functor is its bifunctor of one-hole contexts dis-tinguishing clown elements left of the hole from joker elementsto its right. If we remove this distinction, we recover the usual no-tion of one-hole context, as given by the derivative (McBride 2001;Abbott et al. 2005b). Indeed, weve already seen, the rules for dis-section just refine the centuries-old rules of the calculus with a left-right distinction. We can undo this refinement by taking the diago-nal of the dissection, identifying clowns with jokers.

    p x = p x xLet us now develop the related operations.

    5.1 Plugging In

    We can add another method to class p p,

    plug :: x p x x p x

    saying, in effect, that if clowns and jokers coincide, we can fill thehole directly and without any need to traverse all the way to theend. The implementation is straightforward.

    plug{-K1 a-} x (K2 z) = magic z

    plug{-Id-} x (K2 ()) = Id x

    plug{-p +1 q-} x (L2 pd) = L1 (plug{-p -} x pd)

    plug{-p +1

    q-} x (R2

    qd) = R1

    (plug{-q-} x qd)plug{-p 1 q-} x (L2 (pd,2 qx)) = (plug{-p -} x pd,1 qx)plug{-p 1 q-} x (R2 ( px ,2 qd)) = (px ,1 plug{-q-} x qd)

    5.2 Zipping Around

    We now have almost all the equipment we need to reconstructHuets operations (Huet 1997), navigating a tree of type p forsome dissectable functor p.

    zUp, zDown, zLeft, zRight :: p p (p, [ p (p) (p)]) Maybe (p, [ p (p) (p)])

    I leave zLeft as an exercise, to follow the implementation of theleftward step operation, but the other three are straightforward usesofplug{-p-} and right{-p-}. This implementation corresponds quite

    closely to the Generic Haskell version from (Hinze et al. 2004), butrequires a little less machinery.

    zUp (t, [ ]) = NothingzUp (t, pd : pds) = Just (In (plug{-p -} t pd), pds)

    zDown (In pt, pds) = case right{-p -} (L pt) ofL (t, pd) Just (t, pd: pds)

    R NothingzRight (t, [ ]) = NothingzRight (t :: p, pd: pds) = case right{-p -} (R (pd, t)) of

    L (t, pd) Just (t, pd : pds)R ( :: p (p)) Nothing

    Notice that I had to give the typechecker a little help in thedefinition of zRight. The trouble is that is not known to beinvertible, so when we say right{-p-} (R (pd, t)), the type of pddoes not actually determine pits easy to forget that the{-p-} isonly a comment. Ive forced the issue by collecting p from the typeof the input tree and using it to fix the type of the far right failurecase. This is perhaps a little devious, but when type inference iscompulsory, what can one do?

    6. Division: No Clowns!The derivative is not the only interesting special case of dissection.In fact, my original motivation for inventing dissection was to findan operator for leftmost on suitable functors p which wouldinduce an isomorphism reminiscent of the remainder theorem inalgebra.

    p x = (x, p x) + p Zero

    This p x is the quotient of p x on division by x, andit represents whatever can remain after the leftmost element ina p x has been removed. Meanwhile, the remainder, p Zero,represents those ps with no elements at all. Certainly, the finitely-sized containers should give us this isomorphism, but what is ?Its the context of the leftmost hole. It should not be possible tomove any further left, so there should be no clowns! We need

    p x = p Zero x

    For the polynomials, we shall certainly have

    divide :: p p p x (x, p Zero x) + p Zerodivide px = right{-p -} (L px)

    To compute the inverse, I could try waiting for you to implementthe leftward step: I know we are sure to reach the far left, for youronly alternative is to produce a clown! However, an alternative is atthe ready. I can turn a leftmost hole into any old hole if I have

    inflateFst :: Bifunctor p p Zero y p x yinflateFst = unsafeCoerce -- faster than bimap magic id

    Now, we may just take

    divide :: p p (x, p Zero x) + p Zero p xdivide (L (x, pl)) = plug{-p -} x (inflateFst pl)divide (R pz) = inflate pz

    It is straightforward to show that these are mutually inverse byinduction on polynomials.

    7. A Generic Abstractor

    So far this has all been rather jolly, but is it just a mathematicalamusement? Why should I go to the trouble of constructing anexplicit context structure, just to write a fold you can give directlyby higher-order recursion? By way of a finale, let me present amore realistic use-case for dissection, where we exploit the first-order representation of the context by inspecting it: the task is to

    Clowns and Jokers 5 2007/7/17

  • 8/8/2019 Clowns to the left of me, Jokers to the right

    6/8

    abstract all occurrences of one term from another, in a generic first-order syntax.

    7.1 Free Monads and Substitution

    What is a generic first-order syntax? A standard way to get holdof such a thing is to define the free monad p of a (container-like)functor p (Barr and Wells 1984).

    data p x = V x | C (p (p x))

    The idea is that p represents the signature of constructors in oursyntax, just as it represented the constructors of a datatype in thep representation. The difference here is that p x also contains free variables chosen from the set x. The monadic structure of p

    is that of substitution.

    instance Functor p Monad (p) wherereturn x = V xV x >>= = xC pt>>= = C (fmap (>>=) pt)

    Here >>= is the simultaneous substitution from variables in one setto terms over another. However, its easy to build substitution fora single variable on top of this. If we a term t over Maybe x, we

    can substitute some s for the distinguished variable, Nothing. Letus rename Maybe to S, successor, for the occasion:

    type S = Maybe

    () :: Functor p p (S x) p x p xt s = t>>= where

    Nothing = s (Just x) = V x

    Our mission is to compute the most abstract inverse to (s), forsuitable p and x, some

    () :: ... p x p x p (S x)

    such that (t s) s = t, and moreover that fmap Just s occursnowhere in ts . In order to achieve this, weve got to abstract every

    occurrence of s in t as V Nothing and apply Just to all the othervariables. Taking t s = fmap Just t is definitely wrong!

    7.2 Indiscriminate Stop-and-Search

    The obvious approach to computing t s is to traverse t checkingeverywhere if weve found s . We shall need to be able to test equal-ity of terms, so we first must confirm that our signature functor ppreserves equality, i.e., that we can lift equality eq on x to equality eq on p x.

    class PresEq p where ::(x x Bool) p x p x Bool

    instance Eq a PresEq (K1 a) whereK1 a1 eq K1 a2 = a1 a2

    instance PresEq Id whereId x1 eq Id x2 = eq x1 x2

    instance (PresEq p, PresEq q) PresEq (p +1 q) whereL1 p1 eq L1 p2 = p1 eq p2R1 q1 eq R1 q2 = q1 eq q2

    eq = False

    instance (PresEq p, PresEq q) PresEq (p 1 q) where(p1 ,1 q1 ) eq (p2 ,1 q2) = p1 eq p2 q1 eq q2

    instance (PresEq p, Eq x) Eq (p x) whereV x V y = x yC ps C pt = ps pt

    = False

    We can now make our first attempt:

    () :: (Functor p, PresEq p, Eq x) p x p x p (S x)t s | t s = V NothingV x s = V (Just x)C pt s = C (fmap (s) pt)

    Here, Im exploiting Haskells Boolean guards to test for a matchfirst: only if the fails do we fall through and try to search moredeeply inside the term. This is short and obviously correct, but its

    rather inefficient. If s is small and t is large, we shall repeatedlycompare s with terms which are far too large to stand a chance ofmatching. Its rather like testing if xs has suffix ys like this.

    hasSuffix :: Eq x [x] [x] BoolhasSuffix xs ys | xs ys = TruehasSuffix [ ] ys = FalsehasSuffix (x : xs) ys = hasSuffix xs ys

    If we ask hasSuffix "xxxxxxxxxxxx" "xxx", we shall test ifx x thirty times, not three. Its more efficient to reverseboth lists and checkonce for a prefix. With fast reverse, this takeslinear time.

    hasSuffix :: Eq x [x] [x] BoolhasSuffix xs ys = hasPrefix (reverse xs) (reverse ys)

    hasPrefix :: Eq x [x] [x] BoolhasPrefix xs [ ] = TruehasPrefix (x : xs) (y : ys) | x y = hasPrefix xs yshasPrefix = False

    7.3 Hunting for a Needle in a Stack

    We can adapt the reversal idea to our purposes. The divide func-tion tells us how to find the leftmost position in a polynomial con-tainer, if it has one. If we iterate divide, we can navigate our waydown the left spine of a term to its leftmost leaf, stacking the con-texts as we go. Thats a way to reverse a tree!

    A leaf is either a variable or a constant. A term either is a leafor has a leftmost subterm. To see this, we just need to adapt dividefor the possibility of variables.

    data Leaf p x = VL x | CL (p Zero)

    leftOrLeaf :: p p p x (p x, p Zero (p x)) + Leaf p x

    leftOrLeaf (V x) = R (VL x)leftOrLeaf (C pt) = fmap CL (divide pt)

    Now we can reverse the term we seek into the form of a needlealeaf with a straight spine of leftmost holes running all the way backto the root

    needle :: p p p x (Leaf p x, [ p Zero (p x)])needle t = grow t [ ] where

    grow t pls = case leftOrLeaf t ofL (t, pl) grow t (pl : pls)R l (l, pls)

    Given this needle representation of the search term, we can imple-

    ment the abstraction as a stack-driven traversal, hunt which tries fora match only when it reaches a suitable leaf. We need only checkfor our needle when were standing at the end of a left spine at leastas long. Let us therefore split our state into an inner left spine andan outer stack of dissections.

    () :: ( p p, PresEq p, PresEq2 p, Eq x) p x p x p (S x)

    t s = hunt t [ ] [ ] where(neel, nees) = needle shunt t spi stk = case leftOrLeaf t of

    L (t, pl) hunt t (pl : spi) stkR l check spi nees (l neel)

    wherecheck =

    Clowns and Jokers 6 2007/7/17

  • 8/8/2019 Clowns to the left of me, Jokers to the right

    7/8

    Current technology for type annotations makes it hard for me towrite hunts type in the code. Informally, its this:

    hunt :: p x [p (p x)] [ p (p (S x)) (p x)] p (S x)

    Now, check is rather like hasPrefix, except that Ive used a littleaccumulation to ensure the expensive equality tests happen after

    the cheap length test.

    check spi [ ] True = next (V Nothing) (spi ++ stk)check (spl : spi) (npl : nees) b =

    check spi nees (b spl magic | npl)check = next (leafS l) (spi ++ stk) where

    leafS (VL x) = V (Just x)leafS (CL pz) = C (inflate pz)

    For the equality tests we need | , the bifunctorial analogue of, although as were working with p, we can just use magic totest equality of clowns. The same trick works for Leaf equality:

    instance (PresEq p, Eq x) Eq (Leaf p x) whereVL x VL y = x yCL a CL b = a magic b

    = FalseNow, instead of returning a Bool, check must explain how to

    move on. If our test succeeds, we must move on from our matchingsubterms position, abstracting it: we throw away the matchingprefix of the spine and stitch its suffix onto the stack. However, ifthe test fails, we must move right from the current leafs position,injecting it into p (S x) and stitching the original spine to thestack. Stitching (++) is just a version of append which inflates aleftmost hole to a dissection.

    (++) :: Bifunctor p [p Zero y] [p x y] [p x y][ ] ++ pxys = pxys(pzy : pzys) ++ pxys = inflateFst pzy : pzys ++ pxys

    Correspondingly, next tries to move rightwards given a newterm and a stack. If we can go right, we get the next old term

    along, so we start hunting again with an empty spine.

    next t (pd : stk) = case right{-p -} (R (pd, t)) ofL (t, pd) hunt t [ ] (pd : stk)R pt next (C pt) stk

    next t [ ] = t

    If we reach the far right of a p, we pack it up and pop on out. If werun out of stack, were done!

    8. Discussion

    The story of dissection has barely started, but I hope I have com-municated the intuition behind it and sketched some of its poten-tial applications. Of course, whats missing here is a more semanticcharacterisation of dissection, with respect to which the operational

    rules for p may be justified.It is certainly straightforward to give a shapes-and-positions

    analysis of dissection in the categorical setting of containers (Ab-bott et al. 2005a), much as we did with the derivative (Abbott et al.2005b). The basic point is that where the derivative requires ele-ment positions to have decidable equality (am I in the hole?), dis-section requires a total order on positions with decidable trichotomy(am I in the hole, to the left, or to the right?). The details, however,deserve a paper of their own.

    I have shown dissection for polynomials here, but it is clear thatwe can go much further. For example, the dissection oflistgives alist of clowns and a list of jokers:

    [ ] = [ ] 2 [ ]

    Meanwhile, the chain rule, for functor composition, becomes

    (p 1 q) = q 2 ( p) 2 ( q; q)

    where

    data (p 2 (q; r)) c j = (p (q c j) (r c j)) 2 (; )

    That is, we have a dissected p, with clown-filled qs left of the hole,joker-filled qs right of the hole, and a dissected q in the hole. If youspecialise this to division, you get

    (p 1 q) x = q x p (q Zero) (q x)

    The leftmost x in a p (q x) might not be in a leftmost p position:there might be q-leaves to the left of the q-node containing thefirst element. That is why it was necessary to invent to define, an operator which deserves further study in its own right. Forfinite structures, its iteration gives rise to a power series formulationof datatypes directly, finding all the elements left-to-right, whereiterating finds them in any order. There is thus a significantconnection with the notion of combinatorial species as studied byJoyal (Joyal 1986) and others.

    The whole development extends readily to the multivariate case,

    although this a little more than Haskell can take at present. Thegeneral i dissects a mutli-sorted container at a hole of sort i,and splits all the sorts into clown- and joker-variants, doublingthe arity of its parameter. The corresponding i finds the contextsin which an element of sort i can stand leftmost in a container.This corresponds exactly to Brzozowskis notion of the partialderivative of a regular expression (Brzozowski 1964).

    But if there is a message for programmers and programminglanguage designers, it is this: the miserablist position that typesexist only to police errors is thankfully no longer sustainable, oncewe start writing programs like this. By permitting calculations oftypes and from types, we discover what programs we can have, justfor the price of structuring our data. What joy!

    References

    Michael Abbott, Thorsten Altenkirch, and Neil Ghani. Containers- constructing strictly positive types. Theoretical Computer Sci-ence, 342:327, September 2005a. Applied Semantics: SelectedTopics.

    Michael Abbott, Thorsten Altenkirch, Neil Ghani, and ConorMcBride. for data: derivatives of data structures. FundamentaInformaticae, 65(1&2):128, 2005b.

    Michael Barr and Charles Wells. Toposes, Triples and Theories,chapter 9. Number 278 in Grundlehren der MathematischenWissenschaften. Springer, New York, 1984.

    Richard Bird and Oege de Moor. Algebra of Programming. Pren-tice Hall, 1997.

    Janusz Brzozowski. Derivatives of regular expressions. Journal ofthe ACM, 11(4):481494, 1964.

    Jeremy Gibbons. Datatype-generic programming. In Roland Back-house, Jeremy Gibbons, Ralf Hinze, and Johan Jeuring, editors,Spring School on Datatype-Generic Programming, volume 4719of Lecture Notes in Computer Science. Springer-Verlag, 2007.To appear.

    Thomas Hallgren. Fun with functional dependencies. In JointWinter Meeting of the Departments of Science and ComputerEngineering, Chalmers University of Technology and GoteborgUniversity, Varberg, Sweden., January 2001.

    Ralf Hinze, Johan Jeuring, and Andres Loh. Type-indexed datatypes. Science of Computer Programmming, 51:117151, 2004.

    Clowns and Jokers 7 2007/7/17

  • 8/8/2019 Clowns to the left of me, Jokers to the right

    8/8

    Gerard Huet. The Zipper. Journal of Functional Programming, 7(5):549554, 1997.

    Patrik Jansson and Johan Jeuring. PolyPa polytypic program-ming language extension. In Proceedings of POPL 97, pages470482. ACM, 1997.

    Andre Joyal. Foncteurs analytiques et especes de structures. In

    Combinatoire enumerative, number 1234 in LNM, pages 126 159. 1986.

    Conor McBride. The Derivative of a Regular Type is its Type ofOne-Hole Contexts. Available at http://www.cs.nott.ac.uk/ctm/diff.pdf, 2001.

    Conor McBride. Faking It (Simulating Dependent Types inHaskell). Journal of Functional Programming, 12(4& 5):375392, 2002. Special Issue on Haskell.

    Matthias Neubauer, Peter Thiemann, Martin Gasbichler, andMichael Sperber. A Functional Notation for Functional De-pendencies. In The 2001 ACM SIGPLAN Haskell Workshop,Firenze, Italy, September 2001.

    Clowns and Jokers 8 2007/7/17