\subsection{Midi} \seclabel{midi} Midi (``musical instrument digital interface'') is a standard protocol adopted by most, if not all, manufacturers of electronic instruments. At its core is a protocol for communicating \keyword{musical events} (note on, note off, key press, etc.) as well as so-called \keyword{meta events} (select synthesizer patch, change volume, etc.). Beyond the logical protocol, the Midi standard also specifies electrical signal characteristics and cabling details. In addition, it specifies what is known as a \keyword{standard Midi file} which any Midi-compatible software package should be able to recognize. Over the years musicians and manufacturers decided that they also wanted a standard way to refer to {\em common} or {\em general} instruments such as ``acoustic grand piano'', ``electric piano'', ``violin'', and ``acoustic bass'', as well as more exotic ones such as ``chorus aahs'', ``voice oohs'', ``bird tweet'', and ``helicopter''. A simple standard known as \keyword{General Midi} was developed to fill this role. It is nothing more than an agreed-upon list of instrument names along with a \keyword{program patch number} for each, a parameter in the Midi standard that is used to select a Midi instrument's sound. Most ``sound-blaster''-like sound cards on conventional PC's know about Midi, as well as General 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 a different \keyword{channel}. Modern keyboards and tone generators are quite amazing little beasts. Not only is the sound quite good (when played on a good stereo system), but they are also usually \keyword{multi-timbral}, which means they are able to generate many different sounds simultaneously, as well as \keyword{polyphonic}, meaning that simultaneous instantiations of the same sound are possible. If you decide to use the General Midi features of your sound-card, you need to know about another set of conventions known as ``General Midi''. The most important aspect of General Midi is that Channel 10 (9 in Haskore's 0-based numbering) is dedicated to \keyword{percussion}. Haskore provides a way to specify a Midi channel number and General Midi instrument selection for each \code{Instr} in a Haskore 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 \code{MidiMusic.T} object in Haskore. In this section the top-level code needed by the user to invoke this functionality will be described, along with the gory details. \begin{haskelllisting} > module Haskore.Interface.MIDI.Write > (fromRhythmicPerformance, fromRhythmicPerformanceMixed, > fromGMPerformance, fromGMPerformanceMixed, > fromGMPerformanceAuto, fromGMPerformanceMixedAuto, > fromRhythmicMusic, fromRhythmicMusicMixed, > fromGMMusic, fromGMMusicAuto, > fromGMMusicMixed, fromGMMusicMixedAuto, > volumeHaskoreToMIDI, volumeMIDIToHaskore) > where > import qualified Sound.MIDI.File as MidiFile > import qualified Sound.MIDI.File.Event as MidiFileEvent > import qualified Sound.MIDI.File.Event.Meta as MetaEvent > import qualified Sound.MIDI.Message.Channel as ChannelMsg > import qualified Sound.MIDI.Message.Channel.Voice as Voice > import qualified Haskore.Interface.MIDI.InstrumentMap as InstrMap > import qualified Haskore.Interface.MIDI.Note as MidiNote > import qualified Haskore.Music.GeneralMIDI as MidiMusic > import qualified Haskore.Music.Rhythmic as RhyMusic > import qualified Haskore.Performance as Performance > import qualified Haskore.Performance.Context as Context > import qualified Haskore.Performance.BackEnd as PerformanceBE > import qualified Haskore.Performance.Fancy as FancyPf > import qualified Data.EventList.Relative.TimeBody as TimeList > import qualified Data.EventList.Relative.MixedBody as TimeList > import qualified Data.EventList.Relative.BodyBody as BodyBodyList > import qualified Haskore.Basic.Pitch as Pitch > import qualified Numeric.NonNegative.Class as NonNeg > import qualified Haskore.General.Map as Map > import Data.Ord.HT (limit, ) > import Data.Maybe (mapMaybe, ) > import Control.Monad.Trans.State (state, evalState, ) > import Control.Monad (liftM, ) \end{haskelllisting} Instead of converting a Haskore \code{Performance.T} directly into a Midi file, Haskore first converts it into a datatype that {\em represents} a Midi file, which is then written to a file in a separate pass. This separation of concerns makes the structure of the Midi file clearer, makes debugging easier, and provides a natural path for extending Haskore's functionality with direct Midi capability. Here is the basic structure of the modules and functions: \begin{center} \input{src/Doc/Pics/midi} \end{center} Given instrument and drum maps (\secref{user-patch-map}), a performance is converted to a datatype representing a Standard Midi File of type 0 (\code{Mixed} - one track containing data of all channels) or type 1 (\code{Parallel} - tracks played simultaneously) using the \function{from*PerformanceMixed} and \function{from*Performance} functions, respectively. The ``\code{Mixed}'' mode is the only one which can be used in principle for infinite music, since the number of tracks is stored explicitly in the MIDI file which depends on the number of instruments actually used in the song. Nevertheless such a stream can not be written to a pipe (not to speak of a physical disk), since the binary MIDI file format stores lengths of tracks. The functions with names of the form \function{fromRhythmicPerformance*} convert from generic rhythmic music performances using appropriate tables. In contrast to that, for General MIDI music the instrument and drum maps are fixed. There are the two variants \function{fromGMPerformance*}, which allows explicit assignment of instruments to channels, and \function{fromGMPerformance*Auto}, which assigns the channels automatically one by one. \begin{haskelllisting} > type Perf time dyn drum instr = > Performance.T time dyn (RhyMusic.Note drum instr) > type NotePerfToBE dyn drum instr = > dyn -> Pitch.Relative -> > RhyMusic.Note drum instr -> MidiNote.T > getInstrument :: > Performance.Event time dyn (RhyMusic.Note drum instr) -> Maybe instr > getInstrument = > RhyMusic.maybeInstrument . RhyMusic.body . Performance.eventNote > fromRhythmicPerformance :: > (NonNeg.C time, RealFrac time, RealFrac dyn, > Eq drum, Eq instr) => > InstrMap.ChannelProgramPitchTable drum -> > InstrMap.ChannelProgramTable instr -> > Perf time dyn drum instr -> MidiFile.T > fromRhythmicPerformance dMap iMap = > fromRhythmicPerformanceBase > (const (MidiNote.fromRhyNote > (InstrMap.lookup dMap) (InstrMap.lookup iMap))) > fromGMPerformance :: > (NonNeg.C time, RealFrac time, RealFrac dyn) => > (MidiMusic.Instrument -> ChannelMsg.Channel) -> > Performance.T time dyn MidiMusic.Note -> MidiFile.T > fromGMPerformance cMap = > fromRhythmicPerformanceBase > (const (MidiNote.fromGMNote cMap)) > fromGMPerformanceAuto :: > (NonNeg.C time, RealFrac time, RealFrac dyn) => > Performance.T time dyn MidiMusic.Note -> MidiFile.T > fromGMPerformanceAuto = > fromRhythmicPerformanceBase > (\instrs -> MidiNote.fromGMNote > (InstrMap.fromInstruments instrs)) > fromRhythmicPerformanceBase :: > (NonNeg.C time, RealFrac time, Eq instr) => > ([instr] -> NotePerfToBE dyn drum instr) -> > Perf time dyn drum instr -> MidiFile.T > fromRhythmicPerformanceBase makeNoteMap pf = > let splitList = TimeList.slice getInstrument pf > noteMap = makeNoteMap (mapMaybe fst splitList) > {- noteMap will always lookup instruments in a map > although the instrument will be the same for each track. -} > pfBEs = map (PerformanceBE.fromPerformance noteMap) > (map snd splitList) > in MidiFile.Cons MidiFile.Parallel (MidiFile.Ticks division) > (map trackFromPfBE pfBEs) > fromRhythmicPerformanceMixed :: > (NonNeg.C time, RealFrac time, RealFrac dyn, Eq drum, Eq instr) => > InstrMap.ChannelProgramPitchTable drum -> > InstrMap.ChannelProgramTable instr -> > Perf time dyn drum instr -> MidiFile.T > fromRhythmicPerformanceMixed dMap iMap = > fromRhythmicPerformanceMixedBase > (MidiNote.fromRhyNote > (InstrMap.lookup dMap) (InstrMap.lookup iMap)) > fromGMPerformanceMixed :: > (NonNeg.C time, RealFrac time, RealFrac dyn) => > (MidiMusic.Instrument -> ChannelMsg.Channel) -> > Performance.T time dyn MidiMusic.Note -> MidiFile.T > fromGMPerformanceMixed cMap = > fromRhythmicPerformanceMixedBase (MidiNote.fromGMNote cMap) > fromGMPerformanceMixedAuto :: > (NonNeg.C time, RealFrac time, RealFrac dyn) => > Performance.T time dyn MidiMusic.Note -> MidiFile.T > fromGMPerformanceMixedAuto pf = > let instrs = mapMaybe fst (TimeList.slice getInstrument pf) > cMap = InstrMap.fromInstruments instrs > in fromRhythmicPerformanceMixedBase > (MidiNote.fromGMNote cMap) pf > fromRhythmicPerformanceMixedBase :: > (NonNeg.C time, RealFrac time, RealFrac dyn, Eq instr) => > NotePerfToBE dyn drum instr -> > Perf time dyn drum instr -> MidiFile.T > fromRhythmicPerformanceMixedBase noteMap pf = > MidiFile.Cons MidiFile.Mixed (MidiFile.Ticks division) > [trackFromPfBE (PerformanceBE.fromPerformance noteMap pf)] \end{haskelllisting} The more comfortable function \function{fromRhythmicMusic} turns a \code{MidiMusic.T} immediately into a \code{MidiFile.T}. Thus it needs also a \code{Context} and drum and instrument table. The signature of \function{fromGMMusic} is chosen so that it can be used as an inverse to \function{ReadMidi.toGMMusic}. The function \function{fromGMMusicAuto} is similar but doesn't need a \code{InstrMap.ChannelTable} because it creates one from the set of instruments actually used in the \code{MidiMusic.T}. \begin{haskelllisting} > fromRhythmicMusic, fromRhythmicMusicMixed :: > (NonNeg.C time, RealFrac time, RealFrac dyn, > Ord drum, Ord instr) => > (InstrMap.ChannelProgramPitchTable drum, > InstrMap.ChannelProgramTable instr, > Context.T time dyn (RhyMusic.Note drum instr), > RhyMusic.T drum instr) -> MidiFile.T > fromGMMusic, fromGMMusicMixed :: > (NonNeg.C time, RealFrac time, RealFrac dyn) => > (InstrMap.ChannelTable MidiMusic.Instr, > Context.T time dyn MidiMusic.Note, MidiMusic.T) -> MidiFile.T > fromGMMusicAuto, fromGMMusicMixedAuto :: > (NonNeg.C time, RealFrac time, RealFrac dyn) => > (Context.T time dyn MidiMusic.Note, MidiMusic.T) -> MidiFile.T > fromRhythmicMusic (dm,im,c,m) = > fromRhythmicMusicBase (fromRhythmicPerformance dm im) c m > fromRhythmicMusicMixed (dm,im,c,m) = > fromRhythmicMusicBase (fromRhythmicPerformanceMixed dm im) c m > fromGMMusic (cm,c,m) = > fromRhythmicMusicBase (fromGMPerformance (InstrMap.lookup cm)) c m > fromGMMusicMixed (cm,c,m) = > fromRhythmicMusicBase (fromGMPerformanceMixed (InstrMap.lookup cm)) c m > fromGMMusicAuto (c,m) = > fromRhythmicMusicBase fromGMPerformanceAuto c m > fromGMMusicMixedAuto (c,m) = > fromRhythmicMusicBase fromGMPerformanceMixedAuto c m > fromRhythmicMusicBase :: > (NonNeg.C time, RealFrac time, Fractional dyn, Ord dyn, > Ord drum, Ord instr) => > (Perf time dyn drum instr -> MidiFile.T) -> > Context.T time dyn (RhyMusic.Note drum instr) -> > RhyMusic.T drum instr -> MidiFile.T > fromRhythmicMusicBase p c m = p (Performance.fromMusic FancyPf.map c m) \end{haskelllisting} General Midi specific definitions are imported from \module{GeneralMidi} (see \secref{general-midi}). The Midi file datatype itself is imported from the module \module{MidiFile}, functions for writing it to files are found in the module \module{SaveMidi}, and functions for reading MIDI files come from the modules \module{LoadMidi} and \module{ReadMidi}. All these modules are described later in this section. \subsubsection{The Gory Details} Some preliminaries, otherwise known as constants: \begin{haskelllisting} > division :: MidiFile.Tempo > division = 96 -- time-code division: 96 ticks per quarter note \end{haskelllisting} When writing Type 1 Midi Files, we can associate each instrument with a separate track. So first we partition the event list into separate lists for each instrument. (Again, due to the limited number of MIDI channels, we can handle no more than 15 instruments.) The crux of the conversion process is \function{trackFromPfBE}, which converts a \type{Performance.T} into a stream of \type{Midi.Event}s. As said before, we can't use absolute times, but the difficulties with relatively timed events are handled by the \module{Data.EventList.Relative.TimeBody}. We first convert all Performance events to MIDI events preserving the time stamps from the Performance. In the second step we discretize the time stamps with \function{Data.EventList.Relative.TimeBody.resample}, yielding a perfect \type{Midi.Track}. On the one hand with this order of execution it may be that notes with equal duration can have slightly different durations in the MIDI file. On the other hand small rests between notes or small overlappings are avoided.% \footnote{It would be better to define \code{rate = 4*division}, since this would map a quarter note to \code{division} ticks, as stated by the MIDI File specification. For compensation \code{SetTempo} could be set to 250000, meaning a quarter second per quarter note, or one second per whole note.} We manage a \module{Map} which stores the active program number of each MIDI channel. If a note on a channel needs a new program or there was no note before, a \code{ProgChange} is inserted in the stream of MIDI events. The function \function{updateChannelMap} updates this map each time a note occurs and it returns the MIDI channel for the note and a \code{Maybe} that contains a program change if necessary. \begin{haskelllisting} > trackFromPfBE :: (NonNeg.C time, RealFrac time) => > PerformanceBE.T time MidiNote.T -> MidiFile.Track > trackFromPfBE = > uncurry TimeList.cons setTempo . > TimeList.mapBody MidiFileEvent.MIDIEvent . > TimeList.resample rate . > TimeList.foldr TimeList.consTime addEvent TimeList.empty . > progChanges > > setTempo :: (MidiFile.ElapsedTime, MidiFileEvent.T) > setTempo = > (0, MidiFileEvent.MetaEvent > (MetaEvent.SetTempo MetaEvent.defltTempo)) > > getChanProg :: MidiNote.T -> (ChannelMsg.Channel, Voice.Program) > getChanProg note = (MidiNote.channel note, MidiNote.program note) > > updateChannelMap :: > (ChannelMsg.Channel, Voice.Program) -> > Map.Map ChannelMsg.Channel Voice.Program -> > (Maybe ChannelMsg.T, > Map.Map ChannelMsg.Channel Voice.Program) > updateChannelMap (midiChan, progNum) cm = > if Just progNum == Map.lookup cm midiChan > then (Nothing, cm) > else (Just (ChannelMsg.Cons midiChan (ChannelMsg.Voice > (Voice.ProgramChange progNum))), > Map.insert midiChan progNum cm) > > progChanges :: > PerformanceBE.T time MidiNote.T > -> PerformanceBE.T time (MidiNote.T, Maybe ChannelMsg.T) > progChanges = > flip evalState Map.empty . > TimeList.mapBodyM > (\(PerformanceBE.Event dur note) -> > liftM (\mn -> PerformanceBE.Event dur (note, mn)) > (state (updateChannelMap (getChanProg note)))) > > rate :: (Num a) => a > rate = 2 * fromIntegral division > -- ^ would be correctly 4 and the setTempo should be 250000 \end{haskelllisting} A source of incompatibility between Haskore and Midi is that Haskore represents notes with an onset and a duration, while Midi represents them as two separate events, an note-on event and a note-off event. Thus \function{addEvent} turns a Haskore \type{Event} into two \type{ChannelMsg.T}s, a \code{NoteOn} and a \code{NoteOff}. The function \function{TimeList.insert} is used to insert a \code{NoteOff} into the sequence of following MIDI events. It looks a bit cumbersome to insert every single \code{NoteOff}. An alternative may be to \function{merge} the list of \code{NoteOn} events with the list of \code{NoteOff} events. This won't work because the second one isn't ordered. Instead one could merge the two-element lists defined by \code{NoteOn} and \code{NoteOff} for each note using \function{fold}. But there might be infinitely many notes \dots \begin{haskelllisting} > addEvent :: > (NonNeg.C time) => > PerformanceBE.Event time > (MidiNote.T, Maybe ChannelMsg.T) -> > TimeList.T time ChannelMsg.T -> > BodyBodyList.T time ChannelMsg.T > addEvent ev mevs = > let (note, progChange) > = PerformanceBE.eventNote ev > d = PerformanceBE.eventDur ev > (mec0, mec1) = MidiNote.toMIDIEvents note > in maybe (TimeList.consBody mec0) > (\pcME -> > TimeList.consBody pcME . > TimeList.cons NonNeg.zero mec0) > progChange > (TimeList.insert d mec1 mevs) \end{haskelllisting} % *** The MIDI volume handling is still missing. One cannot express the Volume in terms of the velocity! Thus we need some new event constructor for changed controller values. % *** \begin{haskelllisting} > volumeHaskoreToMIDI :: (RealFrac a, Floating a) => a -> Int > volumeHaskoreToMIDI v = round (limit (0,127) (64 + 16 * logBase 2 v)) > volumeMIDIToHaskore :: Floating a => Int -> a > volumeMIDIToHaskore v = 2 ** ((fromIntegral v - 64) / 16) \end{haskelllisting}