{-# LANGUAGE TypeFamilies, DeriveFunctor, DeriveFoldable, FlexibleContexts, GeneralizedNewtypeDeriving #-} ------------------------------------------------------------------------------------- -- | -- Copyright : (c) Hans Hoglund 2012 -- -- License : BSD-style -- -- Maintainer : hans@hanshoglund.se -- Stability : experimental -- Portability : non-portable (TF,GNTD) -- ------------------------------------------------------------------------------------- module Music.Time.Onset ( HasDuration(..), HasOnset(..), HasOffset(..), HasPreOnset(..), HasPostOnset(..), HasPostOffset(..), -- ** Defaults durationDefault, onsetDefault, offsetDefault, -- ** Wrappers AddOffset(..), ) where import Data.Semigroup import Data.VectorSpace import Data.AffineSpace import Music.Time.Pos import Music.Time.Time import Music.Time.Duration import Music.Time.Delayable import Music.Time.Stretchable class HasDuration s where duration :: s a -> Duration s -- | -- Class of types with a position in time. -- -- Onset and offset are logical start and stop time, i.e. the preferred beginning and end -- of the sound, not o the the time of the attack and damp actions on an instrument, -- -- If a type has an instance for both 'HasOnset' and 'HasDuration', the following laws -- should hold: -- -- > duration a = offset a - onset a -- > offset a >= onset a -- -- implying -- -- > duration a >= 0 -- class HasOnset s where -- |  -- Get the onset of the given value. -- onset :: s a -> Time s class HasOffset s where -- |  -- Get the offset of the given value. -- offset :: s a -> Time s class HasPreOnset s where preOnset :: s a -> Time s class HasPostOnset s where postOnset :: s a -> Time s class HasPostOffset s where postOffset :: s a -> Time s -- | Given 'HasOnset' and 'HasOffset' instances, this function implements 'duration'. durationDefault :: (AffineSpace (Time s), HasOffset s, HasOnset s) => s a -> Duration s durationDefault x = offset x .-. onset x -- | Given 'HasDuration' and 'HasOffset' instances, this function implements 'onset'. onsetDefault :: (AffineSpace (Time s), HasOffset s, HasDuration s) => s a -> Time s onsetDefault x = offset x .-^ duration x -- | Given 'HasOnset' and 'HasOnset' instances, this function implements 'offset'. offsetDefault :: (AffineSpace (Time s), HasOnset s, HasDuration s) => s a -> Time s offsetDefault x = onset x .+^ duration x newtype AddOffset t s a = AddOffset (t, s a) type instance Time (AddOffset t s) = t instance (Delayable a, t ~ Time a) => Delayable (AddOffset t a) where delay d (AddOffset (t,a)) = AddOffset (t, delay d a) instance (Stretchable a, t ~ Time a) => Stretchable (AddOffset t a) where stretch d (AddOffset (t,a)) = AddOffset (t, stretch d a) instance (HasOnset a, t ~ Time a) => HasOnset (AddOffset t a) where onset (AddOffset (t,a)) = onset a instance HasOffset (AddOffset t s) where offset (AddOffset (t,_)) = t