
Since I realized my code was always using infinite lists, I replaced it by Data.Stream. However, my code stopped working. The problem is with these functions: scan :: (a -> b -> a) -> a -> Stream b -> Stream ascan f z (Cons x xs) = z <:> scan f (f z x) xs-- | @scan'@ is a strict scan.scan' :: (a -> b -> a) -> a -> Stream b -> Stream ascan' f z (Cons x xs) = z <:> (scan' f $! (f z x)) xs They are too strict I think. My code works again when I add a lazy pattern match: scan f z ~(Cons x xs) = z <:> scan f (f z x) xs scan' f z ~(Cons x xs) = z <:> (scan' f $! (f z x)) xs This is justified since they then behave like scanl on lists. However it seems this package is used a lot, so maybe some code depends on this strictness. What to do? PS: Why does scanl' not exist in Data.List?

Hi Peter,
However, my code stopped working.
Could you send me a smallish example of what breaks, so I can get a better idea of what the problem is? I'd be happy to release a new version of Data.Stream that fixes your issues (the upcoming Hackathon might be a good opportunity to work on this). All the best, Wouter

Hi Wouter,
Sure, here it is. I was doing an adaptation to the integralS function
described in this paper http://www.cs.yale.edu/~hl293/download/leak.pdf
import qualified Data.Stream as S
import Data.Stream (Stream(..))
-- Approximates c + integral f(t) dt for t=0 to infinity using simple Euler
steps
-- Both the function and the steps are provided as streams
eulerIntegral :: Double -> Stream Double -> Stream Double -> Stream Double
eulerIntegral c ft dt = S.scan' (+) c $ S.zipWith (*) ft dt
-- Since scan' is strict it doesn't behave well regarding fixed points,
-- e.g. the computation of the approximation of e blocks
e = es S.!! (10^6)
where
es = eulerIntegral 1 es dts
dts = S.repeat 1e-6
-- Replacing S.scan' with myscan' fixes it
myscan' f b ~(a `Cons` as) = b `seq` (b `Cons` myscan' f (f b a) as)
On Sun, Apr 12, 2009 at 12:25 PM, Wouter Swierstra
Hi Peter,
However, my code stopped working.
Could you send me a smallish example of what breaks, so I can get a better idea of what the problem is? I'd be happy to release a new version of Data.Stream that fixes your issues (the upcoming Hackathon might be a good opportunity to work on this).
Wouter
participants (2)
-
Peter Verswyvelen
-
Wouter Swierstra