Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Generalised twelve-tone operations on un-ordered pitch-class sets with arbitrary Z.
Synopsis
- data Tto t = Tto {}
- tto_identity :: Num t => Tto t
- tto_pp :: (Show t, Num t, Eq t) => Tto t -> String
- p_tto :: Integral t => t -> P (Tto t)
- tto_parse :: Integral i => i -> String -> Tto i
- tto_M_set :: Integral t => t -> Tto t -> Tto t
- z_tto_univ :: Integral t => t -> Z t -> [Tto t]
- z_tto_f :: Integral t => Z t -> Tto t -> t -> t
- z_tto_apply :: Integral t => Z t -> Tto t -> [t] -> [t]
- z_tto_rel :: (Ord t, Integral t) => t -> Z t -> [t] -> [t] -> [Tto t]
- z_pcset :: (Integral t, Ord t) => Z t -> [t] -> [t]
- z_tto_tn :: Integral i => Z i -> i -> [i] -> [i]
- z_tto_invert :: Integral i => Z i -> i -> [i] -> [i]
- z_tto_tni :: Integral i => Z i -> i -> [i] -> [i]
- z_tto_mn :: Integral i => Z i -> i -> [i] -> [i]
- z_tto_m5 :: Integral i => Z i -> [i] -> [i]
- z_tto_t_related_seq :: Integral i => Z i -> [i] -> [[i]]
- z_tto_t_related :: Integral i => Z i -> [i] -> [[i]]
- z_tto_ti_related_seq :: Integral i => Z i -> [i] -> [[i]]
- z_tto_ti_related :: Integral i => Z i -> [i] -> [[i]]
Tto
Twelve-tone operator, of the form TMI.
tto_identity :: Num t => Tto t Source #
T0
tto_pp :: (Show t, Num t, Eq t) => Tto t -> String Source #
Pretty printer. It is an error here is M is not 1 or 5.
p_tto :: Integral t => t -> P (Tto t) Source #
Parser for Tto, requires value for M (ordinarily 5 for 12-tone Tto).
tto_parse :: Integral i => i -> String -> Tto i Source #
Parser, transposition must be decimal.
map (tto_pp . tto_parse 5) (words "T5 T3I T11M T9MI") == ["T5","T3I","T11M","T9MI"]
Z
z_tto_f :: Integral t => Z t -> Tto t -> t -> t Source #
Apply Tto to pitch-class.
map (z_tto_f z12 (tto_parse 5 "T1M")) [0,1,2,3] == [1,6,11,4]
z_tto_rel :: (Ord t, Integral t) => t -> Z t -> [t] -> [t] -> [Tto t] Source #
Find Tto
s that map pc-set x to pc-set y given m and z.
map tto_pp (z_tto_rel 5 z12 [0,1,2,3] [1,4,6,11]) == ["T1M","T4MI"]
Plain
z_tto_tn :: Integral i => Z i -> i -> [i] -> [i] Source #
Transpose by n.
z_tto_tn z12 4 [1,5,6] == [5,9,10] z_tto_tn z12 4 [0,4,8] == [0,4,8]
z_tto_invert :: Integral i => Z i -> i -> [i] -> [i] Source #
Invert about n.
z_tto_invert z12 6 [4,5,6] == [6,7,8] z_tto_invert z12 0 [0,1,3] == [0,9,11]
z_tto_tni :: Integral i => Z i -> i -> [i] -> [i] Source #
Composition of z_tto_invert
about 0
and z_tto_tn
.
z_tto_tni z12 4 [1,5,6] == [3,10,11] (z_tto_invert z12 0 . z_tto_tn z12 4) [1,5,6] == [2,3,7]
z_tto_mn :: Integral i => Z i -> i -> [i] -> [i] Source #
Modulo-z multiplication
z_tto_mn z12 11 [0,1,4,9] == z_tto_invert z12 0 [0,1,4,9]
Sequence
z_tto_t_related_seq :: Integral i => Z i -> [i] -> [[i]] Source #
T-related sets of p.
z_tto_t_related :: Integral i => Z i -> [i] -> [[i]] Source #
Unique elements of z_tto_t_related_seq
.
length (z_tto_t_related z12 [0,1,3]) == 12 z_tto_t_related z12 [0,3,6,9] == [[0,3,6,9],[1,4,7,10],[2,5,8,11]]
z_tto_ti_related_seq :: Integral i => Z i -> [i] -> [[i]] Source #
T/I-related set of p.
z_tto_ti_related :: Integral i => Z i -> [i] -> [[i]] Source #
Unique elements of z_tto_ti_related_seq
.
length (z_tto_ti_related z12 [0,1,3]) == 24 z_tto_ti_related z12 [0,3,6,9] == [[0,3,6,9],[1,4,7,10],[2,5,8,11]]