0% found this document useful (0 votes)
17 views55 pages

Haskell Design Pattern - Sherri Shulman - CppCon 2015

Uploaded by

alan88w
Copyright
© © All Rights Reserved
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as PDF, TXT or read online on Scribd
0% found this document useful (0 votes)
17 views55 pages

Haskell Design Pattern - Sherri Shulman - CppCon 2015

Uploaded by

alan88w
Copyright
© © All Rights Reserved
We take content rights seriously. If you suspect this is your content, claim it here.
Available Formats
Download as PDF, TXT or read online on Scribd
You are on page 1/ 55

Haskell Design Patterns for Genericity and Asynchronous

Behavior

Sherri Shulman

The Evergreen State College


[email protected]

October 2, 2015

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 1 / 55


Overview

1 Introduction

2 Type Classes

3 Algebraic Data Types

4 Functors

5 Applicative Functors

6 Continuations and Asynchronous Behavior

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 2 / 55


Introduction

This talk focuses on the development of a series of related Haskell design


patterns that support genericity and (ultimately) asynchronous behavior.

My background is primarily in Haskell and C, but in general I teach


programming language design and am interested in how different language
features and different language paradigms support different problem
solutions.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 3 / 55


Why Haskell?

Statically typed
Strongly typed
Referentially transparent
First class functions
Very expressive type language
Orthogonal language features
Clear semantics
No side effects

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 4 / 55


How does this impact C++?

C++ vs Haskell
Although C++ is a very different language than Haskell, the language
features and design patterns in Haskell can promote ideas about how to
structure solutions. In some sense Haskell can become the ”design
language” and C++ the ”implementation language”

Support for C++ Concepts


These patterns and language primitives can also suggest ways in which a
language like C++ might evolve to include these language features (C++
concepts!)

Current interest in Haskell in the C++ community


Bartosz Milewski’s blog on some Haskell patterns with associated
suggested implementations in current C++

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 5 / 55


Haskell Features

Haskell Features
1 Type classes These features are used to support
2 Algebraic data types genericity and high level abstractions
3 Functors that promote reuse and a particular
style of computation.
4 Monads
5 Continuations

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 6 / 55


Type Classes

1 What is a type class and how does it support genericity?


2 How does it differ from interfaces or abstract classes?
3 Does it have inheritance? Default definitions? Dependencies?
4 How does it support genericity?

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 7 / 55


Type Classes

> type L i s t x = [ x ]
> c l a s s HasEmpty x where
> empty : : x −> Bool

> c l a s s H a s h a b l e x where
> h as h : : x −> Bool

> c l a s s ( HasEmpty x , H a s h a b l e ( E l e m e n t x ) ) =>


> H a s h s e t x where
> type El em e n t x
> s i z e : : x −> I n t

> a l m o s t F u l l : : H a s h s e t t => t −> Bool


> a l m o s t F u l l h = False

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 8 / 55


Instances of Type Classes

> i n s t a n c e H a s h a b l e I n t where
> h as h x = x

> i n s t a n c e HasEmpty ( IntMap k ) where


> empty = Data . IntMap . n u l l

> i n s t a n c e H a s h a b l e k =>
> H a s h s e t ( IntMap ( L i s t k ) ) where
> type El em e n t ( IntMap ( L i s t k ) ) = k
> s i z e m = Data . IntMap . s i z e m

> h : : IntMap ( L i s t I n t )
> h = Data . IntMap . empty
> test = almostFull h
Full code: Figure 1
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 9 / 55
Type class notes

There are three type classes. We restrict the types x that model Hashset
to those types x that model HasEmpty and Hashabale.

This data type IntMap (List k)) is still not a concrete type since k is a
type parameter but so long as k models Hashable we are type correct and
type safe.

The example instantiates k with Int, resulting in a full implementation.


But k can be instantiated with any type with the appropriate constraint,
with full type safety.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 10 / 55


A C++ Implementation using concepts

// c o n c e p t
c o n c e p t H a s h s e t <typename X> : HasEmpty<X> {
typename e l e m e n t ;
r e q u i r e s H a s h a b l e <e l e m e n t >;
i n t s i z e (X ) ;
}

// m o d e l l i n g
template<H a s h a b l e K>
c o n c e p t m a p H a s h s e t <intmap< l i s t <K>>> {
i n t s i z e ( intmap< l i s t <K>> m) { . . . }
}

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 11 / 55


A C++ Implementation using concepts (continued)

// a l g o r i t h m
template<H a s h s e t T>
bool a l m o s t F u l l (T h ) { . . . }

// i n s t a n t i a t i o n
intmap< l i s t <i n t >> h ;
bool t e s t = a l m o s t F u l l (H ) ;
Here Hashset is a subclass of HasEmpty with an independent constraint
that element be Hashable.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 12 / 55


C++ comments

The two implementations and their semantics are parallel. Unfortunately


concepts are not yet a part of standard C++ implementations, although I
hope they will be soon.

They provide an explicit type-level constraint that serves both to explicitly


communicate requirements, but also provide more static information.

Type classes do not have inheritance of code, although the context


constraints enforce an inheritance of type expectations.

They clearly support genericity and reusability in their ability to construct


hash maps from with a variety of types assuming those types meet
required capability: there is a checkable predicate that prevents
instantiations for which the implementation would not make sense.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 13 / 55


Algebraic Data Types

1 What is an Algebraic Data Type?


2 How does it differ from classes and subclasses? Advantages?
3 How does it support genericity? reusability?

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 14 / 55


An example using Algebraic Data Types in Haskell

For this example we’ll use a design and implementation of an evaluator for
a lambda calculus like language.

In Haskell we might implement this using an algebraic data type specifying


what a term looks like.

We’ll do this in two ways: one using standard algebraic data types and one
using GADTs (Generalized Algebraic Datatypes).

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 15 / 55


Algebraic Data Type

If we want to implement a lambda calculus language (untyped) we might


do this directly using an algebraic data type (also known as a
discriminated union):
> data Term = Var S t r i n g | Abs S t r i n g Term |
> App Term Term

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 16 / 55


Algebraic Data type-like implementation in C++

This can be implemented similarly in C++ using abstract and derived


classes:
struct Term { v i r t u a l ˜Term ( ) { } , } ;
struct Var : Term { s t d : : s t r i n g name ; } ;
struct Abs : Term { Var & v a r , Term & body ; } ;
struct App : Term {Term & l f u n c ; Term & a r g ; } ;

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 17 / 55


Pattern Matching

An algebraic data type uses a discriminated union: it enumerates all the


ways in which a value in the type can be constructed.

If we write an evaluator for this language in Haskell we have to enumerate


all the cases for each kind of element:
> e v a l ( Var s ) = . . .
> e v a l ( Abs v t 2 ) = . . .
> e v a l ( App g1 g2 ) = . . .

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 18 / 55


The Oop approach to evaluation

The C++ implementation uses classes and subclasses. Each of the kinds
of term is implemented in a subclass. In order to implement an evaluator,
each subclass will have its own eval method.

How do these two approaches compare?

What if we decide that we want a new kind of Term? Perhaps a constant.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 19 / 55


Extending an algebraic data type

> d a t a Term = Var S t r i n g | Abs S t r i n g Term |


> App Term Term | Cons I n t

> eval ( Var s ) = . . .


> eval ( Abs v t 2 ) = . . .
> eval ( App t 1 t 2 ) = . . .
> eval ( Cons c ) = . . .
We will have to change eval (and any other functions that are written
using the data type Term) to add the new kind of Term.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 20 / 55


Extending an Oop design

In C++ we can add the new subclass Cons:


> s t r u c t Cons : Term { i n t v a l ; }
After this, we will only have to add a new eval function to the Cons class
in order for the evaluator to be extended (and similarly for any other
behaviors on Terms.)

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 21 / 55


Adding behaviors

What if we want to add a behavior? As well as eval, perhaps we want a


pretty printer. In the algebraic data type design, we only have to add the
pretty printer, with all its cases:
> p r e t t y p r ( Var s ) = . . .
> p r e t t y p r ( Abs v t 2 ) = . . .
> p r e t t y p r ( App t 1 t 2 )
On the other hand, in the OOP design we’ll have to add a pretty printer
method to each subclass.

This is sometimes called the Row vs Column effect: in both styles we have
to change something. It’s easier to add behavior to the algebraic data type
design and harder to add a new kind of value. It’s easier to add a new
kind of value in the OOP design but harder to add new behavior.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 22 / 55


Adding Discriminated Unions

Can we get some of the features of discriminated unions in C++? The


desired features are 1) the ability to enumerate the possible allowable
values (or types in OOP) 2) the requirement that the user define behaviors
for all possible types of a discriminated union or get a compile time type
error.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 23 / 55


Discriminated unions in Oop
The ”standard” way to implement discriminated unions is to use an enum
type for a tag and a union to describe the alternate values. This approach
is error prone; it is hard to retain coherence between the tag, the data, and
the functions that use them. There is no support in the language to ensure
that these components are coherent.
s t r u c t DiscType {
enum TypeTag
{ t y p e V a r , typeAbs , typeApp , typeEmpty } t a g ;
union {
char ∗ var ;
s t r u c t Abs a b s ;
s t r u c t App app ;
};
};
(Note there is a slight abuse of the enum type above to make it similar to
the previous example. But see typelists below.)
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 24 / 55
An Oop solution using typelists
Any function wanting to implement a behavior (eval or pretty printer)
would have to inspect the tag, access the appropriate field, etc. Moreover,
the type checker couldn’t check for type-incorrect access since it really
doesn’t know that the enum is connected in any way to the union.

A more expressive approach that embodies type safety, allows user defined
types, and is more dynamic is described in [Alexandrescu, 2002]:
template <c l a s s TList>
class Variant {
....
};

typedef Variant<
TYPELIST 4 ( t y p e V a r , typeAbs , typeApp , typeEmpty )
(Assuming that these user-defined types have been defined.)

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 25 / 55


What must an implementation of Variant do?
The details of the implementation of these discriminated unions are beyond
the scope of this presentation. But now the task of ensuring that functions
using the discriminated union are completely defined is possible statically.

But such a variant must include:


1 Constructors that accept any type in the typelist.
2 Assignment operators that similarly accept any type.
3 A type safe way to convert to any of the type in the typelist.
4 A way to determine the actual type stored in the variant.
(Decoherence)
5 A way to convert/coerce a value appropriately.
6 a way to determine the storage needs (size and alignment).
In addition, the availability of pattern matching would be a plus. The
OOP way to do pattern matching can be implemented via the visitor
pattern, which is not nearly as direct.
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 26 / 55
GADTs

We can step up a bit in abstraction and consider how to encapsulate


specific type information (generalized algebraic data types). The best way
to describe this is with an example. Suppose that we want a term
language that evaluates expressions to a value domain that contain more
than one kind of value (for instance booleans and ints).

> d a t a Term = L i t I n t | Succ Term | I s Z e r o Term |


> I f Term Term Term | Pr Term Term
The problem is that an evaluator would return a value that is either an Int
or a Boolean or a Pair. There is no information that connects these values:
they can’t be unified.

The usual way to do this is to introduce a new data type for the values.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 27 / 55


Gadts
Our evaluator would have to do the following:
> e v a l ( I s Z e r o t ) = e v a l t == 0
> e v a l ( Succ t ) = 1 + e v a l t
> ...
This won’t type since in one case it returns a Boolean and the other an
integer. In order to unify these two disparate types, we can introduce a
value domain:
> d a t a V a l = V I n t I n t | VBool Bool | Vpr V a l V a l
Now we can write an evaluator that always returns a Val. This can be
implemented in OOP using a class and subclass (it’s another algebraic
type). But even with this approach it is possible to construct types that
are correctly formed syntactically but incorrectly typed. For instance the
following is type correct according to Haskell but is still meaningless:
> t 1 = Succ ( I s Z e r o ( L i t 0 ) )
t1 is syntactically correct and will be passed by the Haskell type checker.
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 28 / 55
Gadts
Generalized algebraic data types introduce a new type variable (an
existential) that asserts for any term there is a type that represents its
value:
> d a t a Term a where
> Lit :: I n t −> Term I n t
> Succ :: Term I n t −> Term I n t
> IsZero : : Term I n t −> Term Bool
> If :: Term Bool −> Term a −> Term a −>
> Term a
> Pair : : Term a −> Term b −> Term ( a , b )
This new Term introduces a type variable. Now we can refine each of the
different kinds of terms to the kind of value it embodies. In this new term
we would not be able to construct the previous term because IsZero will be
constrained to apply only to Ints. Implementing this kind of functionality
is explored in [Kennedy, Russo, 2005]
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 29 / 55
Algebraic Data Types vs Oop

The advantages and disadvantages of algebraic datatypes vs


classes/subclasses are not quite as clear as one might like. Algebraic data
types have more precision (there is no need to consider subtype
polymorphism, we don’t have to query what type an object actually is).
Algebraic data types can enforce that each function covers all cases and
inform the programmer about any missed cases statically.

On the other hand, algebraic data types are less dynamic: we have to
consider all the kinds of values that may occur. Adding new kinds of
values is easier in a subclass hierarchy (potentially at increased cost in
adding behavior).

However, generalized algebraic data types add to the expressivity of the


type system and allow more information to be captured in the type
allowing more type errors to be detected statically.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 30 / 55


Functors
Moving up from type classes and algebraic data types, Haskell Functors
capture the idea that something is mappable. A mappable ”thing” is a
generalization of the map function over lists with the type
> map : : ( a −> b ) −> [ a ] −> [ b ]
So map is a function that takes a function mapping values in type a to
values in type b. It then takes a list of values of type a and produces a list
of values of type b, each converted by applying the given function.

A Functor then is something that defines a mapping function (named


fmap) defined as a type class:
> c l a s s F u n c t o r f where
> fmap : : ( a −> b ) −> f a −> f b
If f is a Functor, then it has a function fmap that takes a mapping
function and a Functor holding a value (or values) of type a, and produces
a Functor holding a value (or values) of type b.
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 31 / 55
Functors

You can think (very generally) of a Functor as something that holds a value
and provides this mapping function. A list is an instance of a Functor:
> i n s t a n c e F u n c t o r [ ] where
> fmap = map
Here is a common type in Haskell that embodies the idea that a
computation may fail:
> d a t a Maybe a = J u s t a | N o t h i n g
(A computation either computes a value of type a or Nothing). The
Maybe type is a functor:
> i n s t a n c e F u n c t o r Maybe where
> fmap f ( J u s t x ) = J u s t ( f x )
> fmap f N o t h i n g = N o t h i n g

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 32 / 55


Functors
So far functors don’t seem to do much other than create a uniform way to
look at things that can mapped (lists, trees, pairs, and so on.) There is a
limitation here: we expect the Functor to take one argument. However we
can use partial application to bridge this constraint.

An advantage of this uniform way to look at mappable things is that we


can compose them or combine them because we know they have this
uniform structure. Another functor that may seem unusual is the arrow
constructor: ((→)r ). This takes some getting used to, but → is the
constructor for a function type, here written in prefix form.

A function type is r → b for arbitrary types r and b. If we ”partially”


apply the type to the first argument, we get a constructor of one argument
as required for functors. (For instance ((→)Char ) is the type of a function
that takes a Char to a value of some other type. Similarly ((→)Int) is the
type of a function that takes an Int to a value of some other type.
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 33 / 55
Functors cont

Here is the definition of the functor for arrows:


> i n s t a n c e F u n c t o r ((−>) r ) where
> fmap f g = ( \ x −> f ( g x ) )
So the fmap takes two functions: g is a function that maps an r to some
other type, let’s call it a: ((→)r a). f is a function of type a → b. We
return a new function that takes an r (which we know since g is applied to
the x), and returns an a. We then apply f to get a b. so λx → f (gx) has
the type ((→ r )b). So it converts a function of type r → a to one of type
r → b. As a matter of fact, this is just function composition (as the
definition indicates). So we could just say:
> i n s t a n c e F u n c t o r ((−>) r ) where
> fmap = ( . )

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 34 / 55


Functor laws

Functors obey some laws:


1 fmap id = id
2 fmap (f . g) = fmap f . fmap g or equivalently fmap (f.g) F = fmap f
(fmap g F)
Ignoring Nothing for brevity, we can demonstrate this for the Maybe type:
fmap i d ( J u s t x ) = J u s t ( i d x ) = J u s t x
fmap ( f . g ) ( J u s t x ) = J u s t ( ( f . g ) x ) = J u s t ( f ( g x ) )
( fmap f . fmap g ) ( J u s t x ) = fmap f ( fmap g ( J u s t x ) )
= fmap f ( J u s t ( g x ) ) = J u s t ( f ( g x ) )

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 35 / 55


Functors cont
Functors generalize a certain kind of behavior that we can use to build
further abstractions. The laws themselves allow us (and the compiler) to
prove properties, and simplify code, particularly in the presence of pure
functions with no side-effects (which is not necessarily true in C++.)

What might a Functor look like in C++? The following sketch is due to
Bartosz Milewski in [Bartosz Milewski. Jan 2015] and
[Bartosz Milewski. Sep 2012].
template<template<c l a s s > F , c l a s s A , c l a s s B>
F<B> fmap ( s t d : : f u n c t i o n <B(A) > , F<A>

template<c l a s s A , c l a s s B>
o p t i o n a l <B> fmap ( s t d : : f u n c t i o n <B(A)> f ,
o p t i o n a l <A> o p t ) {
i f ( ! o p t . i s V a l i d ( ) ) r e t u r n o p t i o n a l <B>{}
e l s e r e t u r n o p t i o n a l <B>{ f ( o p t . v a l ( ) ) } ;
} Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 36 / 55
Functors cont
A note on partial application and curried vs uncurried functions. The
function fmap defined for a Functor f with type (a → b) → fa → fb
expects to get a function of one argument and a Functor holding a value
of type a. If I apply fmap to a function g (fmap g) we get a function of
type fa → fb. So in a sense fmap has transformed a function g of type
a → b to a function of type fa → fb. Examples:
fmap length [[1 ,2] , [3 ,4 ,5] , [5 ,6 ,7]]
fmap Just [1 ,2 ,3 ,4]
fmap chr [101 , 102 , 103]
fmap o r d ” abcd ”
In order to do partial application we require first-order functions and the
function must be curried form (a → b → c) rather than uncurried form
((a, b) → c. Using higher order functions we can move back and forth
between the curried and uncurried forms.
c u r r y f = \ a −> \b −> f ( a , )
u n c u r r y f = \ ( a , b ) −> f a b
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 37 / 55
Functor types

Function fmap’d function


length :: [a] → Int fmap length :: Functor f ⇒ fa → fInt
Just :: a → Maybea fmap Just :: Functor f ⇒ fa → f (Maybea)
chr :: Int → Char fmap chr :: Functor f ⇒ fInt → fChar
ord :: Char → Int fmap ord :: Functorlf ⇒ fChar → fInt

Using fmap we’ve been able to use a mapping function without knowing
any of the detail of its implementation so there would be no need to break
encapsulation, similar to the motivation for using an iterator pattern as
opposed to a loop. In addition the functor laws guarantee composition in a
very general way.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 38 / 55


Applicative Functors

We can build on the Functor typeclass to introduce applicative functors.


Functors express a regularity associated with mappable things, including
function composition.

An applicative Functor typeclass is defined by:


> c l a s s ( Functor f ) => A p p l i c a t i v e f where
> p u r e : : a −> f a
> (<∗>) : : f ( a−>b ) −> f a −> f b
If f is a functor, then f is an Applicative functor IF it provides a definition
of pure and h∗i. Pure is just a way to wrap something of type a in a
Functor. h∗i is an explicit apply at the level of Functors: a Functor holding
a computation. Since f must be a Functor, we know we can use fmap.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 39 / 55


Applicative Functors cont

pure takes a value of type a and returns an applicative functor holding a


value of type a.

h∗i takes an applicative functor holding a function of type a → b, and a


Functor holding an a, and returns a Functor holding a b (by extracting the
function from the Functor and the value of type a and applying the
function to the value to get the value of type b).

A simple example with the Maybe type:


> i n s t a n c e A p p l i c a t i v e Maybe where
> pure = Just
> N o t h i n g <∗> = Nothing
> ( J u s t f ) <∗> s o m e t h i n g = fmap f s o m e t h i n g

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 40 / 55


What do Applicative Functors do for us?

We want to incrementally build a function out of pre-existing functions


(possibly using partial application). As a simple example, (+3) is a
partially applied function that adds 3 to what it is applied to. So (Just
(+3)) holds a function of type Int → Int which adds 3 to its argument. If
we do (Just (+3)) h∗i (Just 9) we get (Just 12);

The operator h∗i is really just an apply operator for Functors. Thinking in
types again,
c o n c a t : : [ [ a ] ] −> [ a ]
((<∗>) ( J u s t c o n c a t ) ) : : Maybe [ [ a ] ] −> Maybe [ a ]
In order to move from a function a → b to a function f a → f b we can
use the function pure (it will lift any value, and wrap it in a functor,
functions included.)

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 41 / 55


Example Applicative

> i n s t a n c e A p p l i c a t i v e ((−>) r ) where


> p u r e x = ( \ −> x )
> f <∗> g = \ x −> f x ( g x )

> i n s t a n c e A p p l i c a t i v e [ ] where
> pure x = [ x ]
> f s <∗> x s = [ f x | f <− f s , x <− x s ]

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 42 / 55


Applicative Functors in C++
We need a function to apply a function over functors (which require
unwrapping the functor to get to the function it holds) and then to wrap a
function over values in a functor. Here is pure:
t e m p l a t e < c l a s s A>
u n i q u e p t r <A> p u r e (A a ) {
r e t u r n u n i q u e p t r <A> ( new A( a ) ) ;
}
And then the apply:
t e m p l a t e <c l a s s A , c l a s s B>
u n i q u e p t <B> a p p l y ( u n i q u e p t r <f u n c t i o n <B(A)>> f ,
u n i q u e p t r <A> p ) {
u n i q u e p t r <B> r e s u l t ;
i f ( f && p ) r e s u l t . r e s e t ( new B( ( ∗ f ) ( ∗ p ) ) ) ;
return result ;
}
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 43 / 55
Applicative axioms

These are somewhat less satisfying than the Haskell because they do
expose some of the underlying structure and require an explicit reference
to the wrapping effect.

Applicative Functors also have laws:


p u r e i d <∗> v = v
p u r e ( . ) <∗> u <∗> v <∗> w = u <∗> ( v <∗> w)
p u r e f <∗> p u r e x = p u r e ( f x )
u <∗> p u r e y = p u r e ( \ $ y ) <∗> u
But we won’t prove these here.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 44 / 55


Applicative Functions to Monads

One thing the applicative functions do for us is allow us to create chains of


computations:
[ ( + ) , ( ∗ ) ] <∗> [ 1 , 2 ] <∗> [ 3 , 4 ]
First this does
[ ( + ) , ( ∗ ) ] <∗> [ 1 , 2 ]
resulting in [(1+), (2+), (1∗), (2∗)]. Then each of these functions is
applied to [3, 4]. This chain of computations is possible since h∗i expects a
Functor and returns a Functor. The limitation is that we often want to do
a chain of computations that involves conditional computation: we need
to make a decision based on a previous result. This leads to monads which
allow us to extract a value from a computation, make a decision, and stuff
the value back in. We won’t cover monads in detail today but move on to
Continuations.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 45 / 55


What is a monad?
A monad is a type class that identifies how to return a function and how
to sequence chain, having access to the result of a computation.
> c l a s s Monad m where
> r e t u r n : : a −> m a
> (>>=) : : m a −> ( a −> m b ) −> m b
> (>>) : : m a −> m b −> m b
> x >> y = x >>= \ y
> f a i l : : S t r i n g −> m a
> f a i l msg = e r r o r msg
There are two default definitions, so usually we only have to define return
and >>= (called bind). The constraint that m be Applicative is not
explicit but is so. Intuitively, >>= allows us to run a computation, extract
the result (something of type a), and convert to something of type b, and
return the value (to be used in further computation). Because we have the
result of the computation available in a sequence, we can take actions
(make decisions) based on the result. Return is just like pure.
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 46 / 55
Simple Example

A simple example:
> i n s t a n c e Monad Maybe where
> return x = Just x
> N o t h i n g >>= f = N o t h i n g
> J u s t x >>= f = f x
> fail = Nothing
So in the Maybe monad we can write a function f that examines the
contents of the Maybe monad does some computation, and then rewraps
it for further computation.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 47 / 55


Continuations

A continuation is a future computation. We can use the Monad structure


to capture this idea:
newtype Cont r a = Cont { r u n C o n t : : ( a−>r ) −> r }

> i n s t a n c e Monad ( Cont r ) where


> r e t u r n a = Cont $ \ k −> k a
> ( Cont c ) >>= f = Cont $ \ k −>
> c ( \ a −> r u n C o n t ( f a ) k )
The return function creates the continuation that will pass the value on.
The bind operator adds the bound function f into the computation
(continuation) chain.

We can expand on the Monad with a MonadCont that has a mechanism


to escape the continuation (abort the current computation.)

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 48 / 55


Continuations cont

We can introduce a callCC to do the abort:


> c l a s s ( Monad m) => MonadCont m where
> c a l l C C : : ( ( a −> m b ) −> m a ) −> m a

> i n s t a n c e MonadCont ( Cont r ) where


> c a l l C C f = Cont $ \ k −> r u n C o n t
> ( f ( \ a −> Cont $ \ k a ) ) k
callCC calls a function with the current continuation. The lambda
expression gives the continuation a name. Calling the named continuation
anywhere in its scope escapes the computation, regardless of the nesting
level. (This discussion is based on the information in the Haskell wiki: All
About Monads(The Continuation monad).)

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 49 / 55


Conclusions

There is so much information here on generic programming using Haskell


design patterns (and I haven’t covered them all and certainly have not
gone into sufficient detail on a number of the patterns)!
Without suggesting that Haskell is the ultimate in programming languages,
examining the kinds of patterns that it defines and manipulates can serve
both to structure how we write programs in C++ and to also suggest how
we might proceed in expanding the language to cover these kinds of
solutions more effectively and expressively.

In particular thinking about ways to package delayed computations so that


we can manipulate them appropriately seems a natural outgrowth of
Monads and their ability to sequence operations and wrap computations.

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 50 / 55


Citations
The Hashmap examples in this presentation were derived from
[Bernady, Jansson, Zalewski, Schupp, Prisnitz , 2008].

The Evaluator example in C++ was derived from


[Solodkyy, Reis, Stroustrup, 2013].

The Evaluator example in Haskell and GADTs was derived from


[Ralf Hinze, 2004].

The discussion of discriminated unions in C++ was motivated by


[Alexandrescu, 2002] and [Alexandrescu, 2002].

The comments on generalized algebraic data types in OOP were based on


[Kennedy, Russo, 2005].

The C++ implementation sketches of Functors and Applicative functors


were from [Bartosz Milewski. Jan 2015] and [Bartosz Milewski. Sep 2012].
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 51 / 55
References

Bernady, Jansson, Zalewski, Schupp, Prisnitz (2008)


A comparison of C++ concepts and Haskell type classes
Workshop on Generic Programming, WGP 2008 WGP 2008.

Solodkyy, Reis, Stroustrup (2013)


Open Pattern Matching for C++
GPCE’13 GPCE’13 Oct 27-28 2013.
Ralf Hinze (2003)
Fun With Phantom Types
Institut fur Informatik III, Universitat Bonn (March 2003).

Andrei Alexandrescu (2002)


Discriminated Unions
Discriminated Unions (April 2002).

Andrei Alexandrescu (2002)


An Implementation of Discriminated Unions in C++
An Implementaiton of Discriminated Unions in C++ (Aug 2002)
Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 52 / 55
References continued

Andrew Kennedy and Claudio Russo (2005)


Generalized Algebraic Data Types and Object-Oriented Programming
OOPSLA’05 OOPS’05 Oct 16-20
Bartosz Milewski (2015)
Functors
Bartosz Milewski (2012)
Functional Patterns in C++
https://www.fpcomplete.com/blog/2012/09/functional-patterns-in-c

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 53 / 55


Links to papers

1 A comparison of C++ concepts and Haskell type classes


2 Open Pattern Matching for C++
3 Fun with Phantom Types
4 An Implementation of Discriminated Unions in C++
5 Discriminated Unions
6 Generalized Algebraic Data types and Object-Oriented Programming
7 Functors
8 Functional-Patterns

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 54 / 55


The End

Sherri Shulman (TESC) Haskell Design Patterns title October 2, 2015 55 / 55

You might also like