[Haskell-cafe] Lazy cons, Stream-Fusion style?
Stephen Tetley
stephen.tetley at gmail.com
Sun Jan 2 14:35:20 CET 2011
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
More information about the Haskell-Cafe
mailing list