[Haskell-cafe] Re: Implicit parameters and Arrows/Yampa?
ChrisK
haskell at list.mightyreason.com
Mon Jan 7 15:40:38 EST 2008
Could I has one question? What is the purpose of the "stream" function in the
ArrowLoop instance? Is it just to catch an unexpected [] at runtime?
> ----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
It looks like stream is (almost) an identity which would crash at runtime if it
encountered a []. In particular it is equivalent to
> where stream xs = head xs:stream (tail 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<----
More information about the Haskell-Cafe
mailing list