Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
KeyKit phrase literal (constant) parser and printer.
Synopsis
- type P a = GenParser Char () a
- kk_parse_either :: P t -> String -> Either String t
- kk_parse :: P t -> String -> t
- (>>~) :: Monad m => m t -> m u -> m t
- kk_lexeme :: P t -> P t
- kk_uint :: P Int
- kk_int :: P Int
- kk_note_name_p :: P Char
- kk_midi_note_p :: P Int
- kk_rest_p :: P Char
- kk_accidental_p :: P Char
- kk_char_to_note_number :: Char -> Int
- kk_char_to_alteration :: Char -> Int
- kk_note_number_to_name :: Int -> String
- kk_named_note_number_p :: P Int
- kk_note_number_p :: P Int
- kk_modifier_p :: P (Char, Int)
- kk_modifiers_p :: P [(Char, Int)]
- data Kk_Contextual_Note = Kk_Contextual_Note {}
- kk_empty_contextual_note :: Kk_Contextual_Note
- kk_empty_contextual_rest :: Int -> Kk_Contextual_Note
- kk_contextual_note_pp :: (Int, Kk_Contextual_Note) -> String
- kk_contextual_note_p :: P Kk_Contextual_Note
- kk_contextual_note_is_rest :: Kk_Contextual_Note -> Bool
- kk_comma_p :: P Char
- kk_contextual_phrase_element_p :: P (Kk_Contextual_Note, Bool)
- kk_contextual_phrase_p :: P [(Kk_Contextual_Note, Bool)]
- data Kk_Note = Kk_Note {}
- kk_default_note :: Kk_Note
- kk_note_to_initial_contextual_note :: Kk_Note -> Kk_Contextual_Note
- kk_note_to_contextual_note :: Kk_Note -> Kk_Note -> (Int, Kk_Contextual_Note)
- kk_note_pp :: Kk_Note -> String
- kk_decontextualise_note :: Kk_Note -> Bool -> Kk_Contextual_Note -> Either Kk_Note Int
- data Kk_Phrase = Kk_Phrase {}
- kk_phrase_pp :: Kk_Phrase -> String
- kk_decontextualise_phrase :: [(Kk_Contextual_Note, Bool)] -> Kk_Phrase
- kk_recontextualise_phrase :: Kk_Phrase -> [(Int, Kk_Contextual_Note)]
- kk_phrase_read :: String -> Kk_Phrase
- kk_phrase_print :: Kk_Phrase -> String
Parser setup
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.
Note elements parsers
kk_note_name_p :: P Char Source #
kk_midi_note_p :: P Int Source #
kk_accidental_p :: P Char Source #
kk_char_to_note_number :: Char -> Int Source #
kk_char_to_alteration :: Char -> Int Source #
kk_note_number_to_name :: Int -> String Source #
kk_note_number_p :: P Int Source #
kk_modifier_p :: P (Char, Int) Source #
The octave key can be elided, ordinarily directly after the note name, ie. c2.
Contextual note
data Kk_Contextual_Note Source #
A note where all fields are optional. If the note number is absent it indicates a rest. All other fields infer values from the phrase context.
Instances
Show Kk_Contextual_Note Source # | |
Defined in Music.Theory.Time.KeyKit.Parser showsPrec :: Int -> Kk_Contextual_Note -> ShowS # show :: Kk_Contextual_Note -> String # showList :: [Kk_Contextual_Note] -> ShowS # | |
Eq Kk_Contextual_Note Source # | |
Defined in Music.Theory.Time.KeyKit.Parser (==) :: Kk_Contextual_Note -> Kk_Contextual_Note -> Bool # (/=) :: Kk_Contextual_Note -> Kk_Contextual_Note -> Bool # | |
Ord Kk_Contextual_Note Source # | |
Defined in Music.Theory.Time.KeyKit.Parser compare :: Kk_Contextual_Note -> Kk_Contextual_Note -> Ordering # (<) :: Kk_Contextual_Note -> Kk_Contextual_Note -> Bool # (<=) :: Kk_Contextual_Note -> Kk_Contextual_Note -> Bool # (>) :: Kk_Contextual_Note -> Kk_Contextual_Note -> Bool # (>=) :: Kk_Contextual_Note -> Kk_Contextual_Note -> Bool # max :: Kk_Contextual_Note -> Kk_Contextual_Note -> Kk_Contextual_Note # min :: Kk_Contextual_Note -> Kk_Contextual_Note -> Kk_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_comma_p :: P Char Source #
kk_contextual_phrase_element_p :: P (Kk_Contextual_Note, Bool) Source #
A contextual note and an is_parallel? indicator.
kk_contextual_phrase_p :: P [(Kk_Contextual_Note, Bool)] Source #
Note
A note with all fields required.
Kk_Note | |
|
kk_note_to_contextual_note :: Kk_Note -> Kk_Note -> (Int, Kk_Contextual_Note) Source #
kk_note_pp :: Kk_Note -> String Source #
Elide octave modifier character.
kk_decontextualise_note :: Kk_Note -> Bool -> Kk_Contextual_Note -> Either Kk_Note Int Source #
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" -- ?