Proposal: Strict scanl, scanl1 and mapAccumL

Bas van Dijk v.dijk.bas at gmail.com
Mon Nov 12 14:12:57 CET 2012


On 12 November 2012 13:25, Henning Thielemann
<lemming at henning-thielemann.de> wrote:
> I don't think of changing it. We could provide a package that exports "the
> right 'seq'" and then encourage people to use this instead of Prelude.seq.

I think I like this idea. So the package would export something like:

module Control.Seq where

import Prelude hiding (seq)
import GHC.Base hiding (seq)

class WHNFData a where
    rwhnf :: a -> ()

instance WHNFData [a] where
    rwhnf []    = ()
    rwhnf (_:_) = ()

-- and all the others...

seq :: WHNFData a => a -> b -> b
seq a b = case rwhnf a of () -> b

($!) :: WHNFData a => (a -> b) -> a -> b
f $! x = x `seq` f x

force :: WHNFData a => a -> a
force x = x `seq` x

-- Doesn't type check unfortunately
-- since the b in seq :: a -> b -> b is of kind * and not #:
-- evaluate :: WHNFData a => a -> IO a
-- evaluate x = IO (\s ->  x `seq` (# s, x #))


However, I still think it doesn't hurt to add the strict versions now.
And then in the future possibly change the whole base library at once
(and other libraries like containers) to support the Seq class.

Bas



More information about the Libraries mailing list