\begin{code} -- | -- Maintainer : silva.samuel@alumni.uminho.pt -- Stability : experimental -- Portability: portable -- This module implements specific music notation module Music.Analysis.Abstract.Notations where import Music.Analysis.PF ((><), p1) import Music.Analysis.Base (Number, Text, Invariant(..)) import Music.Analysis.Abstract.Settings (Settings) import Music.Analysis.Abstract.Motive import Music.Analysis.Abstract.Zip as Zip import Data.Ord (Ord(..)) import Data.Bool (Bool(..)) import Data.Function (id, (.)) import Data.Either (Either(..)) import Data.Maybe (Maybe(..)) import Prelude () \end{code} This are defined settings to Motive NotationNode, that will be equal to Zip settings. \begin{code} -- | Info type NotationInfo = Either Text Number -- | New Notation Node type NotationNode = [(NotationPosition, NotationInfo)] -- for each note -- | New Notation Position type NotationPosition = Maybe Position -- Nothing -> Point; Just -> Interval (more x) -- | Position type Position = Number -- | sefault settings settings :: Settings settings = Zip.settings instance Invariant NotationPosition where invariant (Just n) | n < 0 = False invariant _ = True \end{code} \begin{code} -- | addNotation :: NotationPosition -> NotationInfo -> NotationNode -> NotationNode addNotation a b = (:) (a,b) \end{code} Next functions are combinators like transpose. \begin{code} -- | transpose using above layers transpose :: Number -> Motive (VoiceZipAbsolute, NotationNode) -> Motive (VoiceZipAbsolute, NotationNode) transpose n = joinMotivePair . ((Zip.transpose n) >< id) . splitMotivePair -- | tempo transformation using above layers tempo :: Number -> Motive (VoiceZipAbsolute, NotationNode) -> Motive (VoiceZipAbsolute, NotationNode) tempo n = joinMotivePair . ((Zip.tempo n) >< id) . splitMotivePair -- | duration computation using above layers duration :: Motive (VoiceZipNode, NotationNode) -> Number duration = Zip.duration . p1 . splitMotivePair -- | reverse using above layers reverse :: Motive (VoiceZipNode, NotationNode) -> Motive (VoiceZipNode, NotationNode) reverse = joinMotivePair . (Zip.reverse >< id) . splitMotivePair -- | relative transformation using above layers relative :: Motive (VoiceZipAbsolute, NotationNode) -> Motive (VoiceZipRelative, NotationNode) relative = joinMotivePair . (Zip.relative >< id) . splitMotivePair -- | absolute transformation using above layers absolute :: Motive (VoiceZipRelative, NotationNode) -> Motive (VoiceZipAbsolute, NotationNode) absolute = joinMotivePair . (Zip.absolute >< id) . splitMotivePair \end{code}