Difference between revisions of "The Monad.Reader/Issue2/Haskore"

From HaskellWiki
Jump to navigation Jump to search
 
(show code snippets by teletype)
 
Line 3: Line 3:
 
= Haskore =
 
= Haskore =
   
This Article will be about ''Haskore'', which is a Haskell library
+
This Article will be about [[Haskore]], which is a Haskell library
 
for describing music. It follows an approach of
 
for describing music. It follows an approach of
 
describing a domain specific language and thus reduces complications
 
describing a domain specific language and thus reduces complications
Line 11: Line 11:
   
 
A core of the Haskore system is Score data, which is
 
A core of the Haskore system is Score data, which is
stored as a Type called {{{Music}}}. Score data is usually
+
stored as a Type called <code>Music</code>. Score data is usually
 
represented like this:
 
represented like this:
   
Line 44: Line 44:
 
Unpack the file. It provides some documentation and the Haskore sources.
 
Unpack the file. It provides some documentation and the Haskore sources.
   
To use Haskore interactively, change to {{{Haskore/Src}}} and start
+
To use Haskore interactively, change to <code>Haskore/Src</code> and start
{{{hugs}}} (you could also use {{{ghci}}}, but be sure
+
<code>hugs</code> (you could also use <code>ghci</code>, but be sure
to put the file {{{Haskore/ghc_add/IOExtensions.lhs}}} into the
+
to put the file <code>Haskore/ghc_add/IOExtensions.lhs</code> into the
{{{Haskore/Src}}} Directory before.) Type {{{:l HaskoreLoader}}} and
+
<code>Haskore/Src</code> Directory before.) Type <code>:l HaskoreLoader</code> and
{{{:m Basics}}} to initialize Haskore for immediate
+
<code>:m Basics</code> to initialize Haskore for immediate
Experimentation. {{{:l example}}} will load Haskore, some
+
Experimentation. <code>:l example</code> will load Haskore, some
 
declarations in the examples in this text, and import
 
declarations in the examples in this text, and import
{{{TestHaskore}}} which will save us some time and brains by
+
<code>TestHaskore</code> which will save us some time and brains by
 
defining reasonable defaults for some features.
 
defining reasonable defaults for some features.
   
Line 60: Line 60:
 
== Building blocks of Music ==
 
== Building blocks of Music ==
   
Haskore offers a data type called {{{Music}}} that represents - as
+
Haskore offers a data type called <code>Music</code> that represents - as
 
you might have guessed - music. The "atoms" of music, notes, can be
 
you might have guessed - music. The "atoms" of music, notes, can be
 
generated by giving their "pitch class" (This is where the
 
generated by giving their "pitch class" (This is where the
Line 67: Line 67:
 
, octave, duration, and a List of Attributes , like in:
 
, octave, duration, and a List of Attributes , like in:
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
Basics> :t (c 1 (1%4) [])
 
Basics> :t (c 1 (1%4) [])
 
c 1 (1 % 4) [] :: Music
 
c 1 (1 % 4) [] :: Music
  +
</code>
}}}
 
   
 
This snippet would represent a "c4" note, played for a fourth
 
This snippet would represent a "c4" note, played for a fourth
measure. The infix operator {{{%}}} is used to create a rational
+
measure. The infix operator <code>%</code> is used to create a rational
 
number. This way we can easily specify triplets, for example, which
 
number. This way we can easily specify triplets, for example, which
 
are harder in inherently quantized environments.
 
are harder in inherently quantized environments.
Line 79: Line 79:
 
The names Haskore gives to the "pitch classes" are, as one
 
The names Haskore gives to the "pitch classes" are, as one
 
would expect, the names used in the Anglo-Saxon languages, that are,
 
would expect, the names used in the Anglo-Saxon languages, that are,
{{{a b c d e f g}}}. Sharp and Flat pitches are available via
+
<code>a b c d e f g</code>. Sharp and Flat pitches are available via
{{{as}}} and {{{af}}}, respectively. Note that this encoding is
+
<code>as</code> and <code>af</code>, respectively. Note that this encoding is
 
an absolute one and does not differentiate in any way among
 
an absolute one and does not differentiate in any way among
"enharmonics", like {{{es}}} and {{{f}}}
+
"enharmonics", like <code>es</code> and <code>f</code>
   
 
Now how do we make this single note a music? We will have to combine
 
Now how do we make this single note a music? We will have to combine
 
it with other notes. There are two obvious way to do this.
 
it with other notes. There are two obvious way to do this.
   
||<^> attachment:haskore1-ex2.gif ||<#eeeeee> {{{:+:}}} ||<^> http://www.students.uni-marburg.de/~Zapf/haskore1-ex3.gif || = ||<^> http://www.students.uni-marburg.de/~Zapf/haskore1-ex4.gif ||
+
||<^> attachment:haskore1-ex2.gif ||<#eeeeee> <code>:+:</code> ||<^> http://www.students.uni-marburg.de/~Zapf/haskore1-ex3.gif || = ||<^> http://www.students.uni-marburg.de/~Zapf/haskore1-ex4.gif ||
   
 
The sequential composition, expressed by the operator
 
The sequential composition, expressed by the operator
{{{(:+:) :: Music -> Music -> Music}}}
+
<code>(:+:) :: Music -> Music -> Music</code>
 
results in a value that represents both values in temporal
 
results in a value that represents both values in temporal
 
composition (I am tempted to write "played one after the other", but
 
composition (I am tempted to write "played one after the other", but
 
there is no playing going on for now, so this would be a bad idea)
 
there is no playing going on for now, so this would be a bad idea)
   
||<^> attachment:haskore1-ex2.gif ||<#eeeeee> {{{:=:}}} ||<^> http://www.students.uni-marburg.de/~Zapf/haskore1-ex3.gif || = ||<^> http://www.students.uni-marburg.de/~Zapf/haskore1-ex5.gif ||
+
||<^> attachment:haskore1-ex2.gif ||<#eeeeee> <code>:=:</code> ||<^> http://www.students.uni-marburg.de/~Zapf/haskore1-ex3.gif || = ||<^> http://www.students.uni-marburg.de/~Zapf/haskore1-ex5.gif ||
   
The parallel composition {{{:=:}}} has the same type, but composes
+
The parallel composition <code>:=:</code> has the same type, but composes
 
both values to one that represents them simultaneously ("played at the
 
both values to one that represents them simultaneously ("played at the
 
same time").
 
same time").
   
Using {{{:t}}}, we can see that both Operators take two
+
Using <code>:t</code>, we can see that both Operators take two
{{{Music}}} values
+
<code>Music</code> values
and return a {{{Music}}} value. Using these Features and the rests
+
and return a <code>Music</code> value. Using these Features and the rests
 
(which
 
(which
are named {{{qnr}}}, {{{hnr}}} etc., for ''quarter note
+
are named <code>qnr</code>, <code>hnr</code> etc., for ''quarter note
 
rest'', ''half note rest''), we can already construct a lot of
 
rest'', ''half note rest''), we can already construct a lot of
 
music.
 
music.
Line 111: Line 111:
 
Other useful operators (Actually, all the "operators"
 
Other useful operators (Actually, all the "operators"
 
mentioned are just infix type
 
mentioned are just infix type
constructors for {{{Music}}} values - see {{{Basics.lhs}}}
+
constructors for <code>Music</code> values - see <code>Basics.lhs</code>
 
line 34...43. The semantics of the constructed Score is to be added
 
line 34...43. The semantics of the constructed Score is to be added
later) are {{{Trans :: Int -> Music -> Music}}} and
+
later) are <code>Trans :: Int -> Music -> Music</code> and
{{{Tempo :: Ratio Int -> Music -> Music}}}. Use them to Transpose
+
<code>Tempo :: Ratio Int -> Music -> Music</code>. Use them to Transpose
 
tunes, or to change their speed.
 
tunes, or to change their speed.
   
Line 120: Line 120:
 
until now. It is intended to hold notewise attributes. For example,
 
until now. It is intended to hold notewise attributes. For example,
 
the Volume of a Note can be kept here, since it might be different for
 
the Volume of a Note can be kept here, since it might be different for
each single Note. {{{c 4 (1%4) [Volume 50]}}}, for example, would
+
each single Note. <code>c 4 (1%4) [Volume 50]</code>, for example, would
 
represent a quarter "c 4", played at "Volume 50". While we have a
 
represent a quarter "c 4", played at "Volume 50". While we have a
 
clear definition for "c 4" and "1%4", we don't have one for
 
clear definition for "c 4" and "1%4", we don't have one for
Line 131: Line 131:
 
support for Music in "Computers" (Turing-Equivalent Machines), we
 
support for Music in "Computers" (Turing-Equivalent Machines), we
 
need to output something that a given synthesis equipment
 
need to output something that a given synthesis equipment
understands. A canonical choice for score data would be {{{midi}}}. The
+
understands. A canonical choice for score data would be <code>midi</code>. The
only information still missing in our {{{Music}}} Data is {{{midi}}}
+
only information still missing in our <code>Music</code> Data is <code>midi</code>
 
channel numbers.
 
channel numbers.
   
 
A Haskore abstraction for converting score Data to something closer to
 
A Haskore abstraction for converting score Data to something closer to
 
acoustical reality is a "Performance". There is a function
 
acoustical reality is a "Performance". There is a function
{{{perform :: PMap -> Context -> Music -> Performance}}} that
+
<code>perform :: PMap -> Context -> Music -> Performance</code> that
can convert {{{Music}}} to a {{{Performance}}}, given a
+
can convert <code>Music</code> to a <code>Performance</code>, given a
{{{PMap}}} (a Mapping from player Names to Players) and a
+
<code>PMap</code> (a Mapping from player Names to Players) and a
{{{Context}}} (which is not interesting right now, but
+
<code>Context</code> (which is not interesting right now, but
 
can control how various performances will be coordinated).
 
can control how various performances will be coordinated).
   
For example, we can turn an arbitrary {{{Music}}} Value to a
+
For example, we can turn an arbitrary <code>Music</code> Value to a
{{{Performance}}} like this:
+
<code>Performance</code> like this:
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
Main> perform (\_->defPlayer) defCon example1
 
Main> perform (\_->defPlayer) defCon example1
 
[Event{eTime=0.0,eInst="piano",ePitch=48,eDur=0.5,eVol=113.5,pFields=[]}]
 
[Event{eTime=0.0,eInst="piano",ePitch=48,eDur=0.5,eVol=113.5,pFields=[]}]
  +
</code>
}}}
 
   
 
Using some default Values we nicked from
 
Using some default Values we nicked from
{{{TestHaskore.lhs}}}. We see that the {{{Volume 100}}} note
+
<code>TestHaskore.lhs</code>. We see that the <code>Volume 100</code> note
attribute was converted to an event volume of {{{113.5}}}. Considering
+
attribute was converted to an event volume of <code>113.5</code>. Considering
 
that result, it's questionable if the default values were chosen
 
that result, it's questionable if the default values were chosen
 
all that wisely.
 
all that wisely.
Line 159: Line 159:
 
Using
 
Using
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
Main> perform (\_->defPlayer) defCon example2
 
Main> perform (\_->defPlayer) defCon example2
 
[Event{eTime=0.0,eInst="piano",ePitch=48,eDur=0.5,eVol=113.5,pFields=[]},
 
[Event{eTime=0.0,eInst="piano",ePitch=48,eDur=0.5,eVol=113.5,pFields=[]},
 
Event{eTime=0.5,eInst="piano",ePitch=48,eDur=0.5,eVol=113.5,pFields=[]},
 
Event{eTime=0.5,eInst="piano",ePitch=48,eDur=0.5,eVol=113.5,pFields=[]},
 
...
 
...
  +
</code>
}}}
 
   
We see that a performance is a flat list of {{{Event}}}s as opposed to a
+
We see that a performance is a flat list of <code>Event</code>s as opposed to a
{{{Score}}} value, which is rather tree-like in structure.
+
<code>Score</code> value, which is rather tree-like in structure.
   
 
Now we are ready to write these events out to some musical format, for
 
Now we are ready to write these events out to some musical format, for
example {{{midi}}}. We needed some additional information to write out the
+
example <code>midi</code>. We needed some additional information to write out the
{{{midi}}} file, namely a "patch map" to map the instrument name
+
<code>midi</code> file, namely a "patch map" to map the instrument name
"piano" to the {{{midi}}} "Acoustic Grand Piano" (Instrument 1) on
+
"piano" to the <code>midi</code> "Acoustic Grand Piano" (Instrument 1) on
 
Channel 1. For other instruments, you could just extend the
 
Channel 1. For other instruments, you could just extend the
 
list. (For a list of instrument names, see
 
list. (For a list of instrument names, see
{{{Haskore/Src/GeneralMidi.lhs}}})
+
<code>Haskore/Src/GeneralMidi.lhs</code>)
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
Main> outputMidiFile "example2.mid" (performToMidi (perform (\_->defPlayer) defCon example2) [("piano","Acoustic Grand Piano",1)])
 
Main> outputMidiFile "example2.mid" (performToMidi (perform (\_->defPlayer) defCon example2) [("piano","Acoustic Grand Piano",1)])
  +
</code>
}}}
 
   
 
This call gives no visible output. After that, you should, however,
 
This call gives no visible output. After that, you should, however,
find {{{example2.mid}}} in your current directory. Open it with
+
find <code>example2.mid</code> in your current directory. Open it with
 
your favourite (I recommend "Rosegarden"
 
your favourite (I recommend "Rosegarden"
[http://www.rosegardenmusic.com/] on Unix-derivate systems) {{{midi}}}
+
[http://www.rosegardenmusic.com/] on Unix-derivate systems) <code>midi</code>
 
Sequencer/Editor tool, or play it back. For ease of use i put all
 
Sequencer/Editor tool, or play it back. For ease of use i put all
these bits together to a function in {{{example.lhs}}}
+
these bits together to a function in <code>example.lhs</code>
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
Main> midiout "example2.mid" example2
 
Main> midiout "example2.mid" example2
  +
</code>
}}}
 
   
 
== Functional Music ==
 
== Functional Music ==
   
 
How could functional programming help us specify music? Haskell
 
How could functional programming help us specify music? Haskell
variables can of course take {{{Music}}} values, and build other
+
variables can of course take <code>Music</code> values, and build other
values from them, so we can for example {{{Trans}}}pose a given
+
values from them, so we can for example <code>Trans</code>pose a given
 
piece of music.
 
piece of music.
   
 
We could, for example, write a function that converts
 
We could, for example, write a function that converts
a list of intervals (integers) and a {{{Music}}} value to a chord.
+
a list of intervals (integers) and a <code>Music</code> value to a chord.
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
mychord intervals base = map (\n->Trans n base) intervals
 
mychord intervals base = map (\n->Trans n base) intervals
 
minor = [0,3,7]
 
minor = [0,3,7]
 
major = [0,4,7]
 
major = [0,4,7]
  +
</code>
}}}
 
   
 
0 is the prime, 3 the small third, 4 the large third and 7 the
 
0 is the prime, 3 the small third, 4 the large third and 7 the
 
fifth. Now we can specify a simple chord progression:
 
fifth. Now we can specify a simple chord progression:
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
example3 = (c 4 (1%4) [Volume 100]) :+:
 
example3 = (c 4 (1%4) [Volume 100]) :+:
 
(g 4 (1%4) [Volume 100]) :+:
 
(g 4 (1%4) [Volume 100]) :+:
Line 217: Line 217:
 
(c 4 (1%4) [Volume 100])
 
(c 4 (1%4) [Volume 100])
 
example4 = mychord major example3
 
example4 = mychord major example3
  +
</code>
}}}
 
   
As we see, {{{mychord}}} works with any music value. What
+
As we see, <code>mychord</code> works with any music value. What
 
it can't do is building different chords on top of a sequence of
 
it can't do is building different chords on top of a sequence of
 
notes. So:
 
notes. So:
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
example5 = (mychord major (c 4 (1%4) [Volume 100])) :+:
 
example5 = (mychord major (c 4 (1%4) [Volume 100])) :+:
 
(mychord minor (d 4 (1%4) [Volume 100])) :+:
 
(mychord minor (d 4 (1%4) [Volume 100])) :+:
 
(mychord major (g 4 (1%4) [Volume 100])) :+:
 
(mychord major (g 4 (1%4) [Volume 100])) :+:
 
(mychord major (c 4 (1%4) [Volume 100]))
 
(mychord major (c 4 (1%4) [Volume 100]))
  +
</code>
}}}
 
   
 
gives us a sequence with different kinds of chords.
 
gives us a sequence with different kinds of chords.
Line 236: Line 236:
 
Now as one might know, different "Modes" of (European, traditional)
 
Now as one might know, different "Modes" of (European, traditional)
 
Music use the same sequence of intervals, just starting from a
 
Music use the same sequence of intervals, just starting from a
different point in the sequence ({{{Mode}}}) and note ({{{Key}}},
+
different point in the sequence (<code>Mode</code>) and note (<code>Key</code>,
{{{Tonic}}}). Using the Major scale as the original one:
+
<code>Tonic</code>). Using the Major scale as the original one:
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
> maj_skips = [2,2,1,2,2,2,1]
 
> maj_skips = [2,2,1,2,2,2,1]
  +
</code>
}}}
 
   
we declare a helper function {{{runsum}}}, which just sums up numbers
+
we declare a helper function <code>runsum</code>, which just sums up numbers
 
in a list continuously.
 
in a list continuously.
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
runsum = scanl (+) 0
 
runsum = scanl (+) 0
  +
</code>
}}}
 
   
 
Now we can declare all the scales based on the
 
Now we can declare all the scales based on the
Line 254: Line 254:
 
intervals of the minor scale.
 
intervals of the minor scale.
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
scale kind = runsum (drop kind (cycle maj_skips))
 
scale kind = runsum (drop kind (cycle maj_skips))
  +
</code>
}}}
 
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
Main> take 8 (scale 5)
 
Main> take 8 (scale 5)
 
[0,2,3,5,7,8,10,12]
 
[0,2,3,5,7,8,10,12]
  +
</code>
}}}
 
   
 
We need cycle because scales repeat all 8 "steps" (every
 
We need cycle because scales repeat all 8 "steps" (every
Line 271: Line 271:
 
depending on the exact scale used)
 
depending on the exact scale used)
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
simplemelody = [(0,1%4),(5,1%2),(4,1%8),(3,1%8),(2,1%4),(5,1%2),(0,1%4)]
 
simplemelody = [(0,1%4),(5,1%2),(4,1%8),(3,1%8),(2,1%4),(5,1%2),(0,1%4)]
  +
</code>
}}}
 
   
   
   
* Specify a value of type {{{(Ratio Int->Music)}}} and call it
+
* Specify a value of type <code>(Ratio Int->Music)</code> and call it
{{{base}}} (as it will become the base tone (''Tonic'') of our melody,
+
<code>base</code> (as it will become the base tone (''Tonic'') of our melody,
 
if we give it an arbitrary length)
 
if we give it an arbitrary length)
 
* Find out how many halftones are between the base of a scale and
 
* Find out how many halftones are between the base of a scale and
the "step" wanted: {{{trans n = (fromInteger (scl !! n))}}}
+
the "step" wanted: <code>trans n = (fromInteger (scl !! n))</code>
 
* Transpose the base note, given a length to complete it, about that
 
* Transpose the base note, given a length to complete it, about that
 
amount, to get the ultimate result.
 
amount, to get the ultimate result.
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
realize :: Int -> (Ratio Int->Music) -> (Int,Ratio Int) -> Music
 
realize :: Int -> (Ratio Int->Music) -> (Int,Ratio Int) -> Music
 
realize kind base (n,len) = Trans (trans n) (base len)
 
realize kind base (n,len) = Trans (trans n) (base len)
Line 291: Line 291:
 
trans n = (fromInteger (scl !! n))
 
trans n = (fromInteger (scl !! n))
 
scl = (scale kind)
 
scl = (scale kind)
  +
</code>
}}}
 
   
 
We'll write another helper, that realizes a few notes and puts them in a sequence:
 
We'll write another helper, that realizes a few notes and puts them in a sequence:
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
testrealize kind base melody = allseq $ map (realize kind base) melody
 
testrealize kind base melody = allseq $ map (realize kind base) melody
  +
</code>
}}}
 
   
 
=== Making it Audible ===
 
=== Making it Audible ===
Line 304: Line 304:
 
base pitch, like for example:
 
base pitch, like for example:
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
Main> midiout "major.mid" (testrealize 0 (\l->(c 4 l [Volume 100])) simplemelody)
 
Main> midiout "major.mid" (testrealize 0 (\l->(c 4 l [Volume 100])) simplemelody)
 
Main> midiout "minor.mid" (testrealize 5 (\l->(d 4 l [Volume 100])) simplemelody)
 
Main> midiout "minor.mid" (testrealize 5 (\l->(d 4 l [Volume 100])) simplemelody)
  +
</code>
}}}
 
   
 
in c major, and then in d minor. This task (transpose and change
 
in c major, and then in d minor. This task (transpose and change
Line 317: Line 317:
 
we could want to describe the a'th three and four note chord in our scale:
 
we could want to describe the a'th three and four note chord in our scale:
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
tri a = [a,a+2,a+4]
 
tri a = [a,a+2,a+4]
 
tet a = [a,a+2,a+4,a+6]
 
tet a = [a,a+2,a+4,a+6]
  +
</code>
}}}
 
   
 
and put the chords numbered 1, 5, 4 and 1 after each other (if you ever thought you couldn't
 
and put the chords numbered 1, 5, 4 and 1 after each other (if you ever thought you couldn't
Line 326: Line 326:
 
here and there, and adding an octave to the last ''I'':
 
here and there, and adding an octave to the last ''I'':
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
test2d:: [[(Int,Ratio Int)]]
 
test2d:: [[(Int,Ratio Int)]]
 
test2d = [allength (1%2) (tri 0),
 
test2d = [allength (1%2) (tri 0),
Line 333: Line 333:
 
allength (1%2) (8:(tri 0))]
 
allength (1%2) (8:(tri 0))]
 
where allength l= map (\a->(a,l))
 
where allength l= map (\a->(a,l))
  +
</code>
}}}
 
   
 
Now we only need to map realize twice to that, and then fold twice (first in parallel, then serially) to make this a Music value.
 
Now we only need to map realize twice to that, and then fold twice (first in parallel, then serially) to make this a Music value.
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
rea2d kind base melody = allseq $ map allpar $ map (map (realize kind base)) melody
 
rea2d kind base melody = allseq $ map allpar $ map (map (realize kind base)) melody
  +
</code>
}}}
 
   
 
Try:
 
Try:
   
{{{#!syntax haskell
+
<code>#!syntax haskell
 
midiout "iivviprog.mid" (rea2d 5 (\l->(f 5 l [Volume 100])) test2d)
 
midiout "iivviprog.mid" (rea2d 5 (\l->(f 5 l [Volume 100])) test2d)
  +
</code>
}}}
 
   
 
And listen to it.
 
And listen to it.
Line 351: Line 351:
 
This would be all for this issue of TMR. If you should feel bored, try Haskore yourself. For example, you could:
 
This would be all for this issue of TMR. If you should feel bored, try Haskore yourself. For example, you could:
   
* Try to write an own melody, either using {{{realize}}} to later change scale, or without.
+
* Try to write an own melody, either using <code>realize</code> to later change scale, or without.
* Put fitting chords along {{{simplemelody}}}, or put a melody along {{{test2d}}}
+
* Put fitting chords along <code>simplemelody</code>, or put a melody along <code>test2d</code>
* Read in some existing midi files using {{{readMidi}}} and try to analyze the resulting {{{Music}}} values. (for example, asking: are all notes in one scale? which ones aren't? what's their harmonic function?)
+
* Read in some existing midi files using <code>readMidi</code> and try to analyze the resulting <code>Music</code> values. (for example, asking: are all notes in one scale? which ones aren't? what's their harmonic function?)
 
* If you're really bored: get some sheet music and realize it in Haskore.
 
* If you're really bored: get some sheet music and realize it in Haskore.
   

Latest revision as of 19:12, 11 August 2008

This article needs reformatting! Please help tidy it up.--WouterSwierstra 14:14, 9 May 2008 (UTC)

Haskore

This Article will be about Haskore, which is a Haskell library for describing music. It follows an approach of describing a domain specific language and thus reduces complications of arbitrary language decisions. Imagine, for example, a structure describing Music in any imperative language and compare this to the simplicity of a Haskore representation.

A core of the Haskore system is Score data, which is stored as a Type called Music. Score data is usually represented like this:

attachment:haskore1-ex1.gif

This sequence of Symbols, while looking relatively simple to the musician's eye, gives us a lot of information about the music we associate with it. Some of the information encoded here would be the number of notes struck, their lengths, how they overlap or don't.


Implicitly, we assume that we're dividing an octave into 12 "halftones" (look at the numeric values of (12th root of 2)^n for n=0...12 and compare to "simple" fractions to gain understanding of the significance of this number: n=7 is the "fifth" (c-g), n=4 the "major third", n=3 the "minor third" etc.), that a certain note called "a" represents 440 oscillations per second and a few other, even more arcane things.


We shall see that we need to give our computer all this information to reproduce the music that we associate with these notes.

Preparation

Get [attachment:tmr-Haskore.tar.gz Haskore]. This version of Haskore is ancient but stable. I corrected it slightly to account for features that changed in the meanwhile.

Unpack the file. It provides some documentation and the Haskore sources.

To use Haskore interactively, change to Haskore/Src and start hugs (you could also use ghci, but be sure to put the file Haskore/ghc_add/IOExtensions.lhs into the Haskore/Src Directory before.) Type :l HaskoreLoader and :m Basics to initialize Haskore for immediate Experimentation. :l example will load Haskore, some declarations in the examples in this text, and import TestHaskore which will save us some time and brains by defining reasonable defaults for some features.

Follow-ups of this article will need CSound. Most distributions of operating Software will allow for a relatively easy installation.

Building blocks of Music

Haskore offers a data type called Music that represents - as you might have guessed - music. The "atoms" of music, notes, can be generated by giving their "pitch class" (This is where the implicit assumption that our octave is divided into 12 pitches shows up) , octave, duration, and a List of Attributes , like in:

#!syntax haskell Basics> :t (c 1 (1%4) []) c 1 (1 % 4) [] :: Music

This snippet would represent a "c4" note, played for a fourth measure. The infix operator % is used to create a rational number. This way we can easily specify triplets, for example, which are harder in inherently quantized environments.

The names Haskore gives to the "pitch classes" are, as one would expect, the names used in the Anglo-Saxon languages, that are, a b c d e f g. Sharp and Flat pitches are available via as and af, respectively. Note that this encoding is an absolute one and does not differentiate in any way among "enharmonics", like es and f

Now how do we make this single note a music? We will have to combine it with other notes. There are two obvious way to do this.

||<^> attachment:haskore1-ex2.gif ||<#eeeeee> :+: ||<^> haskore1-ex3.gif || = ||<^> haskore1-ex4.gif ||

The sequential composition, expressed by the operator (:+:) :: Music -> Music -> Music results in a value that represents both values in temporal composition (I am tempted to write "played one after the other", but there is no playing going on for now, so this would be a bad idea)

||<^> attachment:haskore1-ex2.gif ||<#eeeeee> :=: ||<^> haskore1-ex3.gif || = ||<^> haskore1-ex5.gif ||

The parallel composition :=: has the same type, but composes both values to one that represents them simultaneously ("played at the same time").

Using :t, we can see that both Operators take two Music values and return a Music value. Using these Features and the rests (which are named qnr, hnr etc., for quarter note rest, half note rest), we can already construct a lot of music.

Other useful operators (Actually, all the "operators" mentioned are just infix type constructors for Music values - see Basics.lhs line 34...43. The semantics of the constructed Score is to be added later) are Trans :: Int -> Music -> Music and Tempo :: Ratio Int -> Music -> Music. Use them to Transpose tunes, or to change their speed.

The list at the end of each note does not seem to make much sense until now. It is intended to hold notewise attributes. For example, the Volume of a Note can be kept here, since it might be different for each single Note. c 4 (1%4) [Volume 50], for example, would represent a quarter "c 4", played at "Volume 50". While we have a clear definition for "c 4" and "1%4", we don't have one for "Volume 50". This will become important now, when we want to make our music audible.

Output

What is missing now to play that music? Since there is no inherent support for Music in "Computers" (Turing-Equivalent Machines), we need to output something that a given synthesis equipment understands. A canonical choice for score data would be midi. The only information still missing in our Music Data is midi channel numbers.

A Haskore abstraction for converting score Data to something closer to acoustical reality is a "Performance". There is a function perform :: PMap -> Context -> Music -> Performance that can convert Music to a Performance, given a PMap (a Mapping from player Names to Players) and a Context (which is not interesting right now, but can control how various performances will be coordinated).

For example, we can turn an arbitrary Music Value to a Performance like this:

#!syntax haskell Main> perform (\_->defPlayer) defCon example1 [Event{eTime=0.0,eInst="piano",ePitch=48,eDur=0.5,eVol=113.5,pFields=[]}]

Using some default Values we nicked from TestHaskore.lhs. We see that the Volume 100 note attribute was converted to an event volume of 113.5. Considering that result, it's questionable if the default values were chosen all that wisely.

Using

#!syntax haskell Main> perform (\_->defPlayer) defCon example2 [Event{eTime=0.0,eInst="piano",ePitch=48,eDur=0.5,eVol=113.5,pFields=[]},

Event{eTime=0.5,eInst="piano",ePitch=48,eDur=0.5,eVol=113.5,pFields=[]},

...

We see that a performance is a flat list of Events as opposed to a Score value, which is rather tree-like in structure.

Now we are ready to write these events out to some musical format, for example midi. We needed some additional information to write out the midi file, namely a "patch map" to map the instrument name "piano" to the midi "Acoustic Grand Piano" (Instrument 1) on Channel 1. For other instruments, you could just extend the list. (For a list of instrument names, see Haskore/Src/GeneralMidi.lhs)

#!syntax haskell Main> outputMidiFile "example2.mid" (performToMidi (perform (\_->defPlayer) defCon example2) [("piano","Acoustic Grand Piano",1)])

This call gives no visible output. After that, you should, however, find example2.mid in your current directory. Open it with your favourite (I recommend "Rosegarden" [1] on Unix-derivate systems) midi Sequencer/Editor tool, or play it back. For ease of use i put all these bits together to a function in example.lhs

#!syntax haskell Main> midiout "example2.mid" example2

Functional Music

How could functional programming help us specify music? Haskell variables can of course take Music values, and build other values from them, so we can for example Transpose a given piece of music.

We could, for example, write a function that converts a list of intervals (integers) and a Music value to a chord.

#!syntax haskell mychord intervals base = map (\n->Trans n base) intervals minor = [0,3,7] major = [0,4,7]

0 is the prime, 3 the small third, 4 the large third and 7 the fifth. Now we can specify a simple chord progression:

#!syntax haskell example3 = (c 4 (1%4) [Volume 100]) :+:

          (g 4 (1%4) [Volume 100]) :+:
          (f 4 (1%4) [Volume 100]) :+:
          (c 4 (1%4) [Volume 100])

example4 = mychord major example3

As we see, mychord works with any music value. What it can't do is building different chords on top of a sequence of notes. So:

#!syntax haskell example5 = (mychord major (c 4 (1%4) [Volume 100])) :+:

          (mychord minor (d 4 (1%4) [Volume 100])) :+:
          (mychord major (g 4 (1%4) [Volume 100])) :+:
          (mychord major (c 4 (1%4) [Volume 100])) 

gives us a sequence with different kinds of chords.

Scale Theory

Now as one might know, different "Modes" of (European, traditional) Music use the same sequence of intervals, just starting from a different point in the sequence (Mode) and note (Key, Tonic). Using the Major scale as the original one:

#!syntax haskell > maj_skips = [2,2,1,2,2,2,1]

we declare a helper function runsum, which just sums up numbers in a list continuously.

#!syntax haskell runsum = scanl (+) 0

Now we can declare all the scales based on the major scale in one function, and for example, have a look at the intervals of the minor scale.

#!syntax haskell scale kind = runsum (drop kind (cycle maj_skips))

#!syntax haskell Main> take 8 (scale 5) [0,2,3,5,7,8,10,12]

We need cycle because scales repeat all 8 "steps" (every octave). The intervals of the major scale, taken from the sixth (since we start counting with 0: 5), give the (natural or aeolian) minor scale.

We declare a simple melody "step" wise, as in "steps" of a scale (the 8th step being the octave, 12 halftones, and the other steps depending on the exact scale used)

#!syntax haskell simplemelody = [(0,1%4),(5,1%2),(4,1%8),(3,1%8),(2,1%4),(5,1%2),(0,1%4)]


* Specify a value of type (Ratio Int->Music) and call it
base (as it will become the base tone (Tonic) of our melody,
if we give it an arbitrary length)
* Find out how many halftones are between the base of a scale and
the "step" wanted: trans n = (fromInteger (scl !! n))
* Transpose the base note, given a length to complete it, about that 
amount, to get the ultimate result.

#!syntax haskell

realize ::  Int -> (Ratio Int->Music) -> (Int,Ratio Int) -> Music
realize kind base (n,len) = Trans (trans n) (base len)
    where
      trans n = (fromInteger (scl !! n)) 
      scl = (scale kind)

We'll write another helper, that realizes a few notes and puts them in a sequence:

#!syntax haskell testrealize kind base melody = allseq $ map (realize kind base) melody

Making it Audible

Now we can realize our melody in an arbitrary scale, on an arbitrary base pitch, like for example:

#!syntax haskell Main> midiout "major.mid" (testrealize 0 (\l->(c 4 l [Volume 100])) simplemelody) Main> midiout "minor.mid" (testrealize 5 (\l->(d 4 l [Volume 100])) simplemelody)

in c major, and then in d minor. This task (transpose and change mode) makes a nice (and often-cursed) exercise for music students. Thanks to Haskell we were able to solve it in some 20 lines of code.

Now of course we also want to describe music that's not only single-voiced. For example, we could want to describe the a'th three and four note chord in our scale:

#!syntax haskell tri a = [a,a+2,a+4] tet a = [a,a+2,a+4,a+6]

and put the chords numbered 1, 5, 4 and 1 after each other (if you ever thought you couldn't tell a I-IV-V-I progression even if you saw one, now you did), putting in a four note chord here and there, and adding an octave to the last I:

#!syntax haskell test2d:: (Int,Ratio Int) test2d = [allength (1%2) (tri 0),

         allength (1%2) (tet 3),
         allength (1%2) (tet 4),
         allength (1%2) (8:(tri 0))]
     where allength l= map (\a->(a,l))

Now we only need to map realize twice to that, and then fold twice (first in parallel, then serially) to make this a Music value.

#!syntax haskell rea2d kind base melody = allseq $ map allpar $ map (map (realize kind base)) melody

Try:

#!syntax haskell midiout "iivviprog.mid" (rea2d 5 (\l->(f 5 l [Volume 100])) test2d)

And listen to it.

This would be all for this issue of TMR. If you should feel bored, try Haskore yourself. For example, you could:

* Try to write an own melody, either using realize to later change scale, or without.
* Put fitting chords along simplemelody, or put a melody along test2d
* Read in some existing midi files using readMidi and try to analyze the resulting Music values. (for example, asking: are all notes in one scale? which ones aren't? what's their harmonic function?)
* If you're really bored: get some sheet music and realize it in Haskore.

Anyway, stay tuned for the next Issue of TMR. If you have any questions, join us on freenode (just point your IRC client to irc.freenode.net), channel #haskell, and don't hesitate to ask me.

     Bastiaan Zapf (freenode basti_)

CategoryArticle