Applicative Functors in Haskell

9 downloads 211 Views 263KB Size Report
Jun 6, 2010 - 1 Introduction. Applicative functors are a new programming con- ...... userComment). Listing 25: Monadic c
Seminar Program Analysis and Transformation University of Applied Sciences Rapperswil

Applicative Functors in Haskell Michael R¨uegg, [email protected] June 6, 2010

Abstract. Functors are well known and understood and have proven to be useful in the Haskell community. A new concept called applicative functor recently gained attention which overcomes some of functor’s weaknesses and offers new possibilities in solving certain kind of problems. Applicative functors promote an applicative style of programming which is often preferred compared to the more imperative style that comes with the use of monads. This paper shows the theory behind applicative functors and how they are applied in real-world Haskell examples. In the last part of this paper the applicative style is shown in parsing code and applicative functors and monads are compared to each other.

1

Introduction

is commonly known as “applicative style”. Section 4 then shows the applicative way of solving problems through parsing examples with support of the Haskell parser combinator library Parsec. Because applicative functors and monads do have some commonalities and are often discussed together, section 5 outlines their relationships, when it is best to use which of the two and how one can switch from monads to applicative functors. Finally, section 6 concludes with a summary of the most important ideas presented in this paper and mentions a few projects which make use of applicative functors.

Applicative functors are a new programming concept in the functional programming world originally introduced by MyBride and Paterson in their paper “Applicative Programming with Effects”. Their library Control.Applicative provides an implementation of the concept in the programming language Haskell. Applicative functors are based on functors. They build a powerful abstraction that is a more structured form of functors, but less structured than monads. Applicative functors promote a so called applicative style of programming. Although there exist implementations of applicative functors for other programming languages (e.g., in the Scala library ScalaZ [1]), this paper concentrates on Haskell. Its aim is to give the reader a thorough overview of both the concept as well as their implementation in Haskell. Various code examples should make the reader familiar with their syntax and the applicative style of solving problems. Furthermore, the paper tries to show that although monads are used in Haskell since ever and applicative functors are a new concept, it is often preferable to use applicative functors instead of monads in certain contexts, which will be discribed here. This paper is structured as follows: Section 2 gives an introduction into the concepts type classes, kinds and functors including some comments about their mathematical background. The topics of that section can be seen as the preliminaries for understanding applicative functors. Readers that are already familiar with the underlying ideas can safely skip that section. The main part of this paper is contained in section 3 where applicative functors are discussed in detail and a first outlook is given what

2

Haskell Basics

The most important preliminaries for understanding applicative functors in Haskell - beside a basic comprehension of Haskell’s type system - are a fine grasp of type classes, kinds, functors and their underlying mathematical principles. These concepts are discussed in detail in this section. 2.1

Type Classes

Haskell’s concept of type classes, which was first described by Wadler and Blott in [2], offers a new way of polymorphism called ad-hoc polymorphism. Whereas the kind of polymorphism that allows functions to be defined over a range of types working in the same way for each of these - and therefore the type does not matter - is well known (e.g., Haskell’s list concatenation function (++)) and defined as parametric polymorphism, ad-hoc polymorphism allows functions to behave differently for each type. Ad-hoc polymorphism is often circumscribed with overloading. 1

While other languages like C++1 or Java provide operator and method overloading in combination with coercion for ad-hoc polymorhism, Haskell is unique in a way that one just specifies what the types act like and connects them together with the appropriate type classes. Coercion polymorphism allows implicit conversion between a value of one type into a value of another type (consider e.g. Java’s ability to support expressions like "hello" + 1). Haskell does not support this kind of polymorphism. There is - among others - one fundamental distinction to classes in OOP. While in OOP classes contain data and functions, the functions of type classes are separate from the data they work on2 . A commonly referred example for explaining adhoc polymorphism and overloaded behaviors for different types is equality (e.g., in [6], [7] and [8]). Equality in Haskell - which is based on value semantics - is expressed by the (==) function which is defined like this:3

one uses Haskell’s keyword instance. Listing 2 shows a simple example of an instance for testing equality of boolean values. instance Eq Bool where x == y = if x then y else not y

Listing 2: Instance declaration for boolean values

To present a somewhat more elaborate example of an instance declaration, listing 3 shows that it is also possible to define recursive definitions of equality using binary trees. data Tree t = Node (Tree t) (Tree t) | Leaf t deriving (Show) instance (Eq a) => Eq (Tree a) where Leaf a == Leaf b = a == b (Node l1 r1) == (Node l2 r2) = (l1==l2) && (r1==r2) _ == _ = False

Listing 3: Instance declaration for binary trees [8]

Note that it is very important to specify the context Eq a in this example. This constraint basically says that the definition of the equality test for binary trees is dependent on the fact that a’s can be tested too and therefore must be an instance of Eq as well. The following code session shows an example of equality tests with the defined Tree type:

ghci> :type (==) (==) :: (Eq a) => a -> a -> Bool

As one can see from its type signature, (==) uses the class constraint Eq a, which is called a context. (==) expects two objects of type Eq and returns a boolean based on the equality test. Eq itself is a type class which is defined in the Prelude4 as shown in listing 1.

ghci> (Node (Leaf 1) (Leaf 2)) == (Node (Leaf 1) (Leaf 2)) True ghci> (Node (Leaf 1) (Leaf 2)) == Leaf 2 False ghci> (Node (Leaf 1) (Leaf 2)) /= Leaf 2 True

class Eq a where (==), (/=) :: a -> a -> Bool x /= y x == y

= =

not (x == y) not (x /= y)

Listing 1: Definition of the type class Eq

With the help of the keyword deriving it is possible to declare a data type as a member of a specific type class. In this example, Tree is part of the type class Show which is used to convert values into strings and lets one easily display tree objects on the console. An interesting fact is that Haskell allows to make type classes subclasses of other type classes. As an example consider the type class declaration of Ord (listing 4), another built-in type class which is used to sort elements based on a specific ordering which is defined by the instance declarations of the involved types.

As one can see from this class declaration, a type class specifies an interface other types are expected to support. Note that the type variable a represents an arbitrary instance of a class. The class declaration says that if a is an instance of Eq, then (==) and (/=) are used for the equality and inequality tests [9]. The type class declaration in the Prelude also offers a minimal definition of these functions which are implemented in terms of each other. This allows implementors of instances for new classes to only specify one of the two operations and omit the other. Types which support the functions in the interface are known as instances. To define an instance

class (Eq a) => Ord a where compare :: a -> a -> Ordering () :: a -> a -> Bool

1 One can emulate Haskell’s type classes in C++ with the help of templates and traits as described in [3] - but with much more code needed. C++0x’s concepts are similar to Haskell’s type classes [4]. 2 As a further important difference to common OOP languages, Haskell doesn’t embed type information into objects. Instead, class constraints for polymorphic operations are passed in form of dictionaries which contain methods for all operations [5]. 3 Note that in this paper code examples are verified with the help of the interactive environment of the Glasgow Haskell Compiler edition (known as ghci) which provides a read-eval-print loop (REPL) as known from other programming languages. 4 Prelude is Haskell’s standard library which offers a huge amount of useful functions.

Listing 4: Type class declaration Ord

The important fact here is that Ord is defined in terms of Eq: Before one can use a type a in orderrelations, one needs to make sure that a is also an instance of Eq. As a consequence, subclassing in Haskell is implemented as class constraints on class declarations which the compiler must guarantee to check for. Note that an instance declaration for a type class is only valid if all its superclasses have 2

of the category mapped over is preserved. The interested reader will find a short introduction into the topic in appendix A. This section concentrates on how functors are defined and used in Haskell and also shows their shortcomings.

an instance declaration for it. Therefore, the superclass hierarchy is expected to form a directed acyclic graph [5]. 2.2

Kinds

The Haskell compiler is able to verify that type constructors are used correctly with the help of kinds. Kinds guarantee that each specific type is correctly used in expressions. Each type has its associated kind which can basically take one of two forms [8]. The first form is the symbol * which represents a concrete type. As one can see from the following example5 , Int is a concrete type and therefore has the kind *:

2.3.1 Functor Type Class Functors in Haskell are described by the type class Functor, which is defined in the Prelude like written in listing 5. class Functor f where fmap :: (a -> b) -> f a -> f b

Listing 5: Definition of type class Functor

The type class Functor has one function called fmap and does not provide a default implementation for it. fmap takes a function over ordinary values a -> b and a functor and returns a functor [7]. The value in the functor gets unwrapped, the function will be called on it, and then the new value is again wrapped in a functor. If one looks at this similar to curried functions, fmap can also be seen as a function over containers f a -> f b with f as the type of the container [7]. The process of taking a function a -> b and returning a new function f a -> f b is commonly called lifting ([6], [7] and [10]). To make this more obvious, the type signature of fmap can be written with extra parentheses:

ghci> :kind Int Int :: *

The second type of kind is k1 ⇒ k2 , which takes a type of kind k1 and returns a type of kind k2 . An example of a type that has this sort of kind is the formerly introduced Tree type: ghci> :kind Tree Tree :: * -> * ghci> :kind Tree Int Tree Int :: *

The type constructor Tree has the kind ∗ ⇒ ∗. If one partially applies Tree with the help of Haskell’s currying mechanism with the type parameter Int, its kind gets the form of a concrete type. Either is a data type that is used to represent two possibilities. A value of type Either a b can be either Left a or Right b. Its kind has the form ∗ ⇒ ∗ ⇒ ∗:

fmap :: (a -> b) -> (f a -> f b)

In general, functors are used with container types to apply a function over every of its elements. It is important to note that f is not a concrete type with kind * but rather a type constructor that takes one type parameter [6]. For every member of the type class Functor it’s essential that they all have a kind of * -> * because otherwise the compiler would claim a type error. As an example, consider the following Functor instance where the type error is caused by the concrete type parameter Integer which has a kind of * instead of the expected * -> *:

ghci> :kind Either Either :: * -> * -> * ghci> :kind Either Int Either Int :: * -> * ghci> :kind Either Int String Either Int String :: *

As before, Either can be partially applied with type parameters and finally has the kind of a concrete type. Although kinds are not directly visible in Haskell programs, they are a fundamental concept of its type system. Before doing type checking, the compiler infers kinds and therefore there is no need for providing kind declarations [8]. Kinds get visible when one tries to compile a program that has kind errors because of wrong type signatures. Section 2.3.1 will show a kind error related with the use of functors. 2.3

instance Functor Integer where -- type error caused by type parameter Integer

Beside the more obvious explanations, functors are often referred to represent some sort of computational context [10]. The idea is that fmap applies a function to every container element without changing its context. 2.3.2 Functor Applications An important application of functors are lists. Consider the implementation of the Functor instance for lists in listing 6.

Functors

An important prerequisite for understanding applicative functors are functors. Functors are a concept of the mathematical branch Category Theory. A functor basically is a mapping between two categories with the important property that the structure

instance Functor [] where fmap = map

5 ghci provides the command :kind which infers and prints the kind of the given type.

As one can see, fmap for lists is just defined with the map function from the Prelude which executes

Listing 6: Functor for lists

3

2.3.3 Functor Laws Functors should follow certain rules which are commonly referred as functor laws. In general, functors are expected to behave as things that one can map over. When one uses fmap on a functor, it should only apply a function over a functor, and nothing more. Especially it is important that functors preserve the structure of the underlying container (i.e., the underlying category in mathematics). To accomplish this, every functor in Haskell is expected to satisfy the following two laws: f map id == id f map (f . g) == f map f . f map g The first functor law basically says that if one maps the identity function id over a functor, it is expected that one gets the same functor as the original one. The functor for the type Tree meets this first requirement as one can see from the following test:

a function for every member of a list. Notice again that one has to use a type constructor with kind * -> * which is exactly what [] is. There are a lot of other useful types where it makes sense to allow a mapping of a function over the values of the specific container type. Maybe is a type class and used in Haskell to refer to optional values. It is an instance of Functor and is defined in the Prelude. Listing 7 shows the implementation of its data type as well as its Functor instance declaration. data Maybe a = Nothing | Just a instance Functor Maybe where fmap f (Just x) = Just (f x) fmap _ Nothing = Nothing

Listing 7: Data type and functor of Maybe

The first pattern match applies a function to the value inside Just. Mapping a function over a missing value results as expected in Nothing. Of course Haskell also allows the definition of own data types as instances of Functor. Consider as an example a functor implementation for the previous given Tree type in listing 8.

ghci> fmap id (Node (Leaf 25) (Node (Leaf 16) (Leaf 9))) Node (Leaf 25) (Node (Leaf 16) (Leaf 9))

The second law claims that mapping a function composition f . g over a functor should be the same as mapping a function f over a functor and then mapping the other function g over it [6]. Consider again the following test that proves that the tree functor also obeys the second functor law:

instance Functor Tree where fmap f (Leaf x) = Leaf (f x) fmap f (Node lc rc) = Node (fmap f lc) (fmap f rc)

ghci> fmap (( (fmap ( fmap sqrt (Node (Leaf 25) (Node (Leaf 16) (Leaf 9))) Node (Leaf 5.0) (Node (Leaf 4.0) (Leaf 3.0))

It is even possible to have a functor instance for a type that takes two type parameters like it is the case with Either.

2.3.4 Functor Limitations All functions in Haskell are curried and only take one single argument, which means that a function that has a type signature of int -> int -> int actually only takes one parameter of type int and returns a function int -> int. Consider the following example which shows an exemplary mapping of a partially applied multi-parameter function over functors [6]:

data Either a b = Left a | Right b instance Functor (Either a) where fmap f (Right x) = Right (f x) fmap f (Left x) = Left x

Listing 9: Functor instance Either

Because of the fact that Functor expects a type constructor with just one type parameter, one has to use Either a instead of Either to satisfy the kinds requirements6 . Consider that the function is only mapped over the Right value of Either. This is because of the general conventions when using Either, especially when it comes to report errors: whereas the left value is used to hold an error value, the right is used to store the correct or real value of a computation.

ghci> let a = fmap (ˆ) [1..10] ghci> :type a a :: [Integer -> Integer] ghci> fmap (\f -> f 2) a [1,4,9,16,25,36,49,64,81,100]

As one can see from evaluating the type of a, this results in a functor which contains functions inside it [6]. fmap is not different to any other function in Haskell in terms of currying and partial application. Therefore fmap can be seen as a function that takes a function as input and returns a list of functions with functors as input and output parameters

6 Note

that Haskell 98 does not allow Either Int as a type constructor for Functor, although the Glasgow Haskell Compiler GHC can handle this when using a special compiler directive (see [7]).

4

as its first argument instead of an ordinary function (a -> b). To refer to the context analogy introduced earlier, f (a -> b) can be described as a function in a context [10]. () offers the ability which fmap lacks as explained in section 2.3.4: it takes a functor that has a function in it and another functor and somewhat extracts the function from the first functor and applies it to the functor of the second argument. Note that () is an infix operator and left-associative8 :

which then can be evaluated with the help of lambdas as shown before. There is - among others - one important limitation that functors cannot address: with fmap it is not possible to apply a function which is part of a context to a value in a different context [10]. Let’s see what that means: ghci> fmap Just (ˆ2) Just 5 Couldn’t match expected type ’t1 -> t’ against inferred type ’Maybe a’

This example shows that it’s not possible with fmap to take out the function (ˆ2) of a functor and apply it over another functor. One is restricted with fmap to map functions over functors. Applicative functors provide a solution for this problem, which are discussed in the next section.

3

ghci> :module +Control.Applicative ghci Control.Applicative> :info class (Functor f) => Applicative f where ... infixl 4

As a first example of an applicative functor consider listing 11 which shows the applicative version of Maybe:

Applicative Functors

instance Applicative Maybe where pure = Just (Just f) (Just x) = Just (f x) _ _ = Nothing

7

The title of McBride and Ross’ fundamental paper “Applicative Programming with Effects” somehow explains the main purpose of applicative functors: They allow one to encapsulate computations with side effects - which are known from monads - in a functionally pure way. The second important idea behind applicative functors is a special kind of programming style they promote which is called “applicative style”. Both topics will be explained in detail in the following sections. 3.1

Listing 11: Applicative instance of Maybe [12]

pure wraps a value of type Maybe into an applicative functor and returns it. () matches in the first case two functors and applies the function of the first functor to the value in the second functor. The wildcard pattern matching takes care of any other case and returns plain Nothing. The following code shows () with Maybe in action:

Basics

ghci> Just (ˆ2) Just 10 Just 100 ghci> pure (ˆ2) Just 10 100 ghci> Just (++ "bar") Just "foo" Just "foobar" ghci> Just (/2) Nothing Nothing ghci> Nothing Just 3.1415 Nothing

Applicative functors are a more structured form of functors, but less structured than monads [7]. The type class Applicative - which is the heart of applicative functors and shown in listing 12 - is defined in the Haskell module Control.Applicative. It has two methods called pure and () and - similar to Functor - does not provide a default implementation of them. Therefore, everybody who wants to implement an applicative functor instance has to provide an implementation for both of them.

Note that Just and pure have the same effect in this case, but pure is preferable when using it together with [6]. Another important fact this example shows is that applying a function on Nothing results in Nothing same as trying to extract a function out of Nothing and map it over a functor. even allows one to use more than one functor:

class (Functor f) => Applicative f where pure :: a -> f a () :: f (a -> b) -> f a -> f b

Listing 10: Type class Applicative

ghci> pure (ˆ) Just 2 Just 8 256

The class constraint for Applicative makes sure that a type class must be part of Functor when it wants to be an Applicative. Note that the type variable f symbolizes the applicative functor instance here. pure takes some value of any type and returns an applicative functor with that value wrapped in it. () is somewhat similar to fmap of the type class Functor. Both type signatures are the same except that () takes a functor f (a -> b)

As already mentioned, is left-associative and therefore the expression is evaluated like this: (pure (ˆ) Just 2) Just 8. Through currying and partial application of the power function the first part of the evaluation results in Just (ˆ2) which has the following type signature: ghci> :type pure (ˆ) Just 2 (Num a, Integral b) => Maybe (b -> a)

7 McBride and Ross originally named this concept Idiom, but then switched to Applicative Functor [11].

8 For subsequent code snippets it is assumed that the library Control.Applicative has been loaded as shown here.

5

to mention here. The Functor instance must obey the following law [12]:

Finally, the intermediate outcome is then applied to Just 8 which results in 256. These kind of evaluations result in an applicative style of programming, which is discussed in more detail in section 3.3. 3.2

fmap f x = pure f x

To examine that the Functor instance for Maybe (see listing 7) and the one for Applicative both confirm to this rule, consider the following code snippet which shows that indeed both result in the same value:

Laws

Similar to functors, applicative functors should obey to a few laws. The following four laws are generally required by every applicative instance: pure id pure (.) u pure f u pure y

v = v u (v pure x = pure

ghci> fmap (ˆ2) (Just 8) Just 64 ghci> pure (ˆ2) (Just 8) Just 64

-- Identity v w = w) -- Composition = pure (f x) -- Homomorphism ($ y) u -- Interchange

3.3

Listing 12: Applicative Functor Laws [12]

The use of applicative functors advocates a kind of programming that is commonly referred as applicative style [14]. This becomes more apparent with the application of the function ()11 which is defined in the module Control.Applicative as shown in listing 14.

To gain a better understanding of these laws, the QuickCheck9 tests in listing 13 verify that the applicative instance for Maybe (see listing 11) obeys to these rules10 . -- applFunctorLawTests.hs import Control.Applicative import Test.QuickCheck.Batch

() :: Functor f => (a -> b) -> f a -> f b f a = fmap f a

p_identity :: Maybe Integer -> Bool p_identity x = (pure id x) == x

Listing 14: Definition of the function ()

As one can see from this definition, () is a synonym for fmap. Consider again the applicative functor law relating to fmap introduced in section 3.2. According to that law, pure f x is the same as fmap f x. Instead of writing pure f a b ... one can use fmap f a b ... [6]. () allows one to reduce the amount of boilerplate code that would otherwise be necessary. This function is - same as () - defined as a left-associative infix operator:

p_composition :: Integer -> Maybe Integer -> Bool p_composition x y = (pure (.) pure (+x) pure (*x) y) == (pure (+x) (pure (*x) y)) p_homorphism :: Integer -> Integer -> Bool p_homorphism x y = (pure (*x) pure y) == (Just ((*x) y)) p_interchange :: Integer -> Integer -> Bool p_interchange x y = (pure (+x) pure y) == (pure ($ y) Just (+x)) options = TestOptions { no_of_tests , debug_tests

Applicative Style

= 200 = False }

ghci> :info () infixl 4

main = do runTests "applfunctorlaws" options [ run p_identity , run p_composition , run p_homorphism , run p_interchange ]

One can use () to apply a function between applicative functors like this: ghci> (ˆ) Just 2 Just 8 Just 256 ghci> (++) Just "foo" Just "bar" Just "foobar"

Listing 13: QuickCheck Tests for applicative Maybe

Again, partial application plays an important role. The following code shows what happens in each step of the application from left to right because of the left-associative property of ():

QuickCheck allows to parameterize the number of generated tests for every test case as well as to run all tests in batch mode together. When executed, all succeed as expected: $ ghc --make applFunctorLawTests.hs $ ./applFunctorLawTests applfunctorlaws : ....

ghci> Maybe ghci> Maybe

(800)

There is one more rule concerning the relationship of functors and applicative functors that is important

:type (++) Just "foo" ([Char] -> [Char]) :type Just ("foo"++) Just "bar" [Char]

The first application results in a value of type Maybe ([Char] -> [Char]) which is a functor that has a function inside it which maps strings to strings. This partial application then is operated on Just "bar" which results in the final value of Maybe [Char].

9 QuickCheck is a testing tool for Haskell which enables automatic testing based on programmer specifications in form of properties the functions under test must satisfy. From these QuickCheck then generates large numbers of randomly chosen test cases to verify that the specified properties hold (see [13]). 10 The tests shown here are not considered to be exhaustive. To keep the example compact, the tests are based on Integer and the functions applied to them are hard-coded.

11 () should not be confused with the function application operator ($) which allows one to get rid of unnecessary parantheses: f (g (h x)) can then be written as f $ g $ h x.

6

The nature of the “zip-style” processing gets apparent through the use of zipWith in the definition of (). One of the important properties of zipWith is inherent here: The resulting list has the size of the smaller of the two lists given to ():

Paterson and Ross introduced a special notation for the form pure f x1 x2 ... xn which looks like this [14]: [[f x1 x2 ... xn ]] This special bracket notation should make the paradigma behind applicative functors more obvious in the sense that a pure function is applied to a list of arguments using (), whereas effects are present during this application [14] with the consequence that effectful computations can be described by function application [10]. These effects and the mentioned applicative style will get more apparent through reading section 3.4 which discusses the IO monad and section 4 which presents applicative parsing. 3.4

ghci> getZipList $ (mod) ZipList [9, 27, 56] ZipList [1..10] [0,1,2]

Another useful instance of Applicative is IO which is defined as shown in listing 17: instance Applicative IO where pure = return a b = do f (a -> b -> c) -> f a -> f b -> f c liftA2 f a b = f a b liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d liftA3 f a b c = f a b c

Listing 16: Applicative instance ZipList 12 Haskell’s newtype keyword is used to rename an existing type to give it an unambigous identity.

Listing 18: liftA function family

7

Consider that one wants to compute the maximal nesting level of parentheses. With the help of Parsec, this is a somewhat trivial exercise and the code for this task is shown in listing 20.

The liftA family of functions somewhat ”hides” the applicative way of programming because it applies a function (unary, binary or ternary) between the applicatives which is normally done with () [6]. Consider the following example which shows liftA2 in action:

import Text.ParserCombinators.Parsec nImp :: Parser Int nImp = do { char ’(’ ; n f a () :: Applicative f => f a -> f b -> f b (*>) = liftA2 (const id) ( f a -> f b -> f a ( nApp) (char ’)’ *> nApp) pure 0 where countPar n m = max (n+1) m

Applicative Style Parsing

Listing 21: Applicatives style parentheses parsing

The usefulness of applicative functors and the associated “applicative style” of programming can be well shown with parsing examples. The elegance and the compactness of the code that uses applicative functors in the sense of applying parsers followed by combining their results [7] compared to writing parsers in a more procedural style with monad-style do blocks might even further convince the reader of their added value. The parsing problem in this section will be tackled with the help of the Haskell parser combinator library Parsec (see [15])13 . Because Parsec is a monadic14 library, a small wrapper module is needed that defines a Parsec parser as an applicative functor to be able to use Parsec together with applicative functors. The code of this module is shown in appendix B.

As already introduced, (*>) applies its first argument but throws its result away, and afterwards applies the second which is its overall result. In this code (*>) consumes a parenthesis and calls the function recursively. The following code snippet shows the applicative parser version in action with the help of parseTest, which is a built-in function of Parsec that executes a parsing function and prints its result on the standard output or otherwise shows an error with line information: ghci> parseTest nestingApp "((()()))" 3 ghci> parseTest nestingApp "(()" parse error at (line 1, column 4): unexpected end of input expecting "(" or ")"

Compare the applicative version to the imperative style parser: The former is both more readable and needs less code. In opposite to the monadic-style parser the applicative version can be considered as the more ”functional way” of parsing. No variables are needed for storing intermediate parser results.

13 The

examples in this chapter have been tested with Parsec v2.1 and GHC v6.10.4 14 The term monadic is used to relate concepts to monads. Monadic types are simply instances of the type class Monad and monadic values - also known as actions - have a monadic type [7].

8

Ultimately, the programmer is just applying parsers and combining their results.

5

liftM :: Monad

Control.Monad’s function (>>=) is one of the most important differences between monads and applicative functors. This function is commonly called bind function [7]. It combines two computations into a larger one and allows them to interact with another [10]. This works with the help of its second argument (a -> m b) which is a function that produces a computation to run based on the first argument of the bind function. This makes it possible to use the result of the first computation to decide which computation should be run second and to use the latter result as the overall one [10]. The power of (>>=) is what makes monads more powerful than applicative functors. There are more applicative functors than monads exactly because of this reason [14]. Another point of view about this difference is the following: Whereas applicative functors are fixed in their structure, the structure of monad computations can change based on intermediate results [10]. The type signatures shown in listing 24 of the applicative and monadic parsing combinator versions for Parsec make this fact obvious.

Monads vs. Applicative Functors

This section is about the differences and similarities of applicative functors compared to monads and the advantages the former have in certain contexts. As a consequence it is shown how one can replace existing monadic code with an applicative version. 5.1

Differences and Similarities

There is a strong coupling between monads and applicative functors. In category theory, every monad is a functor [17]. Unfortunately, in Haskell this fact is not present in the Prelude. The Haskell typeclass of Monad is not constrained by Functor as can be seen by listing 22 which shows the type class Monad with its two core functions. This is commonly seen as an unfortunate oversight when the type classes have been designed at that time ([7], [10]). As a workaround, Haskell library developers - when defining an instance of Monad for a type usually write an instance of Functor for it too [7].

() :: Parser a -> Parser (a -> b) -> Parser b (>>=) :: Parser a -> (a -> Parser b) -> Parser b

class Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b

Listing 24: Type signatures of monadic and applicative parsing combinators

Listing 22: Definition of type class Monad

Every monad is also an applicative functor but note that the same is not true for the opposite direction which comes from the additional power monads have [7]. As a matter of fact, every monad can be made applicative by setting its corresponding functions equal as seen with the example of Maybe in listing 23.

Not only is it possible to give names to intermediate parsing result, monadic parsing also allows one to make decisions based on these. This leads to the fact that applicative style parsers are restricted to context-free grammars whereas monadic style parsers are also able to parse context-sensitive ones ([18], [19]).

instance Applicative Maybe where pure = return () = ap

5.2

Advantages of using Applicative Functors

Although monads are more powerful than applicative functors, it is often better to use the latter if possible. This is because applicative functors have certain advantages over monads which will be discussed in this section. One of its advantages is that - because there are more applicative functors than monads - applicative functors are more generic which leads to the fact that they can be used in more application areas. Another important advantage is that applicative functors can be easier composed together as it is the case with monads. As powerful they are, standard monads do not allow one to combine them. To accomplish this, the use of so called monad transformers16 is suggested. For applicative functors there are no transformer libraries because there is no need for them. Applicative functors can be combined to-

Listing 23: Definition of applicative instance Maybe in terms of Monad functions

As can be seen from this example15 , pure is set to return and () to ap. ap is a monadic lifting operator defined in Control.Monad and is considered to be equivalent to () from Control.Applicative. Its type signature looks like this: ap :: Monad

m => (a1 -> r) -> m a1 -> m r

m => m (a -> b) -> m a -> m b

As a further striking similarity to Control.Applicative, Control.Monad consists of a family of operations called liftMn where n is is replaced with the needed number of actions. The type signature of liftM looks exactly as the one of fmap: 15 Note

that in order to be able to use Parsec with applicative functors, the module Applicative.Parsec shown in appendix B has to do exactly the same for the type GenParser which is a special monad for parsing.

16 Monad transformers are similar to regular monads, but - as they are not standalone - they modify the properties of the underlying monad [7].

9

gether in a generic way as seen in section 3.5. They are even closed under composition [14]. Especially when it comes to parsing it is not always necessary to have the additional power monadic style parser combinators offer. When the applicative version is enough, one often gains a more elegant solution compared to when using monads. Applicative parsing also has a more functional feeling because it is all about function application with carrying context information. Monadic style parsing looks much more imperative when using Haskell’s do-notation. To follow common wisdom to take the least powerful, but most general tool that is able to get the job done, applicative parsing is preferable. Or to quote McBride and Patterson about the adoption of applicative functors and monads [14]: “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!” 5.3

import Control.Monad hasCommentM blogComments = liftM3 BlogComment (lookup "title" blogComments) (lookup "user" blogComments) (lookup "comment" blogComments)

Listing 26: Use of liftM for blog comment retrieval

This step can be considered as an intermediate step towards the use of applicative functors. The use of the liftM family of functions can often be replaced with the applicative pendants liftA18 . The same is true for (), and the monadic apply function ap can be replaced with the applicative () and return with pure [12]. Finally, listing 27 shows the resulting applicative version which uses no monadic code anymore. Instead, the logic is fully implemented with the chained use of () and (). import Control.Applicative hasCommentA blogComments BlogComment lookup lookup lookup

How to switch from Monads

The last section was all about the advantages one gains when using applicative functors instead of monads in certain situations. This section now describes some common strategies and techniques to transform existing monadic code into applicative one. The existing code base17 for this section is shown in listing 25.

= "title" blogComments "user" blogComments "comment" blogComments

Listing 27: Monadic code fully replaced with applicative functions

The following interactive session shows the new applicative blog comment retrieval functionality in action: ghci> let cmt1 = [("title", "State Monad"), ("user", "Philip Wadler"), ("comment", "Great post, but...")] ghci> hasCommentA cmt1 Just (BlogComment {postTitle = "State Monad", userName = "Philip Wadler", userComment = "Great post, but..."}) ghci> let cmt2 = [("title", "Functors"), ("user", "Conor McBride")] ghci> hasCommentA cmt2 Nothing

data BlogComment = BlogComment { postTitle :: String , userName :: String , userComment :: String } deriving (Show) hasComment blogComments = do postTitle