Portability | GHC (at least generalized newtype deriving) |
---|---|
Stability | unstable |
Maintainer | Stephen Tetley <stephen.tetley@gmail.com> |
Safe Haskell | None |
Concrete syntax tree for MIDI files.
Values are sometimes not interpreted. This means that the
the data types do not fully represent the sematics of MIDI
events, but all the data is either stored within the data type
or synthesizeable. Hence, readFile >>= writeFile
will
produce an identical binary [1].
[1] Or it should, failure indicates a bug...
- data DeltaTime
- type TagByte = Word8
- data MidiFile = MidiFile {
- mf_header :: MidiHeader
- mf_tracks :: [MidiTrack]
- data MidiHeader = MidiHeader {}
- newtype MidiTrack = MidiTrack {}
- data MidiFormat
- data MidiRunningStatus
- type MidiMessage = (DeltaTime, MidiEvent)
- data MidiEvent
- newtype MidiDataOther = MidiDataOther {}
- data MidiVoiceEvent
- data MidiSysExEvent
- = SysExSingle Word32 [Word8]
- | SysExCont Word32 [Word8] [MidiSysExContPacket]
- | SysExEscape Word32 [Word8]
- data MidiSysExContPacket = MidiSysExContPacket DeltaTime Word32 [Word8]
- data MidiSysCommonEvent
- = QuarterFrame Word8
- | SongPosPointer Word8 Word8
- | SongSelect Word8
- | UndefinedF4
- | UndefinedF5
- | TuneRequest
- | EOX
- data MidiSysRealTimeEvent
- data MidiMetaEvent
- data MidiTimeDivision
- data MidiTextType
- = GENERIC_TEXT
- | COPYRIGHT_NOTICE
- | SEQUENCE_NAME
- | INSTRUMENT_NAME
- | LYRICS
- | MARKER
- | CUE_POINT
- data MidiScaleType
- = MAJOR
- | MINOR
- | SCALE_OTHER Word8
MidiFile syntax.
All time values in a MIDI track are represented as a delta from the previous event rather than an absolute time.
DeltaTime is a newtype wrapper over Word32, note that in MIDI
files it is represented as a varlen
to potentially save
space that would otherwise require a four byte number.
data MidiHeader Source
Header
: format * num_tracks * time_division
TimeDivision
is often 384 or 480 ticks per beat.
The header is the start of a MIDI file, it is indicated by the
4 character marker MThd
.
Track
: [message]
In MIDI files, the start of a track is indicated by the 4
character marker MTrk
.
data MidiFormat Source
The file format - in a MIDI file this is a big-endian word16 with 0,1 or 2 being the only valid values.
data MidiRunningStatus Source
Running Status.
MIDI allows a compact representation of voice events where consecutive events (same event, same channel) only need to include the first event-channel byte - subsequent events only send payload until the next event or channel change.
Including MidiRunningStatus
in the data representation is
important for ZMidi as an aim is to allow round-tripping
of exisiting MIDI files. However it makes MIDI generation
more complicated (there is more scope to generate bad
output) - if you are only generating MIDI it is wise to always
set MidiRunningStatus
to RS_OFF
.
type MidiMessage = (DeltaTime, MidiEvent)Source
MIDI messages are pairs of DeltaTime
and Event
wrapped in
a newtype.
Sequential messages with delta time 0 are played simultaneously.
Recognised event types - some types (MidiEventOther
and
SysEx
) are not interpreted.
MidiEventOther MidiDataOther | An unrecognized event. This event is not expected in well formed MIDI, but the parser may insert it - if it encounters ill-formed data. |
VoiceEvent MidiRunningStatus MidiVoiceEvent | Voice event (e.g Note - they are tagged with Running Status, this is pertinent to parsing MIDI where a input stream may use running status to save space. If you are generating MIDI use RunningStatus with caution and ensure that consecutive events are all of the same sort. |
SysExEvent MidiSysExEvent | SysEx - system exclusive event. Usually synthesizer specific, not interpreted. |
SysCommonEvent MidiSysCommonEvent | SysCommon - system common event. |
SysRealTimeEvent MidiSysRealTimeEvent | SysRealTime - system realtime event. |
MetaEvent MidiMetaEvent | Meta event - interpreted (e.g. |
newtype MidiDataOther Source
Data events are events with tags from 0x00 to 0x7F.
Data events have no payload - they are represented only by the tag byte.
data MidiVoiceEvent Source
Voice events control the output of the synthesizer.
Note - change in v0.5.0 - the constructors have been reordered so the Ord instance matches the order of the tag bytes. Any code that relied on sorting MIDI events is likely to need reworking.
In serialized MIDI data the top 4 bits of the first byte of the Voice Event are a tag, the bottom 4 bits are the channel number. ZMidi stores the channel number with a Word8 though values should be limited to the range 0-15.
NoteOff Word8 Word8 Word8 | Note off. 80 to 8F (0 to F is channel number) * note * velocity Turn off a sounding note. |
NoteOn Word8 Word8 Word8 | Note on. 90 to 9F (0 to F is channel number) * note * velocity Start playing a note. |
NoteAftertouch Word8 Word8 Word8 | Polyphonic key pressure. A0 to AF (0 to F is channel number) * note * pressure_value Change of pressure applied to the synthesizer key. |
Controller Word8 Word8 Word8 | Set a controller. B0 to BF (0 to F is channel number) * controller_number * value Controller change, e.g. by a footswitch. |
ProgramChange Word8 Word8 | Set the program. C0 to CF (0 to F is channel number) * program_number Change the instrument playing on the specified channel. For playback on computers (rather than synthesizers) the program numbers will correspond to the General MIDI instrument numbers. |
ChanAftertouch Word8 Word8 | Channel pressure. D0 to DF (0 to F is channel number) * pressure_value |
PitchBend Word8 Word16 | Pitch bend E0 to EF (0 to F is channel number) * value Change the pitch of a sounding note. Often used to approximate microtonal tunings. NOTE - currently value is uninterpreted. |
data MidiSysExEvent Source
SysEx - system exclusive event.
SysExSingle Word32 [Word8] | Single SysEx event. F0 * length * data An uninterpreted sys-ex event. |
SysExCont Word32 [Word8] [MidiSysExContPacket] | SysEx sent as (non-standard) multiple continuation packets. F0 * length * packet1 ... [SysExContPacket] |
SysExEscape Word32 [Word8] | Escape sequence of one-or-more SysEx events. F7 * length * data |
data MidiSysExContPacket Source
Continuation packet for a (non-standard) multi-part SysEx event.
Apprently this format is use by Casio.
data MidiSysCommonEvent Source
System common event.
Common information for all channels in a system.
These events may not be pertinent to MIDI files generated on a computer (as opposed to MIDI generated by a synthesizer or sequencer).
QuarterFrame Word8 | Time code quarter frame. F1 * payload Note the payload is really a byte split into two 4-bit values, however here it is uninterpreted. |
SongPosPointer Word8 Word8 | Song position pointer. F2 * lsb * msb |
SongSelect Word8 | Song number. F3 * song_number Song number should be in the range 0..127. |
UndefinedF4 | Undefined system common event. F4 |
UndefinedF5 | Undefined system common event. F5 |
TuneRequest | Tune request. F6 Tune request message for analogue synthesizers. |
EOX | End-of-system-exclusive message. F7 |
data MidiSysRealTimeEvent Source
System real-time event.
These events may not be pertinent to MIDI files generated on a computer (as opposed to MIDI generated by a synthesizer or sequencer).
TimingClock | Timing signal. F8 |
UndefinedF9 | Undefined real time event. F9 |
StartSequence | Start playing a sequence. FA |
ContinueSequence | Continue playing a stopped sequence. FB |
StopSequence | Stop playing a sequence. FC |
UndefinedFD | Undefined real time event. FD |
ActiveSensing | Active sensing FE Synchronization pulse... |
SystemReset | Reset to power-up status. FF |
data MidiMetaEvent Source
Meta event
In Format 1 files general events (e.g. text events) should only appear in track 1. Certain events (e.g. end-of-track) can appear in any track where necessary.
TextEvent MidiTextType String | Text / copywright etc. FF * text_type * contents Free text field (e.g. copyright statement). The contents can notionally be any length. |
SequenceNumber Word16 | Sequence Number FF 00 02 * value Format 1 files - only track 1 should have a sequence number. Format 2 files - a sequence number should identify each track. The sequence number event should occur at the start of a track, before any non-zero time events. |
ChannelPrefix Word8 | Channel prefix FF 20 01 * channel Relay all meta and sys-ex events to the given channel. |
MidiPort Word8 | Midi port FF 21 01 * port Midi port number - used to workaround 16 channel limit... |
EndOfTrack | End-of-track event. FF 2F 00 |
SetTempo Word32 | Set tempo FF 51 03 * microseconds_per_quarter_note |
SMPTEOffset Word8 Word8 Word8 Word8 Word8 | SMPTE offest FF 54 05 * hour * minute * second * frac * subfrac The SMPTE time when a track should start. This event should occur at the start of a track, before any non-zero time events. |
TimeSignature Word8 Word8 Word8 Word8 | Time signature FF 58 04 * numerator * denominator * metro * num_32nd_notes |
KeySignature Int8 MidiScaleType | Key signature FF 59 02 * key_type * scale_type
|
SSME Word32 [Word8] | SSME FF 7F * length * data Sequencer specific meta-event - uninterpreted. |
MetaOther Word8 Word32 [Word8] | Unrecognized Meta Event FF * type * length * data |
data MidiTimeDivision Source
Default unit of time in the MIDI file.
data MidiTextType Source
Enumeration of the text meta event types.
data MidiScaleType Source
Scale type - major
or minor
or SCALE_OTHER
.
SCALE_OTHER
represents a parse error.