confused by core

Simon Marlow simonmar at microsoft.com
Wed Mar 10 09:41:46 EST 2004


 
> 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#?

Yes, this let will be done strictly.  Indeed, any let which is sure to
be demanded (according to the Demand value of the Id) will turn into a
case in STG, and similarly for an expression in the argument position of
a strict function call.

I believe the motivation was that this makes things much easier for the
simplifier, but Simon PJ will be able to elaborate I'm sure.

> Like how ISTR Int#s always
> appear to have strictness L (these inconsitencies make things 
> much more difficult as a user IMO, incidentally).

ISTR?

Cheers,
	Simon


More information about the Glasgow-haskell-users mailing list