#4261: Add strict version of foldlWithKey to Map
---------------------------------+------------------------------------------
Reporter: tibbe | Owner:
Type: proposal | Status: new
Priority: normal | Component: libraries (other)
Version: | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
There's currently no strict left (pre-order) fold for `Map`s, making it
impractical to do simple things like summing all the values in the map.
The attached patch adds a strict `foldlWithKeys'` function that generates
optimal core for code like:
{{{
module Test (test) where
import qualified Data.Map as M
test :: M.Map Int Int -> Int
test m = M.foldlWithKey' (\n k v -> n + k + v) 0 m
}}}
If we look at the core we see that the `Int` accumulator is unboxed like
we'd hope:
{{{
test_$s$wgo2 :: Data.Map.Map Int Int -> Int# -> Int#
test_$s$wgo2 =
\ (sc_smi :: Data.Map.Map Int Int)
(sc1_smj :: Int#) ->
case sc_smi of _ {
Data.Map.Tip -> sc1_smj;
Data.Map.Bin _ kx_ali x_alj l_alk r_all ->
case test_$s$wgo2 l_alk sc1_smj of ww_slW { __DEFAULT ->
case kx_ali of _ { I# y_alD ->
case x_alj of _ { I# y1_XlT ->
test_$s$wgo2
r_all (+# (+# ww_slW y_alD) y1_XlT)
}
}
}
}
$wtest :: Data.Map.Map Int Int -> Int#
$wtest =
\ (w_slZ :: Data.Map.Map Int Int) ->
test_$s$wgo2 w_slZ 0
test :: Data.Map.Map Int Int -> Int
test =
__inline_me (\ (w_slZ :: Data.Map.Map Int Int) ->
case $wtest w_slZ of ww_sm2 { __DEFAULT ->
I# ww_sm2
})
}}}
Discussion deadline: 2 weeks
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4261>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs