{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE Rank2Types #-} module Synthesizer.LLVM.Parameterized.SignalPrivate where import qualified Synthesizer.LLVM.Parameter as Param import qualified LLVM.Extra.MaybeContinuation as Maybe import qualified LLVM.Extra.Memory as Memory import qualified LLVM.Extra.Class as Class import qualified LLVM.Extra.ScalarOrVector as SoV import qualified LLVM.Extra.Arithmetic as A import qualified LLVM.Extra.Control as C import qualified LLVM.Core as LLVM import LLVM.Extra.Class (MakeValueTuple, ValueTuple, ) import LLVM.Core (CodeGenFunction, ) import LLVM.Util.Loop (Phi, ) import Control.Arrow ((&&&), ) import Control.Monad (liftM2, ) import Control.Applicative (Applicative, pure, (<*>), ) import Data.Tuple.HT (mapFst) import Foreign.Storable.Tuple () import Foreign.Storable (Storable, ) import qualified Number.Ratio as Ratio import qualified Algebra.Field as Field import qualified Algebra.Ring as Ring import qualified Algebra.Additive as Additive import NumericPrelude.Base hiding (and, iterate, map, zip, zipWith, ) import qualified Prelude as P {- In this attempt we use a Haskell value as parameter supply. This is okay, since the Haskell value will be converted to internal parameters and then to LLVM values only once. We can even have a storable vector as parameter. However, this way we cannot easily implement the Vanilla signal using Parameterized.Value as element type. This separation is nice for maximum efficiency, but it cannot be utilized by Generic.Signal methods. Consider an expression like @iterate ((0.5 ** recip halfLife) *) 1@. How shall we know, that the sub-expression @(0.5 ** recip halfLife)@ needs to be computated only once? I do not try to do such optimization, instead I let LLVM do it. However, this means that parameter initialization will be performed (unnecessarily) at the beginning of every chunk. For Generic.Signal method instances we will always set the @(p -> paramTuple)@ to 'id'. Could we drop parameterized signals at all and rely entirely on Causal processes? Unfortunately 'interpolateConstant' does not fit into the Causal process scheme. (... although it would be causal for stretching factor being at least one. It would have to maintain the waiting signal as state, i.e. the state would grow linearly with time.) Consider a signal algorithm, where the LFO frequency is a parameter. -} data T p a = forall context state ioContext parameters. (Storable parameters, MakeValueTuple parameters, Memory.C (ValueTuple parameters), Memory.C context, Memory.C state) => Cons (forall r c. (Phi c) => context -> state -> Maybe.T r c (a, state)) -- compute next value (forall r. ValueTuple parameters -> CodeGenFunction r (context, state)) -- allocate initial state (forall r. context -> state -> CodeGenFunction r ()) {- cleanup You must make sure to call this whenever you allocated context and state with the 'start' function. You must call it with the latest state returned from the 'next' function. -} (p -> IO (ioContext, parameters)) {- initialization from IO monad This will be run within Unsafe.performIO, so no observable In/Out actions please! -} (ioContext -> IO ()) -- finalization from IO monad, also run within Unsafe.performIO withStart :: (startParam -> CodeGenFunction r (context, state0)) -> (state0 -> CodeGenFunction r state1) -> startParam -> CodeGenFunction r (context, state1) withStart start act p = do (c,s) <- start p fmap ((,) c) $ act s combineStart :: Monad m => (paramA -> m (contextA, stateA)) -> (paramB -> m (contextB, stateB)) -> (paramA, paramB) -> m ((contextA, contextB), (stateA, stateB)) combineStart startA startB (paramA, paramB) = liftM2 (\(ca,sa) (cb,sb) -> ((ca,cb), (sa,sb))) (startA paramA) (startB paramB) combineStop :: Monad m => (contextA -> stateA -> m ()) -> (contextB -> stateB -> m ()) -> (contextA, contextB) -> (stateA, stateB) -> m () combineStop stopA stopB (ca, cb) (sa, sb) = stopA ca sa >> stopB cb sb combineCreate :: Monad m => (p -> m (ioContextA, contextA)) -> (p -> m (ioContextB, contextB)) -> p -> m ((ioContextA, ioContextB), (contextA, contextB)) combineCreate createIOContextA createIOContextB p = do (ca,paramA) <- createIOContextA p (cb,paramB) <- createIOContextB p return ((ca,cb), (paramA,paramB)) combineDelete :: (Monad m) => (ca -> m ()) -> (cb -> m ()) -> (ca, cb) -> m () combineDelete deleteIOContextA deleteIOContextB (ca,cb) = deleteIOContextA ca >> deleteIOContextB cb simple :: (Storable parameters, MakeValueTuple parameters, Memory.C (ValueTuple parameters), Memory.C context, Memory.C state) => (forall r c. (Phi c) => context -> state -> Maybe.T r c (al, state)) -> (forall r. ValueTuple parameters -> CodeGenFunction r (context, state)) -> Param.T p parameters -> T p al simple f start param = Param.with param $ \getParam valueParam -> Cons f (start . valueParam) (const $ const $ return ()) (return . (,) () . getParam) (const $ return ()) map :: (Storable ph, MakeValueTuple ph, ValueTuple ph ~ pl, Memory.C pl) => (forall r. pl -> a -> CodeGenFunction r b) -> Param.T p ph -> T p a -> T p b map f selectParamF (Cons next start stop createIOContext deleteIOContext) = Param.with selectParamF $ \getParamF valueF -> Cons (\(parameterF, parameter) sa0 -> do (a,sa1) <- next parameter sa0 b <- Maybe.lift $ f (valueF parameterF) a return (b, sa1)) (\(parameterF, parameter) -> fmap (mapFst ((,) parameterF)) $ start parameter) (stop . snd) (\p -> do (ioContext, param) <- createIOContext p return (ioContext, (getParamF p, param))) deleteIOContext mapSimple :: (forall r. a -> CodeGenFunction r b) -> T p a -> T p b mapSimple f = map (const f) (return ()) zipWith :: (Storable ph, MakeValueTuple ph, ValueTuple ph ~ pl, Memory.C pl) => (forall r. pl -> a -> b -> CodeGenFunction r c) -> Param.T p ph -> T p a -> T p b -> T p c zipWith f selectParamF (Cons nextA startA stopA createIOContextA deleteIOContextA) (Cons nextB startB stopB createIOContextB deleteIOContextB) = Param.with selectParamF $ \getParamF valueParamF -> Cons (\(parameterF, (parameterA, parameterB)) (sa0,sb0) -> do (a,sa1) <- Maybe.onFail (stopB parameterB sb0) $ nextA parameterA sa0 (b,sb1) <- Maybe.onFail (stopA parameterA sa1) $ nextB parameterB sb0 c <- Maybe.lift $ f (valueParamF parameterF) a b return (c, (sa1,sb1))) (\(parameterF, parameter) -> fmap (mapFst ((,) parameterF)) $ combineStart startA startB parameter) (combineStop stopA stopB . snd) (\p -> do (c,param) <- combineCreate createIOContextA createIOContextB p return (c, (getParamF p, param))) (combineDelete deleteIOContextA deleteIOContextB) zipWithSimple :: (forall r. a -> b -> CodeGenFunction r c) -> T p a -> T p b -> T p c zipWithSimple f = zipWith (const f) (return ()) instance Functor (T p) where fmap f = mapSimple (return . f) {- | ZipList semantics -} instance Applicative (T p) where pure x = simple (\() () -> return (x, ())) (\() -> return ((),())) (return ()) (<*>) = zipWithSimple (\f a -> return (f a)) instance (A.Additive a) => Additive.C (T p a) where zero = pure A.zero negate = mapSimple A.neg (+) = zipWithSimple A.add (-) = zipWithSimple A.sub instance (A.PseudoRing a, A.IntegerConstant a) => Ring.C (T p a) where one = pure A.one fromInteger n = pure (A.fromInteger' n) (*) = zipWithSimple A.mul instance (A.Field a, A.RationalConstant a) => Field.C (T p a) where fromRational' x = pure (A.fromRational' $ Ratio.toRational98 x) (/) = zipWithSimple A.fdiv instance (A.PseudoRing a, A.Real a, A.IntegerConstant a) => P.Num (T p a) where fromInteger n = pure (A.fromInteger' n) negate = mapSimple A.neg (+) = zipWithSimple A.add (-) = zipWithSimple A.sub (*) = zipWithSimple A.mul abs = mapSimple A.abs signum = mapSimple A.signum instance (A.Field a, A.Real a, A.RationalConstant a) => P.Fractional (T p a) where fromRational x = pure (A.fromRational' x) (/) = zipWithSimple A.fdiv iterate :: (Storable ph, MakeValueTuple ph, ValueTuple ph ~ pl, Memory.C pl, Storable a, MakeValueTuple a, ValueTuple a ~ al, Memory.C al) => (forall r. pl -> al -> CodeGenFunction r al) -> Param.T p ph -> Param.T p a -> T p al iterate f param initial = simple (\pl al0 -> Maybe.lift $ fmap (\al1 -> (al0,al1)) (f pl al0)) return (param &&& initial) quantizeNext :: (LLVM.IsFloating a, LLVM.CmpRet a, LLVM.CmpResult a ~ Bool, SoV.IntegerConstant a, Phi z, Class.Undefined y, Phi y, Class.Undefined state, Phi state) => (forall zn. Phi zn => context -> state -> Maybe.T r zn (y, state)) -> (valueA -> LLVM.Value a) -> (valueA, context) -> ((y, state), LLVM.Value a) -> Maybe.T r z (y, ((y, state), LLVM.Value a)) quantizeNext next valueK (kl,context) yState0 = do ((y1,state1), frac1) <- Maybe.fromBool $ C.whileLoop (LLVM.valueOf True, yState0) (\(cont1, (_, frac0)) -> LLVM.and cont1 =<< A.fcmp LLVM.FPOLE frac0 A.zero) (\(_,((_,state01), frac0)) -> Maybe.toBool $ liftM2 (,) (next context state01) (Maybe.lift $ A.add frac0 (valueK kl))) frac2 <- Maybe.lift $ A.sub frac1 A.one return (y1, ((y1,state1),frac2)) quantizeStart :: (Monad m, Class.Undefined y, A.Additive al) => (param -> m (context, state)) -> (ap, param) -> m ((ap, context), ((y, state), al)) {- using this initialization code we would not need undefined values (do sa <- start (a,_) <- next sa return (sa, a, A.zero)) -} quantizeStart start (kl,p) = do (c,s) <- start p return ((kl,c), ((Class.undefTuple, s), A.zero)) quantizeStop :: (context -> state -> m ()) -> (ap, context) -> ((y, state), al) -> m () quantizeStop stop (_kl,c) ((_, s), _) = stop c s quantizeCreate :: Monad m => (p -> m (ioContext, param)) -> (p -> ah) -> p -> m (ioContext, (ah, param)) quantizeCreate createIOContext getK p = do (ioContext, param) <- createIOContext p return (ioContext, (getK p, param)) quantizeDelete :: (ioContext -> m ()) -> (ioContext -> m ()) quantizeDelete deleteIOContext = deleteIOContext