{- | A design study about how to design signal processors that adapt to a common sample rate. I tried to simplify "Synthesizer.Inference.DesignStudy.Arrow" to this module which uses only Monads. However the module is now very weird and does not really represent, what I intended to do. -} module Synthesizer.Inference.DesignStudy.Monad where import Control.Monad.Trans.Writer (Writer, execWriter, tell) import Data.List (intersect) data Rates = Rates [Int] | Any deriving Show -- it is a combination of Reader and Writer monad with context processing data Processor a = P Rates (Rates -> Writer Stream a) -- test Stream type Stream = String intersectRates :: Rates -> Rates -> Rates intersectRates Any y = y intersectRates x Any = x intersectRates (Rates xs) (Rates ys) = Rates $ intersect xs ys instance Monad Processor where return x = P Any (\_ -> return x) -- maybe we should turn this into an Applicative instance (P r0 f0) >> (P r1 f1) = P (intersectRates r0 r1) (\r -> f0 r >> f1 r) (P _ _) >>= _ = error "Is it possible to implement that?" runProcessor :: Processor a -> Stream runProcessor (P r f) = execWriter (f r) -- test processors process, processor1, processor2, processor3 :: Processor () processor1 = P (Rates [44100, 48000]) (tell . show) processor2 = P Any (tell . show) processor3 = P (Rates [47000]) (tell . show) process = processor1 >> processor2 >> processor3 test :: Stream test = runProcessor process