%-*- mode: Latex; abbrev-mode: true; auto-fill-function: do-auto-fill -*- %include lhs2TeX.fmt %include myFormat.fmt \out{ \begin{code} -- This code was automatically generated by lhs2tex --code, from the file -- HSoM/Music.lhs. (See HSoM/MakeCode.bat.) \end{code} } %% ToDo: %% Introduce "play" and the Performable class soon after introducing %% the Music type. %% %% Also reformat data decls so that the constructors line up vertically. \chapter{Simple Music} \label{ch:music} \out{ \begin{code} module Euterpea.Music.Note.Music where infixr 5 :+:, :=: \end{code} } \begin{spec} module Euterpea.Music.Note.Music where infixr 5 !:+:, :=: \end{spec} The previous chapters introduced some of the fundamental ideas of functional programming in Haskell. Also introduced were several of Euterpea's functions and operators, such as |note|, |rest|, |(:+:)|, |(:=:)|, and |trans|. This chapter will reveal the actual definitions of these functions and operators, thus exposing Euterpea's underlying structure and overall design at the note level. In addition, a number of other musical ideas will be developed, and in the process more Haskell features will be introduced as well. \section{Preliminaries} Sometimes it is convenient to use a built-in Haskell data type to directly represent some concept of interest. For example, we may wish to use |Int| to represent \emph{octaves}, where by convention octave 4 corresponds to the octave containing middle C on the piano. We can express this in Haskell using a \emph{type synonym}: \begin{code} type Octave = Int \end{code} A type synonym does not create a new data type---it just gives a new name to an existing type. Type synonyms can be defined not just for atomic types such as |Int|, but also for structured types such as pairs. For example, as discussed in the last chapter, in music theory a pitch is defined as a pair, consisting of a \emph{pitch class} and an \emph{octave}. Assuming the existence of a data type called |PitchClass| (which we will return to shortly), we can write the following type synonym: \begin{code} type Pitch = (PitchClass, Octave) \end{code} For example, concert A (i.e.\ A440) corresponds to the pitch |(A,4) :: Pitch|, and the lowest and highest notes on a piano correspond to |(A,0) :: Pitch| and |(C,8) :: Pitch|, respectively. %% For convenience we could define a Haskell variable with that value as %% follows: %% \begin{spec} %% a4 :: Pitch %% a4 = (A,4) -- concert A %% \end{spec} Another important musical concept is \emph{duration}. Rather than use either integers or floating-point numbers, Euterpea uses \emph{rational} numbers to denote duration: \begin{code} type Dur = Rational \end{code} |Rational| is the data type of rational numbers expressed as ratios of |Integer|s in Haskell. The choice of |Rational| is somewhat subjective, but is justified by three observations: (1) many durations are expressed as ratios in music theory (5:4 rhythm, quarter notes, dotted notes, and so on), (2) |Rational| numbers are exact (unlike floating point numbers), which is important in many computer music applications, and (3) irrational durations are rarely needed. %% (Alternatively, we could have used |Ratio Int|.) Rational numbers in Haskell are printed by GHC in the form |n%d|, where |n| is the numerator, and |d| is the denominator. Even a whole number, say the number 42, will print as |42%1| if it is a |Rational| number. To create a |Rational| number in a program, however, once it is given the proper type, we can use the normal division operator, as in the following definition of a quarter note: \begin{spec} qn :: Dur qn = 1/4 -- quarter note \end{spec} So far so good. But what about |PitchClass|? We might try to use integers to represent pitch classes as well, but this is not very elegant---ideally we would like to write something that looks more like the conventional pitch class names C, C$\sharp$, D$\flat$, D, etc.\ The solution is to use an \emph{algebraic data type} in Haskell: \begin{spec} data PitchClass = Cff | Cf | C | Dff | Cs | Df | Css | D | Eff | Ds | Ef | Fff | Dss | E | Ff | Es | F | Gff | Ess | Fs | Gf | Fss | G | Aff | Gs | Af | Gss | A | Bff | As | Bf | Ass | B | Bs | Bss \end{spec} \out{ \begin{code} data PitchClass = Cff | Cf | C | Dff | Cs | Df | Css | D | Eff | Ds | Ef | Fff | Dss | E | Ff | Es | F | Gff | Ess | Fs | Gf | Fss | G | Aff | Gs | Af | Gss | A | Bff | As | Bf | Ass | B | Bs | Bss deriving (Show, Eq, Ord, Read, Enum, Bounded) \end{code} } \syn{All of the names to the right of the equal sign in a |data| declaration are called \emph{constructors}, and must be capitalized. In this way they are syntactically distinguished from ordinary values. This distinction is useful since only constructors can be used in the pattern matching that is part of a function definition, as will be described shortly. %% The last line, |deriving (Eq,Ord,Show,Read,Enum)|, tells Haskell to %% make |PitchClass| an instance of these five type classes, and to %% automatically derive definitions of the operators associated with %% those type classes. (Recall the discussion of qualified types and %% type classes in Section \ref{sec:qualified-types}.) } %% However, we will not discuss type classes in detail until Chapter %% \ref{ch:qualified-types}. For now, here are just two examples of the %% capabilities this provides: %% \begin{enumerate} %% \item The |Eq| class has an operator |(==)| that allows us to test %% for the equality of two pitch classes. For example, |Cf == Gs| %% returns |False|. %% \item The |Ord| class has an operator |(>)| that allows us to %% compare values acording to the order that they appear in the data %% type declaration. For example, |D > C| returns |True|. %% \end{enumerate} The |PitchClass| data type declaration essentially enumerates 35 pitch class names (five for each of the note names A through G). Note that both double-sharps and double-flats are included, resulting in many enharmonics (i.e., two notes that ``sound the same,'' such as G$\sharp$ and A$\flat$). (The order of the pitch classes may seem a bit odd, but the idea is that if a pitch class |pc1| is to the left of a pitch class |pc2|, then |pc1|'s pitch is ``lower than'' that of |pc2|. This idea will be formalized and exploited in Chapter~\ref{sec:qualified-types}.) %% which may be important in certain applications. Keep in mind that |PitchClass| is a completely new, user-defined data type that is not equal to any other. This is what distinguishes a |data| declaration from a |type| declaration. As another example of the use of a |data| declaration to define a simple enumerated type, Haskell's Boolean data type, called |Bool|, is predefined in Haskell simply as: \begin{spec} data Bool = False | True \end{spec} \section{Notes, Music, and Polymorphism} \label{sec:music} We can of course define other data types for other purposes. For example, we will want to define the notion of a \emph{note} and a \emph{rest}. Both of these can be thought of as ``primitive'' musical values, and thus as a first attempt we might write: \begin{spec} data Primitive = Note Dur Pitch | Rest Dur \end{spec} %% deriving (Show, Eq, Ord) Analogously to our previous data type declarations, the above declaration says that a |Primitive| is either a |Note| or a |Rest|. However, it is different in that the constructors |Note| and |Rest| take arguments, like functions do. In the case of |Note|, it takes two arguments, whose types are |Dur| and |Pitch|, respectively, whereas |Rest| takes one argument, a value of type |Dur|. In other words, the types of |Note| and |Rest| are: \begin{spec} Note :: Dur -> Pitch -> Primitive Rest :: Dur -> Primitive \end{spec} For example, |Note qn a440| is concert A played as a quarter note, and |Rest 1| is a whole-note rest. This definition is not completely satisfactory, however, because we may wish to attach other information to a note, such as its loudness, or some other annotation or articulation. Furthermore, the pitch itself may actually be a percussive sound, having no true pitch at all. To resolve this, Euterpea uses an important concept in Haskell, namely \emph{polymorphism}---the ability to parameterize, or abstract, over types (\emph{poly} means \emph{many} and \emph{morphism} refers to the structure, or \emph{form}, of objects). |Primitive| can be redefined as a \emph{polymorphic data type} as follows. Instead of fixing the type of the pitch of a note, it is left unspecified through the use of a \emph{type variable}: \begin{spec} data Primitive a = Note Dur a | Rest Dur \end{spec} \out{ \begin{code} data Primitive a = Note Dur a | Rest Dur deriving (Show, Eq, Ord) \end{code} } Note that the type variable |a| is used as an argument to |Primitive|, and then used in the body of the declaration---just like a variable in a function. This version of |Primitive| is more general than the previous version---indeed, note that |Primitive Pitch| is the same as (or, technically, is \emph{isomorphic to}) the previous version of |Primitive|. But additionally, |Primitive| is now more flexible than the previous version, since, for example, we can add loudness by pairing loudness with pitch, as in |Primitive (Pitch, Loudness)|. Other concrete instances of this idea will be introduced later. \syn{Type variables such as |a| above must begin with a lower-case letter, to distinguish them from concrete types such as |Dur| or |Pitch|. Since |Primitive| takes an argument, it is called a \emph{type constructor}, wherease |Note| and |Rest| are just called constructors (or value constructors).} Another way to interpret this data declaration is to say that for any type |a|, this declaration declares the types of its constructors to be: \begin{spec} Note :: Dur -> a -> Primitive a Rest :: Dur -> Primitive a \end{spec} Even though |Note| and |Rest| are called data constructors, they are still functions, and they have a type. Since they both have type variables in their type signatures, they are examples of \emph{polymorphic functions}. It is helpful to think of polymorphism as applying the abstraction principle at the type level---indeed it is often called \emph{type abstraction}. Many more examples of both polymorphic functions and polymorphic data types will be explored in detail in Chapter~\ref{ch:poly}. So far Euterpea's primitive notes and rests have been introduced---but how do we combine many notes and rests into a larger composition? To achieve this, Euterpea defines another polymorphic data type, perhaps the most important data type used in this textbook, which defines the fundamental structure of a note-level musical entity: \begin{spec} data Music a = Prim (Primitive a) -- primitive value | Music a :+: Music a -- sequential composition | Music a :=: Music a -- parallel composition | Modify Control (Music a) -- modifier \end{spec} \out{ \begin{code} data Music a = Prim (Primitive a) -- primitive value | Music a :+: Music a -- sequential composition | Music a :=: Music a -- parallel composition | Modify Control (Music a) -- modifier deriving (Show, Eq, Ord) \end{code} } Following the reasoning above, the types of these constructors are: \begin{spec} Prim :: Primitive a -> Music a (:+:) :: Music a -> Music a -> Music a (:=:) :: Music a -> Music a -> Music a Modify :: Control -> Music a -> Music a \end{spec} These four constructors then are also polymorphic functions. %% | Music a :=/ Music a -- parallel composition %% (short) %% The first line here looks odd: the name |Primitive| appears %% twice. The first occurence, however, is the name of a new %% \emph{constructor} in the |Music| data type, whereas the second is %% the name of the existing \emph{data type} defined above. Haskell %% allows using the same name to define a constructor and a data type, %% since they can never be confused: the context in which they are used %% will always be sufficient to distinguish them. \syn{ \index{infix constructors} Note the use of the \emph{infix constructors} |(:+:)| and |(:=:)|. Infix constructors are just like infix operators in Haskell, but they must begin with a colon. This syntactic distinction makes it clear when pattern matching is intended, and is analogous to the distinction between ordinary names (which must begin with a lower-case character) and constructor names (which must begin with an upper-case character). The observant reader will also recall that at the very beginning of this chapter---corresponding to the module containing all the code in this chapter---the following line appeared: \begin{spec} infixr 5 !:+:, :=: \end{spec} This is called a \emph{fixity declaration}. The ``|r|'' after the word ``|infix|'' means that the specified operators---in this case |(:+:)| and |(:=:)|---are to have \emph{right} associativity, and the ``5'' specifies their \emph{precedence level} (these operators will bind more tightly than an operator with a lower precedence). } \newpage The |Music| data type declaration essentially says that a value of type |Music a| has one of four possible forms: \begin{itemize} \item |Prim p|, where |p| is a primitive value of type |Primitive a|, for some type |a|. For example: \begin{spec} a440m :: Music Pitch a440m = Prim (Note qn a440) \end{spec} is the musical value corresponding to a quarter-note rendition of concert A. \item |m1 :+: m2| is the \emph{sequential composition} of |m1| and |m2|; i.e.\ |m1| and |m2| are played in sequence. \item |m1 :=: m2| is the \emph{parallel composition} of |m1| and |m2|; i.e.\ |m1| and |m2| are played simultaneously. The duration of the result is the duration of the longer of |m1| and |m2|. (Recall that these last two operators were introduced in the last chapter. You can see now that they are actually constructors of an algebraic data type.) %% \item |m1 :=/ m2| is also a parallel composition of |m1| and |m2|, but %% its duration is that of the shorter of |m1| and |m2|. \item |Modify cntrl m| is an ``annotated'' version of |m| in which the control parameter |cntrl| specifies some way in which |m| is to be modified. \end{itemize} \index{type!recursive} \syn{Note that |Music a| is defined in terms of |Music a|, and thus the data type is said to be \emph{recursive} (analogous to a recursive function). It is also often called an \emph{inductive} data type, since it is, in essence, an inductive definition of an infinite number of values, each of which can be arbitrarily complex.} It is convenient to represent these musical ideas as a recursive datatype because it allows us to not only \emph{construct} musical values, but also take them apart, analyze their structure, print them in a structure-preserving way, transform them, interpret them for performance purposes, and so on. Many examples of these kinds of processes will be seen in this textbook. The |Control| data type is used by the |Modify| constructor to annotate a |Music| value with a \emph{tempo change}, a \emph{transposition}, a \emph{phrase attribute}, a \emph{player name}, or an \emph{instrument}. This data type is unimportant at the moment, but for completeness here is its full definition: \pagebreak \begin{spec} data Control = Tempo Rational -- scale the tempo | Transpose AbsPitch -- transposition | Instrument InstrumentName -- instrument label | Phrase [PhraseAttribute] -- phrase attributes | Player PlayerName -- player label | KeySig PitchClass Mode -- key signature and mode type PlayerName = String data Mode = Major | Minor \end{spec} \out{ \begin{code} data Control = Tempo Rational -- scale the tempo | Transpose AbsPitch -- transposition | Instrument InstrumentName -- instrument label | Phrase [PhraseAttribute] -- phrase attributes | Player PlayerName -- player label | KeySig PitchClass Mode -- key signature and mode deriving (Show, Eq, Ord) type PlayerName = String data Mode = Major | Minor deriving (Show, Eq, Ord) \end{code} } |AbsPitch| (``absolute pitch,'' to be defined in Section \ref{sec:abspitch}) is just a type synonym for |Int|. Instrument names are borrowed from the General MIDI standard \cite{MIDI,General-MIDI}, and are captured as an algebraic data type in Figure \ref{fig:instrument-names}. Phrase attributes and the concept of a ``player'' are closely related, but a full explanation is deferred until Chapter \ref{ch:performance}. The |KeySig| constructor attaches a key signature to a |Music| value, and is different conceptually from transposition. %% are defined in Figure \ref{fig:phase-attributes}. The \begin{figure}{\small \indexhs{InstrumentName} \begin{code} data InstrumentName = AcousticGrandPiano | BrightAcousticPiano | ElectricGrandPiano | HonkyTonkPiano | RhodesPiano | ChorusedPiano | Harpsichord | Clavinet | Celesta | Glockenspiel | MusicBox | Vibraphone | Marimba | Xylophone | TubularBells | Dulcimer | HammondOrgan | PercussiveOrgan | RockOrgan | ChurchOrgan | ReedOrgan | Accordion | Harmonica | TangoAccordion | AcousticGuitarNylon | AcousticGuitarSteel | ElectricGuitarJazz | ElectricGuitarClean | ElectricGuitarMuted | OverdrivenGuitar | DistortionGuitar | GuitarHarmonics | AcousticBass | ElectricBassFingered | ElectricBassPicked | FretlessBass | SlapBass1 | SlapBass2 | SynthBass1 | SynthBass2 | Violin | Viola | Cello | Contrabass | TremoloStrings | PizzicatoStrings | OrchestralHarp | Timpani | StringEnsemble1 | StringEnsemble2 | SynthStrings1 | SynthStrings2 | ChoirAahs | VoiceOohs | SynthVoice | OrchestraHit | Trumpet | Trombone | Tuba | MutedTrumpet | FrenchHorn | BrassSection | SynthBrass1 | SynthBrass2 | SopranoSax | AltoSax | TenorSax | BaritoneSax | Oboe | Bassoon | EnglishHorn | Clarinet | Piccolo | Flute | Recorder | PanFlute | BlownBottle | Shakuhachi | Whistle | Ocarina | Lead1Square | Lead2Sawtooth | Lead3Calliope | Lead4Chiff | Lead5Charang | Lead6Voice | Lead7Fifths | Lead8BassLead | Pad1NewAge | Pad2Warm | Pad3Polysynth | Pad4Choir | Pad5Bowed | Pad6Metallic | Pad7Halo | Pad8Sweep | FX1Train | FX2Soundtrack | FX3Crystal | FX4Atmosphere | FX5Brightness | FX6Goblins | FX7Echoes | FX8SciFi | Sitar | Banjo | Shamisen | Koto | Kalimba | Bagpipe | Fiddle | Shanai | TinkleBell | Agogo | SteelDrums | Woodblock | TaikoDrum | MelodicDrum | SynthDrum | ReverseCymbal | GuitarFretNoise | BreathNoise | Seashore | BirdTweet | TelephoneRing | Helicopter | Applause | Gunshot | Percussion | Custom String \end{code} } \out{ \begin{code} deriving (Show, Eq, Ord) \end{code} } \caption{General MIDI Instrument Names} \label{fig:instrument-names} \end{figure} \out{ \begin{figure}{\small \begin{code} data PhraseAttribute = Dyn Dynamic | Tmp Tempo | Art Articulation | Orn Ornament deriving (Show, Eq, Ord) data Dynamic = Accent Rational | Crescendo Rational | Diminuendo Rational | StdLoudness StdLoudness | Loudness Rational deriving (Show, Eq, Ord) data StdLoudness = PPP | PP | P | MP | SF | MF | NF | FF | FFF deriving (Show, Eq, Ord, Enum) data Tempo = Ritardando Rational | Accelerando Rational deriving (Show, Eq, Ord) data Articulation = Staccato Rational | Legato Rational | Slurred Rational | Tenuto | Marcato | Pedal | Fermata | FermataDown | Breath | DownBow | UpBow | Harmonic | Pizzicato | LeftPizz | BartokPizz | Swell | Wedge | Thumb | Stopped deriving (Show, Eq, Ord) data Ornament = Trill | Mordent | InvMordent | DoubleMordent | Turn | TrilledTurn | ShortTrill | Arpeggio | ArpeggioUp | ArpeggioDown | Instruction String | Head NoteHead | DiatonicTrans Int deriving (Show, Eq, Ord) data NoteHead = DiamondHead | SquareHead | XHead | TriangleHead | TremoloHead | SlashHead | ArtHarmonic | NoHead deriving (Show, Eq, Ord) \end{code}} \caption{Phrase Attributes} \label{fig:phase-attributes} \end{figure} } \section{Convenient Auxiliary Functions} \label{auxiliaries} %% In anticipation of the need to translate between different number %% types, we define the following coercion function: %% \begin{code} %% rtof :: Ratio Int -> Float %% rtof r = float (numerator r) / float (denominator r) %% float :: Int -> Float %% float = fromInteger . toInteger %% \end{code} For convenience, and in anticipation of their frequent use, a number of functions are defined in Euterpea to make it easier to write certain kinds of musical values. For starters: \begin{code} note :: Dur -> a -> Music a note d p = Prim (Note d p) rest :: Dur -> Music a rest d = Prim (Rest d) tempo :: Dur -> Music a -> Music a tempo r m = Modify (Tempo r) m transpose :: AbsPitch -> Music a -> Music a transpose i m = Modify (Transpose i) m instrument :: InstrumentName -> Music a -> Music a instrument i m = Modify (Instrument i) m phrase :: [PhraseAttribute] -> Music a -> Music a phrase pa m = Modify (Phrase pa) m player :: PlayerName -> Music a -> Music a player pn m = Modify (Player pn) m keysig :: PitchClass -> Mode -> Music a -> Music a keysig pc mo m = Modify (KeySig pc mo) m \end{code} Note that each of these functions is polymorphic, a trait inherited from the data types that it uses. Also recall that the first two of these functions were used in an example in the last chapter. We can also create simple names for familiar notes, durations, and rests, as shown in Figures \ref{fig:note-names} and \ref{fig:rest-names}. Despite the large number of them, these names are sufficiently ``unusual'' that name clashes are unlikely. \syn{Figures \ref{fig:note-names} and \ref{fig:rest-names} demonstrate that at the top level of a program, more than one equation can be placed on one line, as long as they are separated by a semicolon. This allows us to save vertical space on the page, and is useful whenever each line is relatively short. The semicolon is not needed at the end of a single equation, or at the end of the last equation on a line. This convenient feature is part of Haskell's \emph{layout} rule, and will be explained in more detail later. More than one equation can also be placed on one line in a |let| expression, as demonstrated below: \begin{spec} let x = 1; y = 2 in x + y \end{spec} } %% In fact this same rule may be used to override layout in any context, %% how the layout rule can be overridden through the use of a semicolon. \begin{figure} \cbox{\small \begin{code} cff,cf,c,cs,css,dff,df,d,ds,dss,eff,ef,e,es,ess,fff,ff,f, fs,fss,gff,gf,g,gs,gss,aff,af,a,as,ass,bff,bf,b,bs,bss :: Octave -> Dur -> Music Pitch cff o d = note d (Cff, o); cf o d = note d (Cf, o) c o d = note d (C, o); cs o d = note d (Cs, o) css o d = note d (Css, o); dff o d = note d (Dff, o) df o d = note d (Df, o); d o d = note d (D, o) ds o d = note d (Ds, o); dss o d = note d (Dss, o) eff o d = note d (Eff, o); ef o d = note d (Ef, o) e o d = note d (E, o); es o d = note d (Es, o) ess o d = note d (Ess, o); fff o d = note d (Fff, o) ff o d = note d (Ff, o); f o d = note d (F, o) fs o d = note d (Fs, o); fss o d = note d (Fss, o) gff o d = note d (Gff, o); gf o d = note d (Gf, o) g o d = note d (G, o); gs o d = note d (Gs, o) gss o d = note d (Gss, o); aff o d = note d (Aff, o) af o d = note d (Af, o); a o d = note d (A, o) as o d = note d (As, o); ass o d = note d (Ass, o) bff o d = note d (Bff, o); bf o d = note d (Bf, o) b o d = note d (B, o); bs o d = note d (Bs, o) bss o d = note d (Bss, o) \end{code}} \caption{Convenient Note Names} \label{fig:note-names} \end{figure} \begin{figure} \cbox{\small \begin{code} bn, wn, hn, qn, en, sn, tn, sfn, dwn, dhn, dqn, den, dsn, dtn, ddhn, ddqn, dden :: Dur bnr, wnr, hnr, qnr, enr, snr, tnr, sfnr, dwnr, dhnr, dqnr, denr, dsnr, dtnr, ddhnr, ddqnr, ddenr :: Music Pitch bn = 2; bnr = rest bn -- brevis rest wn = 1; wnr = rest wn -- whole note rest hn = 1/2; hnr = rest hn -- half note rest qn = 1/4; qnr = rest qn -- quarter note rest en = 1/8; enr = rest en -- eighth note rest sn = 1/16; snr = rest sn -- sixteenth note rest tn = 1/32; tnr = rest tn -- thirty-second note rest sfn = 1/64; sfnr = rest sfn -- sixty-fourth note rest dwn = 3/2; dwnr = rest dwn -- dotted whole note rest dhn = 3/4; dhnr = rest dhn -- dotted half note rest dqn = 3/8; dqnr = rest dqn -- dotted quarter note rest den = 3/16; denr = rest den -- dotted eighth note rest dsn = 3/32; dsnr = rest dsn -- dotted sixteenth note rest dtn = 3/64; dtnr = rest dtn -- dotted thirty-second note rest ddhn = 7/8; ddhnr = rest ddhn -- double-dotted half note rest ddqn = 7/16; ddqnr = rest ddqn -- double-dotted quarter note rest dden = 7/32; ddenr = rest dden -- double-dotted eighth note rest \end{code}} \caption{Convenient Duration and Rest Names} \label{fig:rest-names} \end{figure} \subsection{A Simple Example} As a simple example, suppose we wish to generate a ii-V-I chord progression in a particular major key. In music theory, such a chord progression begins with a minor chord on the second degree of the major scale, followed by a major chord on the fifth degree, and ending in a major chord on the first degree. We can write this in Euterpea, using triads in the key of C major, as follows: \begin{code} t251 :: Music Pitch t251 = let dMinor = d 4 wn :=: f 4 wn :=: a 4 wn gMajor = g 4 wn :=: b 4 wn :=: d 5 wn cMajor = c 4 bn :=: e 4 bn :=: g 4 bn in dMinor :+: gMajor :+: cMajor \end{code} \syn{Note that more than one equation is allowed in a \indexwdkw{let} expression, just like at the top level of a program. The first characters of each equation, however, must line up vertically, and if an equation takes more than one line then the subsequent lines must be to the right of the first characters. For example, this is legal: \begin{spec} let a = aLongName + anEvenLongerName b = 56 in ... \end{spec} but neither of these are: \begin{spec} let a = aLongName + anEvenLongerName b = 56 in ... let a = aLongName + anEvenLongerName b = 56 in ... \end{spec} (The second line in the first example is too far to the left, as is the third line in the second example.) Although this rule, called the {\em \indexwd{layout rule}}, may seem a bit {\em ad hoc}, it avoids having to use special syntax (such as a semicolon) to denote the end of one equation and the beginning of the next, thus enhancing readability. In practice, use of layout is rather intuitive. Just remember two things: First, the first character following |let| (and a few other keywords that will be introduced later) is what determines the starting column for the set of equations being written. Thus we can begin the equations on the same line as the keyword, the next line, or whatever. Second, be sure that the starting column is further to the right than the starting column associated with any immediately surrounding |let| clause (otherwise it would be ambiguous). The ``termination'' of an equation happens when something appears at or to the left of the starting column associated with that equation.} We can play this simple example using Euterpea's |play| function by simply typing: \begin{spec} play t251 \end{spec} at the GHCi command line. Default instruments and tempos are used to convert |t251| into MIDI and then play the result through your computer's standard sound card. \syn{It is important when using |play| that the type of its argument is made clear. In the case of |t251|, it is clear from the type signature in its definition. But for reasons to be explained in Chapter~\ref{ch:qualified-types}, if we write even something very simple such as |play (note qn (C,4))|, Haskell cannot infer exactly what kind of number 4 is, and therefore cannot infer that |(C,4)| is intended to be a |Pitch|. We can get around this either by writing: \begin{spec} m :: Pitch m = note qn (C,4) \end{spec} in which case |play m| will work just fine, or we can include the type signature ``in-line'' with the expression, as in |play (note qn ((C,4)::Pitch))|.} \vspace{.1in}\hrule \begin{exercise}{\em The above example is fairly concrete, in that, for one, it is rooted in C major, and furthermore it has a fixed tempo. Define a function |twoFiveOne :: Pitch -> Dur -> Music Pitch| such that |twoFiveOne p d| constructs a ii-V-I chord progression in the key whose major scale begins on the pitch |p| (i.e.\ the first degree of the major scale on which the progression is being constructed), where the duration of the first two chords is each |d|, and the duration of the last chord is |2*d|. To verify your code, prove by calculation that |twoFiveOne (C,4) wn = t251|.} \end{exercise} \begin{exercise}{\em The |PitchClass| data type implies the use of standard Western harmony, in particular the use of a \emph{twelve-tone equal temperament scale}. But there are many other scale possibilities. For example, the \emph{pentatonic blues scale} consists of five notes (thus ``pentatonic'') and, in the key of C, approximately corresponds to the notes C, E$\flat$, F, G, and B$\flat$. More abstractly, let's call these the root, minor third, fourth, fifth, and minor seventh, respectively. Your job is to: \begin{enumerate} \item Define a new algebraic data type called |BluesPitchClass| that captures this scale (for example, you may wish to use the constructor names |Ro|, |MT|, |Fo|, |Fi|, and |MS|). \item Define a type synonym |BluesPitch|, akin to |Pitch|. \item Define auxiliary functions |ro|, |mt|, |fo|, |fi|, and |ms|, akin to those in Figure \ref{fig:note-names}, that make it easy to construct notes of type |Music BluesPitch|. \item In order to play a value of type |Music BluesPitch| using MIDI, it will have to be converted into a |Music Pitch| value. Define a function |fromBlues :: Music BluesPitch -> Music Pitch| to do this, using the ``approximate'' translation described at the beginning of this exercise. Hint: To do this properly, you will have to pattern match against the |Music| value, something like this: \begin{spec} fromBlues (Prim (Note d p)) = ... fromBlues (Prim (Rest d)) = ... fromBlues (m1 :+: m2) = ... fromBlues (m1 :=: m2) = ... fromBlues (Modify ...) = ... \end{spec} \item Write out a few melodies of type |Music BluesPitch|, and play them using |fromBlues| and |play|. \end{enumerate} } \end{exercise} \vspace{.1in}\hrule \section{Absolute Pitches} \label{sec:abspitch} Treating pitches simply as integers is useful in many settings, so Euterpea uses a type synonym to define the concept of an ``absolute pitch:'' \begin{code} type AbsPitch = Int \end{code} The absolute pitch of a (relative) pitch can be defined mathematically as 12 times the octave, plus the index of the pitch class. We can express this in Haskell as follows: \begin{code} absPitch :: Pitch -> AbsPitch absPitch (pc,oct) = 12*oct + pcToInt pc \end{code} \syn{Note the use of pattern matching to match the argument of |absPitch| to a pair.} |pcToInt| is a function that converts a particular pitch class to an index, easily but tediously expressed as shown in Figure \ref{fig:pcToInt}. But there is a subtlety: according to music theory convention, pitches are assigned integers in the range 0 to 11, i.e.\ modulo 12, starting on pitch class C. In other words, the index of C is 0, C$\flat$ is 11, and B$\sharp$ is 0. However, that would mean the absolute pitch of |(C,4)|, say, would be 48, whereas |(Cf,4)| would be 59. Somehow the latter does not seem right---47 would be a more logical choice. Therefore the definition in Figure~\ref{fig:pcToInt} is written in such a way that the wrap-round does not happen, i.e.\ numbers outside the range 0 to 11 are used. With this definition, |absPitch (Cf,4)| yields 47, as desired. %% Should |Cf| be interpreted as 11 instead of -1, and |Bs| as 0 %% instead of 12? I do not know. In most cases it will not matter, but %% it is an interesting question. \begin{figure} \cbox{\small \begin{spec} pcToInt :: PitchClass -> Int pcToInt Cff = -2; pcToInt Dff = 0; pcToInt Eff = 2 pcToInt Cf = -1; pcToInt Df = 1; pcToInt Ef = 3 pcToInt C = 0; pcToInt D = 2; pcToInt E = 4 pcToInt Cs = 1; pcToInt Ds = 3; pcToInt Es = 5 pcToInt Css = 2; pcToInt Dss = 4; pcToInt Ess = 6 pcToInt Fff = 3; pcToInt Gff = 5; pcToInt Aff = 7 pcToInt Ff = 4; pcToInt Gf = 6; pcToInt Af = 8 pcToInt F = 5; pcToInt G = 7; pcToInt A = 9 pcToInt Fs = 6; pcToInt Gs = 8; pcToInt As = 10 pcToInt Fss = 7; pcToInt Gss = 9; pcToInt Ass = 11 pcToInt Bff = 9 pcToInt Bf = 10 pcToInt B = 11 pcToInt Bs = 12 pcToInt Bss = 13 \end{spec}} \caption{Converting Pitch Classes to Integers} \label{fig:pcToInt} \end{figure} \syn{The repetition of ``|pcToInt|'' above can be avoided by using a Haskell |case| expression, resulting in a more compact definition: \begin{code} pcToInt :: PitchClass -> Int pcToInt pc = case pc of Cff -> -2; Cf -> -1; C -> 0; Cs -> 1; Css -> 2; Dff -> 0; Df -> 1; D -> 2; Ds -> 3; Dss -> 4; Eff -> 2; Ef -> 3; E -> 4; Es -> 5; Ess -> 6; Fff -> 3; Ff -> 4; F -> 5; Fs -> 6; Fss -> 7; Gff -> 5; Gf -> 6; G -> 7; Gs -> 8; Gss -> 9; Aff -> 7; Af -> 8; A -> 9; As -> 10; Ass -> 11; Bff -> 9; Bf -> 10; B -> 11; Bs -> 12; Bss -> 13 \end{code} As you can see, a |case| expression allows multiple pattern-matches on an expression without using equations. Note that layout applies to the body of a case expression, and can be overriden as before using a semicolon. (As in a function type signature, the right-pointing arrow in a |case| expression must be typed as ``{\tt ->}'' on your computer keyboard.) The body of a |case| expression observes layout just as a |let| expression, including the fact that semicolons can be used, as above, to place more than one pattern match on the same line.} Converting an absolute pitch to a pitch is a bit more tricky, because of enharmonic equivalences. For example, the absolute pitch 15 might correspond to either |(Ds,1)| or |(Ef,1)|. Euterpea takes the approach of always returning a sharp in such ambiguous cases: %%\begin{code} %%pitch :: AbsPitch -> Pitch %%pitch ap = ( [C,Cs,D,Ds,E,F,Fs,G,Gs,A,As,B] !! mod ap 12, %% quot ap 12 ) %%\end{code} \begin{code} pitch :: AbsPitch -> Pitch pitch ap = let (oct, n) = divMod ap 12 in ([C,Cs,D,Ds,E,F,Fs,G,Gs,A,As,B] !! n, oct) \end{code} \index{list!indexing} \syn{|(!!)| is Haskell's zero-based list-indexing function; |list !! n| returns the |(n+1)|th element in |list|. |divMod x n| returns a pair |(q,r)|, where |q| is the integer quotient of |x| divided by |n|, and |r| is the value of |x| modulo |n|.} %% |(!!)| behaves as follows: %% \begin{spec} %% infixl 9 !! %% (!!) :: [a] -> Int -> a %% (x:_) !! 0 = x %% (_:xs) !! n | n > 0 = xs !! (n-1) %% \end{spec} Given |pitch| and |absPitch|, it is now easy to define a function |trans| that transposes pitches: %% (analogous to |Trans|, which transposes values of type |Music|) \begin{code} trans :: Int -> Pitch -> Pitch trans i p = pitch (absPitch p + i) \end{code} With this definition, all of the operators and functions introduced in the previous chapter have been covered. \vspace{.1in}\hrule \begin{exercise}{\em Show that |abspitch (pitch ap) = ap|, and, up to enharmonic equivalences, |pitch (abspitch p) = p|.} \end{exercise} \begin{exercise}{\em Show that |trans i (trans j p) = trans (i+j) p|.} \end{exercise} \begin{exercise}{\em |Transpose| is part of the |Control| data type, which in turn is part of the |Music| data type. Its use in transposing a |Music| value is thus a kind of ``annotation''---it doesn't really change the |Music| value, it just annotates it as something that is transposed. Define instead a recursive function |transM :: AbsPitch -> Music Pitch -> Music Pitch| that actually changes each note in a |Music Pitch| value by transposing it by the interval represented by the first argument. Hint: To do this properly, you will have to pattern match against the |Music| value, something like this: \begin{spec} transM ap (Prim (Note d p)) = ... transM ap (Prim (Rest d)) = ... transM ap (m1 :+: m2) = ... transM ap (m1 :=: m2) = ... transM ap (Modify ...) = ... \end{spec} } \end{exercise} \vspace{.1in}\hrule