module HarmTrace.Base.Parse.ChordParser (
  
    pChord
  , pShorthand
  , pRoot
  , pAdditions
  , pAddition
  , pKey
  , pBeat
  ) where
import HarmTrace.Base.Parse.General
import HarmTrace.Base.Chord
import HarmTrace.Base.Time
import Data.List                   ( sort )
pChord :: Parser ChordLabel
pChord =     pChordLabel
         <|> (NoChord    <$ (pString "N"  <|> pString "&pause"))
         <|> (UndefChord <$ (pSym '*'     <|> pSym 'X'))
         <?> "Chord"
pChordLabel :: Parser ChordLabel
pChordLabel = mkChord <$> pRoot <* (pSym ':' `opt` ':')
                      <*> pMaybe pShorthand
                      <*> (pAdditions `opt` [])
                      <*> pInversion where
  mkChord :: Root -> Maybe Shorthand -> [Addition] -> Either Interval Root 
          -> ChordLabel
  
  
  mkChord r Nothing [] b = Chord   r Maj             [] (toInversion r b)
  mkChord r Nothing  a b = toChord r (addToIntSet a)    (toInversion r b)
  mkChord r (Just s) a b = Chord   r s               a  (toInversion r b)
  toInversion :: Root -> Either Interval Root -> Interval
  toInversion _  (Left  iv) = iv
  toInversion ra (Right rb) = pitchToInterval ra rb
  
pInversion :: Parser (Either Interval Root)
pInversion =    Left  <$ pSym '/' <*> pIntNote
           <|>  Right <$ pSym '/' <*> pRoot
           <<|> pure (Left $ Note Nat I1)
           <?> "/Inversion"           
  
pKey :: Parser Key
pKey = f <$> pRoot <* pSym ':' <*> pShorthand <?> "Key"
  where f r m | m == Maj = Key r MajMode
              | m == Min = Key r MinMode
              | otherwise = error ("Tokenizer: key must be Major or Minor, "
                          ++ "found: " ++ show m)
pShorthand :: Parser Shorthand
pShorthand =     Maj      <$ pString "maj"
             <|> Min      <$ pString "min"
             <|> Dim      <$ pString "dim"
             <|> Aug      <$ pString "aug"
             <|> Maj7     <$ pString "maj7"
             <|> Min7     <$ pString "min7"
             <|> Sev      <$ pString "7"
             <|> Dim7     <$ pString "dim7"
             <|> HDim7    <$ pString "hdim" <* opt (pSym '7') '7'
             <|> MinMaj7  <$ pString "minmaj7"
             <|> Aug7     <$ pString "aug7"
             <|> Maj6     <$ pString "maj6"
             <|> Maj6     <$ pString "6"
             <|> Min6     <$ pString "min6"
             <|> Nin      <$ pString "9"
             <|> Maj9     <$ pString "maj9"
             <|> Min9     <$ pString "min9"
             <|> Five     <$ pString "5"
             <|> Sus2     <$ pString "sus2"
             <|> Sus4     <$ pString "sus4"
             <|> SevSus4  <$ pString "7sus4"
             
             <|> Min11    <$ pString "min11"
             <|> Min13    <$ pString "min13"
             <|> Maj13    <$ pString "maj13"
             <|> Eleven   <$ pString "11"
             <|> Thirteen <$ pString "13"
             <|> None     <$ pString "1" 
                                         
             <?> "Shorthand"
pAdditions :: Parser [Addition]
pAdditions = sort <$> pPacked (pSym '(') (pSym ')') ( pListSep (pSym ',') pAddition )
             <?> "Addition List"
pAddition :: Parser Addition
pAddition = (Add   <$>             pIntNote)
        <|> (NoAdd <$> (pSym '*'*> pIntNote))
        <?> "Addition"
pIntNote :: Parser Interval
pIntNote = Note <$> pAccidental <*> pInterval
pAccidental :: Parser Accidental
pAccidental =    Sh <$ pSym    's'
             <|> Sh <$ pSym    '#'
             <|> Fl <$ pSym    'b'
             <|> SS <$ pString "ss"
             <|> SS <$ pString "##"
             <|> FF <$ pString "bb"
             <|> pure Nat <?> "Accidental"
pInterval :: Parser IntNat
pInterval =  foldr (<|>) pFail opts <?> "Interval" where
  opts = [i <$ pString (show i) | i <- [minBound..] ]
pRoot :: Parser Root
pRoot = (flip Note) <$> pDiaNat <*> pAccidental
pDiaNat :: Parser DiatonicNatural
pDiaNat =    A  <$ pSym 'A'
         <|> B  <$ pSym 'B'
         <|> C  <$ pSym 'C'
         <|> D  <$ pSym 'D'
         <|> E  <$ pSym 'E'
         <|> F  <$ pSym 'F'
         <|> G  <$ pSym 'G'
pBeat :: Parser Beat
pBeat =   One    <$ pSym '1'
      <|> Two    <$ pSym '2'
      <|> Three  <$ pSym '3'
      <|> Four   <$ pSym '4'
      <|> NoBeat <$ pSym 'x'
      <?> "Beat"