%-*- 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/ToMidi.lhs. (See HSoM/MakeCode.bat.) \end{code} } \chapter{From Performance to Midi} \label{ch:midi} \begin{code} module Euterpea.IO.MIDI.ToMidi(toMidi, UserPatchMap, defST, defUpm, testMidi, testMidiA, test, testA, writeMidi, writeMidiA, play, playM, playA, makeMidi, mToMF, gmUpm, gmTest) where import Euterpea.Music.Note.Music import Euterpea.Music.Note.MoreMusic import Euterpea.Music.Note.Performance import Euterpea.IO.MIDI.GeneralMidi import Euterpea.IO.MIDI.MidiIO import Euterpea.IO.MIDI.ExportMidiFile import Sound.PortMidi import Data.List(partition) import Data.Char(toLower,toUpper) import Codec.Midi \end{code} writeMidi :: (Performable a) => FilePath -> Music a -> IO () writeMidi fn = exportMidiFile fn . testMidi writeMidiA :: (Performable a) => FilePath -> PMap Note1 -> Context Note1 -> Music a -> IO () writeMidiA fn pm con m = exportMidiFile fn (testMidiA pm con m) \indexwd{Midi} is shorthand for ``Musical Instrument Digital Interface,'' and is a standard protocol for controlling electronic musical instruments \cite{MIDI,General-MIDI}. This chapter describes how to convert an abstract {\em performance} as defined in Chapter \ref{ch:performance} into a \emph{standard Midi file} that can be played on any modern PC with a standard sound card. \section{An Introduction to Midi} \label{sec:midi} Midi is a standard adopted by most, if not all, manufacturers of electronic instruments and personal computers. At its core is a protocol for communicating \emph{musical events} (note on, note off, etc.) and so-called \emph{meta events} (select synthesizer patch, change tempo, etc.). Beyond the logical protocol, the Midi standard also specifies electrical signal characteristics and cabling details, as well as a \emph{standard Midi file} which any Midi-compatible software package should be able to recognize. Most ``sound-blaster''-like sound cards on conventional PC's know about Midi. However, the sound generated by such modules, and the sound produced from the typically-scrawny speakers on most PC's, is often quite poor. It is best to use an outboard keyboard or tone generator, which are attached to a computer via a Midi interface and cables. It is possible to connect several Midi instruments to the same computer, with each assigned to a different \emph{channel}. Modern keyboards and tone generators are quite good. Not only is the sound excellent (when played on a good stereo system), but they are also \emph{multi-timbral}, which means they are able to generate many different sounds simultaneously, as well as \emph{polyphonic}, meaning that simultaneous instantiations of the same sound are possible. %% Euterpea provides a way to specify a Midi channel number and General %% Midi instrument selection for each |InstrumentName| in a Euterpea %% composition. It also provides a means to generate a Standard Midi %% File, which can then be played using any conventional Midi software. %% Finally, it provides a way for existing Midi files to be read and %% converted into a Music object in Euterpea. In this section the %% top-level code needed by the user to invoke this functionality will be %% described, along with the gory details. \subsection{General Midi} Over the years musicians and manufacturers decided that they also wanted a standard way to refer to commonly used instrument sounds, such as ``acoustic grand piano,'' ``electric piano,'' ``violin,'' and ``acoustic bass,'' as well as more exotic sounds such as ``chorus aahs,'' ``voice oohs,'' ``bird tweet,'' and ``helicopter.'' A simple standard known as \emph{General Midi} was developed to fill this role. The General Midi standard establishes standard names for 128 common instrument sounds (also called ``patches'') and assigns an integer called the \emph{program number} (also called ``program change number''), to each of them. The instrument names and their program numbers are grouped into ``familes'' of instrument sounds, as shown in Table \ref{fig:gm-families}. \begin{table} %% \vspace{0.1in} \noindent \begin{tabular}{||l||l||c||l||l||}\hline \bf Family & \bf Program \# && \bf Family & \bf Program \# \\ \hline \hline Piano & 1-8 && Reed & 65-72 \\ \hline Chromatic Percussion & 9-16 && Pipe & 73-80 \\ \hline Organ & 17-24 && Synth Lead & 81-88 \\ \hline Guitar & 25-32 && Synth Pad & 89-96 \\ \hline Bass & 33-40 && Synth Effects & 97-104 \\ \hline Strings & 41-48 && Ethnic & 105-112 \\ \hline Ensemble & 49-56 && Percussive & 113-120 \\ \hline Brass & 57-64 && Sound Effects & 121-128 \\ \hline \hline \end{tabular} %% \vspace{0.1in} \caption{General Midi Instrument Families} \label{fig:gm-families} \end{table} Now recall that in Chapter \ref{ch:music} we defined a set of instruments via the |InstrumentName| data type (see Figure \ref{fig:instrument-names}). All of the names chosen for that data type come directly from the General Midi standard, except for two, |Percussion| and |Custom|, which were added for convenience and extensibility. By listing the constructors in the order that reflects this assignment, we can derive an |Enum| instance for |InstrumentName| that defines the method |toEnum| that essentially does the conversion from instrument name to program number for us. We can then define a function: \begin{spec} toGM :: InstrumentName -> ProgNum toGM Percussion = 0 toGM (Custom name) = 0 toGM in = fromEnum in \end{spec} \begin{code} type ProgNum = Int \end{code} that takes care of the two extra cases, which are simply assigned to program number 0. The derived |Enum| instance also defines a function |fromEnum| that converts program numbers to instrument names. We can then define: \begin{spec} fromGM :: ProgNum -> InstrumentName fromGM pn | pn >= 0 && pn <= 127 = fromEnum pn fromGM pn = error ("fromGM: " ++ show pn ++ " is not a valid General Midi program number") \end{spec} \syn{Design bug: Because the |IntrumentName| data type contains a non-nullary constructor, namely |Custom|, the |Enum| instance cannot be derived. For now it is defined in the module |GeneralMidi|, but a better solution is to redefine |InstrumentName| in such a way as to avoid this.} \subsection{Channels and Patch Maps} A Midi \emph{channel} is in essence a programmable instrument. You can have up to 16 channels, numbered 0 through 15, each assigned a different program number (corresponding to an instrument sound, see above). All of the dynamic ``Note On'' and ``Note Off'' messages (to be defined shortly) are tagged with a channel number, so up to 16 different instruments can be controlled independently and simultaneously. The assignment of Midi channels to instrument names is called a \emph{patch map}, and we define a simple association list to capture its structure: \begin{code} type UserPatchMap = [(InstrumentName, Channel)] \end{code} \begin{spec} type Channel = Int \end{spec} The only thing odd about Midi Channels is that General Midi specifies that Channel 10 (9 in Euterpea's 0-based numbering) is dedicated to \emph{percussion} (which is different from the ``percussive instruments'' described in Table \ref{fig:gm-families}). When Channel 10 is used, any program number to which it is assigned is ignored, and instead each note corresponds to a different percussion sound. In particular, General Midi specifies that the notes corresponding to Midi Keys 35 through 82 correspond to specific percussive sounds. Indeed, recall that in Chapter \ref{ch:more-music} we in fact captured these percussion sounds through the |PercussionSound| data type, and we defined a way to convert such a sound into an absolute pitch (i.e.\ |AbsPitch|). Euterpea's absolute pitches, by the way, are in one-to-one correspondence with Midi Key nunmbers. Except for percussion, the Midi Channel used to represent a particular instrument is completely arbitrary. Indeed, it is tedious to explicitly define a new patch map every time the instrumentation of a piece of music is changed. Therefore it is convenient to define a function that automatically creates a |UserPatchMap| from a list of instrument names: \begin{code} makeGMMap :: [InstrumentName] -> UserPatchMap makeGMMap ins = mkGMMap 0 ins where mkGMMap _ [] = [] mkGMMap n _ | n>=15 = error "MakeGMMap: Too many instruments." mkGMMap n (Percussion : ins) = (Percussion, 9) : mkGMMap n ins mkGMMap n (i : ins) = (i, chanList !! n) : mkGMMap (n+1) ins chanList = [0..8] ++ [10..15] -- channel 9 is for percussion \end{code} Note that, since there are only 15 Midi channels plus percussion, we can handle only 15 different instruments, and an error is signaled if this limit is exceeded.\footnote{It is conceivable to define a function to test whether or not two tracks can be combined with a Program Change (tracks can be combined if they don't overlap), but this remains for future work.} Finally, we define a function to look up an |InstrumentName| in a \newline |UserPatchMap|, and return the associated channel as well as its program number: \begin{code} upmLookup :: UserPatchMap -> InstrumentName -> (Channel, ProgNum) upmLookup upm iName = (chan, toGM iName) where chan = maybe (error ( "instrument " ++ show iName ++ " not in patch map") ) id (lookup iName upm) \end{code} %% Note that the function that does string matching ignores case, and %% allows substring matches. For example, |"chur"| matches |"Church %% Organ"|. Note also that the \emph{first} match succeeds, so using a %% substring should be done with care to be sure that the correct %% instrument is selected. \subsection{Standard Midi Files} The Midi standard defines the precise format of a \emph{standard Midi file}. At the time when the Midi standard was first created, disk space was at a premium, and thus a compact file structure was important. Standard Midi files are thus defined at the bit and byte level, and are quite compact. We are not interested in this low-level representation (any more than we are interested in the signals that run on Midi cables), and thus in Euterpea we take a more abstract approach: We define an algebraic data type called |Midi| to capture the abstract structure of a standard Midi file, and then define functions to convert values of this data type to and from actual Midi files. This separation of concerns makes the structure of the Midi file clearer, makes debugging easier, and provides a natural path for extending Euterpea's functionality with direct Midi capability. % (discussed further in Chapter \ref{ch:reactivity}). \begin{figure} \cbox{\small \begin{spec} -- From the |Codec.Midi| module data Midi = Midi { fileType :: FileType, timeDiv :: TimeDiv tracks :: [Track Ticks] } deriving (Eq, Show) data FileType = SingleTrack | MultiTrack | MultiPattern deriving (Eq, Show) type Track a = [(a, Message)] data TimeDiv = TicksPerBeat Int -- 1 through ($2^{15}$ - 1) | ... deriving (Show,Eq) type Ticks = Int -- 0 through ($2^{28}$ - 1) type Time = Double type Channel = Int -- 0 through 15 type Key = Int -- 0 through 127 type Velocity = Int -- 0 through 127 type Pressure = Int -- 0 through 127 type Preset = Int -- 0 through 127 type Tempo = Int -- microseconds per beat, 1 through ($2^{24}$ - 1) data Message = -- Channel Messages NoteOff { channel :: !Channel, key :: !Key, velocity :: !Velocity } | NoteOn { channel :: !Channel, key :: !Key, velocity :: !Velocity } | ProgramChange { channel :: !Channel, preset :: !Preset } | ... -- Meta Messages | TempoChange !Tempo | | ... deriving (Show,Eq) fromAbsTime :: (Num a) => Track a -> Track a fromAbsTime trk = zip ts' ms where (ts,ms) = unzip trk (_,ts') = mapAccumL (\acc t -> (t,t - acc)) 0 ts \end{spec}} \caption{Partial Definition of the |Midi| Data Type} \label{fig:MidiFile} \end{figure} We will not discuss the details of the functions that read and write the actual Midi files; the interested reader may find them in the modules |ReadMidi| and |OutputMidi|, respectively. Instead, we will focus on the |Midi| data type, which is defined in the module |Codec.Midi|. We do not need all of its functionality, and thus we show in Figure \ref{fig:MidiFile} only those parts of the module that we need for this chapter. Here are the salient points about this data type and the structure of Midi files: \begin{enumerate} \item There are three types of Midi files: \begin{itemize} \item A Format 0, or |SingleTrack|, Midi file stores its information in a single track of events, and is best used only for monophonic music. \item A Format 1, or |MultiTrack|, Midi file stores its information in multiple tracks that are played simultaneously, where each track normally corresponds to a single Midi Channel. \item A Format 2, or |MultiPattern|, Midi file also has multiple tracks, but they are temporally independent. \end{itemize} In this chapter we only use |SingleTrack| and |MultiTrack| Midi files, depending on how many Channels we need. \item The \indexwdhs{TimeDiv} field refers to the \emph{time-code division} used by the Midi file. We will always use 96 time divisions, or ``ticks,'' per quarternote, and thus this field will always be |TicksPerBeat 96|. \item The main body of a Midi file is a list of \indexwdhs{Track}s, each of which in turn is a list of time-stamped (in number of ticks) |Message|s (or ``events''). \item There are two kinds of \indexwdhs{Message}s: \emph{channel messages} and \emph{meta messages}. Figure \ref{fig:MidiFile} shows just those messages that we are interested in: \begin{enumerate} \item \indexhs{NoteOn} |NoteOn ch k v| turns on key (pitch) |k| with velocity (volume) |v| on Midi channel |ch|. The velocity is an integer in the range 0 to 127. \item \indexhs{NoteOff} |NoteOff ch k v| performs a similar function in turning the note off. \item \indexhs{ProgChange} |ProgChange ch pr| sets the program number for channel |ch| to |pr|. This is how an instrument is selected. \item \indexhs{SetTempo} |TempoChange t| sets the tempo to |t|, which is the time, in microseconds, of one whole note. Using 120 beats per minute as the norm, or 2 beats per second, that works out to 500,000 microseconds per beat, which is the default value that we will use. \end{enumerate} \end{enumerate} \section{Converting a Performance into Midi} Our goal is to convert a value of type |Performance| into a value of type |Midi|. We can summarize the situation pictorially as follows ... %% \begin{verbatim} %% *LoadMidi* *ReadMidi* %% +------+ =loadMidiFile= +-----------+ =readMidi= +-----------+ %% | Midi |----------------->| MidiFile |---------------->| Music | %% | File | | data type | | data type | %% | |<-----------------| |<----------------| | %% +------+ +-----------+ *HaskToMidi* +-----------+ %% *OutputMidi* *MidiFile* *Performance* *Basics* %% =outputMidiFile= =makeMidi= %% \end{verbatim} Given a |UserPatchMap|, a |Performance| is converted into a |Midi| value by the |toMidi| function. If the given |UserPatchMap| is invalid, it creates a new one using |makeGMMap| described earlier. \begin{code} toMidi :: Performance -> UserPatchMap -> Midi toMidi pf upm = let split = splitByInst pf insts = map fst split rightMap = if (allValid upm insts) then upm else (makeGMMap insts) in Midi (if length split == 1 then SingleTrack else MultiTrack) (TicksPerBeat division) (map (fromAbsTime . performToMEvs rightMap) split) division = 96 :: Int \end{code} The following function is used to test whether or not every instrument in a list is found in a |UserPatchMap|: \begin{code} allValid :: UserPatchMap -> [InstrumentName] -> Bool allValid upm = and . map (lookupB upm) lookupB :: UserPatchMap -> InstrumentName -> Bool lookupB upm x = or (map ((== x) . fst) upm) \end{code} %% lookupB [] _ = False %% lookupB ((y,_):ys) x = x == y || lookupB ys x The strategy is to associate each channel with a separate track. Thus we first partition the event list into separate lists for each instrument, and signal an error if there are more than 16: \begin{code} splitByInst :: Performance -> [(InstrumentName,Performance)] splitByInst [] = [] splitByInst pf = (i, pf1) : splitByInst pf2 where i = eInst (head pf) (pf1, pf2) = partition (\e -> eInst e == i) pf \end{code} Note how |partition| is used to group into |pf1| those events that use the same instrument as the first event in the performance. The rest of the events are collected into |pf2|, which is passed recursively to |splitByInst|. \indexhs{partition} \syn{|partition| takes a predicate and a list and returns a pair of lists: those elements that satisfy the predicate, and those that do not, respectively. |partition| is defined in the |List| Library as: \begin{spec} partition :: (a -> Bool) -> [a] -> ([a],[a]) partition p xs = foldr select ([],[]) xs where select x (ts,fs) | p x = (x:ts,fs) | otherwise = (ts, x:fs) \end{spec} } The crux of the conversion process is in |performToMEvs|, which converts a |Performance| into a stream of time-stamped messages, i.e.\ a stream of |(Tick,Message)| pairs: \begin{code} type MEvent = (Ticks, Message) defST = 500000 performToMEvs :: UserPatchMap -> (InstrumentName, Performance) -> [MEvent] performToMEvs upm (inm, pf) = let (chan,progNum) = upmLookup upm inm setupInst = (0, ProgramChange chan progNum) setTempo = (0, TempoChange defST) loop [] = [] loop (e:es) = let (mev1,mev2) = mkMEvents chan e in mev1 : insertMEvent mev2 (loop es) in setupInst : setTempo : loop pf \end{code} A source of incompatibilty between Euterpea and Midi is that Euterpea represents notes with an onset and a duration, while Midi represents them as two separate events, a note-on event and a note-off event. Thus |MkMEvents| turns a Euterpea |Event| into two |MEvents|, a |NoteOn| and a |NoteOff|. \begin{code} mkMEvents :: Channel -> Event -> (MEvent,MEvent) mkMEvents mChan (Event { eTime = t, ePitch = p, eDur = d, eVol = v}) = ( (toDelta t, NoteOn mChan p v'), (toDelta (t+d), NoteOff mChan p v') ) where v' = max 0 (min 127 (fromIntegral v)) toDelta t = round (t * 2.0 * fromIntegral division) \end{code} The time-stamp associated with an event in Midi is called a {\em delta-time}, and is the time at which the event should occur expressed in time-code divisions since the beginning of the performance. Since there are 96 time-code divisions per quarter note, there are 4 times that many in a whole note; multiplying that by the time-stamp on one of our |Event|s gives us the proper delta-time. In the code for |performToMEvs|, note that the location of the first event returned from |mkMEvents| is obvious; it belongs just where it was created. However, the second event must be inserted into the proper place in the rest of the stream of events; there is no way to know of its proper position ahead of time. The function \indexwdhs{insertMEvent} is thus used to insert an |MEvent| into an already time-ordered sequence of |MEvent|s. \begin{code} insertMEvent :: MEvent -> [MEvent] -> [MEvent] insertMEvent mev1 [] = [mev1] insertMEvent mev1@(t1,_) mevs@(mev2@(t2,_):mevs') = if t1 <= t2 then mev1 : mevs else mev2 : insertMEvent mev1 mevs' \end{code} \section{Putting It All Together} \todo{Move the code for the |PerformanceDefault| type class, the family of |play| functions, and so on, to this section.} %% We are almost done. All that remains is to write the |MidiFile| %% value into a real file. The details of this are surprisingly ugly, %% however, primarily because Midi files were invented at a time when %% disk space was precious, and thus a compact bit-level representation %% was chosen. Fortunately, there is a function in the |Euterpea| %% library that solves this problem for us: \indexhs{outputMidiFile} %% \begin{code} %% outputMidiFile :: String -> MidiFile -> IO () %% \end{code} %% To make this easier to use, let's define a function |test| that %% converts a |Music| value using a default |Context| into a %% |MidiFile| value, and then writes that to a file |"test.mid"|: %% \begin{code} %% test :: Music -> IO () %% test m = outputMidiFile "test.mid" %% (performToMidi (perform defCon m)) %% defCon :: Context %% defCon = Context { cTime = 0, %% cInst = AcousticGrandPiano, %% cDur = metro 120 qn, %% cKey = 0 } %% \end{code} %% So if you type |test m| for some |Music| value |m|, it will %% be converted to Midi and written to the file |"test.mid"|, which %% you can then play using whatever Midi-file player is supplied with %% your computer. If you are running the Hugs implementation of Haskell %% on Windows 95/NT or Linux, you can invoke the standard media player %% from Haskell by defining one of the following functions (for these to %% work you must also import |system| from the Hugs module %% |System|, via |import System (system)|): %% \indexhs{testWin95} %% \indexhs{testNT} %% \indexhs{testLinux} %% \begin{code} %% testWin95, testNT, testLinux :: Music -> IO () %% testWin95 m = do test m %% system "mplayer test.mid" %% return () %% testNT m = do test m %% system "mplay32 test.mid" %% return () %% testLinux m = do test m %% system "playmidi -rf test.mid" %% return () %% \end{code} %% For example, typing: %% \begin{code} %% testNT funkGroove %% \end{code} %% using Hugs on an NT system will write the |funkGroove| example from %% Chapter \ref{ch:music} into a Midi file and then automatically fire up %% the media player so that you can hear the result. Try the above for %% other examples from Chapter \ref{ch:music}, such as |cMajArp|, %% |cMajChd|, |pr12|, |waterfall|, and |main|. \out{ A default UserPatchMap ---------------------- \begin{code} defUpm :: UserPatchMap defUpm = [(AcousticGrandPiano,1), (Vibraphone,2), (AcousticBass,3), (Flute,4), (TenorSax,5), (AcousticGuitarSteel,6), (Viola,7), (StringEnsemble1,8), (AcousticGrandPiano,9)] -- the GM name for drums is unimportant, only channel 9 \end{code} Generating MIDI values and MIDI files ------------------------------------- Generate a MIDI datatype: \begin{code} testMidi :: Performable a => Music a -> Midi testMidi m = toMidi (defToPerf m) defUpm testMidiA :: Performable a => PMap Note1 -> Context Note1 -> Music a -> Midi testMidiA pm con m = toMidi (toPerf pm con m) defUpm \end{code} Generate a MIDI file: \begin{code} test :: Performable a => Music a -> IO () test m = exportMidiFile "test.mid" (testMidi m) testA :: Performable a => PMap Note1 -> Context Note1 -> Music a -> IO () testA pm con m = exportMidiFile "test.mid" (testMidiA pm con m) writeMidi :: Performable a => FilePath -> Music a -> IO () writeMidi fn = exportMidiFile fn . testMidi writeMidiA :: Performable a => FilePath -> PMap Note1 -> Context Note1 -> Music a -> IO () writeMidiA fn pm con m = exportMidiFile fn (testMidiA pm con m) \end{code} Alternatively, just run "play m", which will play the music through the default Midi output device on your computer: \begin{code} play :: Performable a => Music a -> IO () play = playM . testMidi \end{code} Or play a Midi data directly: \begin{code} playM :: Midi -> IO () playM midi = do initialize (defaultOutput playMidi) midi terminate return () \end{code} A play function that takes a PMap and Context: \begin{code} playA :: Performable a => PMap Note1 -> Context Note1 -> Music a -> IO () playA pm con m = let pf = fst $ perfDur pm con m in playM (toMidi pf defUpm) \end{code} %$ A more general function in the tradition of testMidi, makeMidi also takes a Context and a UserPatchMap. \begin{code} makeMidi :: (Music1, Context Note1, UserPatchMap) -> Midi makeMidi (m,c,upm) = toMidi (perform defPMap c m) upm \end{code} The most general export function from Music to a Midi file. \begin{code} mToMF :: PMap a -> Context a -> UserPatchMap -> FilePath -> Music a -> IO () mToMF pmap c upm fn m = let pf = perform pmap c m mf = toMidi pf upm in exportMidiFile fn mf \end{code} Some General Midi test functions (use with caution) --------------------------------------------------- A General MIDI user patch map; i.e. one that maps GM instrument names to themselves, using a channel that is the patch number modulo 16. This is for use ONLY in the code that follows, o/w channel duplication is possible, which will screw things up in general. \begin{code} gmUpm :: UserPatchMap gmUpm = map (\n -> (toEnum n, mod n 16 + 1)) [0..127] \end{code} Something to play each "instrument group" of 8 GM instruments; this function will play a C major arpeggio on each instrument. \begin{code} gmTest :: Int -> IO () gmTest i = let gMM = take 8 (drop (i*8) [0..127]) mu = line (map simple gMM) simple n = Modify (Instrument (toEnum n)) cMajArp in mToMF defPMap defCon gmUpm "test.mid" mu cMaj = [ n 4 qn | n <- [c,e,g] ] -- octave 4, quarter notes cMajArp = toMusic1 (line cMaj) \end{code} }