[Haskell-cafe] `zip` doesn't work with infinite `Seq`s

Matteo Ferrando matteo.ferrando2 at gmail.com
Tue Oct 7 03:49:13 UTC 2014


Thanks to Chris and Sam for the explanation! That explains it.

On Mon, Oct 6, 2014 at 10:57 PM, Chris Wong <lambda.fairy at gmail.com> wrote:

> Hi Matteo,
>
> Data.Sequence provides a general-purpose *finite* sequence. There is
> no such thing as an infinite Seq!
>
> In fact, you'll find that while
>
>     head $ repeat 'a'
>
> results in 'a',
>
>     Seq.head . Seq.fromList $ repeat 'a'
>
> never returns.
>
> Chris
>
> On Tue, Oct 7, 2014 at 3:57 PM, Matteo Ferrando
> <matteo.ferrando2 at gmail.com> wrote:
> > Hello,
> >
> > We are writing a compiler[1] for a course and found that the `zip`
> function
> > included in the `Data.Sequence` module, `zip :: Seq a -> Seq b -> Seq (a,
> > b)` would hang on the following code:
> >
> >> -- using the `zip` from `Data.Sequence`
> >> zip ys (fomList $ repeat x)
> >
> > We checked the implementation[2] in the source of `Data.Sequence` and
> found
> > the following:
> >
> >> zip :: Seq a -> Seq b -> Seq (a, b)
> >> zip = zipWith (,)
> >
> >> -- Here `zipWith` assumes *non-infinite `Seq`s*
> >> zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c
> >> zipWith f xs ys
> >>   | length xs <= length ys      = zipWith' f xs ys
> >>   | otherwise                   = zipWith' (flip f) ys xs
> >
> >> -- Function not exported by `Data.Seq`, assumes `length xs <= length ys`
> >> zipWith' :: (a -> b -> c) -> Seq a -> Seq b -> Seq c
> >> zipWith' f xs ys = snd (mapAccumL k ys xs)
> >>   where
> >>     k kys x = case viewl kys of
> >>            (z :< zs) -> (zs, f x z)
> >            EmptyL    -> error "zipWith': unexpected EmptyL"
> >
> > In the lazy reading of the documentation we did, we didn't find any
> warning
> > of using infinite `Seq`s for zips. (Maybe there are warings that we
> didn't
> > see). But looking at the code of `zip` in the `Prelude`:
> >
> >> zip :: [a] -> [b] -> [(a,b)]
> >> zip (a:as) (b:bs) = (a,b) : zip as bs
> >> zip _      _      = []
> >
> > We see that we could just *pattern-match* both heads, instead of making
> > assumptions.
> >
> > Maybe this should be better explained in the documentation[3] of `zip`
> for
> > `Seq`s:
> >
> >> zip :: Seq a -> Seq b -> Seq (a, b)
> >> O(min(n1,n2)). zip takes two sequences and returns a sequence of
> >> corresponding pairs. If one input is short, excess elements are
> discarded
> >> from the right end of the longer sequence.
> >
> > Or just change the implementation for it to work with infinite `Seq`s.
> >
> > For those of you who are curious, we ended up using the following code to
> > fix the *infinite `Seq`s problem*:
> >
> >> -- using the `zip` from `Prelude`
> >> zip (toList ys) (repeat x)
> >
> > [1] https://github.com/chamini2/sapphire
> > [2]
> >
> http://hackage.haskell.org/package/containers-0.5.5.1/docs/src/Data-Sequence.html#zip
> > [3]
> http://hackage.haskell.org/package/containers-0.5.5.1/docs/Data-Sequence.html#v:zip
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20141006/616ac5e3/attachment.html>


More information about the Haskell-Cafe mailing list