module Synthesizer.PiecewiseConstant.Generic (
toSignal,
toSignalInit,
toSignalInitWith,
) where
import qualified Synthesizer.PiecewiseConstant.Private as PC
import Synthesizer.PiecewiseConstant.Private (StrictTime)
import qualified Synthesizer.Generic.Signal as SigG
import qualified Synthesizer.Generic.Cut as CutG
import qualified Data.EventList.Relative.BodyTime as EventListBT
import qualified Data.EventList.Relative.TimeBody as EventList
import qualified Numeric.NonNegative.Wrapper as NonNegW
replicateLong ::
(SigG.Write sig y) =>
StrictTime -> y -> sig y
replicateLong :: forall (sig :: * -> *) y. Write sig y => StrictTime -> y -> sig y
replicateLong StrictTime
tl y
y =
forall sig. Monoid sig => [sig] -> sig
CutG.concat forall a b. (a -> b) -> a -> b
$
forall a b. (a -> b) -> [a] -> [b]
map (\ShortStrictTime
t ->
forall (sig :: * -> *) y.
(Write0 sig, Storage (sig y)) =>
LazySize -> Int -> y -> sig y
SigG.replicate
LazySize
SigG.defaultLazySize
(forall a. T a -> a
NonNegW.toNumber ShortStrictTime
t) y
y) forall a b. (a -> b) -> a -> b
$
StrictTime -> [ShortStrictTime]
PC.chopLongTime StrictTime
tl
{-# INLINE toSignal #-}
toSignal :: (SigG.Write sig y) => EventListBT.T StrictTime y -> sig y
toSignal :: forall (sig :: * -> *) y. Write sig y => T StrictTime y -> sig y
toSignal = forall (sig :: * -> *) y.
Transform sig y =>
(StrictTime -> y -> sig y) -> T StrictTime y -> sig y
PC.toSignal forall (sig :: * -> *) y. Write sig y => StrictTime -> y -> sig y
replicateLong
{-# INLINE toSignalInit #-}
toSignalInit :: (SigG.Write sig y) => y -> EventList.T StrictTime y -> sig y
toSignalInit :: forall (sig :: * -> *) y.
Write sig y =>
y -> T StrictTime y -> sig y
toSignalInit = forall (sig :: * -> *) y.
Transform sig y =>
(StrictTime -> y -> sig y) -> y -> T StrictTime y -> sig y
PC.toSignalInit forall (sig :: * -> *) y. Write sig y => StrictTime -> y -> sig y
replicateLong
{-# INLINE toSignalInitWith #-}
toSignalInitWith ::
(SigG.Write sig c) =>
(y -> c) -> c -> EventList.T StrictTime [y] -> sig c
toSignalInitWith :: forall (sig :: * -> *) c y.
Write sig c =>
(y -> c) -> c -> T StrictTime [y] -> sig c
toSignalInitWith = forall (sig :: * -> *) c y.
Transform sig c =>
(StrictTime -> c -> sig c)
-> (y -> c) -> c -> T StrictTime [y] -> sig c
PC.toSignalInitWith forall (sig :: * -> *) y. Write sig y => StrictTime -> y -> sig y
replicateLong