[Haskell-cafe] curious about sum

Claus Reinke claus.reinke at talk21.com
Sun Jun 14 17:29:00 EDT 2009


> A much better idea than making sum strict, would simply be to add a  
> sum'.

Even better to abstract over strictness, to keep a lid on code duplication?

    {-# LANGUAGE TypeOperators #-}

    sum  = foldlS ($)  (+) 0
    sum' = foldlS ($!) (+) 0

    -- identity on constructors of t (from a), modulo strictness in a
    type a :-?> t = (a -> t) -> (a -> t)

    foldlS ::  (b :-?> ([a] -> b)) -> (a -> b -> b) -> (b -> [a] -> b)
    foldlS ($) op n []    = n
    foldlS ($) op n (h:t) = (foldlS ($) op $ (op h n)) t

Strictness is encoded as a constructor transformer - ($) keeps the
constructor in question unchanged, ($!) makes it strict. Also works 
with container types (Maps strict or not strict in their elements can
share the same strictness-abstracted code, for instance). Though 
sometimes there is more than one strictness choice to make in the 
same piece of code..

Claus




More information about the Haskell-Cafe mailing list