Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type Param = [(String, Double)]
- param_parse :: (Char, Char) -> String -> Param
- param_pp :: (Char, Char) -> Int -> Param -> String
- data_value_pp :: Real t => Int -> t -> String
- type Channel = Int
- csv_mnd_hdr :: [String]
- type Mnd t n = (t, String, n, n, Channel, Param)
- csv_mnd_parse_f :: (Read t, Real t, Read n, Real n) => (n -> m) -> Csv_Table String -> [Mnd t m]
- csv_mnd_parse :: (Read t, Real t, Read n, Real n) => Csv_Table String -> [Mnd t n]
- load_csv :: FilePath -> IO (Csv_Table String)
- csv_mnd_read :: (Read t, Real t, Read n, Real n) => FilePath -> IO [Mnd t n]
- csv_mnd_write :: (Real t, Real n) => Int -> FilePath -> [Mnd t n] -> IO ()
- type Event n = (n, n, Channel, Param)
- event_mnn :: Event t -> t
- event_ch :: Event t -> Channel
- event_eq_mnn :: Eq t => Event t -> Event t -> Bool
- event_eq_ol :: Eq t => Event t -> Event t -> Bool
- event_map :: (t -> u, t -> u, Channel -> Channel, Param -> Param) -> Event t -> Event u
- event_cast :: (t -> u) -> Event t -> Event u
- event_transpose :: Num a => a -> Event a -> Event a
- midi_tseq_to_midi_wseq :: (Num t, Eq n) => Tseq t (Begin_End (Event n)) -> Wseq t (Event n)
- midi_wseq_to_midi_tseq :: (Num t, Ord t) => Wseq t x -> Tseq t (Begin_End x)
- mnd_to_tseq :: Num n => [Mnd t n] -> Tseq t (Begin_End (Event n))
- csv_mnd_read_tseq :: (Read t, Real t, Read n, Real n) => FilePath -> IO (Tseq t (Begin_End (Event n)))
- csv_mnd_write_tseq :: (Real t, Real n) => Int -> FilePath -> Tseq t (Begin_End (Event n)) -> IO ()
- csv_mndd_hdr :: [String]
- type Mndd t n = (t, t, String, n, n, Channel, Param)
- mndd_compare :: (Ord t, Ord n) => Mndd t n -> Mndd t n -> Ordering
- csv_mndd_parse_f :: (Read t, Real t, Read n, Real n) => (n -> m) -> Csv_Table String -> [Mndd t m]
- csv_mndd_parse :: (Read t, Real t, Read n, Real n) => Csv_Table String -> [Mndd t n]
- csv_mndd_read :: (Read t, Real t, Read n, Real n) => FilePath -> IO [Mndd t n]
- csv_mndd_write :: (Real t, Real n) => Int -> FilePath -> [Mndd t n] -> IO ()
- mndd_to_wseq :: [Mndd t n] -> Wseq t (Event n)
- csv_mndd_read_wseq :: (Read t, Real t, Read n, Real n) => FilePath -> IO (Wseq t (Event n))
- csv_mndd_write_wseq :: (Real t, Real n) => Int -> FilePath -> Wseq t (Event n) -> IO ()
- csv_midi_parse_wseq_f :: (Read t, Real t, Read n, Real n, Num m, Eq m) => (n -> m) -> Csv_Table String -> Wseq t (Event m)
- csv_midi_parse_wseq :: (Read t, Real t, Read n, Real n) => Csv_Table String -> Wseq t (Event n)
- csv_midi_read_wseq :: (Read t, Real t, Read n, Real n) => FilePath -> IO (Wseq t (Event n))
Param ; Sound.SC3.Server.Param
Mnd
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.
csv_mnd_hdr :: [String] Source #
The required header (column names) 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.
note and velocity data is (0-127), channel is (0-15), param are ;-separated key:string=value:float.
unwords csv_mnd_hdr == "time on/off note velocity channel param"
all_notes_off = zipWith (\t k -> (t,"off",k,0,0,[])) [0.0,0.01 ..] [0 .. 127] csv_mnd_write 4 "/home/rohan/sw/hmt/data/csv/mnd/all-notes-off.csv" all_notes_off
csv_mnd_parse_f :: (Read t, Real t, Read n, Real n) => (n -> m) -> Csv_Table String -> [Mnd t m] 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" let fn = "/home/rohan/sw/hmt/data/csv/mnd/1080-C01.csv" m <- csv_mnd_read fn :: IO [Mnd Double Int] length m -- 1800 17655 csv_mnd_write 4 "/tmp/t.csv" m
Mnd Seq forms
event_map :: (t -> u, t -> u, Channel -> Channel, Param -> Param) -> Event t -> Event u Source #
Apply (mnn-f,vel-f,ch-f,param-f) to Event.
event_cast :: (t -> u) -> Event t -> Event u Source #
Apply f at mnn and vel fields.
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 #
Midi note/duration data.
The type parameters are to allow for fractional note & velocity values.
The command is a string, note
is standard, other commands may be present.
unwords csv_mndd_hdr == "time duration message note velocity channel param"
mndd_compare :: (Ord t, Ord n) => Mndd t n -> Mndd t n -> Ordering Source #
Compare sequence is: start-time,channel-number,note-number,velocity,duration,param.
csv_mndd_parse_f :: (Read t, Real t, Read n, Real n) => (n -> m) -> Csv_Table String -> [Mndd t m] Source #
csv_mndd_parse :: (Read t, Real t, Read n, Real n) => Csv_Table String -> [Mndd t n] Source #
Pars midi note/duration data from Csv table.
Mndd Seq forms
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_f :: (Read t, Real t, Read n, Real n, Num m, Eq m) => (n -> m) -> Csv_Table String -> Wseq t (Event m) Source #
Parse either Mnd or Mndd data to Wseq, Csv type is decided by header.