{- | Copyright : (c) Henning Thielemann 2007 License : GPL Maintainer : synthesizer@henning-thielemann.de Stability : provisional Portability : requires multi-parameter type classes (OccasionallyScalar) Light-weight sample parameter inference which will fit most needs. We only do \"poor man's inference\", only for sample rates. The sample rate will be provided in a Reader monad. We almost do not need monad functionality but only "Control.Applicative" functionality. In contrast to the run-time inference approach, we have the static guarantee that the sample rate is fixed before passing a signal to the outside world. -} module Synthesizer.Inference.Reader.Process ( T(..), run, share, injectParam, extractParam, convertTimeParam, loop, pure, ($:), ($::), ($^), ($#), (.:), (.^), liftP, liftP2, liftP3, liftP4, ) where import Control.Monad.Fix (MonadFix(mfix), ) import Synthesizer.ApplicativeUtility import qualified Control.Applicative as App import Control.Applicative (Applicative) {- import NumericPrelude import PreludeBase as P -} {- | This wraps a function which computes a sample rate dependent result. Sample rate tells how many values per unit are stored for representation of a signal. -} newtype T t t' a = Cons {process :: t' -> a} instance Functor (T t t') where fmap f x = Cons (f . process x) instance Applicative (T t t') where pure = pure (<*>) = apply instance Monad (T t t') where return = pure (>>=) = share instance MonadFix (T t t') where mfix = loop . injectParam run :: t' -> T t t' a -> (t', a) run sr (Cons p) = (sr, p sr) {- | Re-use a result several times without recomputing. With a simple @let@ you can re-use a result but it must be recomputed due to the dependency on the sample rate. -} share :: T t t' a {-^ process that provides a result -} -> (a -> T t t' b) {-^ function that can re-use that result as much as it wants -} -> T t t' b share p f = Cons $ \sr -> process (f (process p sr)) sr {- | This corresponds to 'Control.Applicative.pure' -} pure :: a -> T t t' a pure x = Cons $ const x apply :: T t t' (a -> b) -> T t t' a -> T t t' b apply f proc = Cons $ \sr -> process f sr (process proc sr) extractParam :: T t t' (a -> b) -> (a -> T t t' b) extractParam = ($#) injectParam :: (a -> T t t' b) -> T t t' (a -> b) injectParam f = Cons $ \sr x -> process (f x) sr {- | The first argument will be a function like 'InferenceReader.Signal.toTimeScalar'. If you use this function instead of 'InferenceReader.Signal.toTimeScalar' directly, the type @t@ can be automatically infered. -} convertTimeParam :: (t' -> t' -> t) -> t' -> (t -> a) -> T t t' a convertTimeParam convert t' f = Cons $ \sr -> f (convert sr t')