midi-util-0.2: Utility functions for processing MIDI files

Safe HaskellNone
LanguageHaskell2010

Sound.MIDI.Util

Contents

Description

It is recommended to view this Haddock documentation using the -q local option so that, for example, the types Data.EventList.Relative.TimeBody.T, Sound.MIDI.File.T, and Sound.MIDI.File.Event.T don't all get displayed simply as T. Otherwise, hover over the types to see what is referred to.

Synopsis

Types

newtype Beats Source

Musical time, measured in beats a.k.a. quarter notes.

Constructors

Beats 

Fields

fromBeats :: Rational
 

newtype BPS Source

A ratio between musical time and real time, measured in beats per second.

Constructors

BPS 

Fields

fromBPS :: Rational
 

Reading/writing MIDI files

decodeFile :: T -> Either [T Beats T] [T Seconds T] Source

Assigns units to the tracks in a MIDI file. Supports both the common ticks-based files as well as real-time SMPTE-encoded files.

encodeFileBeats :: Type -> Integer -> [T Beats T] -> T Source

Encodes the tracks' beat positions in ticks, using the given resolution. Positions will be rounded if necessary; see minResolution.

minResolution :: [T Beats T] -> Integer Source

To correctly encode all the given tracks without rounding, the resolution must be a multiple of the returned number.

Tempos

readTempo :: T -> Maybe BPS Source

Extracts the tempo from a tempo change event.

showTempo :: BPS -> T Source

Creates a MIDI event to set the tempo to the given value. Rounds the tempo to the nearest whole "microseconds per beat" if necessary.

makeTempo :: Beats -> Seconds -> BPS Source

Creates a tempo as a ratio of a music duration to a real time duration.

applyTempo :: BPS -> Beats -> Seconds Source

Uses a tempo to convert from musical time to real time.

unapplyTempo :: BPS -> Seconds -> Beats Source

Uses a tempo to convert from real time to musical time.

data TempoMap Source

Converts between positions in musical time and real time.

Measures and time signatures

readSignature :: T -> Maybe Beats Source

Given a MIDI event, if it is a time signature event, returns the length of one measure set by the time signature.

showSignature :: Beats -> Maybe T Source

Given a measure length, tries to encode it as a MIDI time signature.

data MeasureMap Source

Converts between a simple beat position, and a measure offset plus a beat position.

type MeasureBeats = (Int, Beats) Source

A number of measures (starting from 0), and an offset within that measure (also starting from 0).

data MeasureMode Source

What to do when makeMeasureMap finds a misaligned time signature?

Constructors

Error

Throw an exception.

Ignore

Ignore it.

Truncate

Truncate the previous measure.

measures :: Int -> Beats -> Beats Source

The duration of a number of measures in a given time signature.

makeMeasureMap :: MeasureMode -> T Beats T -> MeasureMap Source

Computes the measure map, given the tempo track from the MIDI.

applyMeasureMap :: MeasureMap -> Beats -> MeasureBeats Source

Uses the measure map to compute which measure a beat position is in.

unapplyMeasureMap :: MeasureMap -> MeasureBeats -> Beats Source

Uses the measure map to convert a measures+beats position to just beats.

Track names

trackName :: C t => T t T -> Maybe String Source

Looks for a track name event at position zero.

setTrackName :: C t => String -> T t T -> T t T Source

Removes any existing track name events at position zero and adds a new one.

Misc. track operations

trackSplitZero :: C t => T t a -> ([a], T t a) Source

trackGlueZero :: C t => [a] -> T t a -> T t a Source

Prepends the given events to the event list at position zero.

trackTakeZero :: C t => T t a -> [a] Source

Returns the list of events at position zero of the event list.

trackDropZero :: C t => T t a -> T t a Source

Drops all events at position zero of the event list.

trackJoin :: (C t, Ord a) => T t (T t a) -> T t a Source

Equivalent to join, except T doesn't have a Monad instance, presumably because merge has an Ord constraint.

trackSplit :: C t => t -> T t a -> (T t a, T t a) Source

Combines trackTake and trackDrop.

trackTake :: C t => t -> T t a -> T t a Source

Drops all events at or after the given time from the event list.

trackDrop :: C t => t -> T t a -> T t a Source

Drops the given amount of time from the start of the event list. Events that are exactly at the time that is dropped will be kept in the list.

extractFirst :: C t => (a -> Maybe b) -> T t a -> Maybe ((t, b), T t a) Source

Finds and extracts the first event for which the function returns Just.