{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} {- | Copyright : (c) Henning Thielemann 2006 License : GPL Maintainer : synthesizer@henning-thielemann.de Stability : provisional Portability : requires multi-parameter type classes Similar to "Synthesizer.Inference.Monad.Signal" but the functions have monadic input and sequentialize it. This allows for a more functional looking style of programming because the type signature of signal modifiers is essentially @SigI.Process a q v -> SigI.Process a q v@ and thus they are perfectly composable with (.) and normal function application. The processor sequentializes its inputs and the order is quite arbitrary, but actually the order within monad sequences influences only the order of inference of signal parameters. The core signal processing does not depend on the monad order. The interfaces used here allow for function calls like @superProc (proc1 x) (proc2 y)@ . However, we have to be careful with sharing of the results of signal processors. E.g. @superProc x x@ does not mean, that the signal generated by @x@ is used twice. Instead it means that @x@ is computed twice. This can be avoided by explicitly sharing the result signal with 'Inference.Process.share'. This is absolutely the same situation as in "UniqueLogicNP.Explicit.Expression". @ do y <- Process.share x superProc y y @ A rule of thumb: Whenever you use the @let@ syntax, you are probably planing to use the variable more than once. Thus you should better use @do@ notation together with 'Inference.Process.share'. -} module Synthesizer.Inference.Monad.SignalSeq ( T, Process, run, returnCons, sampleRateExpr, amplitudeExpr, toTimeScalar, toFrequencyScalar, toAmplitudeScalar, fixSampleRate, loop ) where import qualified Synthesizer.Inference.Monad.Signal as SigI import Synthesizer.Inference.Monad.Signal (T, Process, run, returnCons, sampleRateExpr, amplitudeExpr, toTimeScalar, toFrequencyScalar, toAmplitudeScalar) import UniqueLogicNP.Monad(liftP) -- import NumericPrelude import PreludeBase as P fixSampleRate :: (Eq q) => q {-^ sample rate -} -> Process a q v {-^ passed through signal -} -> Process a q v fixSampleRate sampleRate = liftP (SigI.fixSampleRate sampleRate) {- | Create a loop from one node to another one. That is, compute the fix point of a process iteration. -} loop :: (Eq q) => (Process a q v -> Process a q v) {-^ process chain that shall be looped -} -> Process a q v loop f = SigI.loop (f . return)