hmt-0.20: Haskell Music Theory
Safe HaskellSafe-Inferred
LanguageHaskell2010

Music.Theory.Time.KeyKit.Parser

Description

KeyKit phrase literal (constant) parser and printer.

Synopsis

Parser setup

type P a = GenParser Char () a Source #

A Char parser with no user state.

kk_parse_either :: P t -> String -> Either String t Source #

Run parser and return either an error string or an answer.

kk_parse :: P t -> String -> t Source #

Run parser and report any error. Does not delete leading spaces.

(>>~) :: Monad m => m t -> m u -> m t Source #

Run p then q, returning result of p.

kk_lexeme :: P t -> P t Source #

Note elements parsers

kk_modifier_p :: P (Char, Int) Source #

The octave key can be elided, ordinarily directly after the note name, ie. c2.

Contextual note

kk_contextual_note_pp :: (Int, Kk_Contextual_Note) -> String Source #

If t is set and is at the end time of the previous note print a preceding comma, else print t annotation.

c = kk_empty_contextual_note {kk_contextual_note_number = Just 0, kk_contextual_time = Just 96}
map (\t -> kk_contextual_note_pp (t, c)) [0, 96] == ["ct96",", c"]

kk_contextual_note_p :: P Kk_Contextual_Note Source #

If the note number is given as p60, then derive octave of and set it, ignoring any modifier. Note that in KeyKit c3 is p60 or middle c.

kk_contextual_phrase_element_p :: P (Kk_Contextual_Note, Bool) Source #

A contextual note and an is_parallel? indicator.

Note

data Kk_Note Source #

A note with all fields required.

Instances

Instances details
Show Kk_Note Source # 
Instance details

Defined in Music.Theory.Time.KeyKit.Parser

Eq Kk_Note Source # 
Instance details

Defined in Music.Theory.Time.KeyKit.Parser

Methods

(==) :: Kk_Note -> Kk_Note -> Bool #

(/=) :: Kk_Note -> Kk_Note -> Bool #

Ord Kk_Note Source # 
Instance details

Defined in Music.Theory.Time.KeyKit.Parser

kk_note_pp :: Kk_Note -> String Source #

Elide octave modifier character.

data Kk_Phrase Source #

Constructors

Kk_Phrase 

Instances

Instances details
Show Kk_Phrase Source # 
Instance details

Defined in Music.Theory.Time.KeyKit.Parser

Eq Kk_Phrase Source # 
Instance details

Defined in Music.Theory.Time.KeyKit.Parser

kk_phrase_pp :: Kk_Phrase -> String Source #

This should, but does not, append a trailing rest as required.

kk_decontextualise_phrase :: [(Kk_Contextual_Note, Bool)] -> Kk_Phrase Source #

Rests are elided, their duration is accounted for in the time of the following notetaken into account.

kk_recontextualise_phrase :: Kk_Phrase -> [(Int, Kk_Contextual_Note)] Source #

In addition to contextual note give end time of previous note, to allow for sequence (comma) notation.

kk_phrase_read :: String -> Kk_Phrase Source #

Read KeyKit phrase constant.

let rw = (\p -> (kk_phrase_pp p, kk_phrase_length p)) . kk_phrase_read
rw "c" == ("c3v63d96c1t0",96)
rw "c, r" == ("c3v63d96c1t0",192)
rw "c, r, c3, r, p60" == ("c3v63d96c1t0 c3v63d96c1t192 c3v63d96c1t384",480)
rw "c, e, g" == ("c3v63d96c1t0 e3v63d96c1t96 g3v63d96c1t192",288)
rw "c2" == rw "co2"

kk_phrase_print :: Kk_Phrase -> String Source #

Re-contextualise and print phrase.

rw = kk_phrase_print . kk_phrase_read
rw_id i = rw i == i
rw_id "c"
rw_id "c e g"
rw_id "c , e , g"
rw_id "c e g , c f a , c e g , c e- g"
rw_id "c , e , g c4t384"
rw "c, r, c3, r, p60" == "c ct192 ct384"
rw "c , e , g c4t288" == "c , e , g , c4"
rw "c r" == "c" -- ?