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

Music.Theory.Tuning.Scala.Mode

Contents

Description

Parser for the modename.par file.

The terminology here is:

  • a mode is a subset of the notes of a tuning system (which in scala is called a scale)
  • the length (or degree) of the mode is the number of tones in the mode
  • the universe (or scale) of the mode is the number of tones in the tuning system (or scale) the mode is a subset of
Synopsis

Documentation

type Mode = (Int, [Int], String) Source #

(mode-start-degree,mode-intervals,mode-description)

mode_starting_degree :: Mode -> Int Source #

Starting degree of mode in underlying scale. If non-zero the mode will not lie within an ordinary octave of the tuning.

mode_intervals :: Mode -> [Int] Source #

Intervals (in steps) between adjacent elements of the mode.

mode_iset :: Mode -> [Int] Source #

Interval set of mode (ie. nub of sort of mode_intervals)

mode_description :: Mode -> String Source #

The text description of the mode, ordinarily a comma separated list of names.

mode_length :: Mode -> Int Source #

length (or degree) of mode_intervals (ie. number of notes in mode)

mode_univ :: Mode -> Int Source #

sum of mode_intervals (ie. number of notes in tuning system)

mode_degree_seq :: Mode -> [Int] Source #

dx_d of mode_intervals. This seqence includes the octave.

type ModeNam = (Int, Int, [Mode]) Source #

(mode-count,mode-length-maxima,mode-list)

modenam_search_seq :: ModeNam -> [Int] -> [Mode] Source #

Search for mode by interval list.

modenam_search_seq1 :: ModeNam -> [Int] -> Maybe Mode Source #

Expect one result.

mn <- load_modenam
let sq = putStrLn . unlines . mode_stat . fromJust . modenam_search_seq1 mn
sq [2,2,1,2,2,2,1]
sq [2,1,2,2,1,2,2]
sq [2,1,2,2,1,3,1]
sq (replicate 6 2)
sq [1,2,1,2,1,2,1,2]
sq [2,1,2,1,2,1,2,1]
sq (replicate 12 1)

modenam_search_description :: ModeNam -> String -> [Mode] Source #

Search for mode by description text.

map (modenam_search_description mn) ["Messiaen","Xenakis","Raga"]

mode_rot_eqv :: Mode -> Mode -> Bool Source #

Is p an element of the set of rotations of q.

mode_stat :: Mode -> [String] Source #

Pretty printer.

mn <- load_modenam
let r = filter ((/=) 0 . mode_starting_degree) (modenam_modes mn) -- non-zero starting degrees
let r = filter ((== [(1,2),(2,5)]) . mode_histogram) (modenam_modes mn) -- 2×1 and 5×2
let r = filter ((== 22) . mode_univ) (modenam_search_description mn "Raga") -- raga of 22 shruti univ
[(p,q) | p <- r, q <- r, p < q, mode_rot_eqv p q] -- rotationally equivalent elements of r
length r
putStrLn $ unlines $ intercalate ["\n"] $ map mode_stat r

Parser

non_implicit_degree :: String -> Maybe Int Source #

Bracketed integers are a non-implicit starting degree.

map non_implicit_degree ["4","[4]"] == [Nothing,Just 4]

join_long_lines :: [String] -> [String] Source #

Lines ending with @@ continue to next line.

parse_modenam :: [String] -> ModeNam Source #

Parse joined non-comment lines of modenam file.

Io

load_modenam :: IO ModeNam Source #

parse_modenam of load_dist_file of modenam.par.

mn <- load_modenam
let (n,x,m) = mn
(n, x, length m) == (3087,15,3087) -- Scala 2.64p