Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Scala "keyboard mapping" files (.kbm) and related data structure.
Synopsis
- type Kbm = (Int, (Int, Int), Int, (Int, Double), Int, [Maybe Int])
- kbm_pp :: Kbm -> String
- kbm_in_rng :: Kbm -> Int -> Bool
- kbm_is_linear :: Kbm -> Bool
- kbm_lookup :: Kbm -> Int -> Maybe (Int, Int)
- kbm_lookup_mF :: Kbm -> (Int, (Int, Int), Double)
- kbm_parse :: String -> Kbm
- kbm_load_file :: FilePath -> IO Kbm
- kbm_load_dist :: String -> IO Kbm
- kbm_load :: String -> IO Kbm
- kbm_load_dir_fn :: FilePath -> IO [(FilePath, Kbm)]
- kbm_load_dist_dir_fn :: IO [(FilePath, Kbm)]
- kbm_format :: Kbm -> String
- kbm_wr :: FilePath -> Kbm -> IO ()
- kbm_d12_a440 :: Kbm
- kbm_d12_c256 :: Kbm
- kbm_k0 :: Int -> Int -> (Int, Int)
- kbm_oct_key_seq :: Kbm -> [(Int, (Int, Int))]
- kbm_mC_freq :: Kbm -> Scale -> Double
- kbm_fmidi_tbl :: Kbm -> Scale -> [(Int, Double)]
- kbm_cps_tbl :: Kbm -> Scale -> [(Int, Double)]
Documentation
type Kbm = (Int, (Int, Int), Int, (Int, Double), Int, [Maybe Int]) Source #
Scala keyboard mapping
(sz,(m0,mN),mC,(mF,f),o,m)
- sz = size of map, the pattern repeats every so many keys
- (m0,mN) = the first and last midi note numbers to retune
- mC = the middle note where the first entry of the mapping is mapped to
- (mF,f) = the reference midi-note for which a frequency is given, ie. (69,440)
- o = scale degree to consider as formal octave
- m = mapping, numbers represent scale degrees mapped to keys, Nothing indicates no mapping
kbm_is_linear :: Kbm -> Bool Source #
Is kbm linear?, ie. is size zero? (formal-octave may or may not be zero)
kbm_lookup :: Kbm -> Int -> Maybe (Int, Int) Source #
Given kbm and midi-note-number lookup (octave,scale-degree).
k <- kbm_load_dist "example.kbm" -- 12-tone scale k <- kbm_load_dist "a440.kbm" -- linear k <- kbm_load_dist "white.kbm" -- 7-tone scale on white notes k <- kbm_load_dist "black.kbm" -- 5-tone scale on black notes k <- kbm_load_dist "128.kbm"
map (kbm_lookup k) [48 .. 72]
kbm_lookup_mF :: Kbm -> (Int, (Int, Int), Double) Source #
Return the triple (mF,kbm_lookup k mF,f). The lookup for mF is not-nil by definition.
kbm_lookup_mF k
kbm_load_dist :: String -> IO Kbm Source #
pp nm = kbm_load_dist nm >>= \x -> putStrLn (kbm_pp x) pp "example" pp "bp" pp "7" -- error -- 12/#13 pp "8" -- error -- 12/#13 pp "white" -- error -- 12/#13 pp "black" -- error -- 12/#13 pp "128" pp "a440" pp "61"
kbm_load :: String -> IO Kbm Source #
If nm is a file name (has a .kbm) extension run kbm_load_file
else run kbm_load_dist
.
kbm_load_dist_dir_fn :: IO [(FilePath, Kbm)] Source #
Load all .kbm files at scala dist dir.
db <- kbm_load_dist_dir_fn length db == 41 x = map (\(fn,(sz,_,_,_,o,m)) -> (System.FilePath.takeFileName fn,sz,length m,o)) db filter (\(_,i,j,_) -> i < j) x -- size < map-length filter (\(_,i,_,k) -> i == 0 && k == 0) x -- size and formal octave both zero
map (\(fn,k) -> (System.FilePath.takeFileName fn,kbm_lookup_mF k)) db
kbm_format :: Kbm -> String Source #
Pretty-printer for scala .kbm file.
m <- kbm_load_dist "7.kbm" kbm_parse (kbm_format m) == m putStrLn $ kbm_pp m
kbm_d12_a440 :: Kbm Source #
Standard 12-tone mapping with A=440hz (ie. example.kbm)
fmap (== kbm_d12_a440) (kbm_load_dist "example.kbm") putStrLn $ kbm_pp kbm_d12_a440
kbm_d12_c256 :: Kbm Source #
kbm_k0 :: Int -> Int -> (Int, Int) Source #
Given size and note-center calculate relative octave and key number (not scale degree) of the zero entry.
map (kbm_k0 12) [59,60,61] == [(-4,1),(-5,0),(-5,11)]
kbm_oct_key_seq :: Kbm -> [(Int, (Int, Int))] Source #
Given size and note-center calculate complete octave and key number sequence (ie. for entries 0 - 127).
map (zip [0..] . kbm_oct_key_seq 12) [59,60,61]