------------------------------------------------------------------------------

-- Pitch.hs
-- created: Sun Mar 14 18:22:22 JST 2010

------------------------------------------------------------------------------

module Sound.Conductive.Pitch where

import Data.List
import Data.List.Utils
import Data.Maybe

a440 = 9 :: Int
a440MIDI = 69 :: Int
a4MIDI = 69 :: Int
a4 = 9 :: Int

-- scientific pitch notation
-- http://en.wikipedia.org/wiki/Scientific_pitch_notation

cent = 2**(1/12) :: Double

-- all pitch degrees from C0 to B10, must be centered around 440

pitches :: Int -> Int -> [Double]
pitches lowerN higherN = let
    below440 = reverse $ take lowerN $ iterate (/cent) 440
    above440 = tail $ take higherN $ iterate (*cent) 440
    in below440 ++ above440

pitchTableInWiki :: [Double]
pitchTableInWiki = pitches 58 75

notes :: [[Char]]
notes = ["c","c#","d","d#","e","f","f#","g","g#","a","a#","b"]

notesOctave :: (Show a) => a -> [[Char]]
notesOctave o = map (\x -> x ++ (show o)) notes

octaves :: (Show a) => [a] -> [[Char]]
octaves os = concat $ map notesOctave os

noteNames :: [[Char]]
noteNames = octaves [0..10]

pitchValues :: [Integer]
pitchValues = [(-48)..83]

audibleSemitones :: [(Integer, Double)]
audibleSemitones = zip pitchValues pitchTableInWiki

audiblePitches :: [([Char], (Integer, Double))]
audiblePitches = zip noteNames audibleSemitones

pitchesAndNotes :: [(Integer, [Char])]
pitchesAndNotes = zip pitchValues noteNames

pLookup :: ((Integer, Double) -> b) -> [Char] -> Maybe b
pLookup f x = let
    val = lookup x audiblePitches
    in if (val == Nothing) then Nothing else Just $ f $ fromJust val

pitch :: [Char] -> Maybe Integer
pitch = pLookup fst

frequency :: [Char] -> Maybe Double
frequency = pLookup snd

midiPitch :: [Char] -> Maybe Integer
midiPitch x = let
    p = pitch x
    in if (p == Nothing) then Nothing else Just $ 60 + (fromJust $ pitch x)

semitoneToFreq :: Integer -> Maybe Double
semitoneToFreq x = lookup x audibleSemitones