Arrows (Re: [Haskell-cafe] Sample rate inference)

Koji Nakahara yu- at div.club.ne.jp
Thu Nov 11 12:59:31 EST 2004


On Fri, 12 Nov 2004 01:10:06 +0900
Koji Nakahara <yu- at div.club.ne.jp> wrote:

> On Thu, 11 Nov 2004 10:49:13 +0100 (MEZ)
> Henning Thielemann <iakd0 at clusterf.urz.uni-halle.de> wrote:
> 
> >  The computation sample rate should be propagated through the network as
> > follows:
> >   If in a component of equal sample rate some processors have the same
> > fixed sample rate, all uncertain processors must adapt that. 
> >   If some processors have different fixed sample rates this is an error. 
> >   If no processor has a fixed sample rate, the user must provide one
> > manually.
> >  To me this looks very similar to type inference. Is there some mechanism
> > in Haskell which supports this programming structure? 
> 
> This may not what you are looking for,
> but I would simply use Reader Monad or like.


I fall on Arrows and come up with the following.
I'm not sure this is a proper usage of Arrows, though.

I'd appreciate any advices.

--
{-# OPTIONS -fglasgow-exts #-}
import Control.Arrow
import Data.List (intersect)
data Rates = Rates [Int] | Any deriving Show
data Processor b c = P Rates (Rates -> (b, Stream) -> (c, Stream))

-- test Stream
type Stream = String

intersectRates Any (Rates xs) = Rates xs
intersectRates (Rates xs) (Rates ys) = Rates $ intersect xs ys
intersectRates x y = intersectRates y x

instance Arrow Processor where
  arr f = P Any (\r (x, s) -> (f x, s))
  (P r0 f0) >>> (P r1 f1)
    = P (intersectRates r0 r1) (\r -> (f1 r) . (f0 r))
  first (P r f) = P r (\r ((x, y), s) -> let (z, s') = f r (x, s) 
													in ((z, y), s'))

runProcessor (P r f) a s = f r (a, s)

-- test processors
processor1 = P (Rates [44100, 48000]) (\r (x, s) -> ((), s ++ show r))
processor2 = P Any (\r (x, s) -> ((),(s ++ show r)))
processor3 = P (Rates [48000]) (\r (x, s) -> ((), (s ++ show r)))

process = processor1 >>> processor2 >>> processor3

-- 
Koji Nakahara


More information about the Haskell-Cafe mailing list