Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
- newtype Beats = Beats {}
- newtype Seconds = Seconds {}
- newtype BPS = BPS {}
- decodeFile :: T -> Either [T Beats T] [T Seconds T]
- encodeFileBeats :: Type -> Integer -> [T Beats T] -> T
- minResolution :: [T Beats T] -> Integer
- readTempo :: T -> Maybe BPS
- showTempo :: BPS -> T
- makeTempo :: Beats -> Seconds -> BPS
- applyTempo :: BPS -> Beats -> Seconds
- unapplyTempo :: BPS -> Seconds -> Beats
- applyTempoTrack :: TempoMap -> T Beats a -> T Seconds a
- unapplyTempoTrack :: TempoMap -> T Seconds a -> T Beats a
- data TempoMap
- makeTempoMap :: T Beats T -> TempoMap
- applyTempoMap :: TempoMap -> Beats -> Seconds
- unapplyTempoMap :: TempoMap -> Seconds -> Beats
- readSignature :: T -> Maybe Beats
- showSignature :: Beats -> Maybe T
- data MeasureMap
- type MeasureBeats = (Int, Beats)
- data MeasureMode
- measures :: Int -> Beats -> Beats
- makeMeasureMap :: MeasureMode -> T Beats T -> MeasureMap
- applyMeasureMap :: MeasureMap -> Beats -> MeasureBeats
- unapplyMeasureMap :: MeasureMap -> MeasureBeats -> Beats
- trackName :: C t => T t T -> Maybe String
- setTrackName :: C t => String -> T t T -> T t T
- readTrackName :: T -> Maybe String
- showTrackName :: String -> T
- trackSplitZero :: C t => T t a -> ([a], T t a)
- trackGlueZero :: C t => [a] -> T t a -> T t a
- trackTakeZero :: C t => T t a -> [a]
- trackDropZero :: C t => T t a -> T t a
- trackJoin :: (C t, Ord a) => T t (T t a) -> T t a
- trackSplit :: C t => t -> T t a -> (T t a, T t a)
- trackTake :: C t => t -> T t a -> T t a
- trackDrop :: C t => t -> T t a -> T t a
- extractFirst :: C t => (a -> Maybe b) -> T t a -> Maybe ((t, b), T t a)
Types
Musical time, measured in beats a.k.a. quarter notes.
Real time, measured in seconds.
A ratio between musical time and real time, measured in beats per second.
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
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.
applyTempoMap :: TempoMap -> Beats -> Seconds Source
unapplyTempoMap :: TempoMap -> Seconds -> Beats Source
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?
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
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.
readTrackName :: T -> Maybe String Source
showTrackName :: String -> T Source
Misc. track operations
trackSplitZero :: C t => T t a -> ([a], T t a) Source
Combines trackTakeZero
and trackDropZero
.
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.
trackTake :: C t => t -> T t a -> T t a Source
Drops all events at or after the given time from the event list.