Behavior of the inliner on imported class methods

José Pedro Magalhães jpm at cs.uu.nl
Tue Jan 18 11:33:28 CET 2011


Hello all,

I fail to understand the behavior of the inliner in the following example:

module M1 where
>
> class MyEnum a where myEnum :: [a]
>
> instance MyEnum () where myEnum = [()]
>


> module M2 where
>
> import M1
>
> f1 = map (\() -> 'p') [()]
> f2 = map (\() -> 'q') myEnum
>

The generated core code for M2 with ghc-7.0.1 -O is:

M2.f22 :: GHC.Types.Char
> [GblId,
>  Caf=NoCafRefs,
>  Str=DmdType m,
>  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
>          ConLike=True, Cheap=True, Expandable=True,
>          Guidance=IF_ARGS [] 1 2}]
> M2.f22 = GHC.Types.C# 'q'
>
> M2.f11 :: GHC.Types.Char
> [GblId,
>  Caf=NoCafRefs,
>  Str=DmdType m,
>  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
>          ConLike=True, Cheap=True, Expandable=True,
>          Guidance=IF_ARGS [] 1 2}]
> M2.f11 = GHC.Types.C# 'p'
>
> M2.f21 :: () -> GHC.Types.Char
> [GblId,
>  Arity=1,
>  Caf=NoCafRefs,
>  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=1, Value=True,
>          ConLike=True, Cheap=True, Expandable=True,
>          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=True)}]
> M2.f21 =
>   \ (ds_dch :: ()) -> case ds_dch of _ { () -> M2.f22 }
>
> M2.f2 :: [GHC.Types.Char]
> [GblId,
>  Str=DmdType,
>  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=False,
>          ConLike=False, Cheap=False, Expandable=False,
>          Guidance=IF_ARGS [] 3 0}]
> M2.f2 =
>   GHC.Base.map
>     @ () @ GHC.Types.Char M2.f21 M1.$fMyEnum()_$cmyEnum
>
> M2.f1 :: [GHC.Types.Char]
> [GblId,
>  Caf=NoCafRefs,
>  Str=DmdType,
>  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
>          ConLike=True, Cheap=True, Expandable=True,
>          Guidance=IF_ARGS [] 1 3}]
> M2.f1 =
>   GHC.Types.:
>     @ GHC.Types.Char M2.f11 (GHC.Types.[] @ GHC.Types.Char)
>

So, why does the inliner fail to get rid of the map in f2, while correctly
ditching it in f1? Note that using two modules is essential here: if the
instance is in M2 (and thus becoming orphan), the inliner works "correctly".
Adding INLINE/INLINABLE pragmas to myEnum doesn't improve things either. Is
this a bug, or is there a reason for this behavior?


Thanks,
Pedro
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20110118/dc111f93/attachment.htm>


More information about the Glasgow-haskell-users mailing list