{-# LANGUAGE FlexibleContexts #-} -- | Functions for score composition. -- -- module Temporal.Music.Notation.Score ( -- * Types Time, Dur, Score, -- * Constructors rest, note, -- * Duration querry dur, -- * Composition (+:+), (=:=), (=:/), line, chord, chordT, loop, trill, -- * Transformers -- ** In time domain delay, stretch, bpm, dot, ddot, tri, slice, takeS, dropS, reverseS, pedal, pedalBy, sustain, sustainBy, -- ** Mappings tmap, dmap, tdmap, -- * Rendering Event(..), EventList(..), renderScore, -- * Miscellaneous tmapRel, dmapRel, tdmapRel, linseg ) where import qualified Temporal.Media as M import Temporal.Media(Event(..), EventList(..), linseg) import Control.Arrow(first, second) -- | time type Time = Double -- | duration type Dur = Double -- | In 'Score' @a@ values of type @a@ -- can be wrapped in time events as if they present or abscent for some -- time 'Dur' and combined together in parrallel or sequent ways. -- -- Score is instance of -- -- * 'Functor' 'Score' -- -- 'Functor' instance means that you can map over score values -- with some function @(a -> b)@, rests are mapped to rests and values -- transformed with given function. type Score a = M.Media Dur a -- | querry score's duration dur :: Score a -> Dur dur = M.dur -- | pause for some "Dur" time rest :: Dur -> Score a rest = M.none -- | stretch in time domain. Duration of every note segemnt is multiplied by -- given factor. stretch :: Dur -> Score a -> Score a stretch = M.stretch -- | stretch with 1.5 dot :: Score a -> Score a dot = stretch 1.5 -- | double 'dot', stretch with 1.75 ddot :: Score a -> Score a ddot = stretch 1.75 -- | stretch with 2/3 tri :: Score a -> Score a tri = stretch (2/3) -- | adds given amount of duration to all notes sustain :: Dur -> Score a -> Score a sustain k = sustainBy $ \t d a -> (d + k, a) -- | set tempo in beats per minute, -- if 1 "Dur" is equal to 1 second before transformation. bpm :: Double -> (Score a -> Score a) bpm beat = stretch (x1/x0) where x0 = 0.25 x1 = 60/beat -- | general sustain sustainBy :: (Time -> Dur -> a -> (Dur, b)) -> Score a -> Score b sustainBy f = M.eventMap $ \(M.Event t d a) -> let (d', a') = f t d a in M.Event t d' a' -- | adds sustain, but total duration of score elements remains unchaged -- -- notes are sustained within total duration interval. -- adds given amount of time to all notes. pedal :: Dur -> Score a -> Score a pedal dt' = pedalBy (\t dt a -> (dt + dt', a)) -- | general \"pedal\" -- -- Total duration of score element remains unchanged. notes are sustained within total duration interval pedalBy :: (Time -> Dur -> a -> (Dur, b)) -> Score a -> Score b pedalBy f x = sustainBy f' x where d = dur x f' t dt a = first (min (d - t)) $ f t dt a -- | Constructor of score. Constructs note out of given value that lasts -- for some time. note :: Dur -> a -> Score a note = M.temp -- | Delay scores by given duration. delay :: Dur -> Score a -> Score a delay = M.delay -- | binary sequential composition, @a +:+ b@ means play a and then play b. (+:+) :: Score a -> Score a -> Score a (+:+) = (M.+:+) -- | binary parallel composition, @a =:= b@ means play a and b simultoneously. (=:=) :: Score a -> Score a -> Score a (=:=) = (M.=:=) -- | turncating parallel composition -- -- for a =:/ b composes two scores together and turncates biggest one by -- duration of smallest one. (=:/) :: Score a -> Score a -> Score a a =:/ b | dur a < dur b = a =:= takeS (dur a) b | otherwise = b =:= takeS (dur b) a -- | sequential composition for list of scores line :: [Score a] -> Score a line = M.sequent -- | parallel composition for list of scores chord :: [Score a] -> Score a chord = M.parallel -- | turncating parallel composition for lists of scores chordT :: [Score a] -> Score a chordT xs = chord $ map (takeS d) xs where d = minimum $ map dur xs -- | Arranges n copies of score in line. loop :: Int -> Score a -> Score a loop = M.loop -- | loop for two groups of notes. Repeats n times line of two scores. trill :: Int -> Score a -> Score a -> Score a trill n a b = loop n $ line [a, b] -- | extracting score parts in some time interval. -- it reverses output if @t1 < t0@. slice :: Dur -> Dur -> Score a -> Score a slice = M.slice -- | take sub-score from begining takeS :: Dur -> Score a -> Score a takeS = M.takeM -- | drop sub-score dropS :: Dur -> Score a -> Score a dropS = M.dropM -- | reverse score reverseS :: Score a -> Score a reverseS = M.reverseM -- | temporal functor 'tmap' method for scores -- -- map with time tmap :: (Time -> a -> b) -> Score a -> Score b tmap = M.tmap -- | temporal functor 'dmap' method for scores -- -- map with duration dmap :: (Dur -> a -> b) -> Score a -> Score b dmap = M.dmap -- | temporal functor 'tdmap' method for scores -- -- map with time and duration tdmap :: (Time -> Dur -> a -> b) -> Score a -> Score b tdmap = M.tdmap -- | relative 'tmap' -- -- map with time normalized by total duration value tmapRel :: (Time -> a -> b) -> Score a -> Score b tmapRel = M.tmapRel -- | relative 'dmap' -- -- map with duration normalized by total duration value dmapRel :: (Dur -> a -> b) -> Score a -> Score b dmapRel = M.dmapRel -- | relative 'tdmap' -- -- map with time and duration normalized by total duration value tdmapRel :: (Time -> Dur -> a -> b) -> Score a -> Score b tdmapRel = M.tdmapRel ------------------------------------------------------- -- Rendering -- | Transform 'Score' to 'EventList' renderScore :: Score a -> EventList Dur a renderScore = M.renderMedia