[Haskell-cafe] >>= definition for list monad in ghc

austin seipp as at hacks.yi.org
Mon May 16 22:15:04 CEST 2011


You're both right indeed - I didn't look for the definition of
concatMap in GHC.List.

I thought it could be some behavior with the new inliner, so I defined
concatMap in terms of foldr, put it in a seperate module, and then
included it and used it in my test:

Concatmap2.hs:
module Concatmap2 (concatMap2) where

concatMap2 :: (a -> [b]) -> [a] -> [b]
concatMap2 f x = foldr ((++) . f) [] x

And concatmap.hs:

module Main where
import Concatmap2

test :: [Int] -> [Int]
test x = concatMap2 k x
  where k i = [i..i*2]

main :: IO ()
main = do
  print $ test [1..10]

Initially I thought it might be something to do with the new inliner
heuristics (something about only inlining if call sites are 'fully
saturated' with the amount of arguments they explicitly take,) but
defining concatMap as a partial function or in terms of 'x' didn't
make a difference - both resulted in generating the longer version of
core.

Attaching an INLINEABLE pragma to the definition of concatMap2
however, causes its definition in the interface file (Concatmap2.hi)
to change, and it results in the core turning into the small version.
Compiling with the pragma causes the persisted version of concatMap2
in the iface file to change from:

8d333e8d08e5926fd304bc7152eb286d
  concatMap2 :: forall a b. (a -> [b]) -> [a] -> [b]
    {- Arity: 2, HasNoCafRefs, Strictness: LS,
       Unfolding: (\ @ a @ b f :: a -> [b] x :: [a] ->
                   letrec {
                     go :: [a] -> [b] {- Arity: 1, Strictness: S -}
                     = \ ds :: [a] ->
                       case @ [b] ds of wild {
                         [] -> GHC.Types.[] @ b : y ys -> GHC.Base.++
@ b (f y) (go ys) }
                   } in
                   go x) -}

To:

075ec6b9bcabc12777955494312f5e61
  concatMap2 :: forall a b. (a -> [b]) -> [a] -> [b]
    {- Arity: 2, HasNoCafRefs, Strictness: LS,
       Inline: INLINABLE[ALWAYS],
       Unfolding: <stable> (\ @ a @ b f :: a -> [b] x :: [a] ->
                            GHC.Base.foldr
                              @ a
                              @ [b]
                              (\ x1 :: a -> GHC.Base.++ @ b (f x1))
                              (GHC.Types.[] @ b)
                              x) -}

Which I assume exposes the needed code (namely the foldr) for
additional RULES to fire later, resulting in the small code.

So perhaps we should mark concatMap INLINEABLE, instead?

On Mon, May 16, 2011 at 2:46 PM, Daniel Fischer
<daniel.is.fischer at googlemail.com> wrote:
> 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) []
>



-- 
Regards,
Austin



More information about the Haskell-Cafe mailing list