ArticlePDF Available

Applicative Programming with Effects

Authors:

Abstract

In this article, we introduce Applicative functors – an abstract characterisation of an applicative style of effectful programming, weaker than Monads and hence more widespread. Indeed, it is the ubiquity of this programming pattern that drew us to the abstraction. We retrace our steps in this article, introducing the applicative pattern by diverse examples, then abstracting it to define the Applicative type class and introducing a bracket notation that interprets the normal application syntax in the idiom of an Applicative functor. Furthermore, we develop the properties of applicative functors and the generic operations they support. We close by identifying the categorical structure of applicative functors and examining their relationship both with Monads and with Arrow.
Under consideration for publication in J. Functional Programming 1
FUNCTIONAL PEARL
Applicative programming with effects
CONOR MCBRIDE
University of Nottingham
ROSS PATERSON
City University, London
Abstract
In this paper, we introduce Applicative functors—an abstract characterisation of an ap-
plicative style of effectful programming, weaker than Monads and hence more widespread.
Indeed, it is the ubiquity of this programming pattern that drew us to the abstraction.
We retrace our steps in this paper, introducing the applicative pattern by diverse exam-
ples, then abstracting it to define the Applicative type class and introducing a bracket
notation which interprets the normal application syntax in the idiom of an Applicative
functor. Further, we develop the properties of applicative functors and the generic opera-
tions they support. We close by identifying the categorical structure of applicative functors
and examining their relationship both with Monads and with Arrows.
1 Introduction
This is the story of a pattern that popped up time and again in our daily work,
programming in Haskell (Peyton Jones, 2003), until the temptation to abstract it
became irresistable. Let us illustrate with some examples.
Sequencing commands One often wants to execute a sequence of commands and
collect the sequence of their responses, and indeed there is such a function in the
Haskell Prelude (here specialised to IO):
sequence :: [IO a]IO [a]
sequence [ ] = return [ ]
sequence (c:cs) = do
xc
xs sequence cs
return (x:xs)
In the (c:cs) case, we collect the values of some effectful computations, which we
then use as the arguments to a pure function (:). We could avoid the need for names
to wire these values through to their point of usage if we had a kind of ‘effectful
application’. Fortunately, exactly such a thing lives in the standard Monad library:
2Conor McBride and Ross Paterson
ap :: Monad mm(ab)m a m b
ap mf mx =do
fmf
xmx
return (f x )
Using this function we could rewrite sequence as:
sequence :: [IO a]IO [a]
sequence [ ] = return [ ]
sequence (c:cs) = return (:) ‘apcapsequence cs
where the return operation, which every Monad must provide, lifts pure values to
the effectful world, whilst ap provides ‘application’ within it.
Except for the noise of the returns and aps, this definition is in a fairly standard
applicative style, even though effects are present.
Transposing ‘matrices’ Suppose we represent matrices (somewhat approximately)
by lists of lists. A common operation on matrices is transposition1.
transpose :: [[a]] [[a]]
transpose [ ] = repeat [ ]
transpose (xs :xss) = zipWith (:) xs (transpose xss )
Now, the binary zipWith is one of a family of operations that ‘vectorise’ pure func-
tions. As Daniel Fridlender and Mia Indrika (2000) point out, the entire family can
be generated from repeat, which generates an infinite stream from its argument,
and zapp, a kind of ‘zippy’ application.
repeat :: a[a]
repeat x=x:repeat x
zapp :: [ab][a][b]
zapp (f:fs) (x:xs) = f x :zapp fs xs
zapp = [ ]
The general scheme is as follows:
zipWithn:: (a1 · · · anb)[a1] · · · [an][b]
zipWithnfxs1. . . xsn=repeat fzappxs1zapp. . . zappxsn
In particular, transposition becomes
transpose :: [[a]] [[a]]
transpose [ ] = repeat [ ]
transpose (xs :xss) = repeat (:) ‘zappxs zapptranspose xss
Except for the noise of the repeats and zapps, this definition is in a fairly standard
applicative style, even though we are working with vectors.
Evaluating expressions When implementing an evaluator for a language of expres-
sions, it is customary to pass around an environment, giving values to the free
variables. Here is a very simple example
1This function differs from the one in the standard library in its treatment of ragged lists
Functional pearl 3
data Exp v=Var v
|Val Int
|Add (Exp v) (Exp v)
eval :: Exp vEnv vInt
eval (Var x)γ=fetch xγ
eval (Val i)γ=i
eval (Add p q)γ=eval pγ+eval qγ
where Env vis some notion of environment and fetch xprojects the value for the
variable x.
We can eliminate the clutter of the explicitly threaded environment with a little
help from some very old friends, designed for this purpose:
eval :: Exp vEnv vInt
eval (Var x) = fetch x
eval (Val i) = Ki
eval (Add p q) = K(+) ‘Seval pSeval q
where
K:: aenv a
Kxγ=x
S:: (env ab)(env a)(env b)
Sef es γ= (ef γ) (es γ)
Except for the noise of the Kand Scombinators2, this definition of eval is in a
fairly standard applicative style, even though we are abstracting an environment.
2 The Applicative class
We have seen three examples of this ‘pure function applied to funny arguments’
pattern in apparently quite diverse fields—let us now abstract out what they have
in common. In each example, there is a type constructor fthat embeds the usual
notion of value, but supports its own peculiar way of giving meaning to the usual
applicative language—its idiom. We correspondingly introduce the Applicative class:
infixl 4~
class Applicative fwhere
pure :: af a
(~) :: f(ab)f a f b
This class generalises Sand Kfrom threading an environment to threading an effect
in general.
We shall require the following laws for applicative functors:
identity pure id ~u=u
composition pure (·)~u~v~w=u~(v~w)
homomorphism pure f~pure x=pure (f x )
interchange u~pure x=pure (λff x )~u
2also known as the return and ap of the environment Monad
4Conor McBride and Ross Paterson
The idea is that pure embeds pure computations into the pure fragment of an
effectful world—the resulting computations may thus be shunted around freely, as
long as the order of the genuinely effectful computations is preserved.
You can easily check that applicative functors are indeed functors, with the fol-
lowing action on functions:
(<$>) :: Applicative f(ab)f a f b
f<$>u=pure f~u
Moreover, any expression built from the Applicative combinators can be transformed
to a canonical form in which a single pure function is ‘applied’ to the effectful parts
in depth-first order:
pure f~u1~. . . ~un
This canonical form captures the essence of Applicative programming: computa-
tions have a fixed structure, given by the pure function, and a sequence of sub-
computations, given by the effectful arguments. We therefore find it convenient, at
least within this paper, to write this form using a special bracket notation,
Jf u1. . . unK
indicating a shift into the idiom of an Applicative functor, where a pure function is
applied to a sequence of effectful arguments using the appropriate ~. Our intention
is to give an indication that effects are present, whilst retaining readability of code.
Given Haskell extended with multi-parameter type classes, enthusiasts for over-
loading may replace ‘J’ and ‘K’ by identifiers iI and Ii with the right behaviour3.
The IO monad, and indeed any Monad, can be made Applicative by taking pure =
return and (~) = ap. We could alternatively use the variant of ap that performs
the computations in the opposite order, but we shall keep to the left-to-right order
in this paper. Sometimes we can implement the Applicative interface a little more
directly, as with ()env :
instance Applicative (()env)where
pure x=λγ x-- K
ef ~ex =λγ (ef γ) (ex γ) -- S
With these instances, sequence and eval become:
sequence :: [IO a]IO [a]
sequence [ ] = J[ ] K
sequence (c:cs) = J(:) c(sequence cs)K
eval :: Exp vEnv vInt
eval (Var x) = fetch x
eval (Val i) = JiK
eval (Add p q) = J(+) (eval p) (eval q)K
If we want to do the same for our transpose example, we shall have to avoid the
3Hint: Define an overloaded function applicative u v1 . . . vn Ii = u~v1 ~. . . ~vn
Functional pearl 5
library’s ‘list of successes’ (Wadler, 1985) monad and take instead an instance
Applicative [ ] that supports ‘vectorisation’, where pure =repeat and (~) = zapp,
yielding
transpose :: [[a]] [[a]]
transpose [ ] = J[ ] K
transpose (xs :xss) = J(:) xs (transpose xss )K
In fact, repeat and zapp are not the return and ap of any Monad.
3 Traversing data structures
Have you noticed that sequence and transpose now look rather alike? The details
that distinguish the two programs are inferred by the compiler from their types.
Both are instances of the applicative distributor for lists:
dist :: Applicative f[f a ]f[a]
dist [ ] = J[ ] K
dist (v:vs) = J(:) v(dist vs)K
Distribution is often used together with ‘map’. For example, given the monadic
‘failure-propagation’ applicative functor for Maybe, we can map some failure-prone
operation (a function in aMaybe b) across a list of inputs in such a way that
any individual failure causes failure overall.
flakyMap :: (aMaybe b)[a]Maybe [b]
flakyMap f ss =dist (fmap f ss)
As you can see, flakyMap traverses ss twice—once to apply f, and again to collect the
results. More generally, it is preferable to define this applicative mapping operation
directly, with a single traversal:
traverse :: Applicative f(af b)[a]f[b]
traverse f[ ] = J[ ] K
traverse f(x:xs) = J(:) (f x ) (traverse f xs)K
This is just the way you would implement the ordinary fmap for lists, but with
the right-hand sides wrapped in J· · ·K, shifting them into the idiom. Just like fmap,
traverse is a useful gadget to have for many data structures, hence we introduce the
type class Traversable, capturing functorial data structures through which we can
thread an applicative computation:
class Traversable twhere
traverse :: Applicative f(af b)t a f(t b)
dist :: Applicative ft(f a)f(t a)
dist =traverse id
Of course, we can recover an ordinary ‘map’ operator by taking fto be the identity—
the simple applicative functor in which all computations are pure:
newtype Id a=An{an :: a}
6Conor McBride and Ross Paterson
Haskell’s newtype declarations allow us to shunt the syntax of types around with-
out changing the run-time notion of value or incurring any run-time cost. The
‘labelled field’ notation defines the projection an :: Id aaat the same time as the
constructor An :: aId a. The usual applicative functor has the usual application:
instance Applicative Id where
pure =An
An f~An x=An (f x )
So, with the newtype signalling which Applicative functor to thread, we have
fmap f=an ·traverse (An ·f)
Meertens (1998) defined generic dist-like operators, families of functions of type
t(f a)f(t a) for every regular functor t(that is, ‘ordinary’ uniform datatype
constructors with one parameter, constructed by recursive sums of products). His
conditions on fare satisfied by applicative functors, so the regular type constructors
can all be made instances of Traversable. The rule-of-thumb for traverse is ‘like fmap
but with J· · ·Kon the right’. For example, here is the definition for trees:
data Tree a=Leaf |Node (Tree a)a(Tree a)
instance Traversable Tree where
traverse fLeaf =JLeaf K
traverse f(Node l x r ) = JNode (traverse f l ) (f x ) (traverse f r )K
This construction even works for non-regular types. However, not every Functor
is Traversable. For example, the functor ()env cannot in general be Traversable.
To see why, take env =Integer and try to distribute the Maybe functor!
Although Meertens did suggest that threading monads might always work, his
primary motivation was to generalise reduction or ‘crush’ operators, such as flat-
tening trees and summing lists. We shall turn to these in the next section.
4Monoids are phantom Applicative functors
The data that one may sensibly accumulate have the Monoid structure:
class Monoid owhere
:: o
() :: ooo
such that ‘’ is an associative operation with identity . The functional program-
ming world is full of monoids—numeric types (with respect to zero and plus, or one
and times), lists with respect to [ ] and ++, and many others—so generic technology
for working with them could well prove to be useful. Fortunately, every monoid
induces an applicative functor, albeit in a slightly peculiar way:
newtype Accy o a =Acc{acc :: o}
Accy o a is a phantom type (Leijen & Meijer, 1999)—its values have nothing to do
with a, but it does yield the applicative functor of accumulating computations:
Functional pearl 7
instance Monoid oApplicative (Accy o)where
pure =Acc
Acc o1~Acc o2=Acc (o1o2)
Now reduction or ‘crushing’ is just a special kind of traversal, in the same way as
with any other applicative functor, just as Meertens suggested:
accumulate :: (Traversable t,Monoid o)(ao)t a o
accumulate f=acc ·traverse (Acc ·f)
reduce :: (Traversable t,Monoid o)t o o
reduce =accumulate id
Operations like flattening and concatenation become straightforward:
flatten :: Tree a[a]
flatten =accumulate (:[ ])
concat :: [[a]] [a]
concat =reduce
We can extract even more work from instance inference if we use the type system
to distinguish different monoids available for a given datatype. Here, we use the
disjunctive structure of Bool to test for the presence of an element satisfying a
given predicate:
newtype Mighty =Might{might :: Bool}
instance Monoid Mighty where
=Might False
Might xMight y=Might (xy)
any :: Traversable t(aBool)t a Bool
any p=might ·accumulate (Might ·p)
Now any ·() behaves just as the elem function for lists, but it can also tell
whether a variable from voccurs free in an Exp v. Of course, Bool also has a
conjunctive Musty structure, which is just as easy to exploit.
5Applicative versus Monad?
We have seen that every Monad can be made Applicative via return and ap. Indeed,
two of our three introductory examples of applicative functors involved the IO
monad and the environment monad ()env. However the Applicative structure we
defined on lists is not monadic, and nor is Accy o(unless ois the trivial one-point
monoid): return can deliver , but if you try to define
(>>=) :: Accy o a (aAccy o b)Accy o b
you’ll find it tricky to extract an afrom the first argument to supply to the second—
all you get is an o. The ~for Accy ois not the ap of a monad.
So now we know: there are strictly more Applicative functors than Monads. Should
we just throw the Monad class away and use Applicative instead? Of course not! The
reason there are fewer monads is just that the Monad structure is more powerful.
Intuitively, the (>>=) :: m a (am b)m b of some Monad mallows the value
returned by one computation to influence the choice of another, whereas ~keeps
8Conor McBride and Ross Paterson
the structure of a computation fixed, just sequencing the effects. For example, one
may write
miffy :: Monad mmBool m a m a m a
miffy mb mt me =do
bmb
if bthen mt else me
so that the value of mb will choose between the computations mt and me, perform-
ing only one, whilst
iffy :: Applicative ffBool f a f a f a
iffy fb ft fe =Jcond fb ft fe Kwhere
cond b t e =if bthen telse e
performs the effects of all three computations, using the value of fb to choose only
between the values of ft and fe. This can be a bad thing: for example,
iffy JTrue K J tKNothing =Nothing
because the ‘else’ computation fails, even though its value is not needed, but
miffy JTrue K J tKNothing =JtK
However, if you are working with miffy, it is probably because the condition
is an expression with effectful components, so the idiom syntax provides quite a
convenient extension to the monadic toolkit:
miffy J(6)getSpeed getSpeedLimit KstepOnIt checkMirror
The moral is this: if you’ve got an Applicative functor, that’s good; if you’ve also
got a Monad, that’s even better! And the dual of the moral is this: if you want a
Monad, that’s good; if you only want an Applicative functor, that’s even better!
One situation where the full power of monads is not always required is parsing, for
which R¨ojemo (1995) proposed a interface including the equivalents of pure and ‘~
as an alternative to monadic parsers (Hutton & Meijer, 1998). Several ingenious
non-monadic implementations have been developed by Swierstra and colleagues
(Swierstra & Duponcheel, 1996; Baars et al., 2004). Because the structure of these
parsers is independent of the results of parsing, these implementations are able to
analyse the grammar lazily and generate very efficient parsers.
Composing applicative functors The weakness of applicative functors makes them
easier to construct from components. In particular, although only certain pairs of
monads are composable (Barr & Wells, 1984), the Applicative class is closed under
composition,
newtype (fg)a=Comp{comp :: (f(g a))}
just by lifting the inner Applicative operations to the outer layer:
instance (Applicative f,Applicative g)Applicative (fg)where
pure x=Comp J(pure x)K
Comp fs ~Comp xs =Comp J(~)fs xs K
Functional pearl 9
As a consequence, the composition of two monads may not be a monad, but it is
certainly applicative. For example, both Maybe IO and IO Maybe are applicative:
IOMaybe is an applicative functor in which computations have a notion of ‘failure’
and ‘prioritised choice’, even if their ‘real world’ side-effects cannot be undone. Note
that IO and Maybe may also be composed as monads (though not vice versa), but the
applicative functor determined by the composed monad differs from the composed
applicative functor: the binding power of the monad allows the second IO action to
be aborted if the first returns a failure.
We began this section by observing that Accy ois not a monad. However, given
Monoid o, it can be defined as the composition of two applicative functors derived
from monads—which two, we leave as an exercise.
Accumulating exceptions The following type may be used to model exceptions:
data Except err a =OK a|Failed err
AMonad instance for this type must abort the computation on the first error, as
there is then no value to pass to the second argument of ‘>>=’. However with the
Applicative interface we can continue in the face of errors:
instance Monoid err Applicative (Except err)where
pure =OK
OK f~OK x=OK (f x )
OK f~Failed err =Failed err
Failed err ~OK x=Failed err
Failed err1~Failed err2=Failed (err 1err 2)
This could be used to collect errors by using the list monoid (as in unpublished
work by Duncan Coutts), or to summarise them in some way.
6Applicative functors and Arrows
To handle situations where monads were inapplicable, Hughes (2000) defined an
interface that he called arrows, defined by the following class with nine axioms:
class Arrow ( )where
arr :: (ab)(a b)
() :: (a b)(b c)(a c)
first :: (a b)((a,c) (b,c))
Examples include ordinary ‘’, Kleisli arrows of monads and comonads, and stream
processors. Equivalent structures called Freyd-categories had been independently
developed to structure denotational semantics (Power & Robinson, 1997).
There are similarities to the Applicative interface, with arr generalising pure. As
with ‘~’, the ‘’ operation does not allow the result of the first computation to
affect the choice of the second. However it does arrange for that result to be fed to
the second computation.
By fixing the first argument of an arrow type, we obtain an applicative functor,
generalising the environment functor we saw earlier:
10 Conor McBride and Ross Paterson
newtype EnvArrow ( )env a =Env (env a)
instance Arrow ( )Applicative (EnvArrow ( )env)where
pure x=Env (arr (const x))
Env u~Env v=Env (u4varr (λ(f,x)f x ))
where u4v=arr dup first uarr swap first varr swap
dup a= (a,a)
swap (a,b) = (b,a)
In the other direction, each applicative functor defines an arrow constructor that
adds static information to an existing arrow:
newtype StaticArrow f( )a b =Static (f(a b))
instance (Applicative f,Arrow ( )) Arrow (StaticArrow f( )) where
arr f=Static J(arr f)K
Static fStatic g=Static J()f g K
first (Static f) = Static Jfirst fK
To date, most applications of the extra generality provided by arrows over monads
have been either various forms of process, in which components may consume mul-
tiple inputs, or computing static properties of components. Indeed one of Hughes’s
motivations was the parsers of Swierstra and Duponcheel (1996). It may turn out
that applicative functors are more convenient for applications of the second class.
7Applicative functors, categorically
The Applicative class features the asymmetrical operation ‘~’, but there is an equiv-
alent symmetrical definition.
class Functor fMonoidal fwhere
unit :: f()
(?) :: f a f b f(a,b)
These operations are clearly definable for any Applicative functor:
unit :: Applicative ff()
unit =pure ()
(?) :: Applicative ff a f b f(a,b)
fa ?fb =J(,)fa fb K
Moreover, we can recover the Applicative interface from Monoidal as follows:
pure :: Monoidal faf a
pure x=fmap (λx)unit
(~) :: Monoidal ff(ab)f a f b
mf ~mx =fmap (λ(f,x)f x ) (mf ?mx )
The laws of Applicative given in Section 2 are equivalent to the usual Functor laws,
plus the following laws of Monoidal:
Functional pearl 11
naturality of ?fmap (f×g) (u?v) = fmap f u ?fmap g v
left identity fmap snd (unit ?v) = v
right identity fmap fst (u?unit) = u
associativity fmap assoc (u?(v?w)) = (u?v)?w
for the functions
(×) :: (ab)(cd)(a,c)(b,d)
(f×g) (x,y) = (f x ,g y)
assoc :: (a,(b,c)) ((a,b),c)
assoc (a,(b,c)) = ((a,b),c)
Fans of category theory will recognise the above laws as the properties of a lax
monoidal functor for the monoidal structure given by products. However the functor
composition and naturality equations are actually stronger than their categorical
counterparts. This is because we are working in a higher-order language, in which
function expressions may include variables from the environment, as in the above
definition of pure for Monoidal functors. In the first-order language of category
theory, such data flow must be explicitly plumbed using functors with tensorial
strength, an arrow:
tAB :A×F B F(A×B)
satisfying standard equations. The natural transformation mcorresponding to ‘?
must also respect the strength:
(A×B)×(F C ×F D)
=(A×F C)×(B×F D)
(A×B)×m
y
y
t×t
(A×B)×F(C×D)F(A×C)×F(B×D)
t
y
y
m
F((A×B)×(C×D))
=F((A×C)×(B×D))
Note that Band F C swap places in the above diagram: strong naturality implies
commutativity with pure computations.
Thus in categorical terms applicative functors are strong lax monoidal functors.
Every strong monad determines two of them, as the definition is symmetrical. The
Monoidal laws and the above definition of pure imply that pure computations com-
mute past effects:
fmap swap (pure x?u) = u?pure x
The proof (an exercise) makes essential use of higher-order functions.
8 Conclusions
We have identified Applicative functors, an abstract notion of effectful computation
lying between Arrow and Monad in strength. Every Monad is an Applicative func-
tor, but significantly, the Applicative class is closed under composition, allowing
computations such as accumulation in a Monoid to be characterised in this way.
12 Conor McBride and Ross Paterson
Given the wide variety of Applicative functors, it becomes increasingly useful
to abstract Traversable functors—container structures through which Applicative
actions may be threaded. Combining these abstractions yields a small but highly
generic toolkit whose power we have barely begun to explore. We use these tools by
writing types that not merely structure the storage of data, but also the properties
of data that we intend to exploit.
The explosion of categorical structure in functional programming: monads, comon-
ads, arrows and now applicative functors should not, we suggest, be a cause for
alarm. Why should we not profit from whatever structure we can sniff out, ab-
stract and re-use? The challenge is to avoid a chaotic proliferation of peculiar and
incompatible notations. If we want to rationalise the notational impact of all these
structures, perhaps we should try to recycle the notation we already possess. Our
Jf u1. . . unKnotation does minimal damage, showing when the existing syntax
for applicative programming should be interpreted with an effectful twist.
Acknowledgements McBride is funded by EPSRC grant EP/C512022/1. We thank
Thorsten Altenkirch, Duncan Coutts, Jeremy Gibbons, Peter Hancock, Simon Pey-
ton Jones, Doaitse Swierstra and Phil Wadler for their help and encouragement.
References
Baars, A.I., L¨oh, A., & Swierstra, S.D. (2004). Parsing permutation phrases. Journal of
functional programming,14(6), 635–646.
Barr, Michael, & Wells, Charles. (1984). Toposes, triples and theories. Grundlehren der
Mathematischen Wissenschaften, no. 278. New York: Springer. Chap. 9.
Fridlender, Daniel, & Indrika, Mia. (2000). Do we need dependent types? Journal of
Functional Programming,10(4), 409–415.
Hughes, John. (2000). Generalising monads to arrows. Science of computer programming,
37(May), 67–111.
Hutton, Graham, & Meijer, Erik. (1998). Monadic parsing in Haskell. Journal of functional
programming,8(4), 437–444.
Leijen, Daan, & Meijer, Erik. 1999 (Oct.). Domain specific embedded compilers. 2nd
conference on domain-specific languages (DSL). USENIX, Austin TX, USA. Available
from http://www.cs.uu.nl/people/daan/papers/dsec.ps.
Meertens, Lambert. 1998 (June). Functor pulling. Workshop on generic programming
(WGP’98).
Peyton Jones, Simon (ed). (2003). Haskell 98 language and libraries: The revised report.
Cambridge University Press.
Power, John, & Robinson, Edmund. (1997). Premonoidal categories and notions of com-
putation. Mathematical structures in computer science,7(5), 453–468.
ojemo, Niklas. (1995). Garbage collection and memory efficiency. Ph.D. thesis, Chalmers.
Swierstra, S. Doaitse, & Duponcheel, Luc. (1996). Deterministic, error-correcting combi-
nator parsers. Pages 184–207 of: Launchbury, John, Meijer, Erik, & Sheard, Tim (eds),
Advanced functional programming. LNCS, vol. 1129. Springer.
Wadler, Philip. (1985). How to replace failure by a list of successes. Pages 113–128 of:
Jouannaud, Jean-Pierre (ed), Functional programming languages and computer archi-
tecture. LNCS, vol. 201. Springer.
... street). This optic (an "affine traversal", see §3. 24) is used to parse a string and then access and modify one of its subfields. ...
... In the Sets-based case, the relation between traversable functors, applicative functors [24] and these power series functors has been studied by [17]. ...
Article
Optics are bidirectional data accessors that capture data transformation patterns such as accessing subfields or iterating over containers. Profunctor optics are a particular choice of representation supporting modularity, meaning that we can construct accessors for complex structures by combining simpler ones. Profunctor optics have previously been studied only in an unenriched and non-mixed setting, in which both directions of access are modelled in the same category. However, functional programming languages are arguably better described by enriched categories; and we have found that some structures in the literature are actually mixed optics, with access directions modelled in different categories. Our work generalizes a classic result by Pastro and Street on Tambara theory and uses it to describe mixed V-enriched profunctor optics and to endow them with V-category structure. We provide some original families of optics and derivations, including an elementary one for traversals. Finally, we discuss a Haskell implementation.
... Haskell 98 resorts to cumbersome stacks of monad transformers [46] (their limitations are discussed in [37]). One solution is to take sums of monads [48]; another, added in Haskell 2010, is to weaken monads to applicative (or monoidal) functors [52], which do compose. Both however need intrusive lifting functions to access different effects, suggesting that the problem is not merely with compositionality, but instead with explicit composition as such. ...
Preprint
Full-text available
The Functional Machine Calculus (Heijltjes 2022) is an extension of the lambda-calculus that preserves confluent reduction and typed termination, while enabling both call-by-name and call-by-value reduction behaviour and encoding the computational effects of mutable higher-order store, input/output, and probabilistic computation. In this note the calculus is extended to capture exception handling and loop constructs.
... It is helpful to invest a little time in defining array combinators. First, we can observe that Ar of a fixed shape is an applicative functor [16], so we can trivially derive: K x to produce a constant array; map f a to apply f to all the elements of a; and zipWith f a b to point-wise apply the binary operation f to a and b. ...
Preprint
Full-text available
In this paper we demonstrate a technique for developing high performance applications with strong correctness guarantees. We use a theorem prover to derive a high-level specification of the application that includes correctness invariants of our choice. After that, within the same theorem prover, we implement an extraction of the specified application into a high-performance language of our choice. Concretely, we are using Agda to specify a framework for automatic differentiation (reverse mode) that is focused on index-safe tensors. This framework comes with an optimiser for tensor expressions and the ability to translate these expressions into SaC and C. We specify a canonical convolutional neural network within the proposed framework, compute the derivatives needed for the training phase and then demonstrate that the generated code matches the performance of hand-written code when running on a multi-core machine.
... (To be precise, L together with certain operations forms a lax monoidal functor (Mac Lane, 1998, Section XI.2) as Applicative instances (McBride & Paterson, 2008;Paterson, 2012) but not endo to be an Applicative instance (Matsuda & Wang, 2018a).) The type parameter s has a similar role to the s of the ST s monad (Launchbury & Jones, 1994), which enables the unlifting that converts a polymorphic function ∀s.L s a → L s b back to a bidirectional transformation (a → b, a → b → a). ...
Article
Full-text available
Invertibility is a fundamental concept in computer science, with various manifestations in software development (serializer/deserializer, parser/printer, redo/undo, compressor/decompressor, and so on). Full invertibility necessarily requires bijectivity, but the direct approach of composing bijective functions to develop invertible programs is too restrictive to be useful. In this paper, we take a different approach by focusing on partially invertible functions—functions that become invertible if some of their arguments are fixed. The simplest example of such is addition, which becomes invertible when fixing one of the operands. More involved examples include entropy-based compression methods (e.g., Huffman coding), which carry the occurrence frequency of input symbols (in certain formats such as Huffman tree), and fixing this frequency information makes the compression methods invertible. We develop a language Sparcl for programming such functions in a natural way, where partial invertibility is the norm and bijectivity is a special case, hence gaining significant expressiveness without compromising correctness. The challenge in designing such a language is to allow ordinary programming (the “partially” part) to interact with the invertible part freely, and yet guarantee invertibility by construction. The language Sparcl is linear-typed and has a type constructor to distinguish data that are subject to invertible computation and those that are not. We present the syntax, type system, and semantics of the language and prove that Sparcl correctly guarantees invertibility for its programs. We demonstrate the expressiveness of Sparcl with examples including tree rebuilding from preorder and inorder traversals, Huffman coding, arithmetic coding, and LZ77 compression.
... This idea has been extended further by Hughes (1982) and many others, even leading to design of custom hardware for efficiently rewriting terms in combinatory logic (Stoye, 1983(Stoye, , 1985Scheevel, 1986). The lambda terms corresponding to the S and K combinators have made a recent reappearance as the operations defining the Reader applicative functor (McBride & Paterson, 2008). ...
Article
Full-text available
This pearl defines a translation from well-typed lambda terms to combinatory logic, where both the preservation of types and the correctness of the translation are enforced statically.
Article
Type inference is essential for statically-typed languages such as OCaml and Haskell. It can be decomposed into two (possibly interleaved) phases: a generator converts programs to constraints; a solver decides whether a constraint is satisfiable. Elaboration, the task of decorating a program with explicit type annotations, can also be structured in this way. Unfortunately, most machine-checked implementations of type inference do not follow this phase-separated, constraint-based approach. Those that do are rarely executable, lack effectful abstractions, and do not include elaboration. To close the gap between common practice in real-world implementations and mechanizations inside proof assistants, we propose an approach that enables modular reasoning about monadic constraint generation in the presence of elaboration. Our approach includes a domain-specific base logic for reasoning about metavariables and a program logic that allows us to reason abstractly about the meaning of constraints. To evaluate it, we report on a machine-checked implementation of our techniques inside the Coq proof assistant. As a case study, we verify both soundness and completeness for three elaborating type inferencers for the simply typed lambda calculus with Booleans. Our results are the first demonstration that type inference algorithms can be verified in the same form as they are implemented in practice: in an imperative style, modularly decomposed into constraint generation and solving, and delivering elaborated terms to the remainder of the compiler chain.
Article
Algebraic effect handlers support composable and structured control-flow abstraction. However, existing designs of algebraic effects often require effects to be executed sequentially. This paper studies parallel algebraic effect handlers. In particular, we formalize λ p , a lambda calculus which models two key features, effect handlers and parallelizable computations, the latter of which takes the form of a for expression, inspired by the Dex programming language. We present various interesting examples expressible in our calculus. To show that our design can be implemented in a type-safe way, we present a higher-order polymorphic lambda calculus F p that extends λ p with a lightweight value dependent type system, and prove that F p preserves the semantics of λ p and enjoys syntactic type soundness. Lastly, we provide an implementation of the language design as a Haskell library, which mirrors both λ p and F p and reveals new connections to free applicative functors. All examples presented can be encoded in the Haskell implementation. We believe this paper is the first to study the combination of user-defined effect handlers and parallel computations, and it is our hope that it provides a basis for future designs and implementations of parallel algebraic effect handlers.
Article
Despite decades of contributions to the theoretical foundations of parsing and the many tools available to aid in parser development, many security attacks in the wild still exploit parsers. The issues are myriad—flaws in memory management in contexts lacking memory safety, flaws in syntactic or semantic validation of input, and misinterpretation of hundred-page-plus standards documents. It remains challenging to build and maintain parsers for common, mature data formats. In response to these challenges, we present Daedalus, a new domain-specific language (DSL) and toolchain for writing safe parsers. Daedalus is built around functional-style parser combinators, which suit the rich data dependencies often found in complex data formats. It adds domain-specific constructs for stream manipulation, allowing the natural expression of parsing noncontiguous formats. Balancing between expressivity and domain-specific constructs lends Daedalus specifications simplicity and leaves them amenable to analysis. As a stand-alone DSL, Daedalus is able to generate safe parsers in multiple languages, currently C++ and Haskell. We have implemented 20 data formats with Daedalus, including two large, complex formats—PDF and NITF—and our evaluation shows that Daedalus parsers are concise and performant. Our experience with PDF forms our largest case study. We worked with the PDF Association to build a reference implementation, which was subject to a red-teaming exercise along with a number of other PDF parsers and was the only parser to be found free of defects.
Article
Full-text available
This paper is a tutorial on defining recursive descent parsers in Haskell. In the spirit of one-stop shopping , the paper combines material from three areas into a single source. The three areas are functional parsers (Burge, 1975; Wadler, 1985; Hutton, 1992; Fokker, 1995), the use of monads to structure functional programs (Wadler, 1990, 1992a, 1992b), and the use of special syntax for monadic programs in Haskell (Jones, 1995; Peterson et al ., 1996). More specifically, the paper shows how to define monadic parsers using do notation in Haskell. Of course, recursive descent parsers defined by hand lack the efficiency of bottom-up parsers generated by machine (Aho et al ., 1986; Mogensen, 1993; Gill and Marlow, 1995). However, for many research applications, a simple recursive descent parser is perfectly sufficient. Moreover, while parser generators typically offer a fixed set of combinators for describing grammars, the method described here is completely extensible: parsers are first-class values, and we have the full power of Haskell available to define new combinators for special applications. The method is also an excellent illustration of the elegance of functional programming.
Article
1. Categories.- 2. Toposes.- 3. Triples.- 4. Theories.- 5. Properties of Toposes.- 6. Permanence Properties of Toposes.- 7. Representation Theorems.- 8. Cocone Theories.- 9. More on Triples.- Index to Exercises.
Article
A permutation phrase is a sequence of elements (possibly of different types) in which each element occurs exactly once and the order is irrelevant. Some of the permutable elements may be optional. We show how to extend a parser combinator library with support for parsing such free-order constructs. A user of the library can easily write parsers for permutation phrases and does not need to care about checking and reordering the recognized elements. Applications include the generation of parsers for attributes of XML tags and Haskell's record syntax.
Article
Monads have become very popular for structuring functional programs since Wadler introduced their use in 1990. In particular, libraries of combinators are often based on a monadic type. Such libraries share (in part) a common interface, from which numerous benefits flow, such as the possibility to write generic code which works together with any library. But, several interesting and useful libraries are fundamentally incompatible with the monadic interface. In this paper I propose a generalisation of monads, which I call arrows, with significantly wider applicability. The paper shows how many of the techniques of monadic programming generalise to the new setting, and gives examples to show that the greater generality is useful. In particular, three non-monadic libraries for efficient parsing, building graphical user interfaces, and programming active web pages fit naturally into the new framework.
Article
We introduce the notions of...
Book
An overview of the Haskell 98 language, which is a general purpose, purely functional programming language incorporating many innovations in programming language design is presented. Haskell provides higher-order functions, non-strict semantics, static polymorphic typing, user-defined algebraic datatypes, pattern-matching, list comprehensions, a module system, and a rich set of primitive datatypes. The syntax for Haskell programs and an informal abstract semantics for the meaning of such programs is defined.
Article
this memory requirement, without reducing the usefulness of the combinators, by rewriting the implementation of them. Such a rewritten set of parsing combinators is described in the fourth paper of this thesis, iEOEcient parsing combinatorsj.