[Haskell-cafe] >>= definition for list monad in ghc
Daniel Fischer
daniel.is.fischer at googlemail.com
Mon May 16 21:46:52 CEST 2011
On Monday 16 May 2011 20:49:35, austin seipp wrote:
> Looking at the Core for an utterly trivial example (test x = concatMap
> k x where k i = [i..i*2]), the foldr definition seems to cause a
> little extra optimization rules to fire, but the result seems pretty
> big. The definition using concatMap results in core like this:
>
Hmm, something seems to be amiss, writing
test :: [Int] -> [Int]
test x = concat (map k x)
where
k :: Int -> [Int]
k i = [i .. 2*i]
the core I get is
Rec {
ConcatMap.test_go [Occ=LoopBreaker]
:: [GHC.Types.Int] -> [GHC.Types.Int]
[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType S]
ConcatMap.test_go =
\ (ds_aoS :: [GHC.Types.Int]) ->
case ds_aoS of _ {
[] -> GHC.Types.[] @ GHC.Types.Int;
: y_aoX ys_aoY ->
case y_aoX of _ { GHC.Types.I# x_aom ->
GHC.Base.++
@ GHC.Types.Int
(GHC.Enum.eftInt x_aom (GHC.Prim.*# 2 x_aom))
(ConcatMap.test_go ys_aoY)
}
}
end Rec }
which is identical to the core I get for foldr ((++) . k) [].
Writing concatMap, I get the larger core (I'm not sure which one's better,
the concatMap core uses only (:) to build the result, that might make up
for the larger code).
But, as Felipe noted, concatMap is defined as
-- | Map a function over a list and concatenate the results.
concatMap :: (a -> [b]) -> [a] -> [b]
concatMap f = foldr ((++) . f) []
in GHC.List. There are no RULES or other pragmas involving concatMap either
there or in Data.List. In the absence of such pragmas, I would expect
concatMap to be inlined and thus to yield exactly the same core as
foldr ((++) . f) []
More information about the Haskell-Cafe
mailing list