Proposal: Strict scanl, scanl1 and mapAccumL
Josef Svenningsson
josef.svenningsson at gmail.com
Thu Nov 15 23:37:59 CET 2012
On Mon, Nov 12, 2012 at 2:12 PM, Bas van Dijk <v.dijk.bas at gmail.com> wrote:
> 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
>
> For reference, older versions of Haskell defined the following class:
class Eval a where
strict :: (a -> b) -> a -> b
seq :: a -> b -> b
strict f x = x `seq` f x
The function `strict` is quite useful for making strict versions of lazy
functions.
Each type was automagically an instance of this class (with the notable
exception of functions, there was no way to force function values).
Cheers,
Josef
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20121115/65fbb19c/attachment-0001.htm>
More information about the Libraries
mailing list