Thu, 27 Jul 2000 07:57:00 -0700, Simon Marlow <[EMAIL PROTECTED]> pisze:

> Since the type is explicit, GHC should be able to inline away all the
> overloading.  In fact there's no recursion here: the recursive call to
> callIO is to a method pulled out of the dictionary passed in as an argument,
> and the values of the dictionaries will all be available at compile time.

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?

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/            GCS/M d- s+:-- a23 C+++$ UL++>++++$ P+++ L++>++++$ E-
  ^^                W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK                5? X- R tv-- b+>++ DI D- G+ e>++++ h! r--%>++ y-


Reply via email to