© Alejandro Serrano Mena 2019
Alejandro Serrano MenaPractical Haskellhttps://doi.org/10.1007/978-1-4842-4480-7_16

16. Architecting Your Application

Alejandro Serrano Mena1 
(1)
Utrecht, The Netherlands
 

In a programming book you usually learn a new language via brief examples. Alas, real applications are usually much bigger than ten or twenty lines and need further work in designing, maintaining, and refactoring their code. This chapter tries to bridge the gap between those two worlds by offering a set of guidelines. Of course, this advice is not carved in stone, but it can give you a good idea of how to use functional programming.

I’ve introduced many different tools for Haskell programming throughout the book: test frameworks, profiling tools, and so on. In this chapter you’ll see a summary of all of them and get some suggestions concerning other good programs that couldn’t be covered in depth here.

Then I’ll compare how design patterns are applied in object-oriented programming and how you can use them in the functional realm. As you’ll see, the gap is not so wide, and many of the concepts translate into functional equivalents but with a different implementation.

One concept which is very specific of Haskell is that of monad. Although you can define them in any language, Haskell gives you libraries and notation to use them more succinctly. At the end of the chapter I’ll describe some design patterns related to monads and review the most commonly found ones.

Tools

During the course of this book I have presented many tools. In this section, I will recap all of them and introduce some others. Because of a lack of space, I am not able to cover every possible tool, but all of them have good and complete documentation on the Internet.

Project and Dependency Management

Cabal and Stack are the tools for managing projects in the Haskell world. As you have seen throughout the book, they share a declarative way to specify which kind of software artifacts should be built, the dependencies you need, and options for compilation. Each artifact is defined in a so-called stanza .

Most of the power of Haskell comes from the great repository of libraries called Hackage . This repository is managed by the Haskell community, which uploads its latest work to make it available to the outer world. Using the cabal install command, you can automatically get a copy of a package and compile it. For those cases in which stability is preferred over novelty, Stackage provides a curated subset of Hackage which is known to compile together.

Note

Pay attention to licensing when using code from repositories such as Hackage. Each Cabal file should list the license, so it’s easy to check that a specific package license is suitable for your use case.

Code Style

You need to write code that satisfies the constraints of the compiler to produce some library or executable. However, code that is accepted may not necessarily be easily maintainable, or it may follow a pattern whose behavior is usually confusing for later readers.

One piece of advice I strongly suggest you follow is to always enable the -Wall flag of the compiler. Setting this flag causes the compiler not only to look for errors but also to issue warnings for your code. The HLint tool is also useful in generating warnings, helping you find poorly written sections of code that may prove troublesome later.

In many cases, you also want your code to follow some style guidelines, that is, a set of recommendations on indentation, newlines, whether to use anonymous functions or define them in let blocks, and so on. Stylish Haskell is a tool that can help you with guidelines. It reads your code and produces a new version following some configurable options. Furthermore, it’s possible to integrate it into Visual Studio Code, Emacs, vi, and many other editors, so you can make it part of your daily development experience.

Documentation

In the previous chapter I discussed the importance of good and up-to-date documentation. As you now know, Haddock is the recommended tool for maintaining that documentation. The main benefit of using Haddock is that the information about an element appears near the element itself. Haddock is also the tool used to produce the massive amount of help documents in Hackage. Finally, Haddock’s output shows the documentation coverage, so you can quickly see whether you’ve forgotten to document any of the functions within your code.

Searching a large number of packages for functions and data types can be a time-consuming task. Hoogle was introduced earlier in the book as a way to search Haskell declarations not only by name or description but also by taking into account the types that are involved in a function’s signature.

Test and Verification

One big part of Chapter 15 has been devoted to testing using HUnit , QuickCheck , and SmallCheck. I can’t stress enough how important testing is for a successful development project. The great benefit of property-based testing tools, such as QuickCheck or SmallCheck, is that you indicate how your program should behave at a higher level. Then, it generates small unit tests for a variety of scenarios. In that way, the coverage is much higher than using traditional tools.

Type-level programming in Haskell opens the door to formally verifying some properties of your data types and algorithms directly inside the language. If this is not enough, you can complement strong types with refinement types as targeted by LiquidHaskell. While formal verification consumes more time than basic testing, it’s the only technique that can guarantee a complete absence of bugs.

Benchmarking

Functional correctness is an important consideration for a piece of code. In many cases, though, an application should run with a certain performance. The Criterion tool helps you define test cases and get statistics on the time of execution. The tool runs the test enough times to make the computed time statistically significant and evaluates the result completely (in other cases, some part of the computation wouldn’t be measured because of laziness).

Profiling

Chapter 5 introduced the GHC profiler, which allows you to gather information about the time and memory consumption of your applications. Because of the lazy nature of Haskell, memory profiling becomes much more important than in other languages. Used wisely, it can shorten the investigation process for performance problems and guide you toward those places you should spend more time optimizing.

The main disadvantage of the profiler is that it’s not designed for applications with several threads, such as those you can write with the libraries presented in Chapter 8. For those cases it’s interesting to consider ThreadScope , a graphic tool for reading GHC event logs. These event logs include information about when different threads are created and terminated, along with the activity of each of them.

Coverage

When you design tests, it’s important to ensure that every possible path of execution is covered. That is, make sure that you’ve covered all possible branches of conditionals, all possible patterns for a data type and match, and so on. The hpc tool, included with GHC, gathers important statistics about the code used in a certain execution. This information can be used to produce a report with the different kinds of coverage and the achieved percentage.

Remote Monitoring

In many cases, applications are not processes with a limited life but are server-like in nature. One example of this kind is web applications. The ekg package enables you to get statistics of the performance and behavior of an application while executing. In addition, it does so via a web interface, so its management is quite simple. When using ekg, you’re not restricted to the information it gives by default; you can include your own counters. For example, for a web application you might be interested in knowing how many pages are served by the minute or how many database connections are kept open through time.

Design Patterns and Functional Programming

You may have heard that functional programming makes design patterns completely irrelevant. This is quite a strong statement. Of course, many of the object-oriented design patterns won’t be directly applicable, because you’re working in a different programming paradigm. But this doesn’t mean that a software project developed using Haskell wouldn’t need a careful analysis and design prior to the start of coding. Furthermore, common and reusable ways of solving problems (called patterns ) also appear in functional code.

In many cases, the statement about design patterns being irrelevant refers to those design patterns I call code templates. Think of the Singleton1 design pattern for keeping just one instance of a specific class in memory. When you need to apply it, you know exactly what to write, and it always looks the same. The code is just boilerplate; that’s the reason why languages like Scala offer specific syntax just for this case. In those scenarios, a Haskell solution would usually abstract the pattern at a high level, usually in a type class or in a higher-order function.

In some other cases, the language features allow a specific pattern to integrate seamlessly into the language. One example is the Strategy design pattern. It’s used to define a computation with some moving parts that depend on later considerations, such as changing the code that shows the total amount, depending on the currency you’re using. In an object-oriented setting, you would define an abstract class or interface, and derived classes would have the code for each currency. Within Haskell, you would instead use a higher-order function, which takes as parameters all those parts of the computation that may change.

From a conceptual point of view, some patterns are still there. In any software system, whether it’s developed in procedural, object-oriented, or functional style, you have the problem of incompatible interfaces between components. In the object-oriented world, you would define a common interface and create wrapper classes to access the functionality of each component (this is known as the Adapter pattern). In Haskell, you would use type classes instead and make each component an instance of that class. In that way, you have a common method to communicate with all of them. In this case, the problem (communicating with incompatible systems) and the idea of the solution (defining a common protocol and making the systems adapt to it) remain; the change is just in the implementation.

Inside the base libraries you can find functors, foldables, applicatives, monads, and many other type classes, which are at a high level of abstraction. In those cases, applying a design pattern is equivalent to instantiating a type class. Some of these type classes actually make the pattern more general. An iterator in object-oriented languages only allows operating on values from the beginning to the end of a collection. But in Haskell you have a whole range of operations of collections: applying a function inside a container via Functor, applying a function repeatedly to obtain a result via Foldable, or iterating while maintaining the structure via Traversable.

You’ve seen that some patterns are subsumed by language features or higher-level abstraction. Of course, many others remain in their original incarnation. One example is the Pool design pattern, which provides a way to efficiently manage a set of resources. You can find many packages that use this pattern. One example is how the Persistent database access layer uses a pool to manage database connections.

Of course, some Haskell features, such as immutability of values, higher-order functions, and laziness, affect the way in which you design your application. Think of concurrency: in an imperative setting, you have to use locks, semaphores, or rendezvous mechanisms to control access to shared resources. In many cases, the reason why you need those low-level operations is the possibility of side effects in any part of the code. Haskell, on the other hand, provides clear separation between pure code and the possible side effects. Thus, you can use a more elegant solution to that problem. When dealing with concurrency in Haskell, you use Software Transactional Memory, which embodies the concept of transactions.

Finally, I would like to point out that the Haskell philosophy and features get on well with the iterative and agile development methodologies. Being able to test functions directly in the interpreter helps you to test your code as you write it. And with QuickCheck, you can generate many more tests than you would if you had to write all of them by hand. In addition to that, Haskell is amenable to refactoring. Higher-order functions allow you to get the skeleton of an algorithm and then obtain variants by function application, and strong types guarantee that your code doesn’t change in unexpected ways.

Many other benefits of a language like Haskell, such as strong typing or strict separation between pure code and code with side effects, were already discussed in Chapter 1. In general, Haskell gives you another perspective on your software design, which will greatly benefit your daily programming.

Medium-Level Guidelines

In this section I’m not going to mention micro-optimizations or code templates for Haskell code. Instead, I will introduce some general guidelines that will make your code much more readable and maintainable.

Use Higher-Order Combinators

Using functions such as map, filter, and fold will make the purpose of your code more apparent to a future reader of it. You saw in Chapters 3 and 14 how recursion over a data type can usually be turned into a series of calls to these functions, so you should keep its use to a minimum.

Refactor

In the previous section I discussed how Haskell goes quite well with agile programming methodologies. The ability to pass functions as parameters can help you to build functions that encapsulate the common parts of many algorithms. Many classes of problems can be divided in a general skeleton and then instantiated to each case by introducing the small parts that are missing.

The benefits of higher-order refactoring are twofold. First, you reduce the amount of code you have to maintain, and thus you have fewer possibilities of introducing new bugs because your code will have been much better tested. Furthermore, when you abstract a common pattern in your code, the correctness or the corner cases of your approach become more obvious.

Use Type Classes Wisely

Type classes are a powerful tool for abstracting the common idioms of several data types. The Haskell libraries are full of type classes, and almost every important programming concept is implemented as a type class. Try to follow the steps of those libraries and implement your concepts as type classes.

At this point, I’ll give you one word of warning: sometimes type classes are overused, and the code becomes much more difficult to read. The resolution mechanism of type class instances happens in the compiler, and the specific instance being chosen may not be directly apparent. Thus, a more direct approach like abstract data types or higher-order functions may be desirable. In particular, be aware of these two scenarios:
  1. 1.

    If all your type classes have only one instance, it may be the case that you don’t really need to abstract those specific concepts.

     
  2. 2.

    Don’t directly map object-oriented classes or interfaces to type classes.

     

Enforce Invariants via the Type System

Chapter 13 discussed many ways in which you can enforce invariants in your values via strong types. Using those techniques in your code will benefit you in the short term because more errors will be caught by the compiler; you will also benefit in the long term because modifications that would break your invariants will be denied.

The type system can help you catch many errors even if you don’t follow all these techniques. One good example is newtype. You can separate different concepts (such as money, a record identifier, or distance) even if they have the same computer representation (which in that case would be an integer).

Stay (As) Pure and Polymorphic (As Possible)

If you write your functions by separating side effects from the rest of your computation, you’ll have a much easier time testing your code. One useful pattern is to create a core of pure functions that work on your core data types, apply a lot of QuickCheck tests and even formal verification, and build from there.

In case you need to work with monadic contexts, try to use monad classes (such as MonadState, MonadError, etc.) to specify exactly what functionality you need from a monad stack. The solution of specifying the complete monad stack you’re using from the beginning is not maintainable because usually you need to add layers for extra functionality. Furthermore, keeping your code polymorphic will enable you to use it in different ways. For example, you may be interested in testing your Persistent code against a list instead of a database, something that would be possible if instead of SqlPersistT (the actual transformer) you specify PersistQuery (the monad class) in your signature.

The essence of this advice is that polymorphism opens the door to reusability. If instead of a function using a list of integers you write a function that works on any Traversable whose elements are Nums, you will be able to change both the representation of the container (tree instead of lists) and the type of number (Integers instead of Ints) without any further change.

Tip

You can find many more guidelines in the “Hoogle Overview” article by Neil Mitchell in issue 12 of The Monad.Reader (the community-managed Haskell magazine), as well as several talks and StackOverflow answers by Don Stewart.

Patterns with Monads

Almost any developer which comes to hear about Haskell also hears about monads. Although monads are a very general concept, which underlies ideas present in other languages such as list comprehensions, promises, or continue-if-not-null operators, Haskell is one of the few languages which makes this concept so central. In this last section of the book we review and introduce many of the most common monads and discuss two design patterns related to them.

Summary of Monads

Table 16-1 shows the most important monad classes and which monads (shown in italics) or monad transformers (shown in regular face) are instances of each class, along with the most important operations that each class embodies. There are more monads explained in this table than there are throughout the entire book. In particular, two kinds of additions are found.
  • In some cases, the specific monad has been introduced, but not the monad class that abstracts the pattern. This is the case of the Par monad, which implements the ParFuture and ParIVar type classes, or the MonadRandom class.

  • Other monads are completely new, but I think they deserve to be listed. MonadSupply, which is used to having a source of new values (which you can use as unique identifiers, for example), fits in this case.

Table 16-1.

Common and Useful Monad Classes

Class

Available

Package

Description

Operations

 

IdentityT

mtl

Function application: no extra effect

None

MonadPlus

MaybeT

mtl

Choice and failure

mzero: represents failure

mplus: offers choice between two results

guard: checks a Boolean condition

ListT

mtl

MonadLogic

LogicT

logict

Backtracking and fair interleaving

interleave: fair disjunction

(>>-): fair conjunction

ifte: conditional check with cut

once: commits to first answer and prunes

MonadZip

ListT

mtl

Parallel comprehension

mzip: converts two lists into a list of pairs

munzip: converts a list of pairs into two lists

MonadReader

ReaderT r

mtl

Adds a context with a read-only value

ask: gets the value from the context

local: executes some computation with a new context

Monoid w => RWST r w s

mtl

MonadWriter

Monoid w => WriterT w

mtl

Produces a write-only output by appending several values

tell: appends a new value

listen: obtains the output of a subcomputation

Monoid w => RWST r w s

mtl

MonadState

StateT s

mtl

Keeps an internal state that can be both read and modified

get: obtains the current value of state

put: gives a new value to the state

modify: applies a function to the state

Monoid w => RWST r w s

mtl

 

ST

base

Restricted mutable variables

Creation and modification of IORef values

MonadSupply

Monoid s => SupplyT s

monad-supply

Consumes values from a supply

supply: gets the next value

MonadError

IO

base

Failure with some extra information: depending on the monad, the failure is represented as pure errors or as extensible exceptions

throwError: signals failure

catchError: recovers from error

MaybeT

mtl

ExcepT e

mtl

MonadCatch

IO

base

Throwing and catching extensible exceptions

throwM: throws an exception

catch, handle: recover from one exception type

catches, handles: recover from several exception types

bracket: resource acquisition and disposal

CatchT ==

ExceptT SomeException

exceptions

MonadIO

IO

base

Performs unrestricted side effects, such as reading and writing files or communicating through network

liftIO: moves a computation in the IO monad into the current monad stack

ParIO

monad-par

Class

Available

Package

Description

Operations

MonadRandom

IO

base

Generates random values

getRandom, randomIO: get unbounded random value

getRandomR, randomRIO: random value within bounds

RandT

MonadRandom

ParFuture

Par

ParIO

monad-par

Parallelism based on promises

spawn, spawnP: asynchronously execute a function and return an IVar that will give its result

get: obtains the result inside an IVar, blocking if needed

ParIVar

Par

ParIO

monad-par

Dataflow parallelism, where dependencies are given via IVars

fork: starts a computation in parallel

new: creates a new IVar for holding a value

put: writes a value inside an IVar

 

Eval

parallel

Deterministic parallelism based on strategies for evaluating lazy types

rseq, rdeepseq: evaluate its argument sequentially

rpar: evaluates its argument in parallel

 

STM

stm

Atomic transactions

atomically: executes a transaction in an atomic way

retry: rolls back the current transaction and tries to execute it again when the circumstances had changed

orElse: executes a transaction in some other fails

Creation and modification of TVars, TQueues, and others

MonadResource

ResourceT

resourcet

Safe allocation and release of resources

allocate: performs some resource acquisition and registers the action needed for releasing at the end

release: deallocates a resource prematurely

 

ConduitT i o

conduit

Streaming data

await: consumes the next element from the input stream

leftover: puts back an element in the input stream

yield: generates an element in the output stream

 

Parser

attoparsec

Matches a list of characters against a predefined pattern

Parser more often used via its Applicative interface

Class

Available

Package

Description

Operations

PersistStore

SqlPersistT

persistent

Obtains and manages records in a database using its key

get: obtains the record with a given key

insert: creates a new record in the database

repsert: replaces a record with new information or creates a new one if that key didn’t exist

delete: deletes a record with a given key

PersistUnique

Obtains and manages records in a database using unique constraints

getBy: obtains the record with a given unique constraint

insertUnique: inserts checking uniqueness constraints

deleteBy: deletes the record with a given constraint

PersistQuery

Obtains and manages records in a database via queries

selectSource, selectList: obtain the record that satisfies a given set of conditions

update: modifies information of a given record

updateWhere: modifies all records from a query

deleteWhere: deleted all records from a query

MonadCont

ContT

mtl

Computations that can be interrupted and resumed

callCC: calls a function with its current continuation

MonadFree

FreeT f

free

Free monad over a functor

 

MonadTrans

All monad transformers

mtl

Type class that all monad transformers instantiate

lift: moves a computation one layer up in the stack

Restrictive Monad Classes

Looking at the previous table you may notice that some monads provide a very restricted set of operations – for example, ReaderT just offers the ability to obtain a single value – while others open the door to many different effects – think of IO or the monads from the persistent package. The latter case goes at odds with Haskell’s philosophy of making types describe your functions: if your signature mentions IO, nothing really could be said about its behavior. Here I describe a small pattern to restrict the operations while keeping a good performance.

To understand this pattern, we need to look back at the monad classes introduced in Chapter 7. At that point the problem was different: we had just introduced monad transformers, and we wanted to have a common interface for any stack which contained a given layer, regardless of where that layer was found. That is, we wanted to keep using the ask function for any stack which contained a ReaderT transformer.

Imagine now that we want to use file operations in a function. If we throw an IO monad in the signature, we could also do network operations or create threads. Or even worse, if we want to write a combinator – a function which takes another as parameter – and we allow IO there, we can never be sure about what that function will do. This is the perfect scenario to restrict the set of operations allowed by IO to the file system subset.

The solution is to introduce a new monad class with only the desired set of operations. In this case, let’s call that monad MonadFS, to follow the convention from the mtl package:
class Monad m => MonadFS m where
  readFile  :: FilePath -> m ByteString
  writeFile :: FilePath -> ByteString -> m ()
Now you can guarantee that a function only uses those operations, and not any from IO, by requiring a MonadFS constructor. For example:
copyFile :: MonadFS m => FilePath -> FilePath -> m ()
copyFile inFile outFile = do contents <- readFile inFile
                             writeFile outFile contents
Being able to specify very tightly the requirements of copyFile is great, but quite useless if you cannot execute the code. The trick is to create an instance of the restrictive monad class for the monad you wanted to restrict. In this case, this boils down to a MonadFS instance for IO:
instance MonadFS IO where ...

The consequence is that now you can use copyFile anywhere a function which operates on IO is expected. Furthermore, the cost of this abstraction is almost negligible, since GHC specializes functions like copyFile when they are used with a single type class.

Roll Your Own Monad

Monads appear everywhere in Haskell code. The special do notation provides a convenient syntax for sequencing and composing actions, and there are many libraries and functions operating on monadic code. Thus, writing a monad appears as an obvious choice for developing a domain-specific language for your actions.

In Hackage there are several packages that ease the creation of those monads, like operational or free . The latter will be focused on in this section. In any case, all these packages encompass a similar abstraction, which is the “sequence of actions”: each monadic value is a list of primitive operations. To create the full monad, you need to provide two sets of data.
  1. 1.

    The primitive operations that you may take and the building blocks of your monad

     
  2. 2.

    How each operation affects the related context and which value provides to the next computation in the list

     
As a running example, let’s consider a small DSL that allows you to manage a database of clients. The basic operations will be adding a new client, querying the client by its identifier, and replacing the information about a client. So, in some sense it’s a restricted version of Persistent. The data types used to define Clients are as follows:
newtype ClientId = ClientId Integer           deriving Show
data Client = Client { clientName :: String } deriving Show
When using the free package, each operation is encoded as a constructor in a regular data type. This is called the syntax of the monad. For each operation you need to first write the parameters to the operation in question. For example, writing a new client in the database takes that client as the parameter. Then, you need to define how the result of the operation gets threaded to the next step in the computation. This is done by requiring a function from the result type to a yet-unknown data type that will refer to a list of computations. In the example of new clients, the result is a ClientId, which must be threaded to the next computation, r. The code for all operations reads as follows:
data AdminOp r = GetClient  ClientId        (Client   -> r)
               | SaveClient ClientId Client r
               | NewClient  Client          (ClientId -> r)

Notice that the SaveClient operation doesn’t return any value, so the next operation doesn’t take any parameter. Thus, you only need to specify r in the data constructor.

The free package mandates that every operation data type follows this schema and that the type is an instance of Functor. The good news is that once again you can use the deriving functionality in GHC and automatically generate such an instance. It now reads as follows:
{-# LANGUAGE DeriveFunctor #-}
data AdminOp r = ...
               deriving Functor
Your monad will now be the free monad over that Functor in question. You could refer each time to the Free type parametrized by your operations, but usually you define a type synonym, as follows:
import Control.Monad.Free
type Admin = Free AdminOp
Still, you cannot use your data type directly inside a do block. You first need to lift your operations to the free monad. For this matter, you should use the liftF function from Control.Monad.Free. The only item left is what to provide as the last parameter in each operation. As rule of thumb, you should provide id if the next list of operation must be given a parameter and provide () elsewhere. In this case, it means the following:
getClient :: ClientId -> Admin Client
getClient i = liftF $ GetClient i id
saveClient :: ClientId -> Client -> Admin ()
saveClient i c = liftF $ SaveClient i c ()
newClient :: Client -> Admin ClientId
newClient c = liftF $ NewClient c id
Finally, you have a monad! It can even be used within the do notation.
import Data.Char
exampleAdmin :: String -> Admin String
exampleAdmin s = do i <- newClient $ Client s
                    n <- fmap clientName $ getClient i
                    return $ map toUpper n
However, exampleAdmin won’t have any effect by itself. At this point, this is only a description of the computation that should happen. The free package represents the list of operations using two constructors: one operation followed by a list of other operations uses Free, whereas the end of a computation is marked using Pure. This means that the previous example is equivalent to writing this:
Free (NewClient (Client s) (i ->
  Free (fmap clientName (GetClient i ( ->
    Pure $ map toUpper n)))))
The final step is giving an interpretation of each operation. The following example interprets the operations as working on an association list of identifiers and clients. As you can see, the interface is like other run functions on other monads.
import Data.List
runAdmin :: Admin a -> ([(Integer,Client)],a)
runAdmin m = runAdmin' m []
  where runAdmin' (Free (GetClient  (ClientId i) n))   l =
          let Just c = lookup i l in runAdmin' (n c) l
        runAdmin' (Free (SaveClient (ClientId i) c n)) l =
          let l' = deleteBy ((j,_) (k,_) -> j == k) (i, c) l
           in runAdmin' n $ (i,c):l'
        runAdmin' (Free (NewClient c n)) [] =
          runAdmin' (n $ ClientId 1) [(1,c)]
        runAdmin' (Free (NewClient c n)) l =
          let (i',_) = maximumBy ((j,_) (k,_) -> compare j k) l
           in runAdmin' (n $ ClientId (i' + 1)) $ (i' + 1,c):l
        runAdmin' (Pure c)                  l = (l, c)
In this case, this interpretation could be used for testing purposes, and another interpretation would provide real access to a database. You may check that your monad indeed works on the interpreter.
*Chapter16.FreeMonads> runAdmin $ exampleAdmin "Alejandro"
([(1,Client {clientName = "Alejandro"})], "ALEJANDRO")

The free package provides many more features for rolling your own monads. For example, you may decide to create a monad transformer instead of a plain monad, just by using FreeT instead of Free. If your application will revolve around a custom monad, it’s useful to read the documentation of the Control.Monad.Free.Church module, which can enhance the performance in the long term. Finally, free provides not only free monads but also free Applicatives, Alternatives, and MonadPlus.

Summary

In this chapter you got a bird’s-eye view of design using Haskell and functional patterns.
  • I walked you through many of the tools that the Haskell Platform and Hackage provide for documentation, testing, profiling, and project management.

  • I discussed the relation between functional design and more traditional object-oriented patterns. Some patterns are kept, others change the way in which they are implemented, and still others are not needed anymore.

  • I explained some specific design patterns related to monads. You can find a summary of useful monad classes in Table 16-1. Furthermore, you have learned how to restrict monads using type classes and how to roll your own monad.

..................Content has been hidden....................

You can't read the all page of ebook, please click here login for view all page.
Reset
3.141.35.185