module Synthesizer.Filter.MonadFix where import qualified Synthesizer.Filter.Graph as Graph import Synthesizer.Filter.Fix (Channel(Channel), ChannelId) import Control.Monad.Trans.State (StateT, evalStateT, get, modify, ) import Control.Monad.Trans.Writer (Writer, execWriter, tell, ) import Control.Monad.Trans.Class (lift, ) {-| If you find 'Filter.Fix.T' still inconvenient, and if you don't care about portability, you can also use the following monad with the @mdo@ notation. > mdo > v <- a·(u + d·w) > w <- b·(v + e·y) > y <- c· w -} type T filter t a v x = StateT ChannelId (Writer [Channel filter t a v]) x makeChannel :: [(ChannelId, filter t a v)] -> T filter t a v ChannelId makeChannel inputs = do n <- get modify succ lift $ tell [Channel n inputs] return n run :: T filter t a v x -> [Channel filter t a v] run m = execWriter (evalStateT m 0) toGraph :: T filter t a v x -> Graph.T filter Int t a v toGraph = Graph.fromList . map (\(Channel n inputs) -> (n, inputs)) . run