the fun of programming - the yale haskell group

35
The Fun of Programming Edited by Jeremy Gibbons and Oege de Moor

Upload: others

Post on 15-Mar-2022

1 views

Category:

Documents


0 download

TRANSCRIPT

The Fun of Programming

Edited by

Jeremy Gibbons and Oege de Moor

Contents

Preface vii

1 Fun with binary heap trees 1Chris Okasaki1.1 Binary heap trees 11.2 Maxiphobic heaps 41.3 Persistence 61.4 Round-robin heaps 71.5 Analysis of skew heaps 101.6 Lazy evaluation 121.7 Analysis of lazy skew heaps 151.8 Chapter notes 16

2 Specification-based testing with QuickCheck 17Koen Claessen and John Hughes2.1 Introduction 172.2 Properties in QuickCheck 182.3 Example: Developing an abstract data type of queues 202.4 Quantifying over subsets of types 252.5 Test coverage 302.6 A larger case study 322.7 Conclusions 392.8 Acknowledgements 39

3 Origami programming 41Jeremy Gibbons3.1 Introduction 413.2 Origami with lists: sorting 423.3 Origami by numbers: loops 493.4 Origami with trees: traversals 523.5 Other sorts of origami 563.6 Chapter notes 60

iv

4 Describing and interpreting music in Haskell 61Paul Hudak4.1 Introduction 614.2 Representing music 614.3 Operations on musical structures 674.4 The meaning of music 704.5 Discussion 78

5 Mechanising fusion 79Ganesh Sittampalam and Oege de Moor5.1 Active source 795.2 Fusion, rewriting and matching 855.3 The MAG system 895.4 A substantial example 985.5 Difficulties 1015.6 Chapter notes 103

6 How to write a financial contract 105Simon Peyton Jones and Jean-Marc Eber6.1 Introduction 1056.2 Getting started 1066.3 Building contracts 1086.4 Valuation 1166.5 Implementation 1236.6 Operational semantics 1276.7 Chapter notes 128

7 Functional images 131Conal Elliott7.1 Introduction 1317.2 What is an image? 1327.3 Colours 1357.4 Pointwise lifting 1377.5 Spatial transforms 1397.6 Animation 1417.7 Region algebra 1427.8 Some polar transforms 1447.9 Strange hybrids 1477.10 Bitmaps 1487.11 Chapter notes 150

8 Functional hardware description in Lava 151Koen Claessen, Mary Sheeran and Satnam Singh8.1 Introduction 1518.2 Circuits in Lava 1528.3 Recursion over lists 153

v

8.4 Connection patterns 1558.5 Properties of circuits 1578.6 Sequential circuits 1608.7 Describing butterfly circuits 1628.8 Batcher’s mergers and sorters 1668.9 Generating FPGA configurations 1708.10 Chapter notes 175

9 Combinators for logic programming 177Michael Spivey and Silvija Seres9.1 Introduction 1779.2 Lists of successes 1789.3 Monads for searching 1799.4 Filtering with conditions 1829.5 Breadth-first search 1849.6 Lifting programs to the monad level 1879.7 Terms, substitutions and predicates 1889.8 Combinators for logic programs 1919.9 Recursive programs 193

10 Arrows and computation 201Ross Paterson10.1 Notions of computation 20110.2 Special cases 20810.3 Arrow notation 21310.4 Examples 21610.5 Chapter notes 222

11 A prettier printer 223Philip Wadler11.1 Introduction 22311.2 A simple pretty printer 22411.3 A pretty printer with alternative layouts 22811.4 Improving efficiency 23311.5 Examples 23611.6 Chapter notes 23811.7 Code 240

12 Fun with phantom types 245Ralf Hinze12.1 Introducing phantom types 24512.2 Generic functions 24812.3 Dynamic values 25012.4 Generic traversals and queries 25212.5 Normalisation by evaluation 25512.6 Functional unparsing 257

vi

12.7 A type equality type 25912.8 Chapter notes 262

Bibliography 263

Index 273

Describing andInterpreting Music

in HaskellPaul Hudak

4

4.1 Introduction

Musicologists have long noted subtle and complex relationships between mu-sical compositions and mathematical structures [55, 111]. Indeed, some wellknown composers deliberately exploited this relationship in their composi-tions. In this chapter we explore a slightly different relationship: that betweenmusical expression and computer languages. Specifically, we accomplish twothings. computer music

musicFirst, we use Haskell to describe musical structures. These structures con-sist of primitive entities (notes and rests), operations to transform musicalstructures (transpose and tempo-scaling), and operations to combine musicalstructures to form more complex ones (concurrent and sequential composi-tion). From these simple roots, much richer musical ideas can be developed.

Second, we define an interpretation of these musical structures in termsof an abstract notion of performance. This interpretation gives meaning toour music (even if not as grandiose as the meaning given by professionalmusicians), which allows us to prove certain laws that collectively form analgebra of music. Renamed ‘axioms’ to ‘laws’:

axioms are assumed, notproved.

The ideas presented here are similar to our previous work on Haskore

Haskore[63, 58] and MDL [60], two domain-specific languages for computer music. Butin this paper we focus more on the algebraic properties of music. For thatpurpose we both simplify the design of the musical structures, and change itslightly to enhance the symmetry and applicability of algebraic methods.

In what follows, we assume that the reader is familiar with very basicmusical concepts such as notes, rests, scales, and chords. No need to specify

knowledge of Haskell:assumed throughout

4.2 Representing music

The most basic musical concept is that of a pitch, which consists of a pitchclass (one of twelve semitones) and an octave:

type Pitch = (PitchClass, Octave)

62 The Fun of Programming

data PitchClass = Cf | C | Cs |Df |D |Ds | Ef | E | Es | Ff | F| Fs |Gf |G |Gs |Af |A |As | Bf | B | Bs

deriving (Show,Eq)type Octave = Int

Cf is read as ‘C-flat’ (normally written as C�), Cs as ‘C-sharp’ (normallywritten as C�), and so on. A Pitch is a pair consisting of a pitch class and anoctave. Octaves are just integers, but we have defined a separate data type forpitch classes because distinguishing enharmonics (that is, pitches that soundthe same, such as G� and A�) may be important in certain contexts. Whentuning instruments there is a notion of ‘A440’, which is the note A at 440 Hz;by convention, we designate that pitch as (A,4) in the above design.

A Note is either a pitch paired with a duration (in number of whole notes),or a Rest that has a duration but no pitch:

data Note = Rest Dur | Note Pitch Durderiving (Show, Eq)

type Dur = Ratio Int

Note that durations are represented using rational numbers; specifically,as ratios of two Haskell Int values. This is more accurate than using floating-point numbers, and for musical structures is often just the right thing, wheremeter is expressed as a ratio (2/4, 3/4, 6/8, etc.), notes are described as frac-tions of a whole (eighth notes, quarter notes, etc.), notes lengths are modifiedby ‘dotting’ (which multiplies the duration by 3/2), and notes are grouped intotriplets (3), quintuplets (5), and so on.

Notes are the primitive building blocks of music. To build more sophisti-cated structures, we define the Music data type:Music@\textitMusic

data Music = Prim Note| Music :+: Music| Music :=: Music| Tempo (Ratio Int)Music| Trans Int Music

deriving (Show, Eq)

whose constructors imply the following informal semantics:

• Prim n is a note (or rest).

• m1 :+: m2 is the ‘sequential composition’ of m1 and m2; that is, m1 andm2 are played in sequence.

• m1 :=: m2 is the ‘parallel composition’ of m1 and m2; that is, m1 and m2

are played simultaneously.

• Tempo a m scales the rate (or ‘tempo’) at which m is played by a factorof a.

• Trans int m transposes m by interval int (in semitones).

4 Describing and Interpreting Music in Haskell 63

We choose to represent these ideas as a recursive data type because wemay wish to not only build musical structures, but also take them apart, anal-yse their structure, print them, transform them, interpret them for perfor-mance purposes, and so on.

There is one aspect of the informal semantics that is somewhat vague:namely, exactly what does the ‘parallel composition’ of m1 and m2 mean; thatis, what does it mean to play m1 and m2 ‘simultaneously?’ If both m1 and m2

are the same duration, then there is no problem, but if they are different thenthere seem to be several reasonable alternatives:

1. One could start them both at the same time, and when the longer onefinishes, the entire construction finishes.

2. One could start them both at the same time, and when the shorter onefinishes, the entire construction finishes (thus truncating the longer one).

3. One could ‘centre’ the two in time, so that the shorter one begins afterone-half of the difference between the durations of the two.

The first option is what we previously used in the design of Haskore and MDL[63, 58, 60]. The second option is similar to what Haskell’s zip function doeswith lists. The third option is what we use in the present treatment. We choosethis option because it is arguably more symmetric than either of the others,and, as we will soon see, results in some simpler algebraic properties.

Absolute pitches

Although naming pitches with a data type is natural and useful, it is oftenmore convenient to treat pitches simply as integers. Thus we define a notionAbsPitch of absolute pitch, along with some functions for converting betweenPitch values and AbsPitch values:

type AbsPitch = Int

absPitch :: Pitch → AbsPitchabsPitch (pc,oct) = 12 × oct + pcToInt pc

pitch :: AbsPitch → Pitchpitch ap = ( [C,Cs,D,Ds,E , F , Fs,G,Gs,A,As,B] !! mod ap 12,

quot ap 12 )

pcToInt :: PitchClass → IntpcToInt pc = case pc of

Cf → −1; C → 0 ; Cs → 1Df → 1 ; D → 2 ; Ds → 3Ef → 3 ; E → 4 ; Es → 5Ff → 4 ; F → 5 ; Fs → 6Gf → 6 ; G → 7 ; Gs → 8Af → 8 ; A → 9 ; As → 10Bf → 10 ; B → 11; Bs → 12

64 The Fun of Programming

Should Cf be interpreted as 11 instead of −1, and Bs as 0 instead of 12?After all, (−1) ‘mod ‘ 12 is 11, and 12 ‘mod ‘ 12 is 0. On the other hand, thiswould imply a large leap when moving from C to C� or B to B�. In most casesthe choice will not matter, but it is prudent for us to be aware of the issue.

We also define a function trans, which transposes pitches (analogous toTrans, which transposes values of type Music):

trans :: Int → Pitch → Pitchtrans i p = pitch (absPitch p + i)

Finally, for convenience, we define simple names for familiar notes, dura-tions, and rests, as shown in Figure 4.1. Despite the large number of them,these names are sufficiently arcane that name clashes are unlikely.

Exercise 4.1 Prove that abspitch · pitch = id, and, up to enharmonic equiva-lences, pitch · abspitch = id. �

Exercise 4.2 Prove that trans i (trans j p) = trans (i + j) p. �

Some simple examples

Lines and chords. Two common ideas in music are the construction of notesin a horizontal fashion (a line or melody), and in a vertical fashion (a chord):

line, chord :: [Music] → Musicline = foldr (:+:) (Prim (Rest 0))chord = foldr (:=:) (Prim (Rest 0))

For example, from the notes in the C major triad in register four, we canconstruct a C major arpeggio and chord as well:

cMaj = [ n 4 qn | n ← [c, e,g] ]

cMajArp = line cMajcMajChd = chord cMaj

Delay and repeat. Suppose that we wish to describe a melody m accompaniedby an identical voice a perfect fifth higher. We can write this very simply asm :=: Trans 7 m (seven semitones being a perfect fifth). Similarly, a canon-likestructure involving m can be expressed as (m :+: Rest d) :=: (Rest d :+: m)where d is the delay between the phrases. Indeed, it is useful to define generic‘delay’ and ‘post-delay’ operators:

delay, pDelay :: Dur → Music → Musicdelay d m = Prim (Rest d) :+: mpDelay d m =m :+: Prim (Rest d)

4 Describing and Interpreting Music in Haskell 65

cf , c, cs,df ,d,ds, ef , e, es, ff , f , fs,gf ,g,gs,af ,a,as,bf ,b,bs:: Octave → Dur → Music

cf o d = Prim (Note (Cf ,o) d); c o d = Prim (Note (C,o) d)cs o d = Prim (Note (Cs,o) d) ; df o d = Prim (Note (Df ,o) d)d o d = Prim (Note (D,o) d) ; ds o d = Prim (Note (Ds,o) d)ef o d = Prim (Note (Ef ,o) d) ; e o d = Prim (Note (E ,o) d)es o d = Prim (Note (Es,o) d) ; ff o d = Prim (Note (Ff ,o) d)f o d = Prim (Note (F ,o) d) ; fs o d = Prim (Note (Fs,o) d)gf o d = Prim (Note (Gf ,o) d); g o d = Prim (Note (G,o) d)gs o d = Prim (Note (Gs,o) d) ; af o d = Prim (Note (Af ,o) d)a o d = Prim (Note (A,o) d) ; as o d = Prim (Note (As,o) d)bf o d = Prim (Note (Bf ,o) d) ; b o d = Prim (Note (B,o) d)bs o d = Prim (Note (Bs,o) d)

wn, hn, qn, en, sn, tn, dhn, dqn, den, dsn :: Durwnr , hnr , qnr , enr , snr , tnr , dhnr , dqnr, denr , dsnr :: Musicwn = 1 ; wnr = Prim (Rest wn) — wholehn = 1%2 ; hnr = Prim (Rest hn) — halfqn = 1%4 ; qnr = Prim (Rest qn) — quarteren = 1%8 ; enr = Prim (Rest en) — eighthsn = 1%16; snr = Prim (Rest sn) — sixteenthtn = 1%32; tnr = Prim (Rest tn) — thirty-seconddhn = 3%4 ; dhnr = Prim (Rest dhn) — dotted halfdqn = 3%8 ; dqnr = Prim (Rest dqn) — dotted quarterden = 3%16; denr = Prim (Rest den) — dotted eighthdsn = 3%32; dsnr = Prim (Rest dsn) — dotted sixteenth

Figure 4.1: Convenient note and rest names.

Of course, Haskell’s non-strict semantics also allows us to define infinitemusical structures. For example, a musical structure may be repeated adnauseum using this simple function:

repeatM :: Music → MusicrepeatM m =m :+: repeatM m

Thus an infinite ostinato can be expressed in this way, and then used in dif-ferent contexts that extract only the portion that’s actually needed. This isexplained in more detail later.

Trills. A trill is an ornament that alternates rapidly between two (usually ad-jacent) pitches. We define a function trill such that trill i d n is a trill beginningon the pitch of note n, with the alternate note being i semitones away, andwith each trill note having duration d. The total duration of trill i d n should

66 The Fun of Programming

be the same as the duration of n.

trill :: Int → Dur → Music → Musictrill i d n@(Prim (Note p nd)) =

if d � nd thenn

elsePrim (Note p d) :+: trill (negate i) d (Prim (Note (trans i p) (nd−d)))

trill = error “Trill input must be a single note”

It is simple to define a version of this function that starts on the alternatenote rather than the start note:

trill′ :: Int → Dur → Music → Musictrill′ i d n@(Prim (Note p nd)) = trill (negate i) d (Prim (Note (trans i p) nd))

Exercise 4.3 Define a function trilln :: Int → Int → Music → Music that isjust like trill except that its second argument is the number of trill notesto be generated, rather than the duration of a single trill note. Also definetrilln′ which is to trilln as trill′ is to trill. �

Here is a simple example of the use of trill and trilln in expressing theopening flute line in John Philip Sousa’s Stars and Stripes Forever :

ssfMelody =m1 :+: m2 :+: m3 :+: m4

m1 = trilln 2 5 (bf 6 en) :+: line [ef 7 en, ef 6 en, ef 7 en]m2 = line [bf 6 sn, c 7 sn, bf 6 sn, g 6 sn, ef 6 en, bf 5 en]m3 = line [ef 6 sn, f 6 sn, g 6 sn, af 6 sn, bf 6 en, ef 7 en]m4 = trill 2 tn (bf 6 qn) :+: bf 6 sn :+: denr

There are many other interesting and more complex applications of theideas presented here, the most notable being various kinds of algorithmiccomposition. For example, in previous work we explored the ideas of fractalmusic [60] and improvisation [61], but many other ideas are possible. Indeed,there are far too many such efforts in the computer music literature to citehere, but see [5] and [110] for good summaries.

Exercise 4.4 Prove that durM (trill i d n) = durM n. �

Exercise 4.5 Transcribe into Haskell a simple piece of music written by yourfavourite composer. In doing so, look for repeating patterns, transposedphrases, and so on, and reflect this in your code, thus revealing deeper struc-tural aspects of the music than that found in conventional music notation. �

Exercise 4.6 Define a data type Mode that enumerates the seven scale modes:ionian, dorian, phrygian, lydian, mixolydian, aeolian, and locrian. Then definea function scale that, given a mode and tonic (a start note), generates a scalein that mode starting on the tonic. �

4 Describing and Interpreting Music in Haskell 67

4.3 Operations on musical structures

We now turn our attention to the design of various operations that we may wishto perform on musical structures. Many of them are analogous to operationson lists, and we borrow similar names when the analogy is strong. We alsoexplore various properties that these operators exhibit, properties that arealso analogous to those for lists [13, 60].

Duration. It is often desirable to compute the duration in beats of a musicalstructure. We do so with an operator durM , analogous to the length operatoron lists, and by the third line in the definition below trivially exhibiting aproperty analogous to length l1 + length l2 = length (l1 ++ l2).

durM :: Music → DurdurM (Prim (Note d)) = ddurM (Prim (Rest d)) = ddurM (m1 :+: m2) = durM m1 + durM m2

durM (m1 :=: m2) = durM m1 ‘max ‘ durM m2

durM (Tempo a m) = durM m / adurM (Trans m) = durM m

Reverse. We define a function revM that reverses any Music value.

revM :: Music → MusicrevM n@(Prim ) = nrevM (m1 :+: m2) = revM m2 :+: revM m1

revM (m1 :=: m2) = revM m1 :=: revM m2

revM (Tempo a m) = Tempo a (revM m)revM (Trans i m) = Trans i (revM m)

Note here that the treatment of (:=:) depends critically on the symmetry of this Turned footnote toparenthetical text toimprove pagebreak

operator, as discussed in Section 4.2. Using a non-symmetric interpretation of(:=:) complicates the definition considerably.

It is easy to show the following property; the proof is by a straightforwardstructural induction on m, and is left as an exercise for the reader. Rearranged, to improve

pagebreak

Theorem 4.1 For any m :: Music, revM (revM m) = m. �

Map. We also define a map function for musical structures that allows apply-ing a function of type Note → Note to each note (and rest):

mapM :: (Note → Note) → Music → MusicmapM f (Prim n) = Prim (f n)mapM f (m1 :+: m2) =mapM f m1 :+: mapM f m2

mapM f (m1 :=: m2) =mapM f m1 :=: mapM f m2

mapM f (Tempo r m) = Tempo r (mapM f m)mapM f (Trans p m) = Trans p (mapM f m)

68 The Fun of Programming

(This function cannot be defined satisfactorily in Haskore and MDL [63, 58, 60],because there is no clear distinction between Music and Note values in theirdesigns.)

The function mapM shares many properties with the ordinary map func-tion. For example:

Theorem 4.2 For any m :: Music and functions f , g :: Note → Note:

mapM (f · g)m = mapM f (mapM g m)mapM id m = m

The proof of both parts is by a straightforward structural induction on m, andis left as an exercise.

Function mapM also interacts nicely with reverse:

Theorem 4.3 For any m :: Music and function f :: Note → Note:

mapM f (revM m) = revM (mapM f m)

The proof of this theorem is also straightforward, and is left as an exercise.

Take and drop. We now define two functions takeM and dropM that are anal-ogous to Haskell’s take and drop functions for lists. The difference is thatinstead of being parameterised by a number of elements, takeM and dropMare parameterised by time. The expression takeM d m returns a music valuecorresponding to the first d seconds of a (so far imagined) performance of m.Similarly, drop d m returns all but the first d seconds.

Defining these functions is straightforward except for the treatment of(:=:), which, if you recall, treats its arguments symmetrically with respect totime. The simplest way to resolve the difficulty that this imposes is to first‘pad’ every application of (:=:) with rests such that both of its arguments havethe same duration:

pad :: Music → Music → Musicpad m1 m2 = let d1 = durM m1

d2 = durM m2

pd = abs (d2 − d1) / 2in

case compare d2 d1 ofGT → delay pd (pDelay pd m1) :=: m2

EQ → m1 :=: m2

LT → m1 :=: delay pd (pDelay pd m2)

With this function we can easily pad an entire Music value:

4 Describing and Interpreting Music in Haskell 69

padM :: Music → MusicpadM n@(Prim ) = npadM (m1 :+: m2) = padM m1 :+: padM m2

padM (Tempo r m) = Tempo r (padM m)padM (Trans p m) = Trans p (padM m)padM (m1 :=: m2) = pad (padM m1) (padM m2)

Finally we define takeM :

takeM :: Dur → Music → MusictakeM d m | d � 0 = Prim (Rest 0)takeM d m = takM d (padM m)

takM :: Dur → Music → MusictakM d (Prim (Note p d0)) = Prim (Note p (min d0 d))takM d (Prim (Rest d0)) = Prim (Rest (min d0 d))takM d (m1 :=: m2) = takM d m1 :=: takM d m2

takM d (Tempo a m) = Tempo a (takM (d × a)m)takM d (Trans a m) = Trans a (takM d m)takM d (m1 :+: m2) = let d1 = durM m1

in if d � d1 thentakM d m1

elsem1 :+: takM (d − d1)m2

dropM is easily defined in terms of takeM :

dropM :: Dur → Music → MusicdropM d m = revM (takeM (durM m − d) (revM (padM m)))

We leave as an exercise the task of defining a more efficient version of dropM .Functions takeM and dropM share many properties analogous to their list

counterparts, such as:

Theorem 4.4 For all non-negative d, d1, d2 :: Dur:

takeM d1 · takeM d2 = takeM (min d1 d2)dropM d1 · dropM d2 = dropM (d1 + d2)takeM d1 · dropM d2 = dropM d2 · takeM (d1 + d2)dropM d1 · takeM d2 = takeM (d2 − d1) · dropM d1 — if d2 � d1

However, note that this property:

takeM d m :+: dropM d m = m — if d � durM m

does not hold, although its analogous version for lists does. There are severalreasons for this:

70 The Fun of Programming

1. takeM and dropM pad their arguments, so unless the value was alreadypadded, some differences in the result might be expected.

2. Notes and rests are truncated by takeM and dropM . For example, if m inthe above equation were a single note, then the left-hand side would resultin two notes instead of one!

3. Even putting the previous two points aside, suppose that m = padM m′

has duration d. Now consider m1 = (m :+: m) :=: (m :+: m). Then:

m2 = takeM d m1 :+: dropM d m1

= (m :=: m) :+: (m :=: m)≠m1

But surely there is some sense in which the two phrases:

m1 = (m :+: m) :=: (m :+: m)m2 = (m :=: m) :+: (m :=: m)

are the same; indeed, in conventional music notation, there is no way todistinguish them!

The last issue above motivates well the following section.

Exercise 4.7 Prove Theorems 4.1, 4.2, 4.3, and 4.4. �

Exercise 4.8 Define a more efficient version of dropM . Prove that it is equiva-lent to that defined earlier. �

Exercise 4.9 Show that padM is idempotent (that is, padM · padM = padM )and preserves duration (that is, durM = durM · padM ). �

4.4 The meaning of music

In the preceding sections we explored a method to describe musical structuresin Haskell, defined a number of operations on those structures, and statedproperties that those operations possess. But in a sense, it is all just syntax:what does a musical structure actually mean?

There is little chance of our answering this question in a deep sense, wherepersonality, emotions, musical background, and so forth will surely muddythe waters. But we can give a formal notion of the ‘meaning’ of values of typeMusic, a meaning that we shall call a literal interpretation. (Alternatively, wefootnote to parenthetical

comment for pagebreak could call this a literal performance, in which no aesthetic interpretation isgiven to a musical object, much like the performance of a technically perfectmusician who is utterly lacking in expression.) Indeed, we will see that theliteral interpretations of the two expressions given at the end of the previoussection are the same, as we might hope.

4 Describing and Interpreting Music in Haskell 71

We define the meaning of a musical structure using an abstract notion ofperformance, which is a temporally ordered sequence of musical events:

type Performance = [Event]

data Event = Event { eTime :: Time,ePitch :: AbsPitch,eDur :: DurT }

deriving (Eq,Ord, Show)

type Time = Ratio Inttype DurT = Ratio Int

An event Event s p d captures the fact that at start time s, pitch p sounds fora duration d (where now duration and time are measured in seconds, ratherthan beats).

We take the position that two identical events (that therefore happen atthe same time) are not the same as just one of them. This models the ideathat in real life a listener is able to distinguish two performers from one,even if they are playing the same music. Similarly, two notes with the samepitch happening in succession are also distinguishable, modeling the notionthat some degree of articulation allows a listener to distingish them in reallife.

To generate a complete performance of, that is, give an interpretation to,a musical structure expressed in Haskell, we must know the time to begin theperformance, and the proper key and tempo. We can thus model a ‘performer’as a function perform that uses all of this information (which we call thecontext) to translate a musical structure into a performance:

perform :: Context → Music → Performance

data Context = Context { cTime :: Time,cDur :: DurT ,cKey :: Key }

deriving Show

type Key = AbsPitch

The cDur :: DurT component of the context is the duration, in seconds, ofone whole note. To make it easier to compute this, we define a ‘metronome’function that, given a standard metronome marking (in beats per minute) andthe note type associated with one beat (quarter note, eighth note, and so on)the duration of one whole note:

metro :: Dur → Dur → DurTmetro setting dur = 60 / (setting × dur)

For example, metro 96 qn creates a tempo of 96 quarter notes per minute.The definition of perform is relatively straightforward, so we present it all

at once:

72 The Fun of Programming

perform :: Context → Music → Performanceperform c m = perf c (padM m)

perf :: Context → Music → Performanceperf c@(Context t dt k)m

= case m ofPrim (Note p d)→ [ Event t (absPitch p+ k) (d×dt) ]Prim (Rest d) → [ ]m1 :+: m2 → let c′ = c { cTime =

t + (durM m1)× dt}in perf c m1 ++ perf c′ m2

m1 :=: m2 →merge (perf c m1) (perf c m2)Tempo a m → perf (c {cDur = dt / a})mTrans p m → perf (c {cKey = k + p})m

A single note is translated into a single-event performance; note how thepitch is transposed to correspond to the key. A rest translates naturally intoan empty performance. The treatment of Tempo and Trans is straightforward;note how the Context is used as the running ‘state’ of the performance, andgets updated in several different ways. For example, the interpretation ofTempo involves scaling dt appropriately and updating the cDur field of thecontext.

In the treatment of (:+:), note that the sub-sequences are appended to-gether, with the start time of the second argument delayed by the duration ofthe first. In contrast, the sub-sequences derived from the arguments to (:=:)are merged into a time-ordered stream. This simple approach works becausethe music has been padded, and therefore both arguments to (:=:) have thesame duration. The definition of merge is:

merge :: Performance→ Performance→ Performancemerge a@(e1 : es1) b@(e2 : es2) = if e1 < e2 then

e1 : merge es1 belse

e2 : merge a es2merge [ ] es2 = es2

merge es1 [ ] = es1

Exercise 4.10 In the treatment of :+: in the definition of perf , the expressionm1 is processed by both durM and perf . Unfortunately, this strategy generatesa number of steps proportional to the square of the size of the Music value.A more efficient solution is to have perform compute the duration directly,returning it as part of its result. Define such an alternative, and prove that itis equivalent to perf . �

4 Describing and Interpreting Music in Haskell 73

An algebra of musicbra of music

There are many musical structures whose literal performances we expect tobe equivalent. We have already seen one such example: the phrases m1 andm2 given at the end of Section 4.3. But there are even simpler examples: thefollowing two musical objects are not equal as data structures, but we wouldexpect their literal performances to be the same:

(m1 :+: m2) :+: m3

m1 :+: (m2 :+: m3)

Thus we define a formal notion of equivalence:

Definition 4.1 m1 :: Music and m2 :: Music are equivalent, written m1 ≡ m2,if and only if (∀c :: Context) perform c m1 = perform c m2. �

One of the most useful things we can do with this notion of equivalence isestablish the validity of certain transformations on musical objects. A trans-formation is valid if the result of the transformation is equivalent (in the sensedefined above) to the original musical object — that is, it is ‘meaning preserv-ing.’

The most basic of these transformation we treat as laws in an algebra ofmusic. For example:

Law 4.1 For any r1, r2, and m:

Tempo r1 (Tempo r2 m) ≡ Tempo (r1 × r2)m

Proof We prove this law by calculation. For clarity we ignore padding andsimplify the context to just dt, the tempo duration:

perf dt (Tempo r1 (Tempo r2 m))= {definition of perf }

perf (dt/r1) (Tempo r2 m)= {definition of perf }

perf ((dt/r1)/(r2))m= {arithmetic}

perf (dt/(r1 × r2))m= {definition of perf }

perf dt (Tempo (r1 × r2)m)

Here is another useful transformation; in words, tempo scaling distributes Rearranged to improvepagebreakover sequential composition.

74 The Fun of Programming

Law 4.2 For any r , m1, and m2:

Tempo r (m1 :+: m2) ≡ Tempo r m1 :+: Tempo r m2

Proof For clarity we again ignore padding, and simplify the context to just(t,dt), the start time and tempo.

perf (t,dt) (Tempo r (m1 :+: m2))= {definition of perf }

perf (t,dt/r) (m1 :+: m2)= {definition of perf ; let t1 = t + (durM m1)× (dt/r)}

perf (t,dt/r)m1 ++ perf (t1,dt/r)m2

= {definition of perf }perf (t,dt) (Tempo r m1) ++ perf (t1,dt) (Tempo r m2)

= {arithmetic; let t2 = t + (durM m1/r)× dt}perf (t,dt) (Tempo r m1) ++ perf (t2,dt) (Tempo r m2)

= {definition of durM ; let t3 = t + (durM (Tempo r m1))× dt}perf (t,dt) (Tempo r m1) ++ perf (t3,dt) (Tempo r m2)

= {definition of perf }perf (t,dt) (Tempo r m1 :+: Tempo r m2)

An even simpler law is given by:

Law 4.3 For any m:

Tempo 1 m ≡ m

In other words, unit tempo scaling is the identity function for type Music. Theproof is as simple as the statement:

perf (t,dt) (Tempo 1 m)= {definition of perf }

perf (t,dt/1)m= {arithmetic}

perf (t,dt)m

Note that the above proofs, being used to establish laws, all involve thedefinition of perform. In contrast, we can also establish theorems whose proofsinvolve only the laws.paragraph break to improve

pagebreak For example, Laws 4.1, 4.2, and 4.3 are all needed to prove the followingtheorem.

4 Describing and Interpreting Music in Haskell 75

Theorem 4.5 For any r, m1, and m2:

Tempo r m1 :+: m2 ≡ Tempo r (m1 :+: Tempo (1/r)m2)

Proof

Tempo r (m1 :+: Tempo (1/r)m2)= {by Law 4.2}

Tempo r m1 :+: Tempo r (Tempo (1/r)m2)= {by Law 4.1}

Tempo r m1 :+: Tempo (r × (1/r))m2

= {arithmetic}Tempo r m1 :+: Tempo 1 m2

= {by Law 4.3}Tempo r m1 :+: m2

Many other interesting transformations of musical structures can be statedand proved correct in this manner. We leave as an exercise the proofs of thelaws listed in the following subsection (which include the above laws as specialcases). But there is one other law whose proof is more complex, and thus weinclude it here. To motivate it, recall the two phrases introduced at the end ofSection 4.3:

m1 = (m :+: m) :=: (m :+: m)m2 = (m :=: m) :+: (m :=: m)

These phrases are equivalent as a special case of the following law:

Law 4.4 For any m1, m2, m3, m4 :: Music such that durM m1 = durM m3

and durM m2 = durM m4, we have:

(m1 :+: m2) :=: (m3 :+: m4) ≡ (m1 :=: m3) :+: (m2 :=: m4)

The proof of this law depends on a couple of lemmas concerning perform andmerge:

Lemma 4.1 For any m :: Music and c :: Context ,

(a) perform c m is a time-ordered sequence, and

(b) (∀ e ∈ perform c m), t � eTime e � t + durM m, where t = cTime c.

76 The Fun of Programming

Lemma 4.2 For any time-ordered sequences xs, ys, zs :: Performance:

(a) xs ‘merge‘ ys = ys ‘merge‘ xs,

(b) xs ‘merge‘ (ys ‘merge‘ zs) = (xs ‘merge‘ ys) ‘merge‘ zs, and

(c) if last xs < head ys, then xs ‘merge‘ ys = xs ++ ys.

With these lemmas (whose proofs are left as an exercise), we now proveLaw 4.4:

Proof Suppose d = durM m1 = durM m3. Then:

perf t ((m1 :+: m2) :=: (m3 :+: m4))= {definition of perf }

perf t (m1 :+: m2) ‘merge‘ perf t (m3 :+: m4)= {definition of perf }(perf t m1 ++ perf (t + d)m2) ‘merge‘ (perf t m3 ++ perf (t + d)m4)= {Lemmas 4.2(c) and 4.1}(perf t m1 ‘merge‘ perf (t + d)m2) ‘merge‘

(perf t m3 ‘merge‘ perf (t + d)m4)= {Lemmas 4.2(a,b) and 4.1}(perf t m1 ‘merge‘ perf t m3) ‘merge‘

(perf (t + d)m2 ‘merge‘ perf (t + d)m4)= {Lemmas 4.2(c) and 4.1}(perf t m1 ‘merge‘ perf t m3) ++(perf (t + d)m2 ‘merge‘ perf (t + d)m4)

= {definition of perf }perf t (m1 :=: m3) ++ perf (t + d) (m2 :=: m4)= {definition of perf }

perf t ((m1 :=: m3) :+: (m2 :=: m4))

Exercise 4.11 Prove Lemmas 4.1 and 4.2. �

Summary of laws

Law 4.5 Tempo scaling is multiplicative and transposition is additive. That is,for any r1, r2, p1, p2, and m:

Tempo r1 (Tempo r2 m) ≡ Tempo (r1 × r2)mTrans p1 (Trans p2 m) ≡ Trans (p1 + p2)

4 Describing and Interpreting Music in Haskell 77

Law 4.6 Function composition is commutative with respect to both temposcaling and transposition. That is, for any r1, r2, p1 and p2:

Tempo r1 · Tempo r2 ≡ Tempo r2 · Tempo r1

Trans p1 · Trans p2 ≡ Trans p2 · Trans p1

Tempo r1 · Trans p1 ≡ Trans p1 · Tempo r1

Law 4.7 Tempo scaling and transposition are distributive over both sequentialand parallel composition. That is, for any r , p, m1, and m2:

Tempo r (m1 :+: m2) ≡ Tempo r m1 :+: Tempo r m2

Tempo r (m1 :=: m2) ≡ Tempo r m1 :=: Tempo r m2

Trans p (m1 :+: m2) ≡ Trans p m1 :+: Trans p m2

Trans p (m1 :=: m2) ≡ Trans p m1 :=: Trans p m2

Law 4.8 Sequential and parallel composition are associative. That is, for anym0, m1, and m2:

m0 :+: (m1 :+: m2) ≡ (m0 :+: m1) :+: m2

m0 :=: (m1 :=: m2) ≡ (m0 :=: m1) :=: m2

Law 4.9 Parallel composition is commutative. That is, for any m0 and m1:

m0 :=: m1 ≡ m1 :=: m0

Law 4.10 Rest 0 is a unit for Tempo and Trans: for any r and p, better call this a ‘fixpoint’?

Tempo r (Rest 0) ≡ Rest 0Trans p (Rest 0) ≡ Rest 0

Moreover, it is a unit for sequential and parallel composition: for any m: unit, not zero!

m :+: Rest 0 ≡ m ≡ Rest 0 :+: mm :=: Rest 0 ≡ m ≡ Rest 0 :=: m

Exercise 4.12 Establish the validity of each of the above laws. �

78 The Fun of Programming

From abstract performance to concrete sounds

In order to actually hear a literal interpretation of a Music value, we need toconvert an abstract performance into concrete sound. The easiest way to dothis is to convert a value of type Performance into a MIDI file, a standard for-MIDI

mat for interchanging electronic music that is playable on most conventionalpersonal computers [67, 113]. Indeed, the Haskore library contains a collectionof useful functions and data structures for interfacing with MIDI files, startingwith a Performance data type very similar to that used here. From that libraryit is easy to define a function:

perfToMidi :: Performance → FilePath → IO ()

with which we can achieve our goal.

4.5 Discussion

There are several shortcomings in our current design, most of which are han-dled by Haskore [63, 58]. For example, we have said nothing about instru-ments. Haskore and MDL handle instruments through the use of an additionalconstructor Instr in the Music data type, such that Instr iName m uses theinstrument iName to play music m. iName, in turn, is one of 129 standardMIDI instrument names (with percussion treated in a special way), which areunderstood by most sound cards on conventional personal computers.

Another shortcoming in our current design is that there is no represen-tation of dynamics, that is, loudness or volume. Haskore has an extra fieldin the Note constructor for volume, as well as more abstract ways to expresstraditional notions of pianissimo, piano, mezzo piano, mezzo forte, forte, andfortissimo (often abbreviated pp, p, mp, mf, f, and ff, respectively). Haskorealso accounts for other notions of dynamics, including legato, staccato, slur-ring, crescendo, and diminuendo. In addition, with respect to tempo, there arenotions of ritardando and accelerando. Each of these is given a special (if stillliteral) interpretation by perform.

Finally, the reader might have already noted that, using mapM , it seemspossible to implement transposition and tempo-scaling directly, without re-sorting to the Trans and Tempo constructors and their associated interpre-tations. Indeed this is true! However, such an approach would have severaldisadvantages. First, it would be less efficient. Nested calls to the functionsimplementing these ideas would each traverse the entire music data type,whereas in our approach only one traversal is needed by perform, which accu-mulates the effect of nested constructors in the context. Second, we lose theability to manipulate the structure of a composition based on its shape, whichis reflected in the application of these constructors.

Of course, ours is not the only effort in designing languages for computermusic, but it is the only purely functional approach that we are aware of. Fora compendium of other approaches, see [5, 110].

Bibliography

[1] Kavi Arya. A functional animation starter-kit. Journal of FunctionalProgramming, 4(1):1–18, January 1994.

[2] Lex Augusteijn. Sorting morphisms. In S. D. Swierstra, P. R. Henriques,and J. N. Oliveira, editors, Advanced Functional Programming, volume1608 of Lecture Notes in Computer Science, pages 1–27.Springer-Verlag, 1999.

[3] Lennart Augustsson. Cayenne: A language with dependent types.SIGPLAN Notices, 34(1):239–250, January 1999.

[4] Franz Baader and Tobias Nipkow. Term Rewriting and All That.Cambridge University Press, 1998.

[5] Roland Backhouse, Patrik Jansson, Johan Jeuring, and LambertMeertens. Generic programming: An introduction. In S. D. Swierstra,P. R. Henriques, and J. N. Oliveira, editors, Advanced FunctionalProgramming, volume 1608 of Lecture Notes in Computer Science,pages 28–115. Springer-Verlag, Berlin, 1999.

[6] Denis Baggi. Computer-Generated Music. IEEE Computer Society Press,Las Alamitos, CA, 1992.

[7] Joel F. Bartlett. Don’t fidget with widgets, draw! Technical Report 6,DEC Western Digital Laboratory, May 1991.

[8] Kenneth E. Batcher. Sorting networks and their applications. In AFIPSSpring Joint Conference, pages 307–314, 1968.

[9] Gerard Berry and Georges Gonthier. The Esterel synchronousprogramming language: Design, semantics, implementation. Science ofComputer Programming, 19(2):87–152, 1992.

[10] A. S. Bhandal, V. Considine, and G. E. Dixon. An array processor forvideo picture motion estimation. In J. McCanny, J. McWhirter, andE. Swartzlander, editors, Systolic Array Processors, pages 369–378.Prentice-Hall International, 1989.

264 The Fun of Programming

[11] Richard Bird. An introduction to the theory of lists. In M. Broy, editor,Proceedings of the NATO Advanced Study Institute on Logic ofProgramming and Caculi of Discrete Design. Springer Verlag, June 1987.

[12] Richard Bird and Oege de Moor. Algebra of Programming. PrenticeHall, 1997.

[13] Richard Bird and John Hughes. The alpha–beta algorithm: an exercisein program transformation. Information Processing Letters, 24(1):53–57,January 1987.

[14] Richard S. Bird. The promotion and accumulation strategies intransformational programming. ACM Transactions on ProgrammingLanguages and Systems, 6(4):487–504, October 1984. Addendum in7(3), p. 490–492.

[15] Richard S. Bird. Introduction to Functional Programming using Haskell.Prentice Hall Europe, 2nd edition, 1998.

[16] Richard S. Bird and Jeremy Gibbons. Arithmetic coding with folds andunfolds. In Johan Jeuring and Simon Peyton Jones, editors, AdvancedFunctional Programming. Springer-Verlag, 2002. To appear.

[17] Per Bjesse, Koen Claessen, Mary Sheeran, and Satnam Singh. Lava:Hardware design in Haskell. In International Conference on FunctionalProgramming. ACM, 1998.

[18] Phelim Boyle, Mark Broadie, and Paul Glasserman. Monte Carlomethods for security pricing. Journal of Economic Dynamics andControl, 21:1267–1321, 1997.

[19] Paul Caspi, Daniel Pilaud, Nicholas Halbwachs, and John A. Plaice.LUSTRE: A declarative language for programming synchronoussystems. In 14th ACM Symposium on Principles of ProgrammingLanguages, pages 178–188, Munich, 1987.

[20] James Cheney and Ralf Hinze. A lightweight implementation ofgenerics and dynamics. In Manuel M.T. Chakravarty, editor, Proceedingsof the 2002 ACM SIGPLAN Haskell Workshop, October 2002.

[21] Olaf Chitil. Pretty printing with lazy dequeues. In ACM SIGPLANHaskell Workshop, pages 183–201, Firenze, Italy, 2001. UniversiteitUtrecht UU-CS-2001-23.

[22] Seonghun Cho and Sartaj Sahni. Weight biased leftist trees andmodified skip lists. In International Computing and CombinatoricsConference, pages 361–370, June 1996.

[23] Koen Claessen and John Hughes. QuickCheck: a lightweight tool forrandom testing of Haskell programs. In International Conference onFunctional Programming, pages 268–279. ACM, 2000.

[24] Koen Claessen and John Hughes. Testing Monadic Code withQuickCheck. In Haskell Workshop. ACM SIGPLAN, 2002.

Bibliography 265

[25] Koen Claessen and David Sands. Observable sharing for functionalcircuit description. In Asian Computer Science Conference, pages62–73, Phuket, Thailand, 1999. ACM SIGPLAN.

[26] William F. Clocksin and Christopher S. Mellish. Programming in Prolog.Springer Verlag, second edition, 1984.

[27] Antony Courtney and Conal Elliott. Genuinely functional userinterfaces. In Haskell Workshop, pages 41–69, 2001.

[28] John C. Cox, Stephen A. Ross, and Mark Rubinstein. Option pricing: asimplified approach. Journal of Financial Economics, 7:229–263, 1979.

[29] Clark Allan Crane. Linear lists and priority queues as balanced binarytrees. PhD thesis, Computer Science Department, Stanford University,February 1972. Available as STAN-CS-72-259.

[30] Olivier Danvy. Functional unparsing. Journal of FunctionalProgramming, 8(6):621–625, November 1998.

[31] Olivier Danvy, Morten Rhiger, and Kristoffer H. Rose. Normalization byevaluation with typed abstract syntax. Journal of FunctionalProgramming, 11(6):673–680, November 2001.

[32] Oege de Moor and Ganesh Sittampalam. Generic programtransformation. In Third International Summer School on AdvancedFunctional Programming, volume 1608 of Lecture Notes in ComputerScience, pages 116–149. Springer-Verlag, 1998.

[33] Oege de Moor and Ganesh Sittampalam. Higher-order matching forprogram transformation. Theoretical Computer Science, 269:135–162,2001.

[34] Conal Elliott. An embedded modeling language approach to interactive3D and multimedia animation. IEEE Transactions on SoftwareEngineering, 25(3):291–308, May/June 1999. Special Section:Domain-Specific Languages (DSL).

[35] Conal Elliott, Sigbjørn Finne, and Oege de Moor. Compiling embeddedlanguages. Journal of Functional Programming, 2001. To appear.

[36] Conal Elliott and Paul Hudak. Functional reactive animation. InInternational Conference on Functional Programming, pages 263–273,1997.

[37] Levent Erkok and John Launchbury. Recursive monadic bindings. InInternational Conference on Functional Programming, pages 174–185,2000.

[38] Sigbjorn Finne and Simon Peyton Jones. Pictures: A simple structuredgraphics model. In Glasgow Functional Programming Workshop,Ullapool, July 1995.

266 The Fun of Programming

[39] Alexandre Frey, Gerard Berry, Patrice Bertin, Francois Bourdoncle, andJean Vuillemin. Jazz. Available fromhttp://www.exalead.com/jazz, 1998.

[40] Daniel P. Friedman, Mitchell Wand, and Christopher T. Haynes.Essentials of Programming Languages. MIT Press, second edition, 2001.

[41] Jeremy Gibbons. Algebras for Tree Algorithms. D. Phil. thesis,Programming Research Group, Oxford University, 1991. Available asTechnical Monograph PRG-94.

[42] Jeremy Gibbons. Deriving tidy drawings of trees. Journal of FunctionalProgramming, 6(3):535–562, 1996.

[43] Jeremy Gibbons. A pointless derivation of radixsort. Journal ofFunctional Programming, 9(3):339–346, 1999.

[44] Jeremy Gibbons. Calculating functional programs. In RolandBackhouse, Roy Crole, and Jeremy Gibbons, editors, Algebraic andCoalgebraic Methods in the Mathematics of Program Construction,volume 2297 of Lecture Notes in Computer Science, pages 148–203.Springer-Verlag, 2002.

[45] Jeremy Gibbons and Geraint Jones. The under-appreciated unfold. InInternational Conference on Functional Programming, pages 273–279,September 1998.

[46] Andrew Gill, John Launchbury, and Simon Peyton Jones. A short cut todeforestation. In Functional Programming Languages and ComputerArchitecture, pages 223–232, 1993.

[47] Carlos Gonzalıa. Analisis asintotico amortizado en lenguajesfuncionales perezosos. In Latin-American Conference on FunctionalProgramming, October 1997.

[48] Nicholas Halbwachs, Fabienne Lagnier, and Pascal Raymond.Synchronous observers and the verification of reactive systems. InAlgebraic Methodology and Software Technology, pages 83–96. SpringerVerlag, 1993.

[49] Nicolas Halbwachs, Paul Caspi, Pascal Raymond, and Daniel Pilaud. Thesynchronous dataflow programming language LUSTRE. Proceedings ofthe IEEE, 79(9):1305–1320, September 1991.

[50] Richard Hamlet. Random testing. In J. Marciniak, editor, Encyclopediaof Software Engineering, pages 970–978. Wiley, 1994.

[51] Michael Hanus, Herbert Kuchen, and Juan Jose Moreno-Navarro. Curry:A truly functional logic language. In ILPS’95 Workshop on Visions for theFuture of Logic Programming, pages 95–107, 1995.

[52] Peter Henderson. Functional geometry. In ACM Symposium on LISP andFunctional Programming, pages 179–187, 1982.

Bibliography 267

[53] Ralf Hinze. A new approach to generic functional programming. InThomas W. Reps, editor, Proceedings of the 27th Symposium onPrinciples of Programming Languages, pages 119–132, January 2000.

[54] Ralf Hinze. Functional Pearl: Formatting: a class act. Journal ofFunctional Programming, 2002. To appear.

[55] Thomas Ho and Sang-Bin Lee. Term Structure Movements and PricingInterest Rate Contingent Claims. Journal of Finance, 41:1011–1028,1986.

[56] Douglas R. Hofstadter. Godel, Escher, Bach: an Eternal Golden Braid.Basic Books, New York, 1979.

[57] Gerard J. Holzmann. Beyond Photography — the Digital Darkroom.Prentice-Hall, Englewood Cliffs, New Jersey, 1988.

[58] Paul Hudak. Building domain-specific embedded languages. ACMComputing Surveys, 28, December 1996.

[59] Paul Hudak. Haskore music tutorial. In Second International School onAdvanced Functional Programming, pages 38–68. Springer Verlag, LNCS1129, August 1996.

[60] Paul Hudak. Modular domain specific languages and tools. InP. Devanbu and J. Poulin, editors, Fifth International Conference onSoftware Reuse, pages 134–142. IEEE Computer Society Press, 1998.

[61] Paul Hudak. The Haskell School of Expression: Learning FunctionalProgramming through Multimedia. Cambridge University Press, NewYork, 2000.

[62] Paul Hudak and Jonathan Berger. A model of performance, interaction,and improvisation. In Proceedings of International Computer MusicConference. International Computer Music Association, 1995.

[63] Paul Hudak and Mark P. Jones. Haskell vs. Ada vs. C++ vs Awk vs . . . :An experiment in software prototyping productivity. Technical report,Yale, 1994.

[64] Paul Hudak, Tom Makucevich, Syam Gadde, and Bo Whong. Haskoremusic notation: An algebra of music. Journal of FunctionalProgramming, 6(3):465–483, May 1996.

[65] John Hughes. A novel representation of lists and its application to thefunction ‘reverse’. Information Processing Letters, 22:141–144, 1986.

[66] John Hughes. The design of a pretty-printer library. In Johan Jeuringand Erik Meijer, editors, Advanced Functional Programming, volume925 of LNCS. Springer, 1995.

[67] John Hughes. Generalising monads to arrows. Science of ComputerProgramming, 37:67–111, May 2000.

[68] MIDI 1.0 detailed specification: Document version 4.1.1, February 1990.

268 The Fun of Programming

[69] Michael A. Jackson. Principles of Program Design. Academic Press,1975.

[70] Patrik Jansson and Johan Jeuring. PolyP—a polytypic programminglanguage extension. In Conference Record 24th ACM SIGPLAN-SIGACTSymposium on Principles of Programming Languages (POPL’97), Paris,France, pages 470–482. ACM Press, January 1997.

[71] Steven Johnson. Synthesis of Digital Designs from Recursion Equations.The ACM Distinguished Dissertation Series, The MIT Press, 1984.

[72] Geraint Jones and Mary Sheeran. Collecting butterflies. TechnicalMonograph PRG-91, Oxford University Computing Laboratory,Programming Research Group, February 1991.

[73] Geraint Jones and Mary Sheeran. The study of butterflies. In GrahamBirtwistle, editor, Proc. 4th Banff Workshop on Higher Order. SpringerWorkshops in Computing, 1991.

[74] Geraint Jones and Mary Sheeran. Circuit design in Ruby. InJ. Staunstrup, editor, Formal Methods for VLSI Design. North Holland,1992.

[75] Geraint Jones and Mary Sheeran. Designing arithmetic circuits byrefinement in Ruby. In R. Bird, C. Morgan, and J. Woodcock, editors,Mathematics of Program Construction, volume 669 of Lecture Notes inComputer Science, pages 208–232. Springer, 1993.

[76] Geraint Jones and Mary Sheeran. Designing Arithmetic Circuits byRefinement in Ruby. Science of Computer Programming, 22(1-2), 1994.

[77] Simon Peyton Jones. Haskell pretty-printer library.http://www.haskell.org/libraries/#prettyprinting, 1997.

[78] Andre Joyal, Ross Street, and Dominic Verity. Traced monoidalcategories. Mathematical Proceedings of the Cambridge PhilosophicalSociety, 119(3):447–468, 1996.

[79] Jerzy Karczmarczuk. Functional approach to texture generation. InShriram Krishnamurthi and C. R. Ramakrishnan, editors, PracticalAspects of Declarative Languages, volume 2257 of Lecture Notes inComputer Science, pages 225–242. Springer, 2002.

[80] Donald E. Knuth. Searching and Sorting, volume 3 of The Art ofComputer Programming. Addison-Wesley, 1973.

[81] Richard E. Ladner and Michael J. Fischer. Parallel prefix computation.Journal of the ACM, 27:831–838, 1980.

[82] D. Lahti. Applications of a functional programming language tohardware synthesis. Master’s thesis, UCLA, 1980.

[83] Ralf Lammel and Simon Peyton Jones. Scrap your boilerplate: apractical approach to generic programming. Available fromhttp://research.microsoft.com/˜simonpj/papers/hmap/, 2002.

Bibliography 269

[84] John Launchbury, Jeff Lewis, and Byron Cook. On embedding amicroarchitecture design language within Haskell. In InternationalConference on Functional Programming. ACM, 1999.

[85] John Launchbury and Tim Sheard. Warm fusion: Deriving build-catasfrom recursive definitions. In Functional Programming Languages andComputer Architecture, pages 314–323. ACM Press, 1995.

[86] Daan Leijen and Erik Meijer. Domain-specific embedded compilers. InProceedings of the 2nd Conference on Domain-Specific Languages,pages 109–122, Berkeley, CA, October 1999. USENIX Association.

[87] Peter Lucas and Stephen N. Zilles. Graphics in an applicative context.Technical report, IBM Almaden Research Center, 650 Harry Road, SanJose, CA 95120-6099, July 8 1987.

[88] Wayne Luk. Systematic serialisation of array-based architectures.Integration, the VLSI Journal, 14(3), February 1993.

[89] Wayne Luk, Geraint Jones, and Mary Sheeran. Computer-based tools forregular array design. In J McCanny, J McWhirter, and E Swartzlander,editors, Systolic Array Processors, pages 589–598. Prentice-HallInternational, 1989.

[90] John Maeda. Design By Numbers. MIT Press, May 1999.

[91] John Matthews and John Launchbury. Elementary microarchitecturealgebra. In Nicolas Halbwachs and Doron Peled, editors, ComputerAided Verification, volume 1633 of Lecture Notes in Computer Science,pages 333–360. Springer, 1999.

[92] Lambert Meertens. Paramorphisms. Formal Aspects of Computing,4(5):413–424, 1992.

[93] Erik Meijer, Maarten Fokkinga, and Ross Paterson. Functionalprogramming with bananas, lenses, envelopes and barbed wire. In JohnHughes, editor, Functional Programming Languages and ComputerArchitecture, volume 523 of Lecture Notes in Computer Science, pages124–144. Springer-Verlag, 1991.

[94] Erik Meijer and Graham Hutton. Bananas in space: Extending fold andunfold to exponential types. In Functional Programming Languagesand Computer Architecture, 1995.

[95] Jayadev Misra. Powerlist: A structure for parallel recursion. ACMTransactions on Programming Languages and Systems,16(6):1737–1767, November 1994.

[96] Marek Musiela and Marek Rutkowski. Martingale Methods in FinancialModelling. Springer, 1997.

[97] John O’Donnell. Hydra: Hardware description in a functional languageusing recursion equations and higher order combining forms. In G. J.

270 The Fun of Programming

Milne, editor, The Fusion of Hardware Design and Verification, pages363–382. North-Holland, 1988.

[98] John O’Donnell. From transistors to computer architecture: Teachingfunctional circuit specification in Hydra. In Functional ProgrammingLanguages in Education, volume 1022 of Lecture Notes in ComputerScience, pages 195–214. Springer-Verlag, 1996.

[99] Chris Okasaki. Amortization, lazy evaluation, and persistence: Listswith catenation via lazy linking. In IEEE Symposium on Foundations ofComputer Science, pages 646–654, October 1995.

[100] Chris Okasaki. Simple and efficient purely functional queues anddeques. Journal of Functional Programming, 5(4):583–592, 1995.

[101] Chris Okasaki. The role of lazy evaluation in amortized data structures.In ACM SIGPLAN International Conference on Functional Programming,pages 62–72, May 1996.

[102] Chris Okasaki. Purely Functional Data Structures. Cambridge UniversityPress, 1998.

[103] Yoshiyuki Onoue, Zhenjiang Hu, Hideya Iwasaki, and Masato Takeichi.A calculational fusion system HYLO. In Richard S. Bird and LambertMeertens, editors, Algorithmic Languages and Calculi, pages 76–106.Chapman and Hall, 1997.

[104] Derek Oppen. Pretty-printing. ACM Transactions on ProgrammingLanguages and Systems, 2(4):465–483, 1980.

[105] Dorab Patel, Martine D. F. Schlag, and Milos D. Ercegovac. νFP: Anenvironment for the multi-level specification, analysis, and synthesis ofhardware algorithms. In Functional Programming Languages andComputer Architecture, volume 201 of Lecture Notes in ComputerScience, pages 238–255. Springer-Verlag, 1985.

[106] Ross Paterson. A new notation for arrows. In International Conferenceon Functional Programming, pages 229–240. ACM Press, September2001.

[107] John Power and Edmund Robinson. Premonoidal categories andnotions of computation. Mathematical Structures in Computer Science,7(5):453–468, October 1997.

[108] Vaughan Pratt. Shellsort and Sorting Networks. PhD thesis, StanfordUniversity, 1971. Also Garland, New York, 1979.

[109] Daniel Revuz and Marc Yor. Continuous Martingales and BrownianMotion. Springer, 1991.

[110] Curtis Roads, editor. The Music Machine (Selected Readings fromComputer Music Journal). MIT Press, Cambridge, MA, 1989.

[111] Edward Rothstein. Emblems of Mind: The Inner Life of Music andMathematics. Times Books, New York, 1995.

Bibliography 271

[112] Robert Sedgewick. Analysis of Shellsort and related algorithms. InEuropean Symposium on Programming, 1996.

[113] Eleanor Selfridge-Field, editor. Beyond MIDI (The Handbook of MusicalCodes). MIT Press, Cambridge, MA, 1997.

[114] Silvija Seres. The Algebra of Logic Programming. D.Phil., ProgrammingResearch Group, University of Oxford, 2001.

[115] Mary Sheeran. µFP, an algebraic VLSI design language. D.Phil.,Programming Research Group, Oxford University, 1983.

[116] Mary Sheeran. Puzzling permutations. In P. Trinder, editor, GlasgowFunctional Programming Workshop, 1996.

[117] Donald L. Shell. A high-speed sorting procedure. Communications ofthe ACM, 2(7):30–32, 1959.

[118] Karl Sims. Artificial evolution for computer graphics. ACM ComputerGraphics, 25(4):319–328, July 1991.

[119] Ganesh Sittampalam and Oege de Moor. Higher-order pattern matchingfor automatically applying fusion transformations. In O. Danvy andA. Filinski, editors, Second Symposium on Programs as Data Objects,volume 2053 of Lecture Notes in Computer Science, pages 198–217.Springer-Verlag, 2001.

[120] Daniel D. K. Sleator and Robert E. Tarjan. Self-adjusting heaps. SIAMJournal on Computing, 15(1):52–69, February 1986.

[121] Alvy Ray Smith. Image compositing fundamentals. Technical ReportTechnical Memo #4, Microsoft, July 1995.http://www.alvyray.com/Memos.

[122] Zoltan Somogyi, Fergus Henderson, and Thomas Conway. Mercury: Anefficient purely declarative logic programming language. In Proceedingsof the Australian Computer Science Conference, pages 499–512,Glenelg, Australia, 1995.

[123] J. Michael Spivey. Unification: A case-study in data refinement,. FormalAspects of Computing, 7(2):158–168, 1995.

[124] J. Michael Spivey. Combinators for breadth-first search. Journal ofFunctional Programming, 10(4):397–408, 2000.

[125] Leon Sterling and Ehud Y. Shapiro. The Art of Prolog. MIT Press, secondedition, 1994.

[126] S. Doaitse Swierstra and Luc Duponcheel. Deterministic,error-correcting combinator parsers. In John Launchbury, Erik Meijer,and Tim Sheard, editors, Advanced Functional Programming, volume1129 of Lecture Notes in Computer Science, pages 184–207. Springer,1996.

272 The Fun of Programming

[127] Robert E. Tarjan. Amortized computational complexity. SIAM Journalon Algebraic and Discrete Methods, 6(2):306–318, April 1985.

[128] Herve Touati and Mark Shand. PamDC: a C++ library for the simulationand generation of Xilinx FPGA designs. Available fromhttp://research.compaq.com/SRC/pametta/PamDC.pdf, 1999.

[129] David A. Turner. An overview of Miranda. SIGPLAN Notices,21(12):158–166, 1986.

[130] Arie van Deursen and Paul Klint. Little languages: little maintenance?Journal of Software Maintenance, 10:75–92, 1998.

[131] Arie van Deursen, Paul Klint, and Joost Visser. Domain-specificlanguages: an annotated bibliography. Technical report, Centrum voorWiskunde en Informatica, Amsterdam, 2000.

[132] Varmo Vene. Categorical Programming with Inductive and CoinductiveTypes. PhD thesis, University of Tartu, 2000.

[133] Varmo Vene and Tarmo Uustalu. Functional programming withapomorphisms (corecursion). Proceedings of the Estonian Academy ofSciences: Physics, Mathematics, 47(3):147–161, 1998. 9th NordicWorkshop on Programming Theory.

[134] Jean Vuillemin. On circuits and numbers. IEEE Transactions onComputers, 43:8:868–879, 1994.

[135] Jean Vuillemin, Patrice Bertin, Didier Roncin, Mark Shand, Herve Touati,and Philippe Boucard. Programmable Active Memories: the Coming ofAge. IEEE Trans. on VLSI, 4(1), March 1996.

[136] William W. Wadge and Edward A. Ashcroft. Lucid, the DataflowProgramming Language. Academic Press, 1985.

[137] Philip Wadler. Deforestation: Transforming programs to eliminatetrees. Theoretical Computer Science, 73:231–248, 1990.

[138] Philip L. Wadler. How to replace failure by a list of successes. In J.-P.Jouannaud, editor, Functional Programming Languages and ComputerArchitecture, volume 201 of Lecture Notes in Computer Science, pages113–128. Springer-Verlag, 1985.

[139] Paul Willmot, Jeff N. Dewynne, and Sam D. Howison. Option Pricing:Mathematical Models and Computation. Oxford Financial Press, 1993.

[140] Stephen N. Zilles, Peter Lucas, T.M. Linden, Jeff B. Lotspiech, and A.R.Harbury. The Escher document imaging model. In ACM Conference onDocument Processing Systems, pages 159–168, December 5–9 1988.