| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Music.Theory.Z.Boros_1990
Description
James Boros. "Some Properties of the All-Trichord Hexachord". _In Theory Only_, 11(6):19--41, 1990.
Synopsis
- singular :: String -> [t] -> t
- set_eq :: Ord t => [t] -> [t] -> Bool
- elem_by :: (t -> t -> Bool) -> t -> [t] -> Bool
- tto_tni_univ :: Integral i => [Tto i]
- all_tn :: Integral i => [i] -> [[i]]
- all_tni :: Integral i => [i] -> [[i]]
- uniq_tni :: Integral i => [i] -> [[i]]
- type Pc = Int
- type Pcset = [Pc]
- type Sc = Pcset
- pcset_trs :: Int -> Pcset -> Pcset
- trichords :: [Pcset]
- self_inv :: Pcset -> Bool
- pcset_pp :: Pcset -> String
- pcset_pp_hex :: Pcset -> String
- ath :: Pcset
- is_ath :: Pcset -> Bool
- ath_univ :: [Pcset]
- ath_tni :: Pcset -> Tto Pc
- ath_pp :: Pcset -> String
- ath_trichords :: [Pcset]
- ath_complement :: Pcset -> Pcset
- ath_completions :: Pcset -> Sc -> [Pcset]
- realise_ath_seq :: [Pcset] -> [[Pcset]]
- ath_gr_extend :: [Edge Pcset] -> Pcset -> [Edge Pcset]
- gr_trs :: Int -> [Edge Pcset] -> [Edge Pcset]
- table_3 :: [((Pcset, Sc, SC_Name), (Pcset, Sc, SC_Name))]
- pp_tbl :: Text_Table -> [String]
- table_3_md :: [String]
- table_4 :: [((Pcset, Pcset, SC_Name), (Pcset, Pcset, SC_Name))]
- table_4_md :: [String]
- table_5 :: [(Pcset, Int)]
- table_5_md :: [String]
- table_6 :: [(Pcset, Int, Int)]
- table_6_md :: [String]
- fig_1 :: [Edge Pcset]
- fig_1_gr :: Gr Pcset ()
- fig_2 :: [[Pcset]]
- fig_3 :: [[Edge Pcset]]
- fig_3_gr :: [Gr Pcset ()]
- fig_4 :: [[Edge Pcset]]
- fig_5 :: [[Edge Pcset]]
- uedge_set :: Ord v => [Edge v] -> [Edge v]
- set_shape :: Pcset -> Dot_Attr
- type Gr = Gr Pcset ()
- gr_pp' :: (Pcset -> String) -> Graph_Pp Pcset ()
- gr_pp :: Graph_Pp Pcset ()
- d_fig_1 :: [String]
- d_fig_3_g :: Gr
- d_fig_3 :: [String]
- d_fig_3' :: [[String]]
- d_fig_4_g :: Gr
- d_fig_4 :: [String]
- d_fig_5_g :: Gr
- d_fig_5 :: [String]
- d_fig_5_e :: [Edge_Lbl Pcset Pcset]
- d_fig_5_g' :: Gr Pcset Pcset
- d_fig_5' :: [String]
Util
Tto
tto_tni_univ :: Integral i => [Tto i] Source #
Forte prime forms of the twelve trichordal set classes.
length trichords == 12
self_inv :: Pcset -> Bool Source #
Is a pcset self-inversional, ie. is the inversion of p a transposition of p.
map (\p -> (p,self_inv p)) trichords
pcset_pp :: Pcset -> String Source #
Pretty printer, comma separated.
pcset_pp [0,3,7,10] == "0,3,7,10"
pcset_pp_hex :: Pcset -> String Source #
Pretty printer, hexadecimal, no separator.
pcset_pp_hex [0,3,7,10] == "037A"
Ath
Forte prime form of the all-trichord hexachord.
T.sc_name ath == "6-Z17" T.sc "6-Z17" == ath
ath_pp :: Pcset -> String Source #
Give label for instance of ath, prime forms are written H and inversions h.
ath_pp [1,2,3,7,8,11] == "h3"
ath_trichords :: [Pcset] Source #
The twenty three-element subsets of ath.
length ath_trichords == 20
ath_complement :: Pcset -> Pcset Source #
ath_completions :: Pcset -> Sc -> [Pcset] Source #
p is a pcset, q a sc, calculate pcsets in q that with p form ath.
ath_completions [0,1,2] (T.sc "3-3") == [[6,7,10],[4,7,8]] ath_completions [6,7,10] (T.sc "3-5") == [[1,2,8]]
realise_ath_seq :: [Pcset] -> [[Pcset]] Source #
Tables
pp_tbl :: Text_Table -> [String] Source #
table_3_md :: [String] Source #
table_4_md :: [String] Source #
table_5_md :: [String] Source #
table_6_md :: [String] Source #