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

Music.Theory.Permutations.Morris_1984

Contents

Description

Place notation (method ringing).

Morris, R. G. T. "Place Notation" Central Council of Church Bell Ringers (1984). http://www.cccbr.org.uk/bibliography/

Synopsis

Documentation

data Change Source #

A change either swaps all adjacent bells, or holds a subset of bells.

Constructors

Swap_All 
Hold [Int] 

Instances

Instances details
Show Change Source # 
Instance details

Defined in Music.Theory.Permutations.Morris_1984

Eq Change Source # 
Instance details

Defined in Music.Theory.Permutations.Morris_1984

Methods

(==) :: Change -> Change -> Bool #

(/=) :: Change -> Change -> Bool #

data Method Source #

A method is a sequence of changes, if symmetrical only half the changes are given and the lead end.

Constructors

Method [Change] (Maybe [Change]) 

Instances

Instances details
Show Method Source # 
Instance details

Defined in Music.Theory.Permutations.Morris_1984

Eq Method Source # 
Instance details

Defined in Music.Theory.Permutations.Morris_1984

Methods

(==) :: Method -> Method -> Bool #

(/=) :: Method -> Method -> Bool #

method_limit :: Method -> Int Source #

Maximum hold value at Method

method_changes :: Method -> [Change] Source #

Complete list of Changes at Method, writing out symmetries.

parse_change :: String -> Change Source #

Parse a change notation.

map parse_change ["-","x","38"] == [Swap_All,Swap_All,Hold [3,8]]

split_changes :: String -> [String] Source #

Separate changes.

split_changes "-38-14-1258-36-14-58-16-78"
split_changes "345.145.5.1.345" == ["345","145","5","1","345"]

type Place = (String, Maybe String) Source #

Place notation, sequence of changes with possible lead end.

parse_method :: Place -> Method Source #

Parse Method given PLACE notation.

parse_place :: String -> Place Source #

Parse string into Place.

parse_method (parse_place "-38-14-1258-36-14-58-16-78,12")

is_swap_all :: String -> Bool Source #

  • or x?
map is_swap_all ["-","x","38"] == [True,True,False]

flatten_pairs :: [(a, a)] -> [a] Source #

Flatten list of pairs.

flatten_pairs [(1,2),(3,4)] == [1..4]

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

Swap all adjacent pairs at list.

swap_all [1 .. 8] == [2,1,4,3,6,5,8,7]

nchar_to_int :: Char -> Int Source #

Parse abbreviated Hold notation, characters are NOT hexadecimal.

map nchar_to_int "380ETA" == [3,8,10,11,12,13]

int_to_nchar :: Int -> Char Source #

Inverse of nchar_to_int.

map int_to_nchar [3,8,10,11,12,13] == "380ETA"

gen_swaps :: (Num t, Ord t) => t -> [t] -> [Either t (t, t)] Source #

Given a Hold notation, generate permutation cycles.

let r = [Right (1,2),Left 3,Right (4,5),Right (6,7),Left 8]
gen_swaps 8 [3,8] == r
r = [Left 1,Left 2,Right (3,4),Right (5,6),Right (7,8)]
gen_swaps 8 [1,2] == r

derive_holds :: (Eq a, Enum n, Num n) => ([a], [a]) -> [n] Source #

Given two sequences, derive the one-indexed "hold" list.

derive_holds ("12345","13254") == [1]

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

Two-tuple to two element list.

swaps_to_cycles :: [Either t (t, t)] -> [[t]] Source #

Swap notation to plain permutation cycles notation.

let n = [Left 1,Left 2,Right (3,4),Right (5,6),Right (7,8)]
in swaps_to_cycles n == [[1],[2],[3,4],[5,6],[7,8]]

to_zero_indexed :: Enum t => [[t]] -> [[t]] Source #

One-indexed permutation cycles to zero-indexed.

let r = [[0],[1],[2,3],[4,5],[6,7]]
to_zero_indexed [[1],[2],[3,4],[5,6],[7,8]] == r

swap_abbrev :: Int -> [Int] -> [a] -> [a] Source #

Apply abbreviated Hold notation, given cardinality.

swap_abbrev 8 [3,8] [2,1,4,3,6,5,8,7] == [1,2,4,6,3,8,5,7]

apply_change :: Int -> Change -> [a] -> [a] Source #

Apply a Change.

apply_method :: Method -> [a] -> ([a], [[a]]) Source #

Apply a Method, gives next starting sequence and the course of the method.

let r = ([1,2,4,5,3]
        ,[[1,2,3,4,5],[2,1,3,4,5],[2,3,1,4,5],[3,2,4,1,5],[3,4,2,5,1]
         ,[4,3,2,5,1],[4,2,3,1,5],[2,4,1,3,5],[2,1,4,3,5],[1,2,4,3,5]])
apply_method cambridgeshire_slow_course_doubles [1..5] == r

closed_method :: Eq a => Method -> [a] -> [[[a]]] Source #

Iteratively apply a Method until it closes (ie. arrives back at the starting sequence).

length (closed_method cambridgeshire_slow_course_doubles [1..5]) == 3

closed_method_lp :: Eq a => Method -> [a] -> [[a]] Source #

concat of closed_method with initial sequence appended.

closed_place :: Eq t => Place -> [t] -> [[[t]]] Source #

Methods

smithsonian_surprise_royal_pl :: Place Source #

https://rsw.me.uk/blueline/methods/view/Smithsonian_Surprise_Royal

let c = closed_place smithsonian_surprise_royal_pl [1..10]
(length c,nub (map length c),sum (map length c)) == (9,[40],360)

ecumenical_surprise_maximus_pl :: Place Source #

https://rsw.me.uk/blueline/methods/view/Ecumenical_Surprise_Maximus

c = closed_place ecumenical_surprise_maximus_pl [1..12]
(length c,nub (map length c),sum (map length c)) == (11,[48],528)