hmt-0.20: Haskell Music Theory
Safe HaskellSafe-Inferred
LanguageHaskell2010

Music.Theory.Z.Sro

Description

Serial (ordered) pitch-class operations on Z.

Synopsis

Documentation

data Sro t Source #

Serial operator,of the form rRTMI.

Constructors

Sro 

Fields

Instances

Instances details
Show t => Show (Sro t) Source # 
Instance details

Defined in Music.Theory.Z.Sro

Methods

showsPrec :: Int -> Sro t -> ShowS #

show :: Sro t -> String #

showList :: [Sro t] -> ShowS #

Eq t => Eq (Sro t) Source # 
Instance details

Defined in Music.Theory.Z.Sro

Methods

(==) :: Sro t -> Sro t -> Bool #

(/=) :: Sro t -> Sro t -> Bool #

sro_pp :: (Show t, Eq t, Num t) => Sro t -> String Source #

Printer in rnRTnMI form.

p_sro :: Integral t => t -> P (Sro t) Source #

Parser for Sro.

sro_parse :: Integral i => i -> String -> Sro i Source #

Parse a Morris format serial operator descriptor.

sro_parse 5 "r2RT3MI" == Sro 2 True 3 5 True

Z

z_sro_univ :: Integral i => Int -> i -> Z i -> [Sro i] Source #

The total set of serial operations.

let u = z_sro_univ 3 5 z12
zip (map sro_pp u) (map (\o -> z_sro_apply z12 o [0,1,3]) u)

z_sro_Tn :: Integral i => Z i -> [Sro i] Source #

The set of transposition Sros.

z_sro_TnI :: Integral i => Z i -> [Sro i] Source #

The set of transposition and inversion Sros.

z_sro_RTnI :: Integral i => Z i -> [Sro i] Source #

The set of retrograde and transposition and inversion Sros.

z_sro_TnMI :: Integral i => i -> Z i -> [Sro i] Source #

The set of transposition, M and inversion Sros.

z_sro_RTnMI :: Integral i => i -> Z i -> [Sro i] Source #

The set of retrograde,transposition,M5 and inversion Sros.

Serial operations

z_sro_apply :: Integral i => Z i -> Sro i -> [i] -> [i] Source #

Apply Sro.

z_sro_apply z12 (Sro 1 True 1 5 False) [0,1,2,3] == [11,6,1,4]
z_sro_apply z12 (Sro 1 False 4 5 True) [0,1,2,3] == [11,6,1,4]

z_sro_rel :: (Ord t, Integral t) => t -> Z t -> [t] -> [t] -> [Sro t] Source #

Find Sros that map x to y given m and z.

map sro_pp (z_sro_rel 5 z12 [0,1,2,3] [11,6,1,4]) == ["r1T4MI","r1RT1M"]

Plain

z_sro_tn :: (Integral i, Functor f) => Z i -> i -> f i -> f i Source #

Transpose p by n.

z_sro_tn z5 4 [0,1,4] == [4,0,3]
z_sro_tn z12 4 [1,5,6] == [5,9,10]

z_sro_invert :: (Integral i, Functor f) => Z i -> i -> f i -> f i Source #

Invert p about n.

z_sro_invert z5 0 [0,1,4] == [0,4,1]
z_sro_invert z12 6 [4,5,6] == [8,7,6]
map (z_sro_invert z12 0) [[0,1,3],[1,4,8]] == [[0,11,9],[11,8,4]]
import Data.Word {- base -}
z_sro_invert z12 (0::Word8) [1,4,8] == [3,0,8]

z_sro_tni :: (Integral i, Functor f) => Z i -> i -> f i -> f i Source #

Composition of invert about 0 and tn.

z_sro_tni z5 1 [0,1,3] == [1,0,3]
z_sro_tni z12 4 [1,5,6] == [3,11,10]
(z_sro_invert z12 0 . z_sro_tn z12 4) [1,5,6] == [7,3,2]

z_sro_mn :: (Integral i, Functor f) => Z i -> i -> f i -> f i Source #

Modulo multiplication.

z_sro_mn z12 11 [0,1,4,9] == z_sro_tni z12 0 [0,1,4,9]

z_sro_m5 :: (Integral i, Functor f) => Z i -> f i -> f i Source #

M5, ie. mn 5.

z_sro_m5 z12 [0,1,3] == [0,5,3]

z_sro_t_related :: (Integral i, Functor f) => Z i -> f i -> [f i] Source #

T-related sequences of p.

length (z_sro_t_related z12 [0,3,6,9]) == 12
z_sro_t_related z5 [0,2] == [[0,2],[1,3],[2,4],[3,0],[4,1]]

z_sro_ti_related :: (Eq (f i), Integral i, Functor f) => Z i -> f i -> [f i] Source #

T/I-related sequences of p.

length (z_sro_ti_related z12 [0,1,3]) == 24
length (z_sro_ti_related z12 [0,3,6,9]) == 24
z_sro_ti_related z12 [0] == map return [0..11]

z_sro_rti_related :: Integral i => Z i -> [i] -> [[i]] Source #

R/T/I-related sequences of p.

length (z_sro_rti_related z12 [0,1,3]) == 48
length (z_sro_rti_related z12 [0,3,6,9]) == 24

z_sro_tmi_related :: Integral i => Z i -> [i] -> [[i]] Source #

T/M/I-related sequences of p, duplicates removed.

z_sro_rtmi_related :: Integral i => Z i -> [i] -> [[i]] Source #

R/T/M/I-related sequences of p, duplicates removed.

z_sro_rrtmi_related :: Integral i => Z i -> [i] -> [[i]] Source #

r/R/T/M/I-related sequences of p, duplicates removed.

Sequence operations

z_sro_tn_to :: Integral i => Z i -> i -> [i] -> [i] Source #

Variant of tn, transpose p so first element is n.

z_sro_tn_to z12 5 [0,1,3] == [5,6,8]
map (z_sro_tn_to z12 0) [[0,1,3],[1,3,0],[3,0,1]] == [[0,1,3],[0,2,11],[0,9,10]]

z_sro_invert_ix :: Integral i => Z i -> Int -> [i] -> [i] Source #

Variant of invert, inverse about nth element.

map (z_sro_invert_ix z12 0) [[0,1,3],[3,4,6]] == [[0,11,9],[3,2,0]]
map (z_sro_invert_ix z12 1) [[0,1,3],[3,4,6]] == [[2,1,11],[5,4,2]]

z_tmatrix :: Integral i => Z i -> [i] -> [[i]] Source #

The standard t-matrix of p.

z_tmatrix z12 [0,1,3] == [[0,1,3],[11,0,2],[9,10,0]]