{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE FlexibleInstances #-} module HarmTrace.Audio.ChordTypes where import HarmTrace.Base.MusicRep import Text.Printf (printf) import Control.DeepSeq -------------------------------------------------------------------------------- -- High-level structure -------------------------------------------------------------------------------- -- the standard evaluation format of a chord annotation consists of a -- list with chords and segment boundaries type ChordAnnotation = [ChordSegment] type ChordSegment = TimedData ChordLabel type KeyAnnotation = [KeySegment] type KeySegment = TimedData Key type Block = TimedData [ProbChord] data TimedData a = TimedData {getData :: a, onset :: NumData, offset :: NumData} -- clusering propchords in a collection of chords that share a key data ProbChordSeg = Segment { segKey :: Key , segChords :: [TimedData [ProbChord]] } -- combining a chord with a probability data ProbChord = ProbChord {chordLab :: ChordLabel, prob :: NumData} -- a chord candidate: an intermediate datatype that matches shorthand, -- chord structure and root note data ChordCand = ChordCand Root Shorthand ChordStruct type ChordStruct = [NumData] -- an iterable list of Roots chromaPC ::[Root] chromaPC = [ Note Nothing C , Note (Just Fl) D , Note Nothing D , Note (Just Fl) E , Note Nothing E , Note Nothing F , Note (Just Sh) F , Note Nothing G , Note (Just Fl) A , Note Nothing A , Note (Just Fl) B , Note Nothing B ] -------------------------------------------------------------------------------- -- NFData instances -------------------------------------------------------------------------------- -- Simplified instance NFData ChordSegment where rnf (TimedData a b c) = a `seq` rnf b `seq` rnf c -------------------------------------------------------------------------------- -- Instances of high-level datastructure -------------------------------------------------------------------------------- instance Show (ProbChord) where show (ProbChord (Chord r sh _ _ _) p) = show r ++ ':' : show sh ++ ':' : printf "%.2f" p instance Show a => Show (TimedData a) where show (TimedData bk s l) = show bk ++ " (" ++ show s ++ ':' : show l ++ ")\n" instance Show ProbChordSeg where show pc = concatMap (\x -> (show $ segKey pc) ++ ' ' : show x) (segChords pc) -------------------------------------------------------------------------------- -- numerical data representation -------------------------------------------------------------------------------- data AudioFeat = AudioFeat String ChordinoData BeatTrackerData KeyStrengthData instance Show AudioFeat where show (AudioFeat idStr _ _ _) = idStr type ChordinoData = [ChordinoLine] data ChordinoLine = ChordinoLine { time :: NumData , bass :: [NumData] -- each of the lists has always 12 elements , treb :: [NumData] -- A, Bb, B, C, Db, D, Eb, E, F, F#, G, Ab } deriving (Eq, Show) -- and is shifted 3 positions to match C, Db, .., B type KeyStrengthData = ChordinoData type BeatTrackerData = [NumData] -- deriving (Eq, Show) type NumData = Double type BeatChroma = [[ChordinoLine]] -- one list per beat -- data TimeChroma = TimeChroma {stamp :: NumData, croma :: [NumData]}