[Haskell-cafe] stream/bytestring questions

Chad Scherrer chad.scherrer at gmail.com
Wed Feb 20 13:31:55 EST 2008


On Feb 17, 2008 6:06 PM, Derek Elkins <derek.a.elkins at gmail.com> wrote:
> It's -quite- possible that a coalgebraic perspective is much more
> natural for your code/problem.  If that's the case, use it (the
> coalgebraic perspective that is).  Obviously depending on the internals
> of the stream library is not a good idea and using Streams directly was
> not their intent, but it is your code.  Do what you will.

Here's an example of the problem. Start with a function

extract :: [Int] -> [a] -> [a]
extract = f 0
    where
    f !k nss@(n:ns) (x:xs)
      | n == k    = x : f (k+1) ns xs
      | otherwise = f (k+1) nss xs
    f _ _ _ = []

which is just a more efficient way of getting
extract ns xs == [xs !! n | n <- ns]

There should be a way to write this that will be friendly for stream
fusion. The best option I can see is unfoldr. But if you try to write
it this way, you get something like

extract' ns xs = unfoldr f (0,ns,xs)
  where
  f (!k, nss@(n:ns), x:xs)
    | n == k    = Just (x, (k + 1, ns, xs))
    | otherwise = f (k+1, nss, xs)
  f _ = Nothing

This is fine, except that the second-to-last line means this is still
recursive. If I understand correctly, fusion requires that the
recursion be encapsulated within the unfoldr or other functions that
are expressed internally as stream functions.

We could encapsulate the recursion with a function
stepUnfoldr :: (s -> Step a s) -> s -> [a]
stepUnfoldr f s = unfoldr g s
  where
  g s = case f s of
    Done -> Nothing
    Yield x s' -> Just (x,s')
    Skip s' -> g s'

Using this, we could just write

extract'' ns xs = stepUnfoldr f (0,ns,xs)
  where
  f (!k, nss@(n:ns), x:xs)
    | n == k    = Yield x (k + 1, ns, xs)
    | otherwise = Skip (k+1, nss, xs)
  f _ = Done

This is a pretty natural way to write the algorithm, and the recursion
is nicely tucked away. The only remaining question is whether we can
get things to fuse.

The type of stepUnfoldr looks familiar...

*Main> :t stepUnfoldr
stepUnfoldr :: (s -> Step a s) -> s -> [a]

*Main> :t \f s -> unstream $ Stream f s
\f s -> unstream $ Stream f s :: (Data.Stream.Unlifted s) =>
                                 (s -> Step a s) -> s -> [a]

If we could somehow swap out our state type for an unlifted one, we
could write a rule
  stepUnfoldr f = unstream . Stream f

It seems like there might be some subtleties there to watch out for,
but I'm not sure yet.

Anyway, this is the kind of thing I had in mind when I asked about
using the internals of Data.Stream more directly.

Chad


More information about the Haskell-Cafe mailing list