hmt-0.15: Haskell Music Theory

Safe HaskellSafe-Inferred
LanguageHaskell98

Music.Theory.Instrument.Choir

Synopsis

Documentation

data Voice Source

Voice types.

Constructors

Bass 
Tenor 
Alto 
Soprano 

voice_abbrev :: Voice -> Char Source

Single character abbreviation for Voice.

voice_clef :: Integral i => Voice -> Clef i Source

Standard Clef for Voice.

type Voice_Rng_Tbl = [(Voice, (Pitch, Pitch))] Source

Table giving ranges for Voices.

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.

lookup_err :: Eq a => a -> [(a, b)] -> b Source

Erroring variant.

voice_rng :: Voice_Rng_Tbl -> Voice -> (Pitch, Pitch) Source

Lookup voice range table.

in_range_inclusive :: Ord a => a -> (a, a) -> Bool Source

Is p >= l and <= r.

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

Given tbl list Voices that can sing Pitch.

possible_voices_safe :: Pitch -> [Voice] Source

safe variant.

satb :: [Voice] Source

Enumeration of SATB voices.

satb_name :: [String] Source

Names of satb.

type Part = (Voice, Int) Source

Voice & part number.

ch_satb_seq :: Int -> [Part] Source

k part choir, ordered by voice.

ch_parts :: Int -> [[Part]] Source

ch_satb_seq grouped in parts.

map (map part_nm) (ch_parts 8)

part_nm :: Part -> String Source

Abreviated name for part.

part_nm (Soprano,1) == "S1"

k_ch_groups :: Int -> [[Part]] Source

k SATB choirs, grouped by choir.

k_ch_groups 2

dbl_ch_parts :: Int -> [[Part]] Source

Two k part SATB choirs in score order.

map part_nm (concat (dbl_ch_parts 8))