| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Music.Theory.Instrument.Choir
Synopsis
- data Voice
- voice_abbrev :: Voice -> Char
- voice_clef :: Integral i => Voice -> Clef i
- type Voice_Rng_Tbl = [(Voice, (Pitch, Pitch))]
- voice_rng_tbl_std :: Voice_Rng_Tbl
- voice_rng_tbl_safe :: Voice_Rng_Tbl
- voice_rng :: Voice_Rng_Tbl -> Voice -> (Pitch, Pitch)
- voice_rng_std :: Voice -> (Pitch, Pitch)
- voice_rng_safe :: Voice -> (Pitch, Pitch)
- in_range_inclusive :: Ord a => a -> (a, a) -> Bool
- in_voice_rng :: Pitch -> Voice -> (Bool, Bool)
- possible_voices :: Voice_Rng_Tbl -> Pitch -> [Voice]
- possible_voices_std :: Pitch -> [Voice]
- possible_voices_safe :: Pitch -> [Voice]
- satb :: [Voice]
- satb_name :: [String]
- satb_abbrev :: [String]
- type Part = (Voice, Int)
- ch_satb_seq :: Int -> [Part]
- ch_parts :: Int -> [[Part]]
- part_nm :: Part -> String
- k_ch_groups :: Int -> [[Part]]
- k_ch_groups' :: Int -> [Part]
- dbl_ch_parts :: Int -> [[Part]]
- mk_clef_seq :: [Part] -> [Clef Int]
Documentation
Voice types.
voice_rng_tbl_std :: Voice_Rng_Tbl Source #
More or less standard choir ranges, inclusive.
voice_rng_tbl_safe :: Voice_Rng_Tbl Source #
More conservative ranges, inclusive.
voice_rng_std :: Voice -> (Pitch, Pitch) Source #
Lookup voice_rng_tbl_std.
voice_rng_safe :: Voice -> (Pitch, Pitch) Source #
Lookup voice_rng_tbl_safe.
in_voice_rng :: Pitch -> Voice -> (Bool, Bool) Source #
Is p in range for v, (std & safe).
map (in_voice_rng T.c4) [Bass .. Soprano]
possible_voices :: Voice_Rng_Tbl -> Pitch -> [Voice] Source #
possible_voices_std :: Pitch -> [Voice] Source #
std variant.
possible_voices_safe :: Pitch -> [Voice] Source #
safe variant.
satb_abbrev :: [String] Source #
voice_abbrev of satb as Strings.
ch_satb_seq :: Int -> [Part] Source #
k part choir, ordered by voice.
k_ch_groups :: Int -> [[Part]] Source #
k SATB choirs, grouped by choir.
k_ch_groups 2
k_ch_groups' :: Int -> [Part] Source #
concat of k_ch_groups.
dbl_ch_parts :: Int -> [[Part]] Source #
Two k part SATB choirs in score order.
map part_nm (concat (dbl_ch_parts 8))
mk_clef_seq :: [Part] -> [Clef Int] Source #
voice_clef for Parts.