adding isWHNF primop to 5.00.2 native code generator

Bernard James POPE bjpop@cs.mu.OZ.AU
Wed, 1 Aug 2001 19:46:50 +1000 (EST)


Hi all,

More mind boggling questions on prim ops :)

I am happy with isWHNF that is implemented with:

   #define isHNFzh(r,a) r=(! closure_THUNK((StgClosure *)a))

I will re-write for the IO Monad later.

I want to mimic this behaviour in the native code
generator.

Sigbjorn gave me this suggestion, which is based on
DataToTagOp.

   \begin{code}
   primCode [res] IsHNF [arg]
      = let res'        = amodeToStix res
            arg'        = amodeToStix arg
            arg_info    = StInd PtrRep arg'
            word_32     = StInd WordRep (StIndex PtrRep arg_info (StInt (-1)))
            masked_le32 = StPrim SrlOp [word_32, StInt 16]
            masked_be32 = StPrim AndOp [word_32, StInt 65535]
   #ifdef WORDS_BIGENDIAN
            ty_info     = masked_le32
   #else
            ty_info     = masked_be32
   #endif
            not_a_thunk = StPrim IntEqOp [ StPrim AndOp [ty_info, StInt 0x10]
                                         , StInt 0x0
                                         ]
                   -- ToDo: don't hardwire the value of _THUNK from InfoTables.h
            assign      = StAssign IntRep res' not_a_thunk
        in
        returnUs (\ xs -> assign : xs)
   \end{code} 


I get different results with the version using the C macro and
the native code version. In particular I get the wrong (unexpected
result from the native code version).

The C macro version works like this (uses these macros):

   #define closureFlags(c)         (closure_flags[get_itbl(c)->type])
      -- in ghc/includes/InfoTables.h

   #define closure_THUNK(c)        (  closureFlags(c) & _THU)
      -- in ghc/includes/InfoTables.h

   #define get_itbl(c)   (INFO_PTR_TO_STRUCT((c)->header.info))
      -- in ghc/includes/ClosureMacros.h

   #define INFO_PTR_TO_STRUCT(info) ((StgInfoTable *)(info) - 1)
      -- in ghc/includes/ClosureMacros.

The (-1) scares me a little bit, in INFO_PTR_TO_STRUCT.

The array closure_flags[] is just a look up table, indexed by the
closure type. So the key part of the code above is:

   get_itbl(c)->type

In the native code version above, the lines below act like get_itbl(c):

   arg_info    = StInd PtrRep arg'
   word_32     = StInd WordRep (StIndex PtrRep arg_info (StInt (-1)))

After this I am lost. It seems to be grabbing the top or bottom 16 bits
of word_32 (depending on endianness) and then ANDing those bits with
0x10 (which is the bit mask for _THU), and checking for 0.

My feeling is that I should be finding out the "type" field from
the closure and then switching on its value. 

I don't understand the native code generator well enough. I am assuming
that closures are laid out the same way as via-C, in particular that
there is going to be some stuff in the info table before the "type"
field (this looks variable depending on how things are
built). Basically I'm looking for a way to do the equivalent of
"->type". Maybe there is a better way to do it. 

Thanks once again, and apologies if I missed something obvious.

Cheers,
Bernie.