Wow, amazing :) How long did it take you to write this little nice example? Examples like this are really welcome. It will take me a while to decipher, but that's the fun of Haskell, it's an endless learning experience!
Here's a thought: I hardly know Haskell, but I can already write some code much faster and easier than I could do in C/C++ (and I've been programming 2 decades in that language, plus my colleagues tell me I'm pretty productive at it...). So I wonder what the productivity becomes when you can write code as quickly as Claude seemed to do here... Thanks, Peter PS: Also the scissors in your comment (--8<--), very original! Is this copyrighted? ;) -----Original Message----- From: Claude Heiland-Allen [mailto:[EMAIL PROTECTED] Something like this? ----8<---- module Main where import Control.Arrow import Control.Arrow.Operations import Control.Arrow.Transformer.Reader -- -- Standard list/stream arrow. -- newtype SF b c = SF { runSF :: [b] -> [c] } instance Arrow SF where arr f = SF (map f) SF f >>> SF g = SF (g . f) first (SF f) = SF (uncurry zip . (f *** id) . unzip) second (SF f) = SF (uncurry zip . (id *** f) . unzip) instance ArrowLoop SF where loop (SF f) = SF $ \as -> let (bs,cs) = unzip (f (zip as (stream cs))) in bs where stream ~(x:xs) = x:stream xs instance ArrowCircuit SF where delay x = SF (init . (x:)) -- -- Some state we want to pass around without manual plumbing. -- data AudioState = AudioState { sampleRate :: Double } runAudio state graph = proc p -> (| runReader (graph -< p) |) state -- -- Some unit generators for audio. -- wrap x = x - fromIntegral (floor x) -- phasor needs the sample rate phasor phase0 = proc hz -> do sr <- pure sampleRate <<< readState -< () rec accum <- delay (wrap phase0) -< wrap (accum + hz / sr) returnA -< accum -- osc doesn't need to know about sample rate osc phase0 = proc hz -> do phase <- phasor phase0 -< hz returnA -< cos (2 * pi * phase) -- -- Test it out. -- main = print (runSF (runAudio (AudioState{sampleRate=1000}) (osc 0)) (replicate 10 100)) ----8<---- > Cheers, > Peter Thanks, Claude -- http://claudiusmaximus.goto10.org _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe