hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Array.CSV.Midi.MND

Contents

Description

Functions for reading midi note data (MND) from CSV files. This is not a generic text midi notation. The defined commands are on and off, but others may be present. Non-integral note number and key velocity data are allowed.

Synopsis

Documentation

data_value_pp :: Real t => Int -> t -> String Source #

If r is whole to k places then show as integer, else as float to k places.

type Channel = Word8 Source #

Channel values are 4-bit (0-15).

csv_mnd_hdr :: [String] Source #

The required header field.

type MND t n = (t, String, n, n, Channel, [Param]) Source #

Midi note data, the type parameters are to allow for fractional note & velocity values. The command is a string, on and off are standard, other commands may be present.

unwords csv_mnd_hdr == "time on/off note velocity channel param"

csv_mnd_parse :: (Read t, Real t, Read n, Real n) => CSV_Table String -> [MND t n] Source #

csv_mnd_read :: (Read t, Real t, Read n, Real n) => FilePath -> IO [MND t n] Source #

Midi note data.

let fn = "/home/rohan/cvs/uc/uc-26/daily-practice/2014-08-13.1.csv"
m <- csv_mnd_read fn :: IO [MND Double Double]
length m == 17655
csv_mnd_write 4 "/tmp/t.csv" m

csv_mnd_write :: (Real t, Real n) => Int -> FilePath -> [MND t n] -> IO () Source #

Writer.

MND Seq forms

type Event n = (n, n, Channel, [Param]) Source #

(p0=midi-note,p1=velocity,channel,param)

midi_tseq_to_midi_wseq :: (Num t, Eq n) => Tseq t (Begin_End (Event n)) -> Wseq t (Event n) Source #

Translate from Tseq form to Wseq form.

mnd_to_tseq :: Num n => [MND t n] -> Tseq t (Begin_End (Event n)) Source #

Ignores non on/off messages.

csv_mnd_read_tseq :: (Read t, Real t, Read n, Real n) => FilePath -> IO (Tseq t (Begin_End (Event n))) Source #

Tseq form of csv_mnd_read, channel information is retained, off-velocity is zero.

csv_mnd_write_tseq :: (Real t, Real n) => Int -> FilePath -> Tseq t (Begin_End (Event n)) -> IO () Source #

Tseq form of csv_mnd_write, data is .

MNDD (simplifies cases where overlaps on the same channel are allowed).

csv_mndd_hdr :: [String] Source #

Message should be note for note data.

type MNDD t n = (t, t, String, n, n, Channel, [Param]) Source #

csv_mndd_read :: (Read t, Real t, Read n, Real n) => FilePath -> IO [MNDD t n] Source #

Midi note/duration data.

csv_mndd_write :: (Real t, Real n) => Int -> FilePath -> [MNDD t n] -> IO () Source #

Writer.

MNDD Seq forms

mndd_to_wseq :: [MNDD t n] -> Wseq t (Event n) Source #

Ignores non note messages.

csv_mndd_read_wseq :: (Read t, Real t, Read n, Real n) => FilePath -> IO (Wseq t (Event n)) Source #

Wseq form of csv_mndd_read.

csv_mndd_write_wseq :: (Real t, Real n) => Int -> FilePath -> Wseq t (Event n) -> IO () Source #

Wseq form of csv_mndd_write.

Composite

csv_midi_parse_wseq :: (Read t, Real t, Read n, Real n) => CSV_Table String -> Wseq t (Event n) Source #

Parse either MND or MNDD data to Wseq, CSV type is decided by header.

csv_midi_read_wseq :: (Read t, Real t, Read n, Real n) => FilePath -> IO (Wseq t (Event n)) Source #