\begin{code}
-- | 
-- Maintainer : silva.samuel@alumni.uminho.pt
-- Stability  : experimental
-- Portability: portable
-- This module implements multiple voices
module Music.Analysis.Abstract.Voices where
import Music.Analysis.PF ((><), split, p1, p2)
import Music.Analysis.Base (Number, IntegerNumber)
import Music.Analysis.Abstract.Settings (Settings)
import Music.Analysis.Abstract.Motive 
import Music.Analysis.Abstract.Zip 
import Music.Analysis.Abstract.Notations as Notations
import Data.Function (id, (.), const)
import Data.Tuple (uncurry)
import Prelude () 
\end{code} \begin{code}
-- * Types
-- |
type MultiVoiceNode = ((VoiceZipNode, IntegerNumber), NotationNode)
type MultiVoiceAbsolute = ((VoiceZipAbsolute, IntegerNumber), NotationNode)
type MultiVoiceRelative = ((VoiceZipRelative, IntegerNumber), NotationNode)
-- | default settings
settings :: Settings
settings = Notations.settings
\end{code} \begin{code}
joinVoices :: IntegerNumber -> (a, NotationNode) -> 
    ((a, IntegerNumber), NotationNode)
joinVoices b = split (split p1 (const b)) p2
splitVoices :: ((a, IntegerNumber), NotationNode) -> 
    (IntegerNumber, (a, NotationNode))
splitVoices = split (p2 . p1) (split (p1 . p1) p2)
\end{code} This are defined some combinators, like are transpose. These functions are defined using functions from Notations module. \begin{code}
-- | Transpose using above layers
transpose :: Number -> Motive MultiVoiceAbsolute -> Motive MultiVoiceAbsolute
transpose n = 
    mapMotive (const (uncurry joinVoices)) .
        joinMotivePair . (id >< Notations.transpose n) . splitMotivePair .
    mapMotive (const splitVoices) 
-- | tempo transformation using above layers
tempo :: Number -> Motive MultiVoiceAbsolute -> Motive MultiVoiceAbsolute
tempo n = 
    mapMotive (const (uncurry joinVoices)) .
        joinMotivePair . (id >< Notations.tempo n) . splitMotivePair .
    mapMotive (const splitVoices)
-- | duration computation using above layers
duration :: Motive MultiVoiceNode -> Number
duration = 
    Notations.duration . p2 . splitMotivePair . mapMotive (const splitVoices)
-- | reverse using above layers
reverse :: Motive MultiVoiceNode -> Motive MultiVoiceNode
reverse = 
    mapMotive (const (uncurry joinVoices)) .
        joinMotivePair . (id >< Notations.reverse) . 
        splitMotivePair .
    mapMotive (const splitVoices) 
-- | absolute transformation using above layers
absolute :: Motive MultiVoiceRelative -> Motive MultiVoiceAbsolute
absolute = 
    mapMotive (const (uncurry joinVoices)) .
        joinMotivePair . (id >< Notations.absolute) . splitMotivePair .
    mapMotive (const splitVoices) 
-- | relative transformation using above layers
relative :: Motive MultiVoiceAbsolute -> Motive MultiVoiceRelative
relative = 
    mapMotive (const (uncurry joinVoices)) .
        joinMotivePair . (id >< Notations.relative) . splitMotivePair .
    mapMotive (const splitVoices) 
\end{code}