hmt-0.15: Haskell Music Theory

Safe HaskellSafe-Inferred
LanguageHaskell98

Music.Theory.Xenakis.Sieve

Description

"Sieves" by Iannis Xenakis and John Rahn Perspectives of New Music Vol. 28, No. 1 (Winter, 1990), pp. 58-78

Synopsis

Documentation

type I = Integer Source

Synonym for Integer

data Sieve Source

A Sieve.

Constructors

Empty

Empty Sieve

L (I, I)

Primitive Sieve of modulo and index

Union Sieve Sieve

Union of two Sieves

Intersection Sieve Sieve

Intersection of two Sieves

Instances

union :: [Sieve] -> Sieve Source

The Union of a list of Sieves, ie. foldl1 Union.

(∪) :: Sieve -> Sieve -> Sieve infixl 3 Source

Unicode synonym for Union.

(∩) :: Sieve -> Sieve -> Sieve infixl 4 Source

Unicode synonym for Intersection.

l :: I -> I -> Sieve Source

Variant of L, ie. curry L.

l 15 19 == L (15,19)

(⋄) :: I -> I -> Sieve infixl 5 Source

unicode synonym for l.

normalise :: Sieve -> Sieve Source

In a normal Sieve m is > i.

normalise (L (15,19)) == L (15,4)

is_normal :: Sieve -> Bool Source

Predicate to test if a Sieve is normal.

is_normal (L (15,4)) == True

element :: Sieve -> I -> Bool Source

Predicate to determine if an I is an element of the Sieve.

map (element (L (3,1))) [1..4] == [True,False,False,True]
map (element (L (15,4))) [4,19 .. 49] == [True,True,True,True]

build :: Sieve -> [I] Source

Construct the sequence defined by a Sieve. Note that building a sieve that contains an intersection clause that has no elements gives _|_.

let {d = [0,2,4,5,7,9,11]
    ;r = d ++ map (+ 12) d}
in take 14 (build (union (map (l 12) d))) == r

buildn :: Int -> Sieve -> [I] Source

Variant of build that gives the first n places of the reduce of Sieve.

buildn 6 (union (map (l 8) [0,3,6])) == [0,3,6,8,11,14]
buildn 12 (L (3,2)) == [2,5,8,11,14,17,20,23,26,29,32,35]
buildn 9 (L (8,0)) == [0,8,16,24,32,40,48,56,64]
buildn 3 (L (3,2) ∩ L (8,0)) == [8,32,56]
buildn 12 (L (3,1) ∪ L (4,0)) == [0,1,4,7,8,10,12,13,16,19,20,22]
buildn 14 (5⋄4 ∪ 3⋄2 ∪ 7⋄3) == [2,3,4,5,8,9,10,11,14,17,19,20,23,24]
buildn 6 (3⋄0 ∪ 4⋄0) == [0,3,4,6,8,9]
buildn 8 (5⋄2 ∩ 2⋄0 ∪ 7⋄3) == [2,3,10,12,17,22,24,31]
buildn 12 (5⋄1 ∪ 7⋄2) == [1,2,6,9,11,16,21,23,26,30,31,36]
buildn 10 (3⋄2 ∩ 4⋄7 ∪ 6⋄9 ∩ 15⋄18) == [3,11,23,33,35,47,59,63,71,83]
let {s = 3⋄2∩4⋄7∩6⋄11∩8⋄7 ∪ 6⋄9∩15⋄18 ∪ 13⋄5∩8⋄6∩4⋄2 ∪ 6⋄9∩15⋄19
    ;s' = 24⋄23 ∪ 30⋄3 ∪ 104⋄70}
in buildn 16 s == buildn 16 s'
buildn 10 (24⋄23 ∪ 30⋄3 ∪ 104⋄70) == [3,23,33,47,63,70,71,93,95,119]
let r = [2,3,4,5,8,9,10,11,14,17,19,20,23,24,26,29,31]
in buildn 17 (5⋄4 ∪ 3⋄2 ∪ 7⋄3) == r
let r = [0,1,3,6,9,10,11,12,15,16,17,18,21,24,26,27,30]
in buildn 17 (5⋄1 ∪ 3⋄0 ∪ 7⋄3) == r
let r = [0,2,3,4,6,7,9,11,12,15,17,18,21,22,24,25,27,30,32]
in buildn 19 (5⋄2 ∪ 3⋄0 ∪ 7⋄4) == r

differentiate :: Num a => [a] -> [a] Source

Standard differentiation function.

differentiate [1,3,6,10] == [2,3,4]
differentiate [0,2,4,5,7,9,11,12] == [2,2,1,2,2,2,1]

euclid :: Integral a => a -> a -> a Source

Euclid's algorithm for computing the greatest common divisor.

euclid 1989 867 == 51

de_meziriac :: Integral a => a -> a -> a Source

Bachet De Méziriac's algorithm.

de_meziriac 15 4 == 3 && euclid 15 4 == 1

reduce_intersection :: Integral t => (t, t) -> (t, t) -> Maybe (t, t) Source

Attempt to reduce the Intersection of two L nodes to a singular L node.

reduce_intersection (3,2) (4,7) == Just (12,11)
reduce_intersection (12,11) (6,11) == Just (12,11)
reduce_intersection (12,11) (8,7) == Just (24,23)

reduce :: Sieve -> Sieve Source

Reduce the number of nodes at a Sieve.

reduce (L (3,2) ∪ Empty) == L (3,2)
reduce (L (3,2) ∩ Empty) == L (3,2)
reduce (L (3,2) ∩ L (4,7)) == L (12,11)
reduce (L (6,9) ∩ L (15,18)) == L (30,3)
let s = 3⋄2∩4⋄7∩6⋄11∩8⋄7 ∪ 6⋄9∩15⋄18 ∪ 13⋄5∩8⋄6∩4⋄2 ∪ 6⋄9∩15⋄19
in reduce s == (24⋄23 ∪ 30⋄3 ∪ 104⋄70)
let s = 3⋄2∩4⋄7∩6⋄11∩8⋄7 ∪ 6⋄9∩15⋄18 ∪ 13⋄5∩8⋄6∩4⋄2 ∪ 6⋄9∩15⋄19
in reduce s == (24⋄23 ∪ 30⋄3 ∪ 104⋄70)