hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Tuning.Scala

Contents

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 4671 scales in v.85 of the scale library.

Synopsis

Pitch

type Pitch i = Either Cents (Ratio i) 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 

type Epsilon = Double Source #

A nearness value for deriving approximate rationals.

pitch_cents :: Integral i => Pitch i -> Cents Source #

Pitch as Cents, conversion by ratio_to_cents if necessary.

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

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

pitch_representations :: Integral t => [Pitch i] -> (t, t) Source #

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

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

If scale is uniform, give type.

pitch_type_predominant :: [Pitch i] -> Pitch_Type Source #

The predominant type of the pitches for Scale.

Scale

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

A scale has a name, a description, a degree, and a list of Pitches.

scale_name :: Scale i -> String Source #

The name of a scale.

scale_description :: Scale i -> String Source #

Text description of a scale.

scale_degree :: Scale i -> Int Source #

The degree of the scale (number of Pitches).

scale_pitches :: Scale i -> [Pitch i] Source #

The Pitches at Scale.

scale_verify :: Scale i -> Bool Source #

Ensure degree and number of pitches align.

scale_verify_err :: Scale i -> Scale i Source #

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

scale_octave :: Scale i -> Maybe (Pitch i) Source #

The last Pitch element of the scale (ie. the ocatve).

perfect_octave :: Integral i => Scale i -> Bool Source #

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

is_scale_uniform :: Scale i -> Bool Source #

Are all pitches of the same type.

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

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

scale_cents :: Integral i => Scale i -> [Cents] Source #

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

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

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

scale_ratios_req :: Integral i => Scale i -> [Ratio i] Source #

Require that Scale be uniformlay of Ratios.

scale_to_tuning :: Epsilon -> Scale Integer -> Tuning Source #

Translate Scale to Tuning. If Scale is uniformly rational, Tuning is rational, else Tuning is in Cents. Epsilon is used to recover the Rational octave if required.

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

Convert Tuning to Scale.

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

scale_eq :: Eq n => Scale n -> Scale n -> 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 ("","",12,map Right r)) db
scale_name py == "pyth_12"
let c = map T.ratio_to_cents r
let Just py' = find (scale_eqv ("","",12,map Left c)) db
scale_name py' == "pyth_12"

scale_eqv :: Integral n => Scale n -> Scale n -> Bool Source #

Are scales equal (==) at degree and tuning data after 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 null lines and trailing comments.

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

parse_pitch :: (Read i, Integral i) => String -> Pitch i Source #

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

map parse_pitch ["700.0","350.","3/2","2"] == [Left 700,Left 350,Right (3/2),Right 2]

parse_pitch_ln :: (Read i, Integral i) => String -> Pitch i Source #

Pitch lines may contain commentary.

parse_scl :: (Read i, Integral i) => String -> String -> Scale i Source #

Parse .scl file.

IO

scl_get_dir :: IO [String] Source #

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

setEnv "SCALA_DIST_DIR" "/home/rohan/data/scala/85/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/85/scl/young-lm_piano.scl"
scl_resolve_name "/home/rohan/data/scala/85/scl/unknown-tuning.scl"

scl_load :: (Read i, Integral i) => String -> IO (Scale i) 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 :: (Read i, Integral i) => FilePath -> IO [Scale i] Source #

Load all .scl files at dir.

dir <- scl_get_dir
dir == ["/home/rohan/data/scala/85/scl","/home/rohan/sw/hmt/data/scl"]
let [scl_85_dir,ext_dir] = dir
db <- scl_load_dir scl_85_dir
length db == 4671
length (filter ((== 0) . scale_degree) db) == 0
length (filter ((/= 1) . head . scale_ratios 1e-3) db) == 0
length (filter ((/= 0) . head . scale_cents) db) == 0
length (filter (== Just (Right 2)) (map scale_octave db)) == 4003
length (filter is_scale_uniform db) == 2816
let na = filter (not . T.is_ascending . scale_cents) db
length na == 121
mapM_ (putStrLn . unlines . scale_stat) na
import qualified Music.Theory.List as T
import Sound.SC3.Plot
plot_p2_stp [T.histogram (map scale_degree db)]
import Data.List
let r = ["Xenakis's Byzantine Liturgical mode, 5 + 19 + 6 parts"
        ,"Xenakis's Byzantine Liturgical mode, 12 + 11 + 7 parts"
        ,"Xenakis's Byzantine Liturgical mode, 7 + 16 + 7 parts"]
in filter (isInfixOf "Xenakis") (map scale_description db) == r
let r = ["LaMonte Young, tuning of For Guitar '58. 1/1 March '92, inv.of Mersenne lute 1"
        ,"LaMonte Young's Well-Tuned Piano"]
in filter (isInfixOf "LaMonte Young") (map scale_description db) == r
length (filter (not . perfect_octave) db) == 663

scl_load_db :: (Read i, Integral i) => IO [Scale i] Source #

Load Scala data base at scl_get_dir.

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

PP

pitch_pp :: Show i => Pitch i -> String Source #

Pretty print Pitch in Scala format.

scale_pp :: Show i => Scale i -> [String] Source #

Pretty print Scale in Scala format.

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

DIST

dist_get_dir :: IO String Source #

scala distribution directory, given at SCALA_DIST_DIR.

fmap (== "/home/rohan/opt/build/scala-22-pc64-linux") dist_get_dir

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

Load file from dist_get_dir.

s <- load_dist_file "intnam.par"
length s == 473