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

Music.Theory.Z.Drape_1999

Description

Haskell implementations of pct operations. See http://rd.slavepianos.org/?t=pct

Synopsis

Documentation

cf :: Integral n => [n] -> [[a]] -> [[a]] Source #

Cardinality filter

cf [0,3] (cg [1..4]) == [[1,2,3],[1,2,4],[1,3,4],[2,3,4],[]]

cgg :: [[a]] -> [[a]] Source #

Combinatorial sets formed by considering each set as possible values for slot.

cgg [[0,1],[5,7],[3]] == [[0,5,3],[0,7,3],[1,5,3],[1,7,3]]
let n = "01" in cgg [n,n,n] == ["000","001","010","011","100","101","110","111"]

cg :: [a] -> [[a]] Source #

Combinations generator, ie. synonym for powerset.

sort (cg [0,1,3]) == [[],[0],[0,1],[0,1,3],[0,3],[1],[1,3],[3]]

cg_r :: Integral n => n -> [a] -> [[a]] Source #

Powerset filtered by cardinality.

>>> pct cg -r3 0159
015
019
059
159
cg_r 3 [0,1,5,9] == [[0,1,5],[0,1,9],[0,5,9],[1,5,9]]

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

Chain pcsegs.

>>> echo 024579 | pct chn T0 3 | sort -u
579468 (RT8M)
579A02 (T5)
chn_t0 z12 3 [0,2,4,5,7,9] == [[5,7,9,10,0,2],[5,7,9,4,6,8]]
>>> echo 02457t | pct chn T0 2
7A0135 (RT5I)
7A81B9 (RT9MI)
chn_t0 z12 2 [0,2,4,5,7,10] == [[7,10,0,1,3,5],[7,10,8,1,11,9]]

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

Cyclic interval segment.

>>> echo 014295e38t76 | pct cisg
13A7864529B6
ciseg z12 [0,1,4,2,9,5,11,3,8,10,7,6] == [1,3,10,7,8,6,4,5,2,9,11,6]

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

Synonynm for z_complement.

>>> pct cmpl 02468t
13579B
cmpl z12 [0,2,4,6,8,10] == [1,3,5,7,9,11]

cyc :: [a] -> [a] Source #

Form cycle.

>>> echo 056 | pct cyc
0560
cyc [0,5,6] == [0,5,6,0]

d_nm :: Integral a => [a] -> Maybe Char Source #

Diatonic set name. d for diatonic set, m for melodic minor set, o for octotonic set.

dim :: Integral i => [i] -> [(i, [i])] Source #

Diatonic implications.

dim_nm :: Integral i => [i] -> [(i, Char)] Source #

Variant of dim that is closer to the pct form.

>>> pct dim 016
T1d
T1m
T0o
dim_nm [0,1,6] == [(1,'d'),(1,'m'),(0,'o')]

dis :: Integral t => [Int] -> [t] Source #

Diatonic interval set to interval set.

>>> pct dis 24
1256
dis [2,4] == [1,2,5,6]

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

Degree of intersection.

>>> echo 024579e | pct doi 6 | sort -u
024579A
024679B
let p = [0,2,4,5,7,9,11]
doi z12 6 p p == [[0,2,4,5,7,9,10],[0,2,4,6,7,9,11]]
>>> echo 01234 | pct doi 2 7-35 | sort -u
13568AB
doi z12 2 (sc "7-35") [0,1,2,3,4] == [[1,3,5,6,8,10,11]]

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

Embedded segment search.

>>> echo 23A | pct ess 0164325
2B013A9
923507A
ess z12 [0,1,6,4,3,2,5] [2,3,10] == [[9,2,3,5,0,7,10],[2,11,0,1,3,10,9]]

fn :: Integral i => [i] -> String Source #

Forte name (ie sc_name).

frg_cyc :: Integral i => T6 [[i]] Source #

Z-12 cycles.

frg :: Integral i => [i] -> T6 [String] Source #

Fragmentation of cycles.

frg_hdr :: [String] Source #

Header sequence for frg_pp.

frg_pp :: Integral i => [i] -> String Source #

Fragmentation of cycles.

>>> pct frg 024579
Fragmentation of 1-cycle(s):  [0-2-45-7-9--]
Fragmentation of 2-cycle(s):  [024---] [--579-]
Fragmentation of 3-cycle(s):  [0--9] [-47-] [25--]
Fragmentation of 4-cycle(s):  [04-] [-59] [2--] [-7-]
Fragmentation of 5-cycle(s):  [05------4927]
Fragmentation of 6-cycle(s):  [0-] [-7] [2-] [-9] [4-] [5-]
IC cycle vector: <1> <22> <111> <1100> <5> <000000>
putStrLn $ frg_pp [0,2,4,5,7,9]

has_sc_pf :: Integral a => ([a] -> [a]) -> [a] -> [a] -> Bool Source #

Can the set-class q (under prime form algorithm pf) be drawn from the pcset p.

has_sc :: Integral i => Z i -> [i] -> [i] -> Bool Source #

has_sc_pf of forte_prime

let d = [0,2,4,5,7,9,11]
has_sc z12 d (z_complement z12 d) == True
has_sc z12 [] [] == True

ic_cycle_vector :: Integral i => [i] -> T6 [Int] Source #

Interval-class cycle vector.

ic_cycle_vector_pp :: T6 [Int] -> String Source #

Pretty printer for ic_cycle_vector.

let r = "IC cycle vector: <1> <22> <111> <1100> <5> <000000>"
ic_cycle_vector_pp (ic_cycle_vector [0,2,4,5,7,9]) == r

icf :: (Num a, Eq a) => [[a]] -> [[a]] Source #

Interval cycle filter.

>>> echo 22341 | pct icf
22341
icf [[2,2,3,4,1]] == [[2,2,3,4,1]]

ici :: Num t => [Int] -> [[t]] Source #

Interval class set to interval sets.

>>> pct ici -c 123
123
129
1A3
1A9
ici_c [1,2,3] == [[1,2,3],[1,2,9],[1,10,3],[1,10,9]]

ici_c :: [Int] -> [[Int]] Source #

Interval class set to interval sets, concise variant.

ici_c [1,2,3] == [[1,2,3],[1,2,9],[1,10,3],[1,10,9]]

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

Interval segment (INT).

imb :: Integral n => [n] -> [a] -> [[[a]]] Source #

Imbrications.

let r = [[[0,2,4],[2,4,5],[4,5,7],[5,7,9]]
        ,[[0,2,4,5],[2,4,5,7],[4,5,7,9]]]
in imb [3,4] [0,2,4,5,7,9] == r

issb :: Integral i => [i] -> [i] -> [String] Source #

issb gives the set-classes that can append to p to give q.

>>> pct issb 3-7 6-32
3-7
3-2
3-11
issb (sc "3-7") (sc "6-32") == ["3-2","3-7","3-11"]

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

Matrix search.

>>> pct mxs 024579 642 | sort -u
6421B9
B97642
set (mxs z12 [0,2,4,5,7,9] [6,4,2]) == [[6,4,2,1,11,9],[11,9,7,6,4,2]]

nrm :: Ord a => [a] -> [a] Source #

Normalize (synonym for set)

>>> pct nrm 0123456543210
0123456
nrm [0,1,2,3,4,5,6,5,4,3,2,1,0] == [0,1,2,3,4,5,6]

nrm_r :: Ord a => [a] -> [a] Source #

Normalize, retain duplicate elements.

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

Pitch-class invariances (called pi at pct).

>>> pct pi 0236 12
pcseg 0236
pcseg 6320
pcseg 532B
pcseg B235
pci z12 [1,2] [0,2,3,6] == [[0,2,3,6],[5,3,2,11],[6,3,2,0],[11,2,3,5]]

rs :: Integral t => t -> Z t -> [t] -> [t] -> [Tto t] Source #

Relate sets (TnMI), ie z_tto_rel

>>> $ pct rs 0123 641B
>>> T1M
map tto_pp (rs 5 z12 [0,1,2,3] [6,4,1,11]) == ["T1M","T4MI"]

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

Relate segments.

>>> $ pct rsg 156 3BA
>>> T4I
>>> $ pct rsg 0123 05A3
>>> T0M
>>> $ pct rsg 0123 4B61
>>> RT1M
>>> $ pct rsg 0123 B614
>>> r3RT1M
let sros = map (sro_parse 5) . words
rsg 5 z12 [1,5,6] [3,11,10] == sros "T4I r1RT4MI"
rsg 5 z12 [0,1,2,3] [0,5,10,3] == sros "T0M RT3MI"
rsg 5 z12 [0,1,2,3] [4,11,6,1] == sros "T4MI RT1M"
rsg 5 z12 [0,1,2,3] [11,6,1,4] == sros "r1T4MI r1RT1M"

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

Subsets.

cf [4] (sb z12 [sc "6-32",sc "6-8"]) == [[0,2,3,5],[0,1,3,5],[0,2,3,7],[0,2,4,7],[0,2,5,7]]

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

scc = set class completion

>>> pct scc 6-32 168
35A
49B
3AB
34B
scc z12 (sc "6-32") [1,6,8] == [[3,5,10],[4,9,11],[3,10,11],[3,4,11]]

si_hdr :: [String] Source #

Header fields for si.

type Si i = ([i], Tto i, [i]) Source #

(Pcset,Tto,Forte-Prime)

si_calc :: Integral i => [i] -> (Si i, [i], [Int], Si i, Si i) Source #

Calculator for si.

si_calc [0,5,3,11]

si_rhs_pp :: (Integral i, Show i) => [i] -> [String] Source #

Pretty printer for RHS for si.

si_rhs_pp [0,5,3,11]

si :: (Integral i, Show i) => [i] -> [String] Source #

Set information.

$ pct si 053b pitch-class-set: {035B} set-class: TB 4-Z15[0146] interval-class-vector: [4111111] tics: [102222102022] complement: {1246789A} (TAI 8-Z15) multiplication-by-five-transform: {0317} (T0 4-Z29) $

putStr $ unlines $ si [0,5,3,11]

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

Super set-class.

>>> pct spsc 4-11 4-12
5-26[02458]
spsc z12 [sc "4-11",sc "4-12"] == [[0,2,4,5,8]]
>>> pct spsc 3-11 3-8
4-27[0258]
4-Z29[0137]
spsc z12 [sc "3-11",sc "3-8"] == [[0,2,5,8],[0,1,3,7]]
>>> pct spsc `pct fl 3`
6-Z17[012478]
spsc z12 (cf [3] scs) == [[0,1,2,4,7,8]]

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

sra = stravinsky rotational array

>>> echo 019BA7 | pct sra
019BA7
08A96B
021A34
0B812A
0923B1
056243
let r = [[0,1,9,11,10,7],[0,8,10,9,6,11],[0,2,1,10,3,4],[0,11,8,1,2,10],[0,9,2,3,11,1],[0,5,6,2,4,3]]
sra z12 [0,1,9,11,10,7] == r

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

Serial operation.

>>> echo 156 | pct sro T4
59A
sro (Z.sro_parse "T4") [1,5,6] == [5,9,10]
>>> echo 024579 | pct sro RT4I
79B024
sro (Z.Sro 0 True 4 False True) [0,2,4,5,7,9] == [7,9,11,0,2,4]
>>> echo 156 | pct sro T4I
3BA
sro (Z.sro_parse "T4I") [1,5,6] == [3,11,10]
sro (Z.Sro 0 False 4 False True) [1,5,6] == [3,11,10]
>>> echo 156 | pct sro T4  | pct sro T0I
732
(sro (Z.sro_parse "T0I") . sro (Z.sro_parse "T4")) [1,5,6] == [7,3,2]
>>> echo 024579 | pct sro RT4I
79B024
sro (Z.sro_parse "RT4I") [0,2,4,5,7,9] == [7,9,11,0,2,4]

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

tmatrix

>>> pct tmatrix 1258

1258 0147 9A14 67A1

tmatrix z12 [1,2,5,8] == [[1,2,5,8],[0,1,4,7],[9,10,1,4],[6,7,10,1]]

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

trs = transformations search. Search all RTnMI of p for q.

>>> echo 642 | pct trs 024579 | sort -u
531642
6421B9
642753
B97642
let r = [[5,3,1,6,4,2],[6,4,2,1,11,9],[6,4,2,7,5,3],[11,9,7,6,4,2]]
sort (trs z12 [0,2,4,5,7,9] [6,4,2]) == r

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

Like trs, but of z_sro_rti_related.

trs_m z12 [0,2,4,5,7,9] [6,4,2] == [[6,4,2,1,11,9],[11,9,7,6,4,2]]