Lazy cons, Stream-Fusion style?

Hello all Can a lazy cons be implemented for (infinite) Streams in the Stream-Fusion style? I'm trying to make a Stream library, hopefully efficient enough for audio synthesis in the style of Jerzy Karczmarczuk's Clarion. As performance is important, the obvious model is the Stream-Fusion library, but 'cons' is problematic in this style. With the normal, inductive definition of Streams (vis Wouter Swierstra's Stream library), streams are sufficiently lazy: data Stream a = a :< Stream Using the laziness means that this definition of 'ones' is productive: demo01 = take 10 ones where ones = 1 <:> ones -- (<:>) is stream-cons However with Stream-Fusion, streams are not inductively defined, instead they are unfold-like pair of a stepper function and a start state: -- Some details removed... -- data Stream a = forall st. Stream !(st -> Step a st) !st For infinite Streams the Done constructor can be removed from the Step type, a truly infinite is never done: data Step a s = Yield a !s | Skip !s | Done Cons is strict - (:!:) is the constructor for a Strict pair, but the strictness of the pair is irrelevant here (I think). Even with a lazy pair the definition is too strict to be useful for 'ones' defined above as it won't "stream" (S1 and S2 are the constructors of counting / flag datatype used to encode which state the iteration is in): cons :: a -> Stream a -> Stream a cons w (Stream next0 s0) = Stream next (S2 :!: s0) where {-# INLINE next #-} next (S2 :!: s) = Yield w (S1 :!: s) next (S1 :!: s) = case next0 s of Done -> Done Skip s' -> Skip (S1 :!: s') Yield x s' -> Yield x (S1 :!: s') Here's a running example:
{-# LANGUAGE PackageImports #-}
module SFrec where
import qualified "stream-fusion" Data.Stream as S
-- -- The S.append1 construct is used to unwind a Stream -- to a list so it can be printed --
bad_loopy :: [Int] bad_loopy = S.append1 (S.take 10 v) [] where v = 1 `S.cons` v
good_productive :: [Int] good_productive = S.append1 (S.take 10 v) [] where v = S.repeat 1
Thanks Stephen

On Sun, 2 Jan 2011, Stephen Tetley wrote:
I'm trying to make a Stream library, hopefully efficient enough for audio synthesis in the style of Jerzy Karczmarczuk's Clarion.
I am trying to code real-time audio synthesis in Haskell for some years now. I can tell at least, that it is not so easily done. Even with the right data structure, GHC's optimizer does not always make, what you need. Thus the most efficiency I get by using LLVM to construct signal processing code at run time, so far. (see synthesizer-llvm package)
As performance is important, the obvious model is the Stream-Fusion library, but 'cons' is problematic in this style.
Yes, 'cons' is problematic. I think efficient 'cons' needs a material data structure, not just a generator function as in stream-fusion:Stream.
data Stream a = forall st. Stream !(st -> Step a st) !st
For infinite Streams the Done constructor can be removed from the Step type, a truly infinite is never done:
For audio synthesis you need also finite signals. Or am I missing something? At least I found that the 'Skip' constructor can be omitted for audio synthesis: http://hackage.haskell.org/packages/archive/synthesizer-core/0.4.0.4/doc/htm...
bad_loopy :: [Int] bad_loopy = S.append1 (S.take 10 v) [] where v = 1 `S.cons` v
The problem is that S.cons must take the internal state type of 'v' and must wrap it in a new type. Thus every S.cons makes the internal state more complicated. This is inefficient for several applications of S.cons and impossible for infinitely many calls. In order to get both elegant laziness and efficiency I played around with a head-strict list implemented via Storable. Here an efficient 'cons' seems to be doable: http://code.haskell.org/storablevector/Data/StorableVector/Cursor.hs However if there remains only one bit of laziness in an inner loop, you will not get good efficiency.

Hi Henning, thanks. For me, I can live without real-time. Real-time would be nice of course but the simplicity of Jerzy's Clarion (non-real-time, solely a "renderer") is compelling: eliding counting the lines of code for the stream type and the WAV file I/O, Clarion can produce audio in 2-3 lines of code which is amazing for a general purpose language rather than a custom audio language like RTCmix or Chuck. Un-optimized, with a head-strict stream (basically Wouter Swierstra's Stream with a bang on the element), rendering currently takes minutes to generate seconds. But as well as the Stream representation, I've plenty of room to optimize the WAV file generation. For finite signals, my initial thought is simply that the finite part can be the prologue to a tail stream of zeros. Probably I can live without definitions like @ ones = 1 <:> ones @, I would like to know whether of not this is impossible with Stream-Fusion anyway. Thanks again. Stephen

On Sun, 2 Jan 2011, Stephen Tetley wrote:
Un-optimized, with a head-strict stream (basically Wouter Swierstra's Stream with a bang on the element), rendering currently takes minutes to generate seconds. But as well as the Stream representation, I've plenty of room to optimize the WAV file generation.
Using stream-fusion:Stream rendered to a low-level list representation you get relatively efficient computation. I used my signal generator type and StorableVector.Lazy in order to perform this one in real-time: http://www.youtube.com/watch?v=KA6DE9jlpSY (see packages synthesizer-core and synthesizer-alsa) That is, even interactive realtime processing is possible, but not very complex one. It requires very disciplined programming and after a small change to your program the GHC optimizer may decide to compile it completely different and the program becomes five times slower. I have also written an overview of what data structures are useful for what signal processing purpose: http://hackage.haskell.org/packages/archive/synthesizer/0.2.0.1/doc/html/Syn...
Probably I can live without definitions like @ ones = 1 <:> ones @, I would like to know whether of not this is impossible with Stream-Fusion anyway.
The recursive style allows for elegant writing of feedback, solution of differential (e.g. oscillation) equations. It's sad, but I think you cannot have it with stream-fusion. Maybe in future GHC or JHC get more cleverness to eliminate even more lazy values. For feedback with longer and constant delay, you might buffer the data in a chunky storable vector and then get efficient recursive computation.

On 2 January 2011 13:35, Stephen Tetley
Hello all
Can a lazy cons be implemented for (infinite) Streams in the Stream-Fusion style?
In the standard stream fusion style, all stream operations are strict in the stream itself (that is, the pair of stepper function and initial state, not strict in the unfolded sequence or elements). Thus it is not possible to write things like:
bad_ones :: Stream Int bad_ones = s where s = 1 `S.cons` s
I'm not sure if making the stream operations lazy in the stream argument (e.g. using an irrefutable ~pattern) would interfere with the usual stream optimisations. It's an interesting question. The usual optimisations rely on having access to the definitions of input streams and will not apply to a circular definition such as the above. This strictness issue isn't a semantic problem problem when applying stream fusion to data structures like lists. A circular definition of a list will simply not fuse (there is nowhere to apply the stream/unstream rule). Duncan

On 2 January 2011 19:54, Duncan Coutts
In the standard stream fusion style, all stream operations are strict in the stream itself (that is, the pair of stepper function and initial state, not strict in the unfolded sequence or elements). Thus it is not possible to write things like:
bad_ones :: Stream Int bad_ones = s where s = 1 `S.cons` s
...
Thanks Duncan and Henning again ealier. I'll see if I can do without tight, circular definitions or change to an inductive stream representation if I find I need them. Best wishes Stephen

Hi Stephen,
On 2 January 2011 13:35, Stephen Tetley
Can a lazy cons be implemented for (infinite) Streams in the Stream-Fusion style?
I made a mailing list post about almost exactly this issue a while ago (http://www.mail-archive.com/haskell-cafe@haskell.org/msg82981.html). There was no really nice solution offered: I think the best you can do is define your stream operations with a lazy pattern match using my "eta" trick from that post: eta stream = Stream (case stream of Stream s _ -> unsafeCoerce s :: ()) (case stream of Stream _ step -> unsafeCoerce step) Then instead of writing: f (Stream x y) = ... Write: f (eta -> Stream x y) = ... (This is necessary because lazy pattern matches on existential data constructors using ~ cannot even be expressed in System FC, so it is unclear how GHC could implement them). Cheers, Max
participants (4)
-
Duncan Coutts
-
Henning Thielemann
-
Max Bolingbroke
-
Stephen Tetley