module Temporal.Music.Western.TwelveTone(
    -- * 12-tones
    -- | Chromatic scales
          
    -- ** Tones
    Chromatic(..),
    c, d, e, f, g, a, b, 
    cs, ds, es, fs, gs, as, bs,
    cf, df, ef, ff, gf, af, bf,

    -- ** Scales
    eqt, pyth, 
    hind, hindFs, hindGb,
    {-
    -- * 7-tones
    
    -- | Diatonic scales

    -- ** Tones
    Diatonic(..),
    d0, d1, d2, d3, d4, d5, d6,

    -- ** Scales

    -- | Here scales are scale functions. The take chromatic scales
    -- and produce 7-tone subscales.
    major, minor,
    ionian, dorian, phrygian, lydian, 
	mixolydian, aeolian, locrian,

    -- * 5-tones    
    
    -- | Pentatonic scales
    
    -- ** Tones
    Pentatonic(..),
    p0, p1, p2, p3, p4, 
    -}
    
    -- ** Scales

    -- | Here scales are scale functions. The take chromatic scales
    -- and produce 5-tone subscales.
    minor5, major5, bluesMinor5, bluesMajor5, egyptian5,

    -- * Intervals
    
    -- ** pure intervals as factors
    pureOctave, pureFifth, pureForth, pureMajorThird,
        pureMinorThird, pureWholeTone, pureHalfTone, pureMajorSixth,
        pureMinorSixth, pureMajorSeventh, pureMinorSeventh, 

    -- ** in steps for 12 tone scale
    
    majorSeventh, minorSeventh, majorSixth, minorSixth,
        fifth, tritone, forth, majorThird, 
        minorThird, wholeTone, halfTone 

    )
where

import Temporal.Music.Notation.Seg(Seg)
--import Temporal.Music.Notation.Seg(Seg, IntSeg(..), N5, N7)
import Temporal.Music.Notation.Pitch

import Temporal.Music.Notation.Scales(
        eqt, pyth, hind, hindFs, hindGb,
        minor5, major5, bluesMinor5, bluesMajor5, egyptian5,
        major, minor, ionian, dorian, phrygian, lydian, 
	    mixolydian, aeolian, locrian)

-- | 12-tone scale. Default scale defined in 'Pch' class 
-- is equal temperament.
data Chromatic = 
      C  | Cs | D  | Ds | E  | F 
    | Fs | G  | Gs | A  | As | B
    deriving (Enum, Bounded, Eq, Show)

instance Seg Chromatic

instance Pch Chromatic where
    pitch = Pitch (eqt 0 c1)

-- tones

c, d, e, f, g, a, b, 
    cs, ds, es, fs, gs, as, bs,
    cf, df, ef, ff, gf, af, bf :: Tone Chromatic

c    = tone C
cs   = tone Cs
d    = tone D
ds   = tone Ds
e    = tone E
f    = tone F
fs   = tone Fs
g    = tone G
gs   = tone Gs
a    = tone A
as   = tone As
b    = tone B

bs   = c
es   = f

cf   = b
df   = cs
ef   = ds
ff   = e
gf   = fs
af   = gs
bf   = as

{-
-- | 5-tone scale. Default scale defined in 'Pch' class 
-- is minor pentatonic on equal temerament.
newtype Pentatonic = Pentatonic { 
    runPentatonic :: IntSeg N5 
    } deriving (Show, Eq, Bounded)

instance Enum Pentatonic where
    toEnum = Pentatonic . toEnum
    fromEnum = fromEnum . runPentatonic

instance Seg Pentatonic

instance Pch Pentatonic where
    pitch = Pitch (minor5 $ eqt 0 c1)
    

p0, p1, p2, p3, p4 :: Tone Pentatonic

p0 = pn 0
p1 = pn 1
p2 = pn 2
p3 = pn 3
p4 = pn 4

pn :: Int -> Tone Pentatonic
pn = tone . Pentatonic . IntSeg

 
-- | 7-tone scale. Default scale defined in 'Pch' class
-- is C major on equal temperament.
newtype Diatonic = Diatonic { 
    runDiatonic :: IntSeg N7 
    } deriving (Show, Eq, Bounded)

instance Enum Diatonic where
    toEnum = Diatonic . toEnum
    fromEnum = fromEnum . runDiatonic

instance Seg Diatonic

instance Pch Diatonic where
    pitch = Pitch (major $ eqt 0 c1)

d0, d1, d2, d3, d4, d5, d6 :: Tone Diatonic

d0 = dn 0
d1 = dn 1
d2 = dn 2
d3 = dn 3
d4 = dn 4
d5 = dn 5
d6 = dn 6

dn :: Int -> Tone Diatonic
dn = tone . Diatonic . IntSeg
-}
---------------------------------------------------------
-- intervals

pureOctave, pureFifth, pureForth, pureMajorThird,
    pureMinorThird, pureWholeTone, pureHalfTone, pureMajorSixth,
    pureMinorSixth, pureMajorSeventh, pureMinorSeventh :: Fractional a => a

pureOctave = 2
pureFifth  = 3/2
pureForth  = 4/3
pureMajorThird = 5/4
pureMinorThird = 6/5
pureWholeTone = 9/8
pureHalfTone = 25/24
pureMajorSixth = 5/3
pureMinorSixth = 8/5
pureMajorSeventh = 48/25
pureMinorSeventh = 16/9


majorSeventh, minorSeventh, majorSixth, minorSixth,
    fifth, tritone, forth, majorThird, 
    minorThird, wholeTone, halfTone :: Step


majorSeventh = 11
minorSeventh = 10
majorSixth = 9
minorSixth = 8
fifth = 7
tritone = 6
forth = 5
majorThird = 4
minorThird = 3
wholeTone = 2
halfTone = 1