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

Music.Theory.Graph.Johnson_2014

Description

Tom Johnson. Other Harmony: Beyond Tonal and Atonal. Editions 75, 2014.

Synopsis

Common

type Z12 = Int8 Source #

dif :: Num a => (a, a) -> a Source #

absdif :: Num a => (a, a) -> a Source #

i_to_ic :: (Num a, Ord a) => a -> a Source #

interval (0,11) to interval class (0,6)

p2_and :: (t -> u -> Bool) -> (t -> u -> Bool) -> t -> u -> Bool Source #

doi :: Eq t => [t] -> [t] -> Int Source #

degree of intersection

doi_of :: Eq t => Int -> [t] -> [t] -> Bool Source #

loc_dif :: Num t => [t] -> [t] -> t Source #

The sum of the pointwise absolute difference.

loc_dif_of :: (Eq t, Num t) => t -> [t] -> [t] -> Bool Source #

loc_dif_in :: (Eq t, Num t) => [t] -> [t] -> [t] -> Bool Source #

loc_dif_n :: (Eq t, Num i) => [t] -> [t] -> i Source #

The number of places that are, pointwise, not equal.

loc_dif_n "test" "pest" == 1

loc_dif_n_of :: Eq t => Int -> [t] -> [t] -> Bool Source #

min_vl :: (Num a, Ord a) => [a] -> [a] -> a Source #

min_vl_of :: (Num a, Ord a) => a -> [a] -> [a] -> Bool Source #

min_vl_in :: (Num a, Ord a) => [a] -> [a] -> [a] -> Bool Source #

combinations2 :: Ord t => [t] -> [(t, t)] Source #

set_pp :: Show t => [t] -> String Source #

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

set_pp_tto_rel :: (Integral t, Show t) => Z t -> [t] -> [t] -> String Source #

Map

m_get :: Ord k => Map k v -> k -> v Source #

m_doi_of :: Map Int [Z12] -> Int -> Int -> Int -> Bool Source #

degree of intersection

Edge

e_add_id :: k -> [(t, u)] -> [((k, t), (k, u))] Source #

Add k as prefix to both left and right hand sides of edge.

gen_edges :: (t -> t -> Bool) -> [t] -> [(t, t)] Source #

gen_u_edges :: Ord a => (a -> a -> Bool) -> [a] -> [(a, a)] Source #

Graph

gen_graph :: Ord v => [Dot_Meta_Attr] -> Graph_Pp v e -> [Edge_Lbl v e] -> [String] Source #

gen_graph_ul :: Ord v => [Dot_Meta_Attr] -> (v -> String) -> [Edge v] -> [String] Source #

gen_graph_ul_ty :: Ord v => String -> (v -> String) -> [Edge v] -> [String] Source #

gen_flt_graph_pp :: Ord t => [Dot_Meta_Attr] -> ([t] -> String) -> ([t] -> [t] -> Bool) -> [[t]] -> [String] Source #

gen_flt_graph :: (Ord t, Show t) => [Dot_Meta_Attr] -> ([t] -> [t] -> Bool) -> [[t]] -> [String] Source #

P.12

circ_5 :: Integral a => Int -> a -> [a] Source #

all_pairs :: [t] -> [u] -> [(t, u)] Source #

adj :: [t] -> [(t, t)] Source #

adj_cyc :: [t] -> [(t, t)] Source #

e_add_label :: (Edge v -> l) -> [Edge v] -> [Edge_Lbl v l] Source #

P.14

p14_eset :: ([(Int, Int)], [(Int, Int)], [(Int, Int)]) Source #

p14_mk_e :: [(Int, Int)] -> [(Key, Key)] Source #

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

p14_gen_tonnetz_e :: Int -> [Int] -> [Int] -> [((Int, Int), Int)] Source #

P.31

p31_e_set :: [([Z12], [Z12])] Source #

P.114

p114_mk_gr :: Double -> ([Z12] -> [Z12] -> Bool) -> [String] Source #

P.125

P.131

P.148

p148_mk_gr :: ([Int] -> [Int] -> Bool) -> [String] Source #

P.162

P.172

p172_gr :: Gr () () Source #

p172_all_cyc :: ([[Int]], [[Int]]) Source #

tto_tn :: Integral t => t -> Tto t Source #

Tto Tn.

tto_tni :: Integral t => t -> Tto t Source #

Tto TnI.

gen_tto_alt_seq :: Integral t => (t -> Tto t, t -> Tto t) -> Int -> t -> t -> t -> [Tto t] Source #

gen_tni_seq :: Integral t => Int -> t -> t -> t -> [Tto t] Source #

k is length of the T & I sequences, n is the T & I sequence interval, m is the interval between the T & I sequence.

r = ["T0 T5I T3 T8I T6 T11I T9 T2I","T1 T6I T4 T9I T7 T0I T10 T3I"]
map (unwords . map T.tto_pp . gen_tni_seq 4 3 5) [0,1] == r

tto_seq_edges :: (Show t, Num t, Eq t) => [[Tto t]] -> [(String, String)] Source #

P.177

partition_ic :: (Num t, Ord t, Show t) => t -> [t] -> ([t], [t]) Source #

P.178

type SC = [Int] Source #

type PCSET = [Int] Source #

ait :: [SC] Source #

mk_bridge :: SC -> PCSET -> PCSET -> [PCSET] Source #

List of pcsets s where prime(p+s)=r and prime(q+s)=r. #p and #q must be equal, and less than #r.

mk_bridge (T.sc "4-Z15") [0,6] [1,7] == [[2,5],[8,11]]
mk_bridge (T.sc "4-Z29") [0,6] [1,7] == [[2,11],[5,8]]

mk_bridge_set :: [SC] -> PCSET -> PCSET -> [PCSET] Source #

concatMap of mk_bridge.

mk_bridge_set ait [0,6] [1,7] == [[2,5],[8,11],[2,11],[5,8]]

type ID = Char Source #

p178_e :: [((ID, PCSET), (ID, PCSET))] Source #

Add ID to vertices, the 2,11 the is between 0,6 and 1,7 is not the same 2,11 that is between 3,9 and 4,10.

P.196

P.201

type SET = [Int] Source #

type E = (SET, SET) Source #

p201_mk_e :: [Int] -> [E] Source #

p201_e :: [[E]] Source #

P.205

p205_mk_e :: [Int] -> [E] Source #

IO