module Music.Score.Meta.Tempo (
Bpm,
NoteValue,
Tempo,
metronome,
tempoNoteValue,
tempoBeatsPerMinute,
getTempo,
tempoToDuration,
tempo,
tempoDuring,
renderTempo,
) where
import Control.Arrow
import Control.Lens
import Control.Monad.Plus
import Data.AffineSpace
import Data.Default
import Data.Foldable (Foldable)
import qualified Data.Foldable as F
import qualified Data.List as List
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe
import Data.Monoid.WithSemigroup
import Data.Semigroup
import Data.Set (Set)
import qualified Data.Set as Set
import Data.String
import Data.Traversable (Traversable)
import qualified Data.Traversable as T
import Data.Typeable
import Data.VectorSpace
import Data.Void
import Music.Pitch.Literal
import Music.Score.Combinators
import Music.Score.Convert
import Music.Score.Meta
import Music.Score.Note
import Music.Score.Part
import Music.Score.Pitch
import Music.Score.Score
import Music.Score.Util
import Music.Score.Voice
import Music.Time
import Music.Time.Reactive
type Bpm = Duration
type NoteValue = Duration
data Tempo = Tempo (Maybe String) (Maybe Duration) Duration
deriving (Eq, Ord, Typeable)
instance Num Tempo where
fromInteger = Tempo Nothing Nothing . fromInteger
instance Show Tempo where
show (getTempo -> (nv, bpm)) = "metronome " ++ showR nv ++ " " ++ showR bpm
where
showR (realToFrac -> (unRatio -> (x, 1))) = show x
showR (realToFrac -> (unRatio -> (x, y))) = "(" ++ show x ++ "/" ++ show y ++ ")"
instance Default Tempo where
def = metronome (1/1) 60
metronome :: Duration -> Bpm -> Tempo
metronome noteVal bpm = Tempo Nothing (Just noteVal) $ 60 / (bpm * noteVal)
tempoNoteValue :: Tempo -> Maybe NoteValue
tempoNoteValue (Tempo n nv d) = nv
tempoBeatsPerMinute :: Tempo -> Bpm
tempoBeatsPerMinute = snd . getTempo
getTempo :: Tempo -> (NoteValue, Bpm)
getTempo (Tempo _ Nothing x) = (1, (60 * recip x) / 1)
getTempo (Tempo _ (Just nv) x) = (nv, (60 * recip x) / nv)
tempoToDuration :: Tempo -> Duration
tempoToDuration (Tempo _ _ x) = x
tempo :: (HasMeta a, HasPart' a, HasOnset a, HasOffset a) => Tempo -> a -> a
tempo c x = tempoDuring (era x) c x
tempoDuring :: (HasMeta a, HasPart' a) => Span -> Tempo -> a -> a
tempoDuring s c = addGlobalMetaNote (s =: (optionFirst c))
inSpan :: Span -> Time -> Bool
inSpan (view range -> (t,u)) x = t <= x && x <= u
inSpan' (view range -> (t,u)) x = t <= x && x < u
reactiveIn :: Span -> Reactive a -> [Note a]
reactiveIn s r
| duration s <= 0 = error "reactiveIn: Needs positive duration"
| otherwise = let r2 = trim s (fmap optionFirst r)
in fmap (fmap $ fromJust . unOptionFirst) $ case updates r2 of
(frl -> ((t,x),[],(u,_))) -> [t <-> u =: x]
(frl -> ((t0,x0), unzip -> (tn,xn), (tl,_))) -> let
times = [t0] ++ tn
spans = mapWithNext (\t mu -> t <-> fromMaybe tl mu) times
values = [x0] ++ xn
in zipWith (=:) spans values
renderTempo :: Score a -> Score a
renderTempo sc =
flip composed sc $ fmap renderTempoScore
$ tempoRegions (era sc)
$ tempoRegions0 (era sc)
$ getTempoChanges defTempo sc
renderTempoTest :: Score a -> [TempoRegion]
renderTempoTest sc = id
$ tempoRegions (era sc)
$ tempoRegions0 (era sc)
$ getTempoChanges defTempo sc
defTempo :: Tempo
defTempo = metronome (1/1) 60
getTempoChanges :: Tempo -> Score a -> Reactive Tempo
getTempoChanges def = fmap (fromMaybe def . unOptionFirst) . runMeta (Nothing::Maybe Int) . (view meta)
tempoRegions0 :: Span -> Reactive Tempo -> [TempoRegion0]
tempoRegions0 s r = fmap f $ s `reactiveIn` r
where
f (getNote -> (view delta -> (t,u),x)) = TempoRegion0 t u (tempoToDuration x)
tempoRegions :: Span -> [TempoRegion0] -> [TempoRegion]
tempoRegions s = snd . List.mapAccumL f (onset s, onset s)
where
f (nt,st) (TempoRegion0 _ d x) = ((nt .+^ d, st .+^ (d*x)),
TempoRegion nt (nt .+^ d) st x
)
renderTempoTime :: TempoRegion -> Time -> Time
renderTempoTime (TempoRegion notRegOn notRegOff soRegOn str) t
| notRegOn <= t && t < notRegOff = soRegOn .+^ (t .-. notRegOn) ^* str
| otherwise = t
renderTempoTime' (TempoRegion notRegOn notRegOff soRegOn str) t = soRegOn .+^ ((t .-. notRegOn) ^* str)
renderTempoSpan :: TempoRegion -> Span -> Span
renderTempoSpan tr = over range $ \(t,u) ->
if inSpan' (tempoRegionNotated tr) t
then (renderTempoTime' tr t, renderTempoTime' tr u)
else (t, u)
renderTempoScore :: TempoRegion -> Score a -> Score a
renderTempoScore tr = over notes $ fmap $ over (note_ . _1) $ renderTempoSpan tr
data TempoRegion0 =
TempoRegion0 {
notatedOnset0 :: Time,
notatedDuration0 :: Duration,
stretching0 :: Duration
}
deriving (Eq, Ord, Show)
data TempoRegion =
TempoRegion {
notatedOnset :: Time,
notatedOffset :: Time,
soundingOnset :: Time,
stretching :: Duration
}
deriving (Eq, Ord, Show)
tempoRegionNotated (TempoRegion t u _ _) = t <-> u
note_ :: Iso (Note a) (Note b) (Span, a) (Span, b)
note_ = iso getNote (uncurry (=:))
optionFirst = Option . Just . First
unOptionFirst = fmap getFirst . getOption
frl [] = error "frl: No value"
frl [x] = error "frl: Just one value"
frl xs = (head xs, (tail.init) xs, last xs)