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

Music.Theory.Tuning.Scala

Description

Parser for the Scala scale file format.

See http://www.huygens-fokker.org/scala/scl_format.html for details.

This module succesfully parses all scales in v.91 of the scale library.

Synopsis

Pitch

type Pitch = Either Cents Rational Source #

A .scl pitch is either in Cents or is a Ratio.

data Pitch_Type Source #

An enumeration type for .scl pitch classification.

Constructors

Pitch_Cents 
Pitch_Ratio 

Instances

Instances details
Show Pitch_Type Source # 
Instance details

Defined in Music.Theory.Tuning.Scala

Eq Pitch_Type Source # 
Instance details

Defined in Music.Theory.Tuning.Scala

type Epsilon = Double Source #

A nearness value for deriving approximate rationals.

pitch_cents :: Pitch -> Cents Source #

Pitch as Cents, conversion by ratio_to_cents if necessary.

pitch_ratio :: Epsilon -> Pitch -> Rational Source #

Pitch as Rational, conversion by reconstructed_ratio if necessary, hence epsilon.

pitch_representations :: [Pitch] -> (Int, Int) Source #

A pair giving the number of Cents and number of Ratio pitches.

uniform_pitch_type :: [Pitch] -> Maybe Pitch_Type Source #

If scale is uniform, give type.

pitch_type_predominant :: [Pitch] -> Pitch_Type Source #

The predominant type of the pitches for Scale.

Scale

type Scale = (String, String, Int, [Pitch]) Source #

A scale has a name, a description, a degree, and a sequence of pitches. The name is the the file-name without the .scl suffix. By convention the first comment line gives the file name (with suffix). The pitches do NOT include 1:1 or 0c and do include the octave.

scale_name :: Scale -> String Source #

The name of a scale.

scale_description :: Scale -> String Source #

Text description of a scale.

scale_degree :: Scale -> Int Source #

The degree of the scale (number of Pitches).

pitch_non_oct :: Pitch -> Bool Source #

Is Pitch outside of the standard octave (ie. cents 0-1200 and ratios 1-2)

scale_verify :: Scale -> Bool Source #

Ensure degree and number of pitches align.

scale_verify_err :: Scale -> Scale Source #

Raise error if scale doesn't verify, else id.

scale_octave :: Scale -> Maybe Pitch Source #

The last Pitch element of the scale (ie. the octave). For empty scales give Nothing.

scale_octave_err :: Scale -> Pitch Source #

Error variant.

perfect_octave :: Scale -> Bool Source #

Is scale_octave perfect, ie. Ratio of 2 or Cents of 1200.

is_scale_uniform :: Scale -> Bool Source #

Are all pitches of the same type.

is_scale_ascending :: Scale -> Bool Source #

Are the pitches in ascending sequence.

scale_uniform :: Epsilon -> Scale -> Scale Source #

Make scale pitches uniform, conforming to the most predominant pitch type.

scale_cents :: Scale -> [Cents] Source #

Scale as list of Cents (ie. pitch_cents) with 0 prefix.

scale_ratios :: Epsilon -> Scale -> [Rational] Source #

Scale as list of Rational (ie. pitch_ratio) with 1 prefix.

scale_ratios_u :: Scale -> Maybe [Rational] Source #

Require that Scale be uniformly of Ratios.

scale_ratios_req :: Scale -> [Rational] Source #

Erroring variant of 'scale_ratios_u.

scale_eq :: Scale -> Scale -> Bool Source #

Are scales equal (==) at degree and tuning data.

db <- scl_load_db
let r = [2187/2048,9/8,32/27,81/64,4/3,729/512,3/2,6561/4096,27/16,16/9,243/128,2/1]
let Just py = find (scale_eq ("","",length r,map Right r)) db
scale_name py == "pyth_12"

scale_eqv provides an approximate equality function.

let c = map T.ratio_to_cents r
let Just py' = find (scale_eqv 0.00001 ("","",length c,map Left c)) db
scale_name py' == "pyth_12"

scale_eq_n :: Int -> Scale -> Scale -> Bool Source #

Are scales equal at degree and intersect to at least k places of tuning data.

scale_sub :: Scale -> Scale -> Bool Source #

Is s1 a proper subset of s2.

scale_eqv :: Epsilon -> Scale -> Scale -> Bool Source #

Are scales equal at degree and equivalent to within epsilon at pitch_cents.

Parser

is_comment :: String -> Bool Source #

Comment lines begin with !.

remove_eol_comments :: String -> String Source #

Remove to end of line ! comments.

remove_eol_comments " 1 ! comment" == " 1 "

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

Remove comments and trailing comments (the description may be empty, keep nulls)

filter_comments ["!a","b","","c","d!e"] == ["b","","c","d"]

parse_pitch :: String -> Pitch Source #

Pitches are either cents (with decimal point, possibly trailing) or ratios (with /).

map parse_pitch ["70.0","350.","3/2","2","2/1"] == [Left 70,Left 350,Right (3/2),Right 2,Right 2]

parse_pitch_ln :: String -> Pitch Source #

Pitch lines may contain commentary.

parse_scl :: String -> String -> Scale Source #

Parse .scl file.

Io

scl_get_dir :: IO [FilePath] Source #

Read the environment variable SCALA_SCL_DIR, which is a sequence of directories used to locate scala files on.

setEnv "SCALA_SCL_DIR" "/home/rohan/data/scala/90/scl"

scl_derive_filename :: FilePath -> IO FilePath Source #

Lookup the SCALA_SCL_DIR environment variable, which must exist, and derive the filepath. It is an error if the name has a file extension.

mapM scl_derive_filename ["young-lm_piano","et12"]

scl_resolve_name :: String -> IO FilePath Source #

If the name is an absolute file path and has a .scl extension, then return it, else run scl_derive_filename.

scl_resolve_name "young-lm_piano"
scl_resolve_name "/home/rohan/data/scala/90/scl/young-lm_piano.scl"
scl_resolve_name "/home/rohan/data/scala/90/scl/unknown-tuning.scl"

scl_load :: String -> IO Scale Source #

Load .scl file, runs resolve_scl.

s <- scl_load "xenakis_chrom"
pitch_representations (scale_pitches s) == (6,1)
scale_ratios 1e-3 s == [1,21/20,29/23,179/134,280/187,11/7,100/53,2]

scl_load_dir_fn :: FilePath -> IO [(FilePath, Scale)] Source #

Load all .scl files at dir, associate with file-name.

db <- scl_load_dir_fn "/home/rohan/data/scala/91/scl"
length db == 5176 -- v.91
map (\(fn,s) -> (takeFileName fn,scale_name s)) db

scl_load_db :: IO [Scale] Source #

Load Scala data base at scl_get_dir.

db <- scl_load_db
mapM_ (putStrLn . unlines . scale_stat) (filter (not . perfect_octave) db)

Pp

scales_dir_txt_csv :: [Scale] -> String Source #

Format as CSV file.

db <- scl_load_db
writeFile "/tmp/scl.csv" (scales_dir_txt_csv db)

scale_stat :: Scale -> [String] Source #

Simple plain-text display of scale data.

db <- scl_load_db
writeFile "/tmp/scl.txt" (unlines (intercalate [""] (map scale_stat db)))

pitch_pp :: Pitch -> String Source #

Pretty print Pitch in Scala format.

scale_pp :: Scale -> [String] Source #

Pretty print Scale in Scala format.

scl <- scl_load "et19"
scl <- scl_load "young-lm_piano"
putStr $ unlines $ scale_pp scl

scale_wr_dir :: FilePath -> Scale -> IO () Source #

Write scl to dir with the file-name scale_name.scl

Dist

dist_get_dir :: IO String Source #

scala distribution directory, given at SCALA_DIST_DIR.

setEnv "SCALA_DIST_DIR" "/home/rohan/opt/build/scala-22"

load_dist_file_ln :: FilePath -> IO [String] Source #

fmap lines load_dist_file

s <- load_dist_file_ln "intnam.par"
length s == 565 -- Scala 2.46d

Query

scl_is_ji :: Scale -> Bool Source #

Is scale just-intonation (ie. are all pitches ratios)

scl_ji_limit :: Scale -> Integer Source #

Calculate limit for JI scale (ie. largest prime factor)

scl_cdiff_abs_sum :: [Cents] -> Scale -> [(Double, [Cents], Int)] Source #

Sum of absolute differences to scale given in cents, sorted, with rotation.

scl_cdiff_abs_sum_1 :: (Double -> n) -> [Cents] -> Scale -> (Double, [n], Int) Source #

Variant selecting only nearest and with post-processing function.

scl <- scl_load "holder"
scale_cents_i scl
c = [0,83,193,308,388,502,584,695,778,890,1004,1085,1200]
(_,r,_) = scl_cdiff_abs_sum_1 round c scl
r == [0,2,-1,1,0,-1,0,-1,0,0,0,0,0]

scl_db_query_cdiff_asc :: Ord n => (Double -> n) -> [Scale] -> [Cents] -> [((Double, [n], Int), Scale)] Source #

Sort DB into ascending order of sum of absolute of differences to scale given in cents. Scales are sorted and all rotations are considered.

db <- scl_load_db
c = [0,83,193,308,388,502,584,695,778,890,1004,1085,1200]
r = scl_db_query_cdiff_asc round db c
((_,dx,_),_):_ = r
dx == [0,2,-1,1,0,-1,0,-1,0,0,0,0,0]
mapM_ (putStrLn . unlines . scale_stat . snd) (take 10 r)

scale_cmp_ji :: ([Rational] -> [Rational] -> Bool) -> [Rational] -> Scale -> Bool Source #

Is x the same scale as scl under cmp.

scl_find_ji :: ([Rational] -> [Rational] -> Bool) -> [Rational] -> [Scale] -> [Scale] Source #

Find scale(s) that are scale_cmp_ji to x. Usual cmp are (==) and is_subset.

Tuning

scale_to_tuning :: Scale -> Tuning Source #

Translate Scale to Tuning. If Scale is uniformly rational, Tuning is rational, else it is in Cents.

tuning_to_scale :: (String, String) -> Tuning -> Scale Source #

Convert Tuning to Scale.

tuning_to_scale ("et12","12 tone equal temperament") (T.tn_equal_temperament 12)

scl_load_tuning :: String -> IO Tuning Source #

scale_to_tuning of scl_load.

fmap T.tn_limit (scl_load_tuning "pyra") -- Just 59