\begin{code}
-- | 
-- Maintainer : silva.samuel@alumni.uminho.pt
-- Stability  : experimental
-- Portability: portable
-- This module implements annotation over music notation
module Music.Analysis.Abstract.Annotation where
import Music.Analysis.PF ((><), p1)
import Music.Analysis.Base (Text, Number)
import Music.Analysis.Abstract.Settings (Settings)
import Music.Analysis.Abstract.Motive 
import Music.Analysis.Abstract.Melodic 
import Music.Analysis.Abstract.Rhythm 
import Music.Analysis.Abstract.Notations 
import Music.Analysis.Abstract.Instruments as Instruments
import Data.Maybe (Maybe)
import Data.Function (id, (.))
import Data.Bool (Bool)
import Prelude () 
\end{code} Development of Recursive and powerfull Annotation. It still at alpha version. \begin{code}
-- * Types
-- |
type A = Text
-- |
type Annot = 
    ([((((MelodicNode, A),(RhythmNode, A)),Bool),
    [((NotationPosition,NotationInfo),A)])],A)
-- |
type AnnotationNode = [(Maybe Number, Text)]
-- | Definition of annotation
type MultiAnnotationNode = (MultiInstrumentNode, AnnotationNode)
type AnnotationAbsolute = (MultiInstrumentAbsolute, AnnotationNode)
type AnnotationRelative = (MultiInstrumentRelative, AnnotationNode)

-- | sefault settings
settings :: Settings
settings = Instruments.settings
\end{code} \begin{code}
-- | Transpose using above layers
transpose :: Number -> Motive AnnotationAbsolute -> Motive AnnotationAbsolute
transpose n = 
    joinMotivePair . ((Instruments.transpose n) >< id) . splitMotivePair
-- | tempo transformation using above layers
tempo :: Number -> Motive AnnotationAbsolute -> Motive AnnotationAbsolute
tempo n = joinMotivePair . ((Instruments.tempo n) >< id) . splitMotivePair
-- | duration computation using above layers
duration :: Motive MultiAnnotationNode -> [Number]
duration = Instruments.duration . p1 . splitMotivePair
-- | reverse using above layers
reverse :: Motive MultiAnnotationNode -> Motive MultiAnnotationNode
reverse = joinMotivePair . (Instruments.reverse >< id) . splitMotivePair
-- | absolute transformation using above layers
absolute :: Motive AnnotationRelative -> Motive AnnotationAbsolute
absolute = joinMotivePair . (Instruments.absolute >< id) . splitMotivePair
-- | relative transformation using above layers
relative :: Motive AnnotationAbsolute -> Motive AnnotationRelative
relative = joinMotivePair . (Instruments.relative >< id) . splitMotivePair
\end{code}