[ moved to glasgow-haskell-users ]

> Ah, indeed it gets nicely optimized. But one thing worries me:
> 
> module M1 where
> import Foreign
> import Int
> f a i = writeInt8OffAddr (a `plusAddr` i) 42
> 
> [qrczak ~/haskell]$ ghc -c -O -ddump-stg -fglasgow-exts M1.hs
> 
> ==================== STG syntax: ====================
> lvl = NO_CCS I#! [42];
> SRT: []
> f = NO_CCS[] \r[a i]
>       let {
>         stg_c2C6 =
>             NO_CCS[] \u[]
>                 case a of wild {
>                   A# addr ->
>                       case i of wild1 {
>                         I# off ->
>                             case addr2Int# [addr] of stg_c2C4 {
>                               DEFAULT ->
>                                   case +# [stg_c2C4 off] of stg_c2C3 {
>                                     DEFAULT ->
>                                         case int2Addr# 
> [stg_c2C3] of a1 { DEFAULT -> A# [a1] }
>                                   }
>                             };
>                       };
>                 };
>       } in  writeInt8OffAddr stg_c2C6 lvl;
> SRT: []
> --------------------------------------------------------------
> ----------
> 
> Looks like writeInt8OffAddr is not treated as strict - it gets an
> unevaluated closure as the first argument. Why?

Yes, this all stems from the fact that writeInt8OffAddr contains a casm, and
therefore doesn't have an unfolding outside the module in which it is
defined.  The strictness analyser when compiling Int decided that it wasn't
worth worker-wrappering writeInt8OffAddr because it was small enough to
inline everywhere anyway, but didn't notice that it wasn't going to be
inlined outside this module.

Even given that, I'm not sure why the strictness information on
writeInt8OffAddr didn't cause the thunk to be turned into a case.  More
investigation is required.

Cheers,
        Simon

Reply via email to