module HarmTrace.Base.Chord.PitchClass (
PCSet
, pc
, toPitchClass
, pcToRoot
, toPitchClasses
, rootPC
, bassPC
, ignorePitchSpelling
, altPitchSpelling
, keyPitchClasses
, intValToPitchClss
, intSetToPC
, EnHarEq (..)
, Diatonic
) where
import HarmTrace.Base.Chord.Datatypes
import HarmTrace.Base.Chord.Intervals
import HarmTrace.Base.Chord.Internal
import Data.Binary ( Binary )
import Data.IntSet ( IntSet, fromList, union )
import qualified Data.IntSet as S ( map )
import GHC.Generics ( Generic )
newtype PCSet = PCSet {pc :: IntSet} deriving (Show, Eq, Generic)
instance Binary PCSet
majorScale :: Num a => [a]
majorScale = [0,2,4,5,7,9,11]
minorScale :: Num a => [a]
minorScale = [0,2,3,5,7,8,10]
toPitchClass :: (Diatonic a) => Note a -> Int
toPitchClass (Note m p)
| ix <= 6 = ((majorScale !! ix) + modToInt m) `mod` 12
| otherwise = error ("HarmTrace.Base.MusicRep.toPitchClass: no semitone for "
++ show p ++ show m )
where ix = fromEnum p
intSetToPC :: IntSet -> Root -> PCSet
intSetToPC is r = PCSet . S.map (transp (toPitchClass r)) $ is where
transp :: Int -> Int -> Int
transp t i = (i + t) `mod` 12
intValToPitchClss :: Root -> Interval -> Int
intValToPitchClss r i = (toPitchClass r + toIntervalClss i) `mod` 12
pcToRoot :: Int -> Root
pcToRoot i
| 0 <= i && i <= 11 = roots !! i
| otherwise = error ("HarmTrace.Base.MusicRep.toRoot " ++
"invalid pitch class: " ++ show i)
toPitchClasses :: ChordLabel -> PCSet
toPitchClasses c = catchNoChord "Chord.PitchClass.toPitchClasses"
(intSetToPC ivs . chordRoot) c
where ivs = toIntSet c `union` fromList [0, toIntervalClss (chordBass c)]
keyPitchClasses :: Key -> PCSet
keyPitchClasses k = intSetToPC (fromList scale) (keyRoot k) where
scale = case keyMode k of
MajMode -> majorScale
MinMode -> minorScale
bassPC :: ChordLabel -> Int
bassPC = catchNoChord "Chord.PitchClass.rootPC" bassPC' where
bassPC' :: ChordLabel -> Int
bassPC' c = intValToPitchClss (chordRoot c) (chordBass c)
rootPC :: ChordLabel -> Int
rootPC = catchNoChord "Chord.PitchClass.rootPC" (toPitchClass . chordRoot)
ignorePitchSpelling :: ChordLabel -> ChordLabel
ignorePitchSpelling NoChord = NoChord
ignorePitchSpelling UndefChord = UndefChord
ignorePitchSpelling c = fmap (pcToRoot . toPitchClass) c
altPitchSpelling :: ChordLabel -> Maybe ChordLabel
altPitchSpelling NoChord = Nothing
altPitchSpelling UndefChord = Nothing
altPitchSpelling (Chord (Note acc root) short add intervc) = case acc of
Nat -> Nothing
FF -> Nothing
SS -> Nothing
Fl -> Just $ Chord (Note Sh (pred root)) short add intervc
Sh -> Just $ Chord (Note Fl (succ root)) short add intervc
class EnHarEq a where
(&==) :: a -> a -> Bool
(&/=) :: a -> a -> Bool
a &== b = not (a &/= b)
a &/= b = not (a &== b)
instance Diatonic a => EnHarEq (Note a) where
a &== b = toPitchClass a == toPitchClass b
instance EnHarEq ChordLabel where
a &== b = toPitchClasses a == toPitchClasses b
class (Generic a, Show a, Enum a, Bounded a) => Diatonic a
instance Diatonic DiatonicNatural
instance Diatonic DiatonicDegree