module Synthesizer.Plain.Modifier where
import Control.Monad.Trans.State (State, state, runState, evalState, )
import Control.Monad (zipWithM, )
import qualified Data.StorableVector as SV
import Foreign.Storable (Storable(..))
import qualified Data.List as List
import Prelude hiding (init)
type T a = [a]
data Simple s ctrl a b =
   Simple {
      init :: s,
      step :: ctrl -> a -> State s b
   }
static ::
   Simple s ctrl a b -> ctrl -> T a -> T b
static modif control x =
   evalState (mapM (step modif control) x) (init modif)
modulated ::
   Simple s ctrl a b -> T ctrl -> T a -> T b
modulated modif control x =
   evalState (zipWithM (step modif) control x) (init modif)
data Initialized s init ctrl a b =
   Initialized {
      initInit :: init -> s,
      initStep :: ctrl -> a -> State s b
   }
initialize ::
   Initialized s init ctrl a b -> init -> Simple s ctrl a b
initialize modif stateInit =
   Simple (initInit modif stateInit) (initStep modif)
staticInit ::
   Initialized s init ctrl a b -> init -> ctrl -> T a -> T b
staticInit modif state_ =
   static (initialize modif state_)
modulatedInit ::
   Initialized s init ctrl a b -> init -> T ctrl -> T a -> T b
modulatedInit modif state_ =
   modulated (initialize modif state_)
stackStatesR :: (a -> State s a) -> (a -> State [s] a)
stackStatesR m =
   state . List.mapAccumR (runState . m)
stackStatesL :: (a -> State s a) -> (a -> State [s] a)
stackStatesL m =
   state . List.mapAccumL (runState . m)
stackStatesStorableR :: (Storable s) =>
   (a -> State s a) -> (a -> State (SV.Vector s) a)
stackStatesStorableR m =
   state . SV.mapAccumR (runState . m)
stackStatesStorableL :: (Storable s) =>
   (a -> State s a) -> (a -> State (SV.Vector s) a)
stackStatesStorableL m =
   state . SV.mapAccumL (runState . m)
stackStatesStorableVaryL :: (Storable s, Storable c) =>
   (c -> a -> State s a) -> (SV.Vector c -> a -> State (SV.Vector s) a)
stackStatesStorableVaryL m cv a = state $ \sv ->
   
   let (svFinal, mcsa) =
          SV.unfoldrN (SV.length sv)
             (\(cv0,sv0,a0) ->
                  do (c,cv1) <- SV.viewL cv0
                     (s,sv1) <- SV.viewL sv0
                     let (a1,sNew) = runState (m c a0) s
                     return (sNew,(cv1,sv1,a1)))
             (cv,sv,a)
   in  (case mcsa of
           Just (_, _, aFinal) -> aFinal
           _ -> error $ "Modifier: control vector too short - "
                   ++ "status size " ++ show (SV.length sv) ++ " vs. "
                   ++ "control size " ++ show (SV.length cv),
        svFinal)