<<

LambdaPix technical report 2009-01, March 2009 (minor revisions January 28, 2016) 1

Denotational design with type class morphisms (extended version)

Conal Elliott LambdaPix [email protected]

Abstract little. It is form without essence. Users of this abstraction care about Type classes provide a mechanism for varied implementations of what functionality these names have. They care what the names standard interfaces. Many of these interfaces are founded in mathe- mean. matical tradition and so have regularity not only of types but also of Which leads to the question: what do we mean by “mean”? properties (laws) that must hold. Types and properties give strong What is the essence of a type, enlivening its form? One useful an- guidance to the library implementor, while leaving freedom as well. swer is given by denotational semantics. The meaning of a program Some of this remaining freedom is in how the implementation is a type of mathematical object (e.g., numbers, sets, func- works, and some is in what it accomplishes. tions, tuples). The meaning of each operation is defined as a func- To give additional guidance to the what, without impinging on tion from the meanings of its arguments to the meaning of its result. the how, this paper proposes a principle of type class morphisms For instance, the meaning the type Map k v could be partial func- (TCMs), which further refines the compositional style of denota- tions from k to v. In this model, empty is the completely undefined tional semantics. The TCM idea is simply that the instance’s mean- function, insert extends a partial function, and lookup is just func- ing follows the meaning’s instance. This principle determines the tion application, yielding ⊥ where undefined. The meaning of the meaning of each type class instance, and hence defines correctness type and of its operations can be spelled out precisely and simply, of implementation. It also serves to transfer laws about a type’s se- as we will see throughout this paper. mantic model, such as the class laws, to hold for the type itself. In some cases, it provides a systematic guide to implementation, and Haskell provides a way to organize interfaces via type classes in some cases, valuable design feedback. (Wadler and Blott 1989; Jones 1993). Library designers can present The paper is illustrated with several examples of types, mean- parts of a type’s as instances of standard type classes, ings, and morphisms. which then provides the library’s users with standard vocabularies, thus making the library more easily learned. In addition to reducing learning effort, type class instances make libraries more useful, 1. Introduction thanks to other libraries that contain functionality that works across Data types play a central role in structuring our programs, whether all instances of given type classes. checked statically or dynamically. Data type representations col- Type classes provide more than names and types of operations. lect related pieces of information making its use more convenient. They also specify laws to be satisfied by any instance. For example, Adding data abstraction gives a clean separation between a type’s a Monoid instance must not only define a ∅ value and a binary interface and its implementation. The ideal abstraction is as simple (⊕) operation of suitable types (called “mempty” and “mappend” as possible, revealing everything the users need, while shielding in Haskell). Also, ∅ must be a left and right identity for (⊕), and them from implementation complexity. This shield benefits the im- (⊕) must be associative. Thus a type class determines part of the plementor as well, who is free to improve hidden implementation essence, as well as the form, of each of its instances. details later, without breaking existing uses. What about the rest of the meaning of a type class instance–the What of a thing is an interface that can connect implemen- semantic freedom remaining after the types and laws have had their tors with users while still serving the distinct needs of each? say? This paper suggests a principle for answering that question: Part of the answer, which might be named the “form”, is a collection of names of data types and names and types of operations The instance’s meaning follows the meaning’s instance. that work on them. For instance, for a finite map, the interface may That is, the meaning of each method application is given by ap- include operations for creation, insertion, and query: plication of the same method to the meanings of the arguments. In Map :: ∗ → ∗ → ∗ more technical terms, the semantic function is to be a type class empty :: (...) ⇒ Map k v morphism, i.e., it preserves class structure. insert :: (...) ⇒ k → v → Map k v → Map k v For example, suppose we want to define a Monoid instance for our finite map type. The type class morphism (TCM) principle tells lookup :: (Eq k...) ⇒ Map k v → k → Maybe v us that the meaning of ∅ on maps must be ∅ for partial functions, The type signatures will eventually include additional limitations and the meaning of (⊕) of two maps is the (⊕) of the partial (constraints) on the type parameters. The representation of Map functions denoted by those maps. and the implementation of its operations are not revealed. By itself, the form of the interface does not deliver the promised This paper provides several examples of types and their mean- shield. Although it successfully hides implementation details, it ings. Sometimes the TCM property fails, and when it does, exami- fails to reveal an adequate replacement. While the implementation nation of the failure leads to a simpler and more compelling design reveals too much information to users, the signatures provide too for which the principle holds. In each case, class laws are guaran- 2 Denotational design with type class morphisms (extended version) teed to hold, thanks to the morphisms, and so need not be proved A semantics for Map then consists of a model, as given above, specifically. The laws thus come, if not “for free”, then “already and an interpretation for each member of the interface. paid for”. Often, for a simple and fitting semantic model, some- [[·]]:: Map k v → (k → Maybe v) one already has done the hard work of verifying class laws, so the library designer can smile and accept the gift. When the model is [[empty]] = λk → Nothing unusual or complex enough that the work has not been done, it may [[insert k 0 v m]] = λk → if k ≡ k 0 then Just v else [[m]] k be that either the model can be improved, or someone can do the [[lookup m k]] = [[m]] k hard work for the model and share it with others. If it is true, as I Many more functions on maps can be defined semantically within believe, that good semantic models tend to be reusable, then there this model, such as a left-biased “union”: is leverage to be gained from TCMs. Adopting the discipline illustrated in this paper requires addi- unionL :: (...) ⇒ Map k v → Map k v → Map k v tional up-front effort in clarity of thinking, just as static typing does. [[ma ‘unionL‘ mb]] = λk → [[ma]] k ‘mbLeft‘ [[mb]] k The reward is that the resulting designs are simple and general, and mbLeft :: Maybe v → Maybe v → Maybe v sometimes have the feel of profound inevitability—as something mbLeft (Just v) = Just v beautiful we have discovered, rather than something functional we mbLeft Nothing mb0 = mb0 have crafted. A gift from the gods. Other functions can be defined in terms of simpler functions. 2. Denotational semantics and data types For instance, a map defined for only a single key is semantically equivalent to one made via empty and insert. Denotational semantics is a compositional style for precisely speci- fying the meanings of languages, invented by Christopher Strachey singleton :: (...) ⇒ k → v → Map k v and Dana Scott in the 1960s (Scott and Strachey 1971; Stoy 1977). singleton k v ≡ insert k v empty The idea is to specify, for each syntactic category C, Given this relationship, an explicit semantics for singleton would • a mathematical model [[C]] of meanings, and be redundant. What is the meaning of equality (i.e., (≡)) here? The answer • a semantic function [[·]] :: C → [[C]]. C used throughout this paper is that equality is semantic, i.e., Moreover, the various [[·]] must be compositional, i.e.,must be C a ≡ b ⇐⇒ [[a]] ≡ [[b]] defined by (mutual) structural recursion. Notationally, “[[·]]C c” We can use lookup to find out whether a key has a correspond- is shortened to “[[c]]C”, and when unambiguous, “[[·]]C ” will be shortened to “[[·]]”. ing value, i.e., whether the key is in the map’s domain. Suppose we Similarly, we can apply denotational semantics to data types want to know what the domain is without having to query? Maybe within a language to give precise meaning, independent of its we want to know the size of the map’s domain (number of defined implementation. Doing so yields insight into the essence of a type, keys). which may lead to its improvement, or to informed choices about its size :: Map k v → Integer use. It also supports clear reasoning while implementing or using [[size m]] = |{k | [[m]] k 6≡ Nothing}| the type. As an example, consider a data type of finite maps from keys This semantics does not give much hint of how to implement size. to values. The type is abstract, available only through an explicit interface that does not reveal its representation. A central question 3. Simplicity is “What does a map mean?” In other words, “A map is a repre- Most of the time, we programmers reason casually and informally sentation of what mathematical object?” A simple first answer is about our programs, and such reasoning is useful. Sometimes we a partial function from values to keys. Next, we’ll want to be clear want to make sure that our casual reasoning is valid, so precision about the sense of “partial” here. When a map is queried for a miss- tools are useful. For instance, an important aspect of software ing key, we might want the map to yield an error (semantically ⊥). design is simplicity of use. Specifying semantics precisely gives More likely, we’ll want an indication that allows for graceful re- 1 covery. For this reason, it’s appealing to model a map’s partiality us a precise way to measure and compare simplicity of designs. via a success/failure type, for which Haskell’s Maybe type is well Moreover, and of great practical importance, simpler designs are suited. Thus a workable model for maps is easier to reason about, giving us the opportunity to reason further and more deeply. Benefits to software include wider applicability, [[Map k v]] = k → Maybe v easier use, and better implementation performance. For a language, the meaning function is defined recursively over The model we used for maps is fairly simple, k → Maybe v. the abstract syntactic constructors. This practice transfers directly Can we simplify it further? It only has two parts, (→) and Maybe. to algebraic data types. We are doing something different, however, The function part is essential to what a map is, while the Maybe which is to define the meaning of an interface, without any refer- part is an encoding of partiality. ence to representation. 1 Return now to the interface from Section1: In my experience, simplicity often brings generality along with it. When I design an interface, I usually have in mind some things I want to do abstract type Map :: ∗ → ∗ → ∗ with it and how I want it to behave for those things. A complex design is able to address each of those uses and desired behaviors specifically. empty :: (...) ⇒ Map k v A simple design, however, requires achieving these specific goals without insert :: (...) ⇒ k → v → Map k v → Map k v correspondingly specific design features. Instead, the design must make lookup :: (Eq k...) ⇒ Map k v → k → Maybe v do with less specifics, by exploiting more general principles. As a result, unforeseen uses are more likely to be covered as well. The omitted additional type constraints contribute only to the im- “Perfection is achieved not when there is nothing left to add, but when there plementation and not the semantics. (With Ord k for insert and is nothing left to take away” (Antoine de Saint-Exupery).´ In mystical terms, lookup, the implementation can use a balanced tree representation simplicity tugs the human designer out of the way and into the flow of the (Adams 1993).) master Designer (Mathematics, God, The Tao, the elegant universe, etc). LambdaPix technical report 2009-01, March 2009 (minor revisions January 28, 2016) 3

One way to simplify our model is to keep just the function part, class Monoid o where and factor out the Maybe. Think of k → Maybe v not as a partial ∅ :: o map from k to v, but as a total map from k to Maybe v. Then (⊕) :: o → o → o simplify and generalize to total maps to arbitrary types.2 Haskell’s mempty and mappend are ∅ and (⊕), respectively. The abstract type TMap k v -- total map required laws are identity and associativity: [[TMap k v]] = k → v a ⊕ ∅ ≡ a The interface for Map doesn’t quite fit TMap, so let’s make ∅ ⊕ b ≡ b some changes: a ⊕ (b ⊕ c) ≡ (a ⊕ b) ⊕ c constant :: (...) ⇒ v → TMap k v update :: (...) ⇒ k → v → TMap k v → TMap k v Is our type Map a b of partial maps a monoid? To answer sample :: (Eq k...) ⇒ TMap k v → k → v “yes”, we’ll have to find definitions for ∅ and (⊕) that satisfy the required types and properties. The types suggest a likely guess: • In place of an empty Map, we can have a constant TMap. instance Monoid (Map k v) where • Instead of inserting a key/value pair (possibly overwriting), ∅ = empty we’ll update a key (definitely overwriting). (⊕) = unionL • Sampling a map to a key always has a defined value. It’s straightforward to show that Map satisfies the monoid laws. As one might guess, simplifying the semantic model also sim- The crucial lemmas are that Nothing is a left and right identity for plifies the semantic function: mbLeft and mbLeft is associative. [[·]]:: TMap k v → (k → v) [[ma ⊕ ∅]] [[constant v]] = λk → v ≡ { (⊕) on Map } 0 0 [[update k v m]] = λk → if k ≡ k then v else [[m]] k [[ma ‘unionL‘ empty]] [[sample m k]] = [[m]] k ≡ { definition of unionL } [[unionWith mbLeft ma empty]] We can mimic partial maps in terms of total maps: ≡ { semantics of unionWith } type Map k v = TMap k (Maybe v) λk → [[ma]] k ‘mbLeft‘ [[empty]] k empty = constant Nothing ≡ { semantics of ∅ } insert k 0 v m = update k 0 (Just v) m λk → [[ma]] k ‘mbLeft‘ Nothing lookup m k = sample m k ≡ { lemma } λk → [[ma]] k What can a union of total maps mean? For Map, union had L L ≡ { η reduction } to handle the possibility that both maps assign a value to the same [[ma]] key. With TMap, there will always be conflicting bindings. The conflict resolution strategy for Map is specific to Maybe. We can The other proofs are similar. simplify the design by passing a combining function: What about TMap? Since total maps assign a value for every unionWith :: (...) ⇒ (a → b → c) key, ∅ will have to come up with a value from no information. → TMap k a → TMap k b → TMap k c Similarly, (⊕) will have to combine the two values it finds, without being given a specific combination function. Where do we get the [[unionWith f ma mb]] = λk → f ([[ma]] k) ([[mb]] k) empty value and the combining function? From another monoid. This unionWith function is simpler (semantically) than unionL on Map. As the type shows, it is also more general, allowing maps instance Monoid v ⇒ Monoid (TMap k v) where of different value types. ∅ = constant ∅ Some of our gained simplicity is illusory, since now the client (⊕) = unionWith (⊕) of unionWith must provide a definition of f . However, we can provide functionality that is as easy to use, using our definition of This instance satisfies the monoid laws, which is easier to show Map k v as TMap k (Maybe v). than for Map. The simplified reasoning testifies to the value of the simpler semantic model. unionL :: (...) Map k v → Map k v → Map k v However, there is a subtle problem with these two Monoid unionL ≡ unionWith mbLeft instances. Can you spot it? (Warning: Spoiler ahead.) Section3 defined Map in terms of TMap. Given that definition, This definition of unionL is semantically equivalent to the one in Section2. the Monoid instance for TMap imposes a Monoid for the more specific Map type. Are these two instances for Map consistent? Look at the standard Monoid instance for Maybe values: 4. Type classes Type classes provide a handy way to package up parts of an inter- instance Monoid o ⇒ Monoid (Maybe o) where face via a standard vocabulary. Typically, a type class also has an ∅ = Nothing an associated collection of rules that must be satisfied by instances Just a ⊕ Nothing = Just a of the class. Nothing ⊕ Just b = Just b For instance, Map can be made an instance of the Monoid Just a ⊕ Just b = Just (a ⊕ b) class, which is Since constant Nothing ≡ constant ∅, the two definitions 2 For simplicity of presentation, this paper does not use the more strictly of ∅ for Map agree. So far, so good. Next, recall the combining compositional form: [[TMap k v]] = [[k]] → [[v]]. function used to define unionL on partial maps: 4 Denotational design with type class morphisms (extended version)

mbLeft :: Maybe v → Maybe v → Maybe v Now we’re ready to get to the heart of this paper, which is a mbLeft (Just v) = Just v synergy of the two disciplines of denotational semantics and type mbLeft Nothing mb0 = mb0 classes.

This combining function gives unionL its left bias. When we 5.1 Monoid define Map k v = TMap k (Maybe v), two changes result: the Consider again the Monoid instance for total maps: left bias is lost, and a constraint is added that v must be a monoid. So, no, the imposed Monoid instance for Map is not consistent instance Monoid v ⇒ Monoid (TMap k v) where with its desired, original meaning. ∅ = constant ∅ We could eliminate this inconsistency by defining Map from (⊕) = unionWith (⊕) scratch rather than via TMap. This solution comes at the cost of Now recast it into semantic terms, with a “semantic instance”, added complexity, overall. Fortunately, there is another solution specifying the meaning, rather than the implementation, of a type that improves rather than degrades simplicity: fix the semantic class instance: model for Map. The source of the inconsistency is that Maybe has a Monoid instancesem Monoid v ⇒ Monoid (TMap k v) where instance, but it’s the wrong one. It’s unbiased where we want left- [[∅]] = [[constant ∅]] biased. The type’s representation suits our needs, but its associated [[(⊕)]] = [[unionWith (⊕)]] instance does not. So, let’s keep the representation while changing The meanings of constant and unionWith are given in Section3: the type. The Monoid library (Gill et al. 2001) provides some types for [[constant v]] ≡ λk → v this sort of situation, including two wrappers around Maybe: [[unionWith f ma mb]] ≡ λk → f ([[ma]] k) ([[mb]] k) newtype First a = First (Maybe a) Substituting, we get

deriving (Eq, Ord, Read, Show, Functor, ...) instancesem Monoid v ⇒ Monoid (TMap k v) where newtype Last a = Last (Maybe a) [[∅]] = λk → ∅ deriving (Eq, Ord, Read, Show, Functor, ...) [[ma ⊕ mb]] = λk → [[ma]] k ⊕ [[mb]] k The sole purpose of these type wrappers is to replace Maybe’s un- The RHSs (right-hand sides) of these semantic definitions re- biased Monoid instance with a left-biased (First) or right-biased semble an instance in the Monoid library: (Last) instance. instance Monoid b ⇒ Monoid (a → b) where instance Monoid (First a) where ∅ = λa → ∅ ∅ = First Nothing f ⊕ g = λa → f a ⊕ g a l@(First (Just )) ⊕ = l This instance lets us simplify the TMap semantic monoid instance: First Nothing ⊕ r = r instancesem Monoid v ⇒ Monoid (TMap k v) where instance Monoid (Last a) where [[∅]] = ∅ ∅ = Last Nothing [[ma ⊕ mb]] = [[ma]] ⊕ [[mb]] ⊕ r@(Last (Just )) = r l ⊕ Last Nothing = l This property of [[·]] has a special name in mathematics: [[·]] is a monoid homomorphism, or more tersely a “monoid morphism”. This (⊕) for First is just like the function mbLeft used for Note what has happened here. The semantics of the Monoid defining unionL and hence (⊕) for Map. We can solve our con- part of the TMap interface is completely specified by saying that sistency problem by replacing Maybe with First in Map: [[·]] is a morphism for that class. The methods (∅ and (⊕)) on the LHSs refer to the type being type Map k v = TMap k (First v) specified (here TMap k v), while the same methods on the RHSs refer to that type’s meaning (here k → v). The meaning of each With this change, the Monoid instance for Map can disappear method application is given by application of the same method completely. The desired behavior falls out of the Monoid instances on the meanings of the arguments. In other words, the semantic for TMap and First. function is a morphism with respect to the class, i.e., preserves the This definition also translates to a new semantic model for structure defined by the class. partial maps: Besides succinctness, why else might we care that a meaning [[Map k v]] = k → First v function is a monoid morphism? Because this property means that, at least for the Monoid part of the interface, the type behaves like This new version hints of the left-bias of (⊕). It also gives a single its model. As users, we can therefore think of the type as being its point of change if we decide we prefer a right-bias: replace First model. Functions are well-studied, so the experience we have with with Last. the model is a great help in thinking about the type. Our reasoning is shielded from the implementation complexity. The flip side is that we are cut off from reasoning about its operational performance. 5. Type class morphisms What about other type classes, besides Monoid? Section2 illustrated how denotational semantics gives precise meaning to data types, which serves as a basis for casual and pre- 5.2 Functor cise reasoning. Simplicity of semantic models (Section3) improves The Functor interface is generality and ease of reasoning. Section4 then brought in type class Functor f where classes, which give a consistent way to structure interfaces. The se- fmap :: (a → b) → f a → f b mantic models of instances give a basis for proving the associated class properties. with laws: LambdaPix technical report 2009-01, March 2009 (minor revisions January 28, 2016) 5

fmap id ≡ id [[fmap f m]] = fmap f [[m]] fmap (h ◦ g) ≡ fmap h ◦ fmap g [[∅]] = ∅ A total map can be made an instance of Functor. Mapping a [[ma ⊕ mb]] = [[ma]] ⊕ [[mb]] function over a total map applies the function to each value in a In the RHSs, [[·]] is recursively applied to each TMap argument, key/value binding: within exactly the same structure as appears in the LHSs. instancesem Functor (TMap k) where [[fmap f m]] = λk → f ([[m]] k) 5.4 Applicative functor This semantic definition for fmap satisfies the compositional disci- Let’s try one more. The Applicative (applicative functor) type pline of denotational semantics, in that the meaning of fmap f m is class has more structure than Functor, but less than Monad. The defined in terms of the meaning of its TMap argument, m. More- interface: over, this semantics also satisfies the Functor laws: infixl 4 ~ [[fmap id m]] class Functor f ⇒ Applicative f where ≡ { semantics of fmap } pure :: a → f a λk → id ([[m]] k) (~) :: f (a → b) → f a → f b ≡ { definition of id } As usual, this class also comes with collection of laws (McBride λk → [[m]] k and Paterson 2008). ≡ { η contraction } This time, instead of thinking about what Applicative instance [[m]] we might want for TMap, let’s see if the TCM property will tell us. Suppose that TMap is an applicative morphism, i.e., [[fmap (h ◦ g) m]] ≡ { semantics of fmap } instancesem Applicative (TMap k) where λk → (h ◦ g) ([[m]] k) [[pure b]] = pure b ≡ { definition of (◦) } [[mf ~ mx]] = [[mf ]] ~ [[mx]] λk → h (g ([[m]] k)) Indeed, there is an Applicative instance for functions, where ≡ { semantics of fmap } pure and ( ) are the classic K and S combinators: λk → h [[fmap g m]] k ~ ≡ { semantics of fmap } instance Applicative ((→) a) where λk → [[fmap h (fmap g m)]] k pure b = λa → b ≡ { η contraction } h ~ g = λa → (h a)(g a) [[fmap h (fmap g m)]] Substituting the semantic instance (Applicative on functions) Now let’s play with this definition. Write the RHS in point-free in the RHS of our Applicative instance for TMap above yields form, using function composition: instancesem Applicative (TMap k) where [[fmap f m]] = f ◦ [[m]] [[pure v]] = λk → v Next, note the Functor instance for functions: [[mf ~ mx]] = λk → ([[mf ]] k) ([[mx]] k) instance Functor ((→) a) where fmap = (◦) In other words, a pure map is one that maps all keys to the same value; and “application” of a map full of functions to a map full of Our fmap semantics then become arguments is defined pointwise. [[fmap f m]] = fmap f [[m]] Often (~) is used via n-ary lifting functions:

This property of [[·]], often written as [[·]] ◦ fmap f ≡ fmap f ◦ [[·]], liftA2 :: Applicative f ⇒ (a → b → c) also has special name in mathematics: [[·]] is a natural transforma- → f a → f b → f c tion, also called a “morphism on functors” (Mac Lane 1998) or (for liftA3 :: Applicative f ⇒ (a → b → c → d) consistency) a “functor morphism”. → f a → f b → f c → f d ... 5.3 What is a type class morphism? The monoid and functor morphism properties say that the method liftA2 h u v = pure h ~ u ~ v structure is preserved. That is, the interpretation of a method appli- liftA3 h u v w = pure h ~ u ~ v ~ w cation on a type T is the same method applied to the interpretations ... of the type-T arguments. As a design guide, I recommend that any semantic function for For functions, simplifying the RHS of liftA2 gives a type T (a) be as simple as possible without loss of precision, and liftA h u v ≡ λx → h (u x)(v x) (b) be a type class morphism (TCM) with respect to each of the type 2 classes it implements. Consequently, users can think of the type as and similarly for liftA3. being its (simple) model, rather than being an implementation of With these definitions in mind, let’s look again at two of our the model. functions on total maps, from Section3 Another way to describe the TCM property is: constant :: (...) ⇒ v → TMap k v The instance’s meaning follows the meaning’s instance. unionWith :: (...) ⇒ (a → b → c) In other words, meaning preserves class structure, by preserving → TMap k a → TMap k b → TMap k c the structure of each method application, in ways suited to the type [[constant v]] ≡ λk → v of each method. For instance, as shown above for TMap k v, [[unionWith f ma mb]] ≡ λk → f ([[ma]] k) ([[mb]] k) 6 Denotational design with type class morphisms (extended version)

Now we see that constant and unionWith are just synonyms for ≡ { right identity on semantics } pure and liftA2, so we can eliminate the former terms (and their [[m]] definitions) in favor of the Applicative ones. This change gives us more for less: our type’s specification is simpler; and it can be used Associativity: with libraries that work with applicative functors. [[(m >>= f ) >>= g]] We have a last question to answer: Does our Applicative in- ≡ { [[·]] is a monad morphism } stance satisfy the required laws? [[m >>= f ]] >>= [[·]] ◦ g ≡ { [[·]] is a monad morphism } 6. Class laws ([[m]] >>= [[·]] ◦ f ) >>= [[·]] ◦ g Section5 showed that TMap satisfies the Monoid and Functor ≡ { associativity on semantics } laws. Does TMap also satisfy the Applicative laws? We’ll now [[m]] >>= (λx → [[f x]] >>= [[·]] ◦ g) see that the answer is “yes”, simply because TMap is (by con- ≡ { [[·]] is a monad morphism } struction) an applicative morphism. [[m]] >>= (λx → [[f x >>= g]]) Consider, for instance, the composition law. ≡ { definition of (◦) } [[m]] >>= [[·]] ◦ (λx → f x >>= g) pure (◦) u v w ≡ u (v w) ~ ~ ~ ~ ~ ≡ { [[·]] is a monad morphism } We are defining equality semantically, i.e., u ≡ v ⇐⇒ [[u]] ≡ [[v]], [[m >>= λx → f x >>= g]] so the composition law is equivalent to The same reasoning applies to arrows (Hughes 2000) as well. [[pure (◦) ~ u ~ v ~ w]] ≡ [[u ~ (v ~ w)]] One law has a form different from those we’ve looked at so far, which is the extensionality property: If h is onto, then Working left to right, arr h >>> f ≡ arr h >>> g =⇒ f ≡ g [[pure (◦) ~ u ~ v ~ w]] ≡ { [[·]] is an applicative morphism } The proof: [[pure (◦)]] [[u]] [[v]] [[w]] ~ ~ ~ arr h >>> f ≡ arr h >>> g ≡ { [[·]] is an applicative morphism } pure (◦) [[u]] [[v]] [[w]] =⇒ ~ ~ ~ [[arr h >>> f ]] ≡ [[arr h >>> g]] ≡ { composition law on semantics } [[u]] ([[v]] [[w]]) =⇒ { [[·]] is an morphism } ~ ~ [[arr h]] >>> [[f ]] ≡ [[arr h]] >>> [[g]] ≡ { [[·]] is an applicative morphism } [[u]] [[v w]] =⇒ { [[·]] is an arrow morphism } ~ ~ arr h >>> [[f ]] ≡ arr h >>> [[g]] ≡ { [[·]] is an applicative morphism } [[u (v w)]] =⇒ { extensionality on semantics, and h is onto } ~ ~ [[f ]] ≡ [[g]] The proofs for the other laws follow in exactly the same way. =⇒ { semantic equality } These proofs make no use of the specifics of the Applicative f ≡ g instance for TMap. They are, therefore, applicable to every type for which equality is defined by an applicative morphism (e.g., [[·]]). Similar reasoning and conclusions hold for the Monoid, Functor, 7. Type composition Monad, and Arrow classes. As in (Wadler 1990), [[·]] is a monad morphism iff Trying the TCM game with Map in place of TMap reveals a problem. The Monoid case comes out fine, but let’s see what [[return a]] ≡ return a happens with Functor. First, we’ll have to make Map abstract [[u >>= k]] ≡ [[u]] >>= [[·]] ◦ k again (not a synonym) so that we can define a Functor instance. The monad laws: abstract type Map return a >>= f ≡ f a -- left identity [[Map k v]] = k → First v m >>= return ≡ m -- right identity Mapping a function over partial map modifies the defined values: (m >>= f ) >>= g ≡ m >>= (λx → f x >>= g) -- associativity instancesem Functor (Map k) where Left identity: [[fmap f m]] = λk → fmap f ([[m]] k) [[return a >>= f ]] The RHS fmap uses the Functor for First (derived from Maybe). ≡ { [[·]] is a monad morphism } Now if we simplify and re-arrange as with TMap, we get [[return a]] >>= [[·]] ◦ f ≡ { [[·]] is a monad morphism } instancesem Functor (Map k) where return a >>= [[·]] ◦ f [[fmap f m]] = fmap (fmap f ) [[m]] ≡ { left identity on semantics } So [[·]] is not a Functor morphism. [[f a]] A similar difficulty arises with Applicative. The map pure v Right identity: has value v for every key. For a function-valued map mf and an argument-valued map mx, the map mf ~ mx assigns a defined [[m >>= return]] value of f x to a key k if f is the defined value of mf at k and ≡ { [[·]] is a monad morphism } x is the defined value of mx at k. If mf or mx is undefined at k [[m]] >>= [[·]] ◦ return then so is mf ~ mx. This meaning is formalized in the following ≡ { [[·]] is a monad morphism } Applicative instance, which uses the Applicative instance for [[m]] >>= return First (derived from Maybe): LambdaPix technical report 2009-01, March 2009 (minor revisions January 28, 2016) 7

instancesem Applicative (Map k) where ≡ { [[·]]h◦g definition } [[pure v]] = λk → pure v O [[liftA2 (~) hgf hgx]]h [[mf mx]] = λk → [[mf ]] k [[mx]] k ~ ~ ≡ { [[·]]h is an Applicative morphism } Using the Applicative instance for functions, this instance be- O (liftA2 (~) [[hgf ]]h [[hgx]]h) comes ≡ { (~) on [[h]] ◦ g } O [[hgf ]]h ~ O [[hgx]]h instancesem Applicative (Map k) where ≡ { [[·]] definition } [[pure v]] = pure (pure v) h◦g [[O hgf ]]h◦g ~ [[O hgx]] [[mf ~ mx]] = liftA2 (~) [[mf ]] [[mx]] Thus [[·]] is also not an Applicative morphism. Again, these failures look like bad news. Must we abandon the TCM principle, or does the failure point us to a new, and possibly Now redefine Map: better, model for Map, as in Section4? type Map k ≡ TMap k ◦ First The rewritten semantic instances above do not make use of any properties of Map other than being a composition of two functors More explicitly, for the first instance and two applicative functors for the second. [[Map k v]] = [[(TMap k ◦ First) v]] So let’s generalize. As McBride and Paterson(2008) observed, ∼ k → First v Functor and Applicative are closed under composition: = newtype (h ◦ g) a = O (h (g a)) These definitions say exactly what we mean, more directly than the previous definition. A (left-biased) partial map is a composition of instance (Functor h, Functor g) two simpler ideas: total maps and First (left-biased Maybe). Given ⇒ Functor (h ◦ g) where this new, more succinct definition, we can scrap the Functor and fmap f (O hga) = O (fmap (fmap f ) hga) Applicative semantic instance definitions as redundant. instance (Applicative h, Applicative g) It may look like we’ve just moved complexity around, rather ⇒ Applicative (h ◦ g) where than eliminating it. However, type composition is a very reusable pure a = O (pure (pure a)) notion, which is why it was already defined, along with supporting proofs that the Functor and Applicative laws hold. O hgf ~ O hgx = O (liftA2 (~) hgf hgx) Define the meaning of a composition to be a composition: [[(h ◦ g) t]] = ([[h]] ◦ g) t -- types 8. Deriving type class instances [[O hga]] = O [[hga]] -- values Implementations of type class instances can sometimes be derived h◦g h mechanically from desired type class morphisms. Suppose we have 0 0 If [[·]]h is a Functor morphism, then [[·]]h◦g is also a Functor [[·]] :: T → T , where T belongs to one or more classes and [[·]] morphism, and similarly for Applicative. To see why, first consider is invertible. Then, combining [[·]] and [[·]]−1 gives instances that fmap: satisfy the morphism properties. For instance, consider the Monoid morphism properties: [[fmap f (O hga)]]h◦g ≡ { fmap on h ◦ g } [[∅]] ≡ ∅ [[u ⊕ v]] ≡ [[u]] ⊕ [[v]] [[O (fmap (fmap f ) hga)]]h◦g ≡ { [[·]] definition } −1 h◦g Because [[·]] ◦ [[·]] ≡ id, these properties are satisfied if O [[fmap (fmap f ) hga]]h [[[[∅]]]]−1 ≡ [[∅]]−1 ≡ { [[·]]h is a Functor morphism } [[[[u ⊕ v]]]]−1 ≡ [[[[u]] ⊕ [[v]]]]−1 O (fmap (fmap f ) [[hga]]h) ≡ { fmap on [[h]] ◦ g } −1 fmap f (O [[hga]] ) Then, because [[·]] ◦ [[·]] ≡ id, these properties are equivalent to h the following class definition: ≡ { [[·]]h◦g definition } fmap f [[O hga]]h◦g instance Monoid T where ∅ = [[∅]]−1 Then pure: u ⊕ v = [[[[u]] ⊕ [[v]]]]−1 [[pure a]] h◦g By construction, [[·]] is a Monoid morphism. Similarly for the ≡ { pure on h ◦ g } 0 [[O (pure (pure a))]] other type classes. Assuming the class laws hold for T , they hold as well for T , as shown in Section6. ≡ { [[·]] definition } h◦g If [[·]] and [[·]]−1 have implementations, then we can stop here. O [[pure (pure a)]] h Otherwise, or if we want to optimize the implementation, we can ≡ { [[·]]h is an Applicative morphism } do some more work, to rewrite the synthesized definitions. O (pure (pure a)) ≡ { pure on [[h]] ◦ g } pure a 9. Memo tries As an example of synthesizing type class instances, let’s consider Finally, (~): a form of memoization, based on a variant of the total maps from [[O hgf ~ O hgx]]h◦g Section2, namely a complete memo trie. The central idea of the ≡ { (~) on h ◦ g } function memoizer is associating a type of trie to each domain type [[O (liftA2 (~) hgf hgx)]]h◦g we want to memoize over. 8 Denotational design with type class morphisms (extended version)

Following the idea of generic tries (Hinze 2000) and its imple- Hyper-strict functions can be defined purely mathematically, for mentation with associated types (Chakravarty et al. 2005), define a use in specifications only, or they can be defined in the implemen- class of types with trie representations:3 tation language:

class HasTrie a where H newtype a → b = H {unH :: a → b } data () a :: ∗ → ∗ With the condition that the contained a → b is hyper-strict. The type a  b represents a trie that maps values of type a to values of type b. The trie representation depends only on a. With this new and improved semantic domain, we can define a The HasTrie class also contains converters between functions semantic function: and tries: H [[·]]:: (a  b) → (a → b) trie :: (a → b) → (a  b) [[·]] = H ◦ untrie untrie :: (a  b) → (a → b) The reason we can legitimately use H here is that untrie always The untrie and trie methods must be an embedding-projection produces hyper-strict functions. pair: trie ◦ untrie ≡ id 9.2 Type class morphisms regained untrie ◦ trie v id The problem with our first attempt (Section 9.1) was that the se- The reason for (v) is that keys get fully evaluated while building mantic function was not invertible. The new semantic function, and searching the trie structure, even if they are not evaluated by however, is invertible. the function being memoized. −1 H Given the HasTrie class, memoization is trivial to implement: [[·]] :: (a → b) → (a  b) −1 memo :: HasTrie a ⇒ (a → b) → (a → b) [[·]] = trie ◦ unH memo = untrie ◦ trie That [[·]]−1 ◦ [[·]] ≡ id follows as before: The second inverse property implies that memo approximates the −1 identity function (semantically). In practice, memo ≡ hyperstrict, [[[[t]]]] where ≡ { [[·]]−1 and [[·]] definitions } trie (unH (H (untrie t))) hyperstrict :: Hyper a ⇒ (a → b) → (a → b) ≡ { unH ◦ H ≡ id } hyperstrict f a = hyperEval a ‘seq‘ f a trie (untrie t) Here I’ve assumed a hyperEval function to evaluate its argument ≡ { trie ◦ untrie ≡ id } fully. This function could either be built-in magic, or defined as a t method from a type class, Hyper. Multi-argument curried functions can be memoized by repeated To show [[·]] ◦ [[·]]−1 ≡ id, we’ll have to exploit hyper-strictness: uses of memo. For instance, [[[[hf ]]−1]] memo :: (HasTrie a, HasTrie b) ⇒ −1 2 ≡ { [[·]] and [[·]] definitions } (a → b → c) → (a → b → c) H (untrie (trie (unH hf ))) memo2 f = memo (memo ◦ f ) ≡ { untrie ◦ trie ≡ hyperstrict } H (hyperstrict (unH hf )) 9.1 A semantic false start ≡ { unH hf is already hyper-strict } Using [[·]] = untrie as the semantic function looks promising. H (unH hf ) However, untrie has no inverse, simply because it only produces ≡ { H ◦ unH ≡ id } hyper-strict functions. This lack of invertibility means that the hf synthesis technique in Section8 fails to apply. Worse yet, untrie cannot be a monoid morphism for any Because (→H ) is a newtype, H and unH are both strict, so this Monoid instance of a  b. To see why, assume the simplest last step works even if hf ≡ ⊥, The next-to-last step relies on ⊥ morphism property, the Monoid identity: untrie ∅ ≡ ∅. Applying being hyper-strict (trivially true, since ⊥ maps everything to ⊥). trie to both sides, and using trie ◦ untrie ≡ id, it must be that Because [[·]] is invertible, we can synthesize instances for a  b ∅ ≡ trie ∅. It then follows that H for all of the classes that the semantic model (a → b) inhabits, as untrie ∅ ≡ untrie (trie ∅) shown in Section8. As desired, [[·]] is, by construction, a morphism ≡ hyperstrict ∅ with respect to each of those classes. We’re okay if hyperstrict ∅ ≡ ∅, but that is not the case, because ∅ on functions is λx → ∅, which is not even strict (assuming ∅ 6≡ ⊥). 9.3 Some trie representations The conclusion that untrie cannot be a monoid morphism Now let’s consider choices for trie representations. As in (Hinze sounds like a failure, while in fact it gives us helpful informa- 2000), the key is to exploit type isomorphisms. Letting a →S b be tion. It says that untrie cannot be our semantic function and why it the of (head-)strict functions from a to b, cannot. The difficulty came from the presence of non-hyper-strict S functions in the semantic domain, so let’s remove them. Instead of 1 → a =∼ a modeling tries as functions, model them as hyper-strict functions, H S ∼ which we’ll write as “a → b”: (a + b) → c = (a → c) × (b → c) S ∼ 3 This formulation is based on a design from Spencer Janssen. (a × b) → c = a → (b → c) LambdaPix technical report 2009-01, March 2009 (minor revisions January 28, 2016) 9

instance HasTrie () where Similarly for Functor and Applicative. Using the Monoid instance for functions, we can get a more data () a = UnitTrie a  explicit definition of (⊕): trie f = UnitTrie (f ()) untrie (UnitTrie a) = λ() → a hyper (f ⊕ g) instance (HasTrie a, HasTrie b) ⇒ ≡ { (⊕) on functions } hyper (λa → f a ⊕ g a) HasTrie (Either a b) where ≡ { definitions of hyper and hyperstrict } data (Either a b) x = EitherTrie (a x)(b x)    H (λa → hyperEval a ‘seq‘(f a ⊕ g a)) trie f = EitherTrie (trie (f ◦ Left)) (trie (f ◦ Right)) untrie (EitherTrie s t) = either (untrie s)(untrie t) Since f and g were inside an H , they are hyper-strict, so the additional hyper-evaluation of a is unlikely to be needed. Rather instance (HasTrie a, HasTrie b) ⇒ HasTrie (a, b) where than carry it around, let’s add an assumption, which is that (⊕) is data (a, b)  x = PairTrie (a  (b  x)) strict in its first or second argument. Under this assumption, f ⊕ g trie f = PairTrie (trie (trie ◦ curry f )) is already hyper-strict. untrie (PairTrie t) = uncurry (untrie ◦ untrie t) Starting again, H (hyperstrict (f ⊕ g)) Figure 1. Some instances for memo tries ≡ { hyper-strictness of f ⊕ g } H (f ⊕ g) which correspond to the familiar laws of exponents: Now we can show that the monoid laws hold. Start with the right-identity law, hf ⊕ ∅ ≡ hf . There are two cases: hf ≡ H f a1 =∼ a for some hyper-strict f , or hf ≡ ⊥. First take the defined case: ca+b =∼ ca × cb H f ⊕ ∅ H ca×b =∼ (cb)a ≡ { ∅ for a → b } H f ⊕ hyper ∅ (These isomorphisms are slightly simpler than in (Hinze 2000), because they describe total rather than partial maps.) ≡ { hyper definition } The intention is to apply these isomorphisms recursively, but H f ⊕ H (hyperstrict ∅) head-strictness will only take us one level. To go all the way, we’ll ≡ { (⊕) on a →H b } need hyper-strictness. H (hyperstrict (f ⊕ hyperstrict ∅)) H ≡ { assumption on (⊕) } 1 → a ∼ a = H (hyperstrict (hyperstrict (f ⊕ ∅))) H H H (a + b) → c =∼ (a → c) × (b → c) ≡ { monoid right-identity for functions } H (hyperstrict (hyperstrict f )) H ∼ H H (a × b) → c = a →(b → c) ≡ { f is hyper-strict } Writing these type isomorphisms in Haskell: H (hyperstrict f ) H ≡ { f is hyper-strict } () → a =∼ a H f H ∼ H H Either a b → c = (a → c, b → c) The case of hf ≡ ⊥ is easier: H H H (a, b) → c =∼ a →(b → c) ⊥ ⊕ ∅ which leads to the HasTrie instances defined in Figure1. Since ≡ { pattern-match on ⊥ } there is only one (non-bottom) value of type (), a trie over () con- ⊥ tains just a single value, as suggested in the isomorphism equa- tion. A trie for sum-valued domains contains two tries, while a The other two monoid morphism laws follow similarly. trie for pair-valued domains contains nested tries. Tries for other types, such as Bool, can be implemented via isomorphisms using 10. Numeric overloadings the types above, or directly. For instance, Bool is isomorphic to to Either () (). Overloading makes it possible to use familiar and convenient nu- Exercise: Prove that trie ◦ untrie ≡ id and untrie ◦ trie ≡ meric notation for working with a variety of types. The principle hyperstrict for the definitions above. of type class morphisms can help to guide such overloadings, sug- gesting when to use it and how to use it correctly. 9.4 Instances for hyper-strict functions If we want [[·]] to be a monoid morphism, then its range (the 10.1 Functions semantic domain) must be a monoid, and similarly for other type As an example, we can apply numeric notation for manipulating classes. functions. Given functions f and g, what could be the meaning of Indeed, there are simple instances for hyper-strict functions: f + g, f ∗ g, recip f , sqrt f , etc? A useful answer is that the operations are applied point-wise, i.e., instance (Hyper a, Monoid b) ⇒ Monoid (a →H b) where ∅ = hyper ∅ f + g = λx → f x + g x H f ⊕ H g = hyper (f ⊕ g) f ∗ g = λx → f x ∗ g x recip f = λx → recip (f x) where sqrt f = λx → sqrt (f x) hyper = H ◦ hyperstrict ... 10 Denotational design with type class morphisms (extended version)

It’s also handy to add literal numbers to the mix, e.g., 5 ∗ sqrt f , [[pure (fromInteger n)]]x which can mean λx → 5 ∗ sqrt (f x). In Haskell, numeric literals ≡ { [[·]]x is an Applicative morphism } are overloaded, using fromInteger and fromRational, so add pure (fromInteger n) fromInteger n = const (fromInteger n) ≡ { fromInteger on model } fromInteger n And similarly for rational literals. x Thanks to the Functor and Applicative instances for functions [[f + g]] (given in Section5), these interpretations are equivalent to ≡ { (+) on type } x fromInteger = pure ◦ fromInteger [[liftA2 (+) f g]] ≡ { [[·]]x is an Applicative morphism } (+) = liftA2 (+) x x (∗) = liftA2 (∗) liftA2 (+) [[f ]] [[g]] recip = fmap recip ≡ { (+) on model } sqrt = fmap sqrt [[f ]]x + [[g]]x ... This proof makes no use of the specifics of the Functor and With this rephrasing, these definitions can be used not just with Applicative instances. functions, but with any applicative functor. Now show that [[·]]x is indeed a Functor and Applicative This notation is convenient and pretty, but what justifies it, se- morphism: mantically? Looking below the notation, in what sense can func- x tions be interpreted as numbers? [[fmap h f ]] A compelling answer would be a simple function [[·]] mapping ≡ { fmap on functions } functions to a familiar number type, such that the [[·]] is a “nu- [[h ◦ f ]]x meric morphism”, i.e., a morphism over all of the standard numeric ≡ { definition of [[·]]x } classes. Id (h (f x)) Is there such a [[·]]? Yes! And better yet, there’s a great wealth of ≡ { fmap on Id } them. The functions f and g above have type a → b for a numeric fmap h (Id (f x)) type b. Define a family of interpretation functions indexed over a. ≡ { definition of [[·]]x } For all x :: a, fmap h [[f ]] x [[·]] :: (a → b) → b x x [[pure a]] [[h]] = h x ≡ { pure on functions } x Then every [[·]]x is a numeric morphism. To see why, consider two [[const a]] operations. The others all work out similarly.4 ≡ { definition of [[·]]x } x Id (const a x) [[fromInteger n]] ≡ (fromInteger n) x ≡ { definition of const } ≡ (const (fromInteger n)) x Id a ≡ fromInteger n ≡ { pure on Id } [[f + g]]x ≡ (f + g) x pure a ≡ f x + g x x [[hf ~ af ]] ≡ [[f ]]x + [[g]]x ≡ { (~) on functions } [[λz → (hf z)(af z)]]x There is another way to prove the numeric morphisms, which trans- ≡ { definition of [[·]]x } fers to many similar situations. Show that the numeric morphism Id ((hf x)(af x)) properties follow from the second style of definition above, in terms ≡ { (~) on Id } of fmap, pure, and liftA , which is a very common pattern. To 2 ID (hf x) ~ ID (af x) make the proof go through, change the model trivially, to be Id b ≡ { definition of [[·]]x } instead of b, and make use of Id being a functor and applicative [[hf ]] [[af ]] functor. ~ [[·]]x :: (a → b) → Id b 10.2 Errors For now, assume that [[·]]x is a Functor and Applicative mor- For semantic simplicity, errors can be represented as ⊥. If we want phism, and that the numeric instances are defined in terms of fmap, to respond to errors in a semantically tractable way (hence without pure, and Applicative as above. resorting to IO), we’ll want an explicit encoding. One choice is Maybe a, where Nothing means failure and Just s means success x [[fromInteger n]] with values s :: a. Another choice is Either x a, where Left err ≡ { fromInteger on type } means a failure described by err ::x, while Right s means success. Programming with either explicit encoding can be quite tedious, 4 There is a technical difficulty in a Haskell implementation. The Num class but a few well-chosen type class instances can hide almost all of the (and hence its descendants) are required also to implement Eq and Show. routine plumbing of failure and success encodings. The key again The methods of those classes cannot be defined such that [[·]]x is an Eq or is Functor and Applicative. The following instances suffice. Show morphism, because (≡) yields Bool and show yields String, One could perhaps fix this problem by making these classes more morphism- instance Functor (Either x) where friendly or by eliminating them as a superclass of Num. My thanks to fmap (Left x) = Left x Ganesh Sittampalam for pointing out this issue. fmap f (Right y) = Right (f y) LambdaPix technical report 2009-01, March 2009 (minor revisions January 28, 2016) 11

instance Applicative (Either x) where ≡ pure y pure y = Right y Left x = Left x ~ [[Left x ~ y]] ≡ [[Left x]] ~ Left x = Left x ≡ Id ⊥ Right f Right x = Right (f x) ~ ≡ Id ⊥ ~ [[y]] A simple semantics for Either forgets the error information, ≡ [[Left x]] ~ [[y]] replacing it with ⊥: [[·]]:: Either e a → a [[Right f ~ Left x]] ≡ [[Left x]] [[Left e]] = ⊥ ≡ Id ⊥ [[Right a]] = a ≡ Id (f ⊥) -- if f is strict ≡ Id f ~ Id ⊥ To give Either e a numeric instances, follow the same tem- ≡ [[Right f ]] ~ [[Left x]] plate as with functions (Section 10.1), e.g., (+) = liftA2 (+). The numeric morphism properties hold only if the numeric methods on the type a are strict. For an n-ary function h that is strict in all n [[Right f ~ Right x]] ≡ [[Right (f x)]] arguments: ≡ Id (f x) ≡ Id f ~ Id x [[liftA f e ... e ]] ≡ f [[e ]] ... [[e ]] n 1 n 1 n ≡ [[Right f ]] ~ [[Right x]] where fmap ≡ liftA1. The relevance of (⊥-)strictness here is that (~) on Either yields a Left if either argument is a Left. For 10.3 Expressions instance, consider fmap: Another use of numeric overloading is for syntax manipulation, as [[fmap f (Left x)]] in compiling domain-specific embedded languages (Elliott et al. ≡ { fmap for Either x } 2003; Augustsson et al. 2008). In this context, there is a parame- [[Left x]] terized type of numeric expressions, often an . ≡ { definition of [[·]] } Using generalized algebraic data types (Peyton Jones et al. 2006) ⊥ helps with static typing. ≡ { strictness of f } f ⊥ 10.3.1 Simple expressions ≡ { definition of [[·]] } A simple representation for expressions replaces each method with f [[Left x]] a constructor:

The other liftAn are proved similarly. Assuming (+) is strict then, data E :: ∗ → ∗ where [[e + e0]] FromInteger :: Num a ⇒ Integer → E a ≡ { (+) on Either x y } Add :: Num a ⇒ E a → E a → E a 0 [[liftA2 (+) e e ]] Mult :: Num a ⇒ E a → E a → E a ≡ { (+) is strict } ... [[e]]+ [[e0]] FromRational :: Fractional a ⇒ Rational → E a Recip :: Fractional a ⇒ E a → E a liftA The semantic property on n above is nearly a morphism ... property, but the liftAn is missing on the right. We can restore it by changing the semantic domain: A convenient way to build up expressions is through numeric over- newtype Id a = Id a loading, e.g., [[·]]:: Either e a → Id a instance Num a ⇒ Num (E a) where [[Left e]] = Id ⊥ fromInteger = FromInteger [[Right a]] = Id a (+) = Add (∗) = Mult [[·]] is almost a Functor and Applicative morphism, but not quite, ... because of the possibility of non-strict functions. The proof at- tempts: instance Fractional a ⇒ Fractional (E a) where fromRational = FromRational [[fmap f (Left x)]] ≡ [[Left x]] recip = Recip ≡ Id ⊥ ... ≡ Id (f ⊥) -- if f is strict ≡ fmap f (Id ⊥) Expressions are not just representations; they have meaning. To ≡ fmap f [[Left x]] make that meaning precise, define a semantic function: [[·]]:: E a → a [[fmap f (Right y)]] ≡ [[Right (f y)]] [[FromInteger n]] = fromInteger n ≡ Id (f y) [[Add a b]] = [[a]]+ [[b]] ≡ fmap f (Id y) [[Mult a b]] = [[a]] ∗ [[b]] ≡ fmap f [[Right y]] ... [[FromRational n]] = fromRational n [[pure y]] ≡ [[Right y]] [[Recip a]] = recip [[a]] ≡ Id y ... 12 Denotational design with type class morphisms (extended version)

To ensure that expressions behave like what they mean, check [[Recip a]] e = recip [[a]] e that [[·]] is a morphism over Num and Fractional. The definitions [[·]] of [[·]] and the instances make the proofs trivially easy. For instance, Again, we must ask: is a numeric morphism? In order for the question to even make sense, the semantic domain must inhabit the [[a + b]] ≡ [[Add a b]] ≡ [[a]]+ [[b]] numeric classes. Indeed it does, as we saw in Section 10.1. Looking again at the numeric methods for functions, we can see using the definitions of (+) on E and [[·]] on Add. a familiar pattern in the [[·]] definition just above. Using the function How robust are these numeric morphisms? If the representation methods from Section 10.1, we get a more elegant definition of [[·]]: deviates from their one-to-one correspondence with methods, will the numeric morphism properties still hold? [[Literal x]] = pure x Let’s try some variations, including self-optimizing expressions [[VarInt v]] = look v and expressions with variables. [[Add a b]] = [[a]]+ [[b]] 10.3.2 Generalizing literals [[Mult a b]] = [[a]] ∗ [[b]] [[Recip a]] = recip [[a]] As a first step, replace FromInteger and FromRational with a general constructor for literals. With this [[·]] definition, the morphism properties follow easily.

data E :: ∗ → ∗ where 10.3.4 Handling errors Literal :: a → E a ... So far, expression evaluation is assumed to succeed. The variable environment yields values for every possible variable name, which Change the relevant methods: is unrealistic. Let’s now add error-handling to account for unbound instance Num a ⇒ Num (E a) where variables and other potential problems. The result of a variable fromInteger = Literal ◦ fromInteger look-up or an expression evaluation will be either an error message ... or a regular value. instance Fractional a ⇒ Fractional (E a) where type Result a = Either String a fromRational = Literal ◦ fromRational type Env = Map String Int ... type Model a = Env → Result a Finally, replace two [[·]] cases with one: look :: String → Model Int [[Literal x]] = x look s e | Just n ← lookup e s = Right n | otherwise = Left ("unbound: " ++ s) Everything type-checks; but does it morphism-check? Verify the [[·]]:: E a → Model a two affected methods: Model [[fromInteger n]] Again, we’ll rely on the having numeric instances, which is the case, thanks to the definitions in Sections 10.1 and 10.2. ≡ [[Literal (fromInteger n)]] As with the semantic function in Section 10.3.3, the numeric ≡ fromInteger n methods for the semantic domain do almost all the work, leaving and simiarly for fromRational. Morphism check complete. our semantic definition nearly intact. The only change is for literals:

10.3.3 Adding variables [[Literal x]] = pure (pure x) Our expressions so far denote numbers. Now let’s add variables. We As before, most of the morphism proofs are trivial, due to the will use just integer-valued variables, to keep the example simple.5 simplicity of the definitions. The fromInteger and fromRational The new constructor: morphisms use Literal: VarInt :: String → E Int [[fromInteger x]] ≡ { fromInteger definition } This small syntactic extension requires a significant semantic [[Literal (fromInteger x)]] extension. An expression now denotes different values in different ≡ { [[·]] on Literal } binding environments, so the semantic domain is a function: pure (pure (fromInteger x)) type Env = TMap String Int ≡ { fromInteger on Either a } type Model a = Env → a pure (fromInteger x) ≡ { fromInteger on a → b } [[·]]:: E a → Model a fromInteger x The semantic function carries along the environment and looks up and similarly for fromRational. variables as needed: look :: String → Model Int 10.3.5 Self-optimizing expressions look s e = sample e s So far our expressions involve no optimization, but it’s easy to [[Literal x]] = x add. For example, replace the simple method definition (+) = [[VarInt v]] e = look v e Add with the following version, which does constant-folding and recognizes the additive identity: [[Add a b]] e = [[a]] e + [[b]] e [[Mult a b]] e = [[a]] e ∗ [[b]] e Literal x + Literal y = Literal (x + y) Literal 0 + b = b 5 Multi- binding environments can be implemented with an a + Literal 0 = a existential data type and a GADT for type equality. a + b = Add a b LambdaPix technical report 2009-01, March 2009 (minor revisions January 28, 2016) 13

0 00 Other methods can perform similar optimizations. () and initial values e and e , come up with ( ) and e such that With this change, we must re-check whether [[a + b]] ≡ [[a]] + one fold replaces a pair of them:  [[b]]. There are four cases to consider, corresponding to the four 0 00 (foldl ( ) e bs, foldl () e bs) ≡ foldl ( ) e bs cases in the (+) definition.  [[Literal x + Literal y]] 11.1 Folds as data ≡ [[Literal (x + y)]] We want to combine the two left folds before supplying the list ≡ x + y argument, rather than after. To do so, make a data type for the partial ≡ [[Literal x]]+ [[Literal y]] application that does not include the final (list) argument. data FoldL b a = F (a → b → a) a [[·]] (Literal 0 + b) FoldL ≡ [[b]] The is not just a representation; it has meaning, which is partially applied folding: ≡ 0 + [[b]] ≡ [[Literal 0]]+ [[b]] [[·]]:: FoldL b a → ([b ] → a) [[FoldL ( ) e]] = foldl ( ) e The third case is similar; and the fourth case is as in Section 10.3.1. Notice that the correctness of the second case hinges on the With this representation and meaning, we can rephrase our goal: very mathematical property that it implements, i.e., that zero is a given two left folds f and f 0, find another fold f 00 such that left identity for addition. Any such property can be encoded into ([[f ]] bs, [[f 0]] bs) ≡ [[f 00]] bs the implementation and then verified in this way. The discipline of type class morphisms ensure that all optimizations are correct. In other words, [[f ]]&&&[[f 0]] ≡ [[f 00]] 11. Fusing folds where (&&&) is a common operation on functions (more generally, Folds are common in functional programming, to express a cumu- on arrows (Hughes 2000)): lative iteration over a list (or other ), reducing to a (&&&):: (x → a) → (x → b) → (x → (a, b)) single value. There are two flavors, left- and right-associating: f &&& g = λx → (f x, g x) foldl ( ) a [b1, b2, ..., bn ] ≡ (...((a b1) b2) ...) bn Of course, we want a systematic way to construct f 00, so we’re foldr ( ) a [b1, b2, ..., bn ] ≡ b1 (b2 ...(bn a)...) really looking for a combining operation Written recursively, combL :: FoldL c a → FoldL c b → FoldL c (a, b) foldl :: (a → b → a) → a → [b ] → a such that for for all f and f 0 foldl ( ) a [ ] = a 0 0 foldl ( ) a (b : bs) = foldl ( )(a b) bs [[f ]]&&&[[f ]] ≡ [[f ‘combL‘ f ]] foldr :: (b → a → a) → a → [b ] → a This last form is tantalizingly close to a type class morphism. foldr a [ ] = a What’s missing is a shared type class method. foldr ( ) a (b : bs) = b (foldr ( ) a bs) 11.2 Generalized zipping There is also a strict variant of foldl, which eliminates a common Consider the types of the following three functions: form of space leak. If a fold is the only use of a list, then lazy evaluation and garbage zip :: a → Stream b → Stream (a, b) collection conspire to produce efficient use of memory. Laziness (&&&) :: (c → a) → (c → b) → (c → (a, b)) delays computation of list cells until just before they’re combined combL :: FoldL c a → FoldL c b → FoldL c (a, b) into the fold result (using ( )), after which they become inacces- These functions and more can be subsumed by a more general no- sible and can be collected. This pattern allows list generation and tion of zipping. Streams, functions, and folds also have in common folding to run in constant space, regardless of the length of inter- that they provide a “unit”, which will turn out to be useful later. mediate list. (Compile-time fusion can make this process even more These two common features are embodied in a type class: efficient.) Non-strict and right folds can leak due to thunks. On the other hand, if a single list is folded over twice, then class Zip f where the entire list will be kept in memory to make the second fold unit :: f () possible. Borrowing a common example, consider the following (?) :: f a → f b → f (a, b) na¨ıve implementation of the average of the values in a list: Streams and functions zip. Do folds? naiveMean :: Fractional a ⇒ [a ] → a The Zip class corresponds to Monoidal class (McBride and Pa- naiveMean xs = sum xs / fromIntegral (length xs) terson 2008, Section 7), except that Monoidal requires a Functor, which is not the case with FoldL. Each of sum and length can be defined as a (strict) left-fold: Generalized (?) gives us our target TCM. Zipping a left fold sum = foldl (+) 0 means finding a semantic Zip morphism, i.e., length = foldl (λa → a + 1) 0 [[unit]] ≡ unit 0 0 Max Rabkin(2008) gave an elegant way to fuse these two foldl [[f ]] ? [[f ]] ≡ [[f ? f ]] passes into one, reducing the space usage from linear to constant. The following definition suffices:6 We’ll see that Max’s optimization and its correctness flow from a semantic model and its type class morphisms. 6 With this definition, the (?) morphism property fails when f ≡ ⊥ or As a first step, let’s look at a simpler setting: turning a pair of f 0 ≡ ⊥. To fix this problem, use lazy patterns in the definition. My thanks non-strict left foldings into a single one. Given combiners ( ) and to Ryan Ingram for pointing out this bug. 14 Denotational design with type class morphisms (extended version)

instance Zip (FoldL b) where instance Functor (FoldL b) where 0 unit = F const () fmap h (FoldL ( ) e) ≡ FoldL () e where ... ?? F ( ) e ? F ( ) e0 = F ( )(e, e0)  The functor morphism law says that where  0 0 (a, a ) b = (a b, a  b) [[fmap h (FoldL ( ) e)]] ≡ fmap h [[FoldL ( ) e]]  To prove that [[·]] is Zip morphism, first substitute the definitions Substituting our partial fmap definition on the left and (◦) for fmap of (?) for functions and for folds and the definition of [[·]] into the on the right, as well as the definition of [[·]], the property becomes morphism property. We’ll want some structure to work with, so let 0 0 0 foldl () e ≡ h ◦ foldl ( ) e where ... F ( ) e = f and F () e = f . First, the unit morphism property, for empty lists: At this point, I’m stuck, as I don’t see a way to get foldl to apply h just at the end of a fold. Max solved this problem by adding a [[unit]] [ ] post-fold function to the FoldL type (Rabkin 2008). Generalizing ≡ { [[·]] definition } from his solution, we can extend any zippable to foldl const () [ ] have Functor instance, and many to have Applicative, as we’ll ≡ { foldl definition } see next. () ≡ { unit for functions } 12. Enhanced zipping unit [] To get from Zip to Functor and Applicative, add a final phase Then for nonempty lists: data WithCont z c = ∀a.WC (z a)(a → c) [[unit]] (b : bs) ≡ { [[·]] definition } The “∀a” keeps the intermediate value’s type from complicating foldl const () (b : bs) the type of a WithCont. Given a semantic function hh·ii :: z a → u a, for a functor u, ≡ { foldl definition } the meaning of WithCont is foldl const (const () b) bs ≡ { const definition } [[·]]:: WithCont z c → u c foldl const () bs [[WC z k]] = fmap k hhzii ≡ { const definition } For instance, adding Max’s post-fold step just requires wrapping foldl const () bs FoldL with WithCont: ≡ { [[·]] definition } [[unit]] bs type FoldLC b = WithCont (FoldL b) ≡ { induction } Since the meaning of a FoldL is a function, the fmap in [[·]] is unit bs function composition, exactly as we want for applying a post-fold After simplifying, the second morphism law becomes step. It’s now easy to define instances. 0 0 foldl ( )(e, e ) bs ≡ (foldl ( ) e bs, foldl () e bs) 12.1 Functor and Zip where The Functor instance accumulates final steps: 0 0 (a, a ) b = (a b, a  b)  instance Functor (WithCont z) where Prove this form inductively in the list bs, using the definition of fmap g (WC z k) = WC z (g ◦ k) foldl. First, empty lists. Its morphism property: foldl ( )(e, e0)[] where ( ) = ... ≡ { foldl definition }  [[fmap g (WC z k)]] (e, e0) ≡ { fmap on WithCont } ≡ { foldl def, twice } [[WC z (g ◦ k)]] (foldl ( ) e [], foldl ( ) e0 [ ]) ≡ { [[·]] definition }  fmap (g ◦ k) hhzii Next, non-empty lists. ≡ { Second Functor law } foldl ( )(e, e0)(b : bs) where ( ) = ... fmap g (fmap k hhzii) ≡ { foldl definition }  ≡ { [[·]] definition } foldl ( ) ((e, e0) b) bs where ( ) = ... fmap g [[WC z k]] ≡ { ( ) definition}  [To do: Also consider ⊥.] The Zip instance delegates to the inner 0 foldl ( )(e b, e  b) bs where ( ) = ... Zip, and pairs up final transformations. ≡ { induction hypothesis }  instance Zip z ⇒ Zip (WithCont z) where (foldl ( )(e b) bs, foldl ( )(e0 b) bs)   unit = WC ⊥ (const ()) ≡ { foldl def, twice } 0 WC fa ka ? WC fb kb = WC (fa ? fb)(ka × kb) (foldl ( ) e (b : bs), foldl () e (b : bs)) First unit: 11.3 Variations [[unit]] Right folds work similarly. Strict folds are trickier but also impor- ≡ { unit on WithCont } tant, to prevent space leaks. See (Rabkin 2008) and (Elliott 2008). [[WC ⊥ (const ())]] Can we add more instances for FoldL, with corresponding se- ≡ { [[·]] definition } mantic morphisms? Let’s try Functor: fmap (const ()) hh⊥ii LambdaPix technical report 2009-01, March 2009 (minor revisions January 28, 2016) 15

If we had the following property, we would be done: zippedMean = [[liftA (/)(WC id (FoldL (+) 0)) fmap (const ()) m ≡ unit -- required 2 (WC fromIntegral (FoldL (λa → a + 1) 0))]] This property is satisfied for some functors (including ((→) a)) but not others (e.g., []), so the unit morphism property holds only for some functors z (with semantic model u), including the meaning 13. Some more examples of FoldL. 13.1 Functional reactive programming Next, the (?) morphism property: My first exposure to type class morphisms was in giving a denota- [[WC fa ka ? WC fb kb]] tional semantics to functional reactive programming (FRP) struc- ≡ { (?) on WithCont } tured into type classes (Elliott 2009b). “Classic FRP” is based on a [[WC (fa ? fb)(ka × kb)]] model of behaviors as functions of time (Elliott and Hudak 1997). ≡ { [[·]] definition } [[·]]:: Behavior a → (Time → a) fmap (ka × kb) hhfa ? fbii For instance, a 3D animation has type Behavior Geometry, and ≡ { hh·ii is a Zip morphism } its meaning is Time → Geometry. fmap (ka × kb)(hhfaii ? hhfbii) Much of FRP can be re-packaged via type classes. In most ≡ { (?) } naturality of cases, the semantics is specified simply and fully by saying that fmap ka hhfaii ? fmap kb hhfbii the semantic function is a TCM. For events, where the TCM princ- ≡ { [[·]] definition, twice } ple is not applied successfully, the semantics is problematic. (For [[WC fa ka]] ? [[WC fb kb]] instance, the monad associativity law can fail.) 13.2 Functional image synthesis 12.2 Applicative Pan is a system for image synthesis and manipulation with a purely As pointed out in (McBride and Paterson 2008, Section 7), the functional model and a high-performance implementation (Elliott Applicative class has an equivalent but more symmetric variation, 2003; Elliott et al. 2003). The semantic model for images in Pan is which is the (strong) lax monoidal functor, which has the interface simply functions of continuous infinite 2D space: of Zip, in addition to Functor. Using the standard Applicative 2 instance for lax monoidal functors: [[·]]:: Image a → (R → a) instance (Functor z, Zip z) ⇒ With this semantic model, the Image type has instances for Applicative (WithCont z) where Functor and Applicative, which form the basis of all point-wise pure a = fmap (const a) unit operations, including cropping and blending. With the TCM prin- wf wx = fmap app (wf ? wx) ciple clearly in mind, the Image interface can be made more con- ~ venient, regular and powerful, via instances of Monoid, Monad app (f , x) = f x and Comonad, as well all of the number classes. the morphism proof runs into a of trouble for pure: The implementation uses a self-optimizing syntactic represen- tation, packaged as numeric class instances, akin to that in Sec- [[pure a]] ≡ [[fmap (const a) unit]] tion 10.3.5. The semantic function, therefore, is a morphism over ≡ fmap (const a) [[unit]] all of the classes mentioned. ≡ fmap (const a) unit ≡ pure a -- note: only sometimes 13.3 Automatic differentiation Automatic differentiation (AD) is a precise and efficient method for Again, the required property is satisfied for some functors, includ- computing derivatives. It has a simple specification in terms of type ing the meaning of FoldL. Continuing, class morphisms, from which an elegant, correct implementation [[fs ~ xs]] ≡ [[fmap app (fs ? xs)]] can be derived. The specification and implementations can then ≡ fmap app [[fs ? xs]] be generalized considerably to computing higher-order derivatives ≡ fmap app ([[fs]] ? [[xs]]) (infinitely many of them, lazily) and derivatives of functions over arbitrary vector spaces (Elliott 2009a). ≡ [[fs]] ~ [[xs]] Thanks to this morphism, we have a zipping law for folds: 14. Conclusions—advice on software design 0 0 liftA2 h (k ◦ foldl ( ) e)(k ◦ foldl () e ) With the examples in this paper, I am conveying some advice to ≡ my fellow programmers: when designing software, in addition to 0 0 [[liftA2 h (WC k (FoldL ( ) e)) (WC k (FoldL () e ))]] innovating in your implementations, relate them to precise and familiar semantic models. Implementing those models faithfully and similarly for liftA , etc. The proof is a direct application of the 3 guarantees that your library’s users will get simple semantics and semantics and the morphism properties. This transformation could expected properties, in addition to whatever performance benefits be automated with rewrite rules (Peyton Jones et al. 2001). you provide. Returning to the example of combining two folds into one. By defining a type’s denotation clearly, library designers can naiveMean :: Fractional a ⇒ [a ] → a ensure there are no abstraction leaks. When the semantic function naiveMean xs = sum xs / fromIntegral (length xs) maps two program values to the same mathematical value, the de- signer must ensure that those program values be indistinguishable, In point-free form, in order to prevent semantic abstraction leaks. The discipline of naiveMean = liftA (/) sum (fromIntegral ◦ length) denotational semantics, applied to data types, ensures that this con- 2 dition is satisfied, simply because each operation’s meaning is de- So an equivalent optimized definition is fined purely in terms of the meaning of its arguments. 16 Denotational design with type class morphisms (extended version)

Type classes introduce a new source of potential abstraction Conal Elliott, Sigbjørn Finne, and Oege de Moor. Compiling leaks, by allowing a single name to be used at different types. embedded languages. Journal of Functional Prog, 13(2), 2003. Although a type class dictates a set of necessary properties, it also Andy Gill et al. Data.Monoid, 2001. Source code. leaves room for variation in semantics and implementation. For each program type, the library designer must take care that each Ralf Hinze. Generalizing generalized tries. Journal of Functional interface (type class) implementation behaves consistently with the Programming, 10(4):327–351, July 2000. type’s model, i.e., John Hughes. Generalising monads to arrows. Science of Computer Programming The instance’s meaning follows the meaning’s instance. , 37(1-3):67–111, 2000. Mark P. Jones. A system of constructor classes: overloading and which is to say that the semantic function is to be a “type class mor- implicit higher-order polymorphism. In FPCA ’93: Conference phism” (TCM) for each type class implemented. When a library not on Functional Programming and Computer Architecture, pages only type-checks, but also morphism-checks, it is free of abstraction 52–61, New York, N.Y., 1993. ACM Press. leak, and so the library’s users can safely treat a program value as being its meaning. As a bonus, type class laws are guaranteed to Saunders Mac Lane. Categories for the Working Mathematician hold, because they carry over directly from the semantic model. As (Graduate Texts in Mathematics). Springer, September 1998. much as good models tend to be widely reusable, effort invested in Conor McBride and Ross Paterson. Applicative programming with studying them is leveraged. effects. Journal of Functional Programming, 18(1):1–13, 2008. Simon Peyton Jones, Andrew Tolmach, and Tony Hoare. Playing Finally, I see denotational, TCM-based design as in the spirit of by the rules: rewriting as a practical optimisation technique in John Reynolds’s use of category theory for language design. ghc. In In Haskell Workshop, pages 203–233, 2001. Our intention is not to use any deep theorems of category Simon Peyton Jones, Dimitrios Vytiniotis, Stephanie Weirich, and theory, but merely to employ the basic concepts of this field Geoffrey Washburn. Simple unification-based as organizing principles. This might appear as a desire to be for GADTs. In Proceedings of the Eleventh ACM SIGPLAN concise at the expense of being esoteric. But in designing a International Conference on Functional Programming, 2006. programming language, the central problem is to organize a variety of concepts in a way which exhibits uniformity and Max Rabkin. Beautiful folding. Blog post, Novem- generality. Substantial leverage can be gained in attacking ber 2008. URL http://squing.blogspot.com/2008/11/ this problem if these concepts are defined concisely within beautiful-folding.html. a framework which has already proven its ability to impose John C. Reynolds. Using category theory to design implicit con- uniformity and generality upon a wide variety of mathemat- versions and generic operators. In Semantics-Directed Com- ics (Reynolds 1980). piler Generation, Proceedings of a Workshop, pages 211–258. Springer-Verlag, 1980. 15. Acknowledgments Dana Scott and Christopher Strachey. Toward a mathematical se- This paper has benefited by comments from Richard Smith, Tim mantics for computer languages. Programming Research Group Newsham, Ganesh Sittampalam, Matt Hellige, Bas van Dijk, Tech. Monograph PRG-6, Oxford Univ. Computing Lab., 1971. Jeremy Voorhis, Patai Gergely, Phil Wadler, Ivan Tomac, Noam Joseph Stoy. Denotational semantics: The Scott-Strachey approach Lewis, Nicolas Wu, Darryl McAdams, and Ilan Godik. to programming language theory. MIT Press, 1977. References . Comprehending monads. In Conference on LISP and Functional Programming, pages 61–78. ACM, 1990. Stephen Adams. Efficient sets: a balancing act. Journal of Func- tional Programming, 3(4):553–562, October 1993. Philip Wadler and Stephen Blott. How to make ad-hoc polymor- phism less ad-hoc. In The 16th Annual ACM Symposium on Lennart Augustsson, Howard Mansell, and Ganesh Sittampalam. Principles of Programming Languages. ACM, January 1989. Paradise: a two-stage dsl embedded in haskell. In ICFP ’08: Proceeding of the 13th ACM SIGPLAN international conference on Functional programming, pages 225–228, 2008. Manuel M. T. Chakravarty, Gabriele Keller, Simon Peyton Jones, and Simon Marlow. Associated types with class. In Proceedings of the 32nd ACM SIGPLAN-SIGACT sysposium on Principles of programming languages, pages 1–13. ACM Press, 2005. Conal Elliott. Functional images. In The Fun of Programming, “Cornerstones of Computing” series. Palgrave, March 2003. Conal Elliott. More beautiful fold zipping. Blog post, November 2008. URL http://conal.net/blog/posts/ more-beautiful-fold-zipping. Conal Elliott. Beautiful differentiation. In International Confer- ence on Functional Programming (ICFP), 2009a. URL http: //conal.net/papers/beautiful-differentiation. Conal Elliott. Push-pull functional reactive programming. In Haskell Symposium, 2009b. Conal Elliott and Paul Hudak. Functional reactive animation. In International Conference on Functional Programming, 1997.