confused by core
Ian Lynagh
igloo at earth.li
Tue Mar 9 19:32:25 EST 2004
Hi,
If I have this Foo.hs:
-------------------------------
module Foo (foo) where
import Word (Word8)
import Control.Monad.ST (ST)
import Data.Array.ST (STUArray, writeArray)
foo :: STUArray s Int Word8 -> [Word8] -> Int -> ST s ()
foo arr ps i = writeArray arr i w
where i' = 4 * i
w = ps !! i'
-------------------------------
and I compile with (GHC 6.2 and a reasonably recent CVS)
ghc -O -funbox-strict-fields -Wall -c Foo.hs -ddump-simpl
then part of the output is:
let {
n :: GHC.Prim.Int#
Str: DmdType
n = GHC.Prim.*# 4 ww3
} in
case GHC.Prim.<# n 0 of wild1 {
Is this really a lazy let, or is there some magic going on that means it
is actually done strictly as it's an Int#? Like how ISTR Int#s always
appear to have strictness L (these inconsitencies make things much more
difficult as a user IMO, incidentally).
Thanks
Ian
More information about the Glasgow-haskell-users
mailing list