laziness of intersperse

Gwern Branwen gwern0 at gmail.com
Sat Aug 16 12:13:21 EDT 2008


On 2008.08.16 10:51:14 -0400, Reid Barton <rwbarton at math.harvard.edu> scribbled 1.3K characters:
> (This is the same issue as http://www.haskell.org/pipermail/haskell/
> 2004-March/013739.html but there was no follow-up at that time.)
>
> The intersperse library function is not as lazy as it could be.  The
> current definition of intersperse is
>
> intersperse             :: a -> [a] -> [a]
> intersperse _   []      = []
> intersperse _   [x]     = [x]
> intersperse sep (x:xs)  = x : sep : intersperse sep xs
>
> For any list (x:xs) not containing _|_, intersperse sep (x:xs) is a list
> of the form (x:...); yet intersperse sep (x:_|_) = _|_ because the
> pattern match on the second equation diverges.  A better definition would
> be
>
> intersperse _ [] = []
> intersperse sep (x:xs) = x : intersperseWithPrefix xs
>   where intersperseWithPrefix [] = []
>         intersperseWithPrefix (x:xs) = sep : x : intersperseWithPrefix xs
>
> (slightly modified from http://www.haskell.org/pipermail/haskell/2004-
> March/013741.html)
>
> An application: There was a question on #haskell about how to compute
> the "ruler" sequence [1,2,1,3,1,2,1,4,1,2,1,3,1,2,1,5,...].  The
> definition
>
> ruler = fix ((1:) . intersperse 1 . map (1+))
>
> works with the properly lazy intersperse, but not with the intersperse in
> Data.List.
>
> Comments on this new definition?  Can it get added to Data.List?
>
> Regards,
> Reid Barton

I assume you mean something like this (setting up for QC and removing some aliasing in intersperse')

{-# LANGUAGE NoMonomorphismRestriction #-}
import Test.QuickCheck (quickCheck)

intersperse             :: a -> [a] -> [a]
intersperse _   []      = []
intersperse _   [x]     = [x]
intersperse sep (x:xs)  = x : sep : intersperse sep xs

intersperse' :: a -> [a] -> [a]
intersperse' _ [] = []
intersperse' sep (x:xs) = x : intersperseWithPrefix xs
  where intersperseWithPrefix [] = []
        intersperseWithPrefix (y:ys) = sep : y : intersperseWithPrefix ys

prop = \x y -> intersperse x y == intersperse' x y


----

Well, I ran a few thousand QuickChecks. Looks good to me, although I'm not thrilled with the lost of clarity - intersperse' to me is less immediately understandable than intersperse. (Although I don't suppose it's really all that important.)

--
gwern
Nash CIO VIA SHAPE Fax 767 Middleman schloss ASDIC CIA-DST
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org/pipermail/libraries/attachments/20080816/be02518b/attachment.bin


More information about the Libraries mailing list