The Haskore Tutorial
top back next

3  The Basics

 

> module Basics where
> infixr 5 :+:, :=:

Perhaps the most basic musical idea is that of a pitch, which consists of a pitch class (i.e. one of 12 semi-tones) and an octave:  

> type Pitch      = (PitchClass, Octave)
> data PitchClass = Cf | C | Cs | Df | D | Ds | Ef | E | Es | Ff | F | Fs
>                 | Gf | G | Gs | Af | A | As | Bf | B | Bs
>      deriving (Eq,Ord,Ix,Show)
> type Octave     = Int

So a Pitch is a pair consisting of a pitch class and an octave. Octaves are just integers, but we define a datatype for pitch classes, since distinguishing enharmonics (such as G#and Ab) may be important (especially for notation!). By convention, A440 = (A,4).

Musical objects are captured by the Music datatype: (I prefer to call these "musical objects" rather than "musical values" because the latter may be confused with musical aesthetics.)  

> data Music = Note Pitch Dur [NoteAttribute]   -- a note \ atomic 
>            | Rest Dur                         -- a rest /    objects
>            | Music :+: Music                  -- sequential composition
>            | Music :=: Music                  -- parallel composition
>            | Tempo  Int Int Music             -- scale the tempo
>            | Trans  Int Music                 -- transposition
>            | Instr  IName Music               -- instrument label
>            | Player PName Music               -- player label
>            | Phrase [PhraseAttribute] Music   -- phrase attributes
>     deriving Show
>
> type Dur   = Float                            -- in whole notes
> type IName = String
> type PName = String

Here a Note is its pitch paired with its duration (in number of whole notes), along with a list of NoteAttributes (defined later). A Rest also has a duration, but of course no pitch or other attributes.

From these two atomic constructors we can build more complex musical objects using the other constructors, as follows:

It is convenient to represent these ideas in Haskell as a recursive datatype because we wish to not only construct musical objects, but also take them apart, analyze their structure, print them in a structure-preserving way, interpret them for performance purposes, etc.

3.1  Convenient Auxiliary Functions

For convenience we first create a few names for familiar notes, durations, and rests, as shown in Figure 2. Treating pitches as integers is also useful in many settings, so we define some functions for converting between Pitch values and AbsPitch values (integers). These also are shown in Figure 2, along with a definition of trans, which transposes pitches (analogous to Trans, which transposes values of type Music).

Exercise
Show that abspitch . pitch = id, and, up to enharmonic equivalences,
pitch . abspitch = id.

Exercise
Show that trans i (trans j p) = trans (i+j) p.

 

> cf,c,cs,df,d,ds,ef,e,es,ff,f,fs,gf,g,gs,af,a,as,bf,b,bs :: 
>    Octave -> Dur -> [NoteAttribute] -> Music
>
> cf o = Note (Cf,o);  c o = Note (C,o);  cs o = Note (Cs,o)
> df o = Note (Df,o);  d o = Note (D,o);  ds o = Note (Ds,o)
> ef o = Note (Ef,o);  e o = Note (E,o);  es o = Note (Es,o)
> ff o = Note (Ff,o);  f o = Note (F,o);  fs o = Note (Fs,o)
> gf o = Note (Gf,o);  g o = Note (G,o);  gs o = Note (Gs,o)
> af o = Note (Af,o);  a o = Note (A,o);  as o = Note (As,o)
> bf o = Note (Bf,o);  b o = Note (B,o);  bs o = Note (Bs,o)
>
> wn,  hn,  qn,  en,  sn,  tn  :: Dur
> wnr, hnr, qnr, enr, snr, tnr :: Music
>
> 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      -- eight note rest
> sn = 1/16       ; snr = Rest sn      -- sixteenth note rest
> tn = 1/32       ; tnr = Rest tn      -- thirty-second note rest
>
> pitchClass :: PitchClass -> Int
>
> pitchClass pc = case pc of
>      Cf -> -1;  C -> 0;  Cs -> 1    -- or should Cf be 11?
>      Df -> 1;   D -> 2;  Ds -> 3
>      Ef -> 3;   E -> 4;  Es -> 5
>      Ff -> 4;   F -> 5;  Fs -> 6
>      Gf -> 6;   G -> 7;  Gs -> 8
>      Af -> 8;   A -> 9;  As -> 10
>      Bf -> 10;  B -> 11; Bs -> 12   -- or should Bs be 0?
>
> type AbsPitch = Int
>
> absPitch :: Pitch -> AbsPitch
> absPitch (pc,oct) = 12*oct + pitchClass pc
>
> pitch    :: AbsPitch -> Pitch
> pitch    ap       = ( [C,Cs,D,Ds,E,F,Fs,G,Gs,A,As,B] !! mod ap 12, 
>                       quot ap 12)
>
> trans    :: Int -> Pitch -> Pitch
> trans i p = pitch (absPitch p + i)

Figure 2: Convenient note names and pitch conversion functions.

3.2  Some Simple Examples

With this modest beginning, we can already express quite a few musical relationships simply and effectively. For example, two common ideas in music are the construction of notes in a horizontal fashion (a line or melody), and in a vertical fashion (a chord):

> line, chord :: [Music] -> Music
> line  = foldr (:+:) (Rest 0) 
> chord = foldr (:=:) (Rest 0) 

From the notes in the C major triad in register 4, I can now construct a C major arpeggio and chord as well:  

> cMaj = map (\f->f 4 qn []) [c, e, g]  -- octave 4, quarter notes
>
> cMajArp = line  cMaj
> cMajChd = chord cMaj

Suppose now we wish to describe a melody m accompanied by an identical voice a perfect 5th higher. In Haskore we simply write "m :=: Trans 7 m." Similarly, a canon-like structure involving m can be expressed as "m :=: delay d m," where:  

> delay :: Dur -> Music -> Music
> delay d m = Rest d :+: m

Of course, Haskell's non-strict semantics also allows us to define infinite musical objects. For example, a musical object may be repeated ad nauseum using this simple function:  

> repeatM :: Music -> Music
> repeatM m = m :+: repeatM m

Thus an infinite ostinato can be expressed in this way, and then used in different contexts that extract only the portion that's actually needed.

The notions of inversion, retrograde, retrograde inversion, etc. used in 12-tone theory are also easily captured in Haskore. First let's define a transformation from a line created by line to a list:  

> lineToList :: Music -> [Music]
> lineToList n@(Rest 0) = []
> lineToList (n :+: ns) = n : lineToList ns
>
> retro, invert, retroInvert, invertRetro :: Music -> Music
> retro    = line . reverse . lineToList
> invert m = line (map inv l)
>   where l@(Note r _ _: _)  = lineToList m
>         inv (Note p d nas) = Note (pitch (2*(absPitch r) - absPitch p)) d nas
>         inv (Rest d)       = Rest d
> retroInvert = retro  . invert
> invertRetro = invert . retro

Exercise
Show that "retro . retro," "invert . invert," and "retroInvert . invertRetro" are the identity on values created by line.

Polyrhythms
Figure 3: Nested Polyrhythms

For some rhythmical ideas, consider first a simple triplet of eighth notes; it can be expressed as "Tempo 3 2 m," where m is a line of 3 eighth notes. So in fact Tempo can be used to create quite complex rhythmical patterns. For example, consider the "nested polyrhythms" shown in Figure 3. They can be expressed quite naturally in Haskore as follows (note the use of the where clause in pr2 to capture recurring phrases):  

> pr1, pr2 :: Pitch -> Music
> pr1 p = Tempo 5 6 (Tempo 4 3 (mkLn 1 p qn :+:
>                               Tempo 3 2 (mkLn 3 p en :+:
>                                          mkLn 2 p sn :+:
>                                          mkLn 1 p qn    ) :+:
>                               mkLn 1 p qn) :+:
>                    Tempo 3 2 (mkLn 6 p en))
>
> pr2 p = Tempo 7 6 (m1 :+:
>                    Tempo 5 4 (mkLn 5 p en) :+:
>                    m1 :+:
>                    mkLn 2 p en)
>         where m1 = Tempo 5 4 (Tempo 3 2 m2 :+: m2)
>               m2 = mkLn 3 p en
>
> mkLn n p d = line (take n (repeat (Note p d [])))

To play polyrhythms pr1 and pr2 in parallel using middle C and middle G, respectively, we would do the following (middle C is in the 5th octave):  

> pr12 :: Music
> pr12 = pr1 (C,5) :=: pr2 (G,5)

As a final example in this section, we can can compute the duration in beats of a musical object, a notion we will need in Section 4, as follows:

> dur :: Music -> Dur
>
> dur (Note _ d _)  = d
> dur (Rest d)      = d
> dur (m1 :+: m2)   = dur m1   +   dur m2
> dur (m1 :=: m2)   = dur m1 `max` dur m2
> dur (Tempo a b m) = dur m * float b / float a
> dur (Trans  _  m) = dur m
> dur (Instr  _  m) = dur m
> dur (Player _  m) = dur m
> dur (Phrase _  m) = dur m
>
> float = fromInteger . toInteger :: Int -> Float

Using dur we can define a function revM that reverses any Music value (and is thus considerably more useful than retro defined earlier). Note the tricky treatment of (:=:).

> revM :: Music -> Music
> revM n@(Note _ _ _)  = n
> revM r@(Rest _)      = r
> revM (Tempo i1 i2 m) = Tempo i1 i2 (revM m)
> revM (Trans i  m)    = Trans i     (revM m)
> revM (Instr i  m)    = Instr i     (revM m)
> revM (Phrase pas m)  = Phrase pas  (revM m)
> revM (m1 :+: m2)     = revM m2 :+: revM m1
> revM (m1 :=: m2)     = let d1 = dur m1
>                            d2 = dur m2
>                        in if d1>d2 then revM m1 :=:
>                                         (Rest (d1-d2) :+: revM m2)
>                                    else (Rest (d2-d1) :+: revM m1) :=:
>                                         revM m2

Exercise
Find a simple piece of music written by your favorite composer, and transcribe it into Haskore. In doing so, look for repeating patterns, transposed phrases, etc. and reflect this in your code, thus revealing deeper structural aspects of the music than that found in common practice notation.

Appendix C shows the first 28 bars of Chick Corea's "Children's Song No. 6" encoded in Haskore.

3.3  Phrasing and Articulation

Recall that the Note constructor contained a field of NoteAttributes. These are values that are attached to notes for the purpose of notation or musical interpretation. Likewise, the Phrase constructor permits one to annotate an entire musical object with PhraseAttributes. These two attribute datatypes cover a wide range of attributions found in common practice notation, and are shown in Figure 4. Beware that use of them requires the use of a player that knows how to interpret them! Players will be described in more detail in Section 5.

 

> data NoteAttribute = Volume Float        -- by convention: 0=min, 100=max
>                    | Fingering Int
>                    | Dynamics String
>      deriving Show
>
> data PhraseAttribute = Dyn Dynamic
>                      | Art Articulation
>                      | Orn Ornament
>      deriving Show
>
> data Dynamic = Accent Float | Crescendo Float | Diminuendo Float
>              | PPP | PP | P | MP | SF | MF | NF | FF | FFF | Loudness Float
>              | Ritardando Float | Accelerando Float
>      deriving Show
>
> data Articulation = Staccato Float | Legato Float | Slurred Float
>                   | Tenuto | Marcato | Pedal | Fermata | FermataDown | Breath
>                   | DownBow | UpBow | Harmonic | Pizzicato | LeftPizz 
>                   | BartokPizz | Swell | Wedge | Thumb | Stopped
>      deriving Show
>
> data Ornament = Trill | Mordent | InvMordent | DoubleMordent
>               | Turn | TrilledTurn | ShortTrill
>               | Arpeggio | ArpeggioUp | ArpeggioDown
>               | Instruction String | Head NoteHead
>      deriving Show
>
> data NoteHead = DiamondHead | SquareHead | XHead | TriangleHead
>               | TremoloHead | SlashHead | ArtHarmonic | NoHead
>      deriving Show

Figure 4: Note and Phrase Attributes.

Note that some of the attributes are parameterized with a numeric value. This is used by a player to control the degree to which an articulation is to be applied. For example, we would expect Legato 1.2 to create more of a legato feel than Legato 1.1. The following constants represent default values for some of the parameterized attributes:

> legato, staccato  :: Articulation
> accent, bigAccent :: Dynamic
>
> legato    = Legato 1.1
> staccato  = Staccato 0.5
> accent    = Accent 1.2
> bigAccent = Accent 1.5

To understand exactly how a player interprets an attribute requires knowing how players are defined. Haskore defines only a few simple players, so in fact many of the attributes in Figure 4 are to allow the user to give appropriate interpretations of them by her particular player. But before looking at the structure of players we will need to look at the notion of a performance (these two ideas are tightly linked, which is why the Players and Performance modules are mutually recursive).


The Haskore Tutorial
top back next