hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Wyschnegradsky

Contents

Description

Synopsis

Documentation

normalise_step :: (Eq n, Num n) => n -> n -> n Source #

In a modulo m system, normalise step increments to be either -1 or 1. Non steps raise an error.

map (normalise_step 6) [-5,-1,1,5] == [1,-1,1,-1]

parse_num_sign :: (Num n, Read n) => String -> n Source #

Wyschnegradsky writes the direction sign at the end of the number.

map parse_num_sign ["2+","4-"] == [2,-4]

vec_expand :: Num n => Int -> [n] Source #

Expand a chromatic (step-wise) sequence, sign indicates direction.

map vec_expand [2,-4] == [[1,1],[-1,-1,-1,-1]]

parse_vec :: Num n => Maybe Int -> n -> String -> [n] Source #

Parse the vector notation used in some drawings, a comma separated list of chromatic sequences.

parse_vec Nothing 0 "4-,4+,4-,4+,4-,4+,4-,4+,4-"
parse_vec Nothing 0 "2+,2-,2+,2-,2+,2-,2+,2-,2+,18+"

add_m :: Integral a => a -> a -> a -> a Source #

Modulo addition.

parse_hex_clr :: (Read n, Num n) => String -> (n, n, n) Source #

Parse hex colour string, as standard in HTML5.

parse_hex_clr "#e14630" == (225,70,48)

parse_hex_clr_int :: String -> (Int, Int, Int) Source #

Type specialised.

clr_normalise :: (Real r, Fractional f) => f -> (r, r, r) -> (f, f, f) Source #

Normalise colour by dividing each component by m.

clr_normalise 255 (parse_hex_clr "#ff0066") == (1,0,0.4)

data Seq a Source #

Sequences are either in Radial or Circumferential order.

Constructors

Radial [a] 
Circumferential [a] 

seq_group :: Int -> Int -> Seq a -> [[a]] Source #

Group sequence into normal (ie. Circumferential) order given drawing dimensions.

iw_pc_pp :: Integral n => String -> [[n]] -> IO () Source #

Printer for pitch-class segments.

U3

u3_ix_ch :: Integral i => i -> Char Source #

Index to colour name abbreviation.

map u3_ix_ch [0..5] == "ROYGBV"

u3_ch_ix :: Char -> Int Source #

Inverse of u3_ix_ch.

map u3_ch_ix "ROYGBV" == [0..5]

u3_vec_text_iw :: [(String, String)] Source #

Drawing definition, as written by Wyschnegradsky.

mapM_ (\(c,r) -> putStrLn (unlines ["C: " ++ c,"R: " ++ r])) u3_vec_text_iw

u3_vec_text_rw :: [(String, String)] Source #

Re-written for local parser and to correct ambiguities and errors (to align with actual drawing).

let f = parse_vec Nothing 0 in map (\(p,q) -> (f p,f q)) u3_vec_text_rw
let f (c,r) = putStrLn (unlines ["C: " ++ c,"R: " ++ r])
in mapM_ f (interleave u3_vec_text_iw u3_vec_text_rw)

u3_vec_ix :: Num n => ([[n]], [[n]]) Source #

Parse of u3_vec_text_rw.

let {(c,r) = u3_vec_ix ; c' = map length c}
in (length c,c',sum c',length r,map length r)

u3_ix_radial :: Integral n => [[n]] Source #

Radial indices (ie. each ray as an index sequence).

putStrLn $ unlines $ map (map u3_ix_ch) u3_ix_radial

u3_clr_nm :: [String] Source #

Colour names in index sequence.

u3_clr_hex :: [String] Source #

Colour values (hex strings) in index sequence.

u3_clr_rgb :: Fractional n => [(n, n, n)] Source #

RGB form of u3_clr_hex.

u3_radial_ch :: [(Int, [Char])] Source #

Notated radial color sequence, transcribed from drawing.

map (\(n,c) -> let v = u3_ch_seq_to_vec c in (n,sum v,v)) u3_radial_ch

u3_circ_ch :: [(Int, [Char])] Source #

Notated circumferenctial color sequence, transcribed from drawing.

map (\(n,c) -> (n,u3_ch_seq_to_vec c)) u3_circ_ch

u3_ch_seq_to_vec :: [Char] -> [Int] Source #

Translate notated sequence to "re-written" vector notation.

DC9

dc9_circ :: Num n => [[n]] Source #

Circumference pitch classes, C = 0.

let c' = map length dc9_circ in (sum c',c') == (72,[5,6,7,2,3,4,4,3,2,7,7,4,4,3,2,2,3,4])
iw_pc_pp " | " dc9_circ

dc9_rad :: Num n => [n] Source #

Rayon pitch classes, C = 0.

length dc9_rad == 18
putStrLn $ unwords $ map f dc9_rad

dc9_ix :: Integral n => [[n]] Source #

Radial indices.

map length dc9_ix == replicate 72 18

dc9_clr_hex :: [String] Source #

Approximate colours, hex strings.

dc9_clr_rgb :: Fractional n => [(n, n, n)] Source #

RGB form of colours.

U11

u11_circ :: Num n => [[n]] Source #

u11_gen_seq :: Integral i => i -> Int -> [i] -> [i] Source #

u11_rad :: Integral n => [[n]] Source #

u11_clr_rgb :: Fractional n => [(n, n, n)] Source #