[Haskell-cafe] Arrows for Sample rate inference

Henning Thielemann iakd0 at clusterf.urz.uni-halle.de
Fri Nov 19 11:59:37 EST 2004


On Fri, 12 Nov 2004, Koji Nakahara 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? 
> 
> I fall on Arrows and come up with the following.
> I'm not sure this is a proper usage of Arrows, though.

I needed some time to think this over, I'm still not finished. I had no
experiences with Arrows so far, but I read that Arrows are good for
describing networks of processors. Is it possible to model each directed
graph using Arrows? Including all kinds of loops (ArrowLoop?)? 

Your code looks very promising. I tried to simplify it a bit:

module SampleRateInferenceArrow where

import Control.Arrow
import Data.List (intersect)
data Rates = Rates [Int] | Any deriving Show
data Processor b c = P Rates (Rates -> b -> c)

-- test Stream
type Stream = String

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

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

runProcessor (P r f) s = f r s

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

process = processor1 >>> processor2 >>> processor3

test = runProcessor process "bla"


 Now, since you gave me an answer to my question I become aware, that my
question was wrong. :-) One must model the signal processor networks more
detailed. We need wires (the sample streams), sockets and processors. Each
processor has a number of input and output sockets. The number of sockets
may not be fixed at compile time, say for example a list of input stream
is allowed. A wire connects an output with an input socket. A processor
may work with different sampling rates (e.g. a resampling process), but a
wire has always one sample rate. This is the point where I see the
similarity to type inference. Imagine that a processor is a function and
the sample rates are types, then for example a processor of type (a,b,b) 
-> (c,b) takes three inputs, two of them having the same sample rate, and
two outputs, where one output shares the sample rate of the second and the
third input stream.
 I wonder if I can re-use the Processor data above as Socket data. But
since I can connect only two sockets, I wouldn't need Arrow notation. But
if I want to connect processors with (>>>) I don't know how to address
certain sockets.
 Without Arrows I would try to label processors and wires and solve the
problem by a search for connectivity components using Data.Graph. But I
don't want to have the burden of creating and preserving uniqueness of
labels. 



More information about the Haskell-Cafe mailing list