
I want to connect several functions for signal processing. The typical case is that in a network of signal processor there are parts that are already discretized such as sampled sounds, and there are processors with no particular sample rate such as amplifiers. But when it comes to computation each processor must choose a sample rate for processing. There are also processors for converting sample rates. They divide the network into components of equal sample rate. 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?

Henning Thielemann wrote:
I want to connect several functions for signal processing. The typical case is that in a network of signal processor there are parts that are already discretized such as sampled sounds, and there are processors with no particular sample rate such as amplifiers. But when it comes to computation each processor must choose a sample rate for processing. There are also processors for converting sample rates. They divide the network into components of equal sample rate. 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?
If you define a class for sample rates, and an instance for each possible sample rate, then you could use type inference, e.g.
class Rate a where rate :: a -> Int;
data Rate22050 = Rate22050; instance Rate Rate22050 where rate _ = 22050;
data Rate44100 = Rate44100; instance Rate Rate44100 where rate _ = 44100;
data (Rate a) => Stream a = ...
type unaryProcessor a = (Rate a) => Stream a -> Stream a type binaryProcessor a = (Rate a) => Stream a -> Stream a -> Stream a ...
resample :: (Rate a, Rate b) => Stream a -> Stream b resample s = ...
Supporting arbitrary sample rates would require being able to construct a distinct type for every possible sample rate; e.g. using Church numerals:
data Rate0 = Rate0 instance Rate Rate0 where rate _ = 0;
data (Rate a) => RateN a instance (Rate a) => Rate (RateN a) where rate (RateN x) = 1 + rate x;
fourHertzFilter :: unaryProcessor (RateN (RateN (RateN (RateN Rate0)))) fourHertzFilter = ...
I doubt that this specific example wouldn't work in practice (the type
inference would probably give the compiler a heart attack), but you
could presumably construct an equivalent mechanism using base-N
numerals.
--
Glynn Clements

On Thu, 11 Nov 2004, Glynn Clements 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?
If you define a class for sample rates, and an instance for each possible sample rate, then you could use type inference,
Interesting approach, though it's not good idea to restrict to some sample rates. It's also not necessary to do the inference at compile time.
I doubt that this specific example wouldn't work in practice (the type inference would probably give the compiler a heart attack), but you could presumably construct an equivalent mechanism using base-N numerals.
:-) How can one implement a sample rate inference that work at run-time for arbitrary rates? This will be the only way if one works with sampled sounds read from a file.

Henning Thielemann 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?
If you define a class for sample rates, and an instance for each possible sample rate, then you could use type inference,
Interesting approach, though it's not good idea to restrict to some sample rates. It's also not necessary to do the inference at compile time.
Ah. I think that I took your comparision to type inference too literally.
I doubt that this specific example wouldn't work in practice (the type inference would probably give the compiler a heart attack), but you could presumably construct an equivalent mechanism using base-N numerals.
:-)
How can one implement a sample rate inference that work at run-time for arbitrary rates? This will be the only way if one works with sampled sounds read from a file.
This is essentially "unification".
Haskell and ML use it for type inference and for pattern matching,
(although pattern matching is always unidirectional, i.e unifying a
pattern comprised of both variables and constants with a value
comprised solely of constants). Prolog uses it more extensively
(variables can occur on either side).
Essentially, unification involves matching structures comprised of
constants, variables, and other structures. An unbound variable
matches anything, resulting in the variable becoming bound; a bound
variable matches whatever its value matches; a constant matches
itself; and a structure matches another structure if they have the
same number of components and all of their components match.
You could probably use GHC's type inference code, although converting
it for your purposes may be more work than starting from scratch. The
Hugs98 code contains a miniature prolog implementation, so you could
take the unification algorithm from that.
--
Glynn Clements

On Thu, Nov 11, 2004 at 10:49:13AM +0100, Henning Thielemann 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.
To me, it looks like "clock inference". Just making sure: have you had a look at (yet another) functional language namely Lustre? http://www-verimag.imag.fr/SYNCHRONE/lustre-english.html -- (o_ Andreas Bauer, baueran at in.tum.de, http://www4.in.tum.de/~baueran/ //\ "2B or not 2B that is FF." -- Tom Clancy V_/_

On Thu, 11 Nov 2004, Andreas Bauer wrote:
On Thu, Nov 11, 2004 at 10:49:13AM +0100, Henning Thielemann 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.
To me, it looks like "clock inference". Just making sure: have you had a look at (yet another) functional language namely Lustre?
Sounds as if they want to synchronize event-driven processes, right? In my case the signals are equidistantly sampled continuous functions. Agreeing on a sample rate must be done before starting the processes.

On Thu, 11 Nov 2004 10:49:13 +0100 (MEZ)
Henning Thielemann
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. newtype Rate = Rate Int type Processor = Stream -> Reader Rate Stream processor1 s = do rate <- ask; ... processors = processor1 >>= processor2 >>= .. process = runReader (processors input) (Rate 44100) P.S. Sorry for sending the same mail. I didn't notice you set Reply to. -- Koji Nakahara

Koji Nakahara
On Thu, 11 Nov 2004 10:49:13 +0100 (MEZ) Henning Thielemann
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.
Or you could make use of laziness in the following way:
- have every processor give its preferred rate as an output, and take the chosen rate as input.
- have the combinator examine all the outputs, choose the rate (giving an error if this is not possible), and pass the chosen rate to all the processors' inputs.
This could be wrapped in a reader and a writer monad if desired, or some custom combinators could be constructed.
See http://www.haskell.org/hawiki/CircularProgramming for more examples of this pattern.
--KW 8-)
--
Keith Wansbrough

On Fri, 12 Nov 2004 01:10:06 +0900
Koji Nakahara
On Thu, 11 Nov 2004 10:49:13 +0100 (MEZ) Henning Thielemann
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

On Fri, 12 Nov 2004, Koji Nakahara wrote:
On Thu, 11 Nov 2004 10:49:13 +0100 (MEZ) Henning Thielemann
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.

Hello, This sounds vaguely like the encryption modulus problem dealt with in this paper: http://www.eecs.harvard.edu/~ccshan/prepose/prepose.pdf "Function Pearl: Implicit Configurations -- or, Type Classes Reflect the Values of Types". Though, I have not thought about it too hard... Jeremy Shaw. At Thu, 11 Nov 2004 10:49:13 +0100 (MEZ), Henning Thielemann wrote:
I want to connect several functions for signal processing. The typical case is that in a network of signal processor there are parts that are already discretized such as sampled sounds, and there are processors with no particular sample rate such as amplifiers. But when it comes to computation each processor must choose a sample rate for processing. There are also processors for converting sample rates. They divide the network into components of equal sample rate. 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?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- This message contains information which may be confidential and privileged. Unless you are the addressee (or authorized to receive for the addressee), you may not use, copy or disclose to anyone the message or any information contained in the message. If you have received the message in error, please advise the sender and delete the message. Thank you.
participants (6)
-
Andreas Bauer
-
Glynn Clements
-
Henning Thielemann
-
Jeremy Shaw
-
Keith Wansbrough
-
Koji Nakahara