help needed for adding isWHNF primop to 5.00.2
Bernard James POPE
bjpop@cs.mu.OZ.AU
Sun, 29 Jul 2001 00:34:50 +1000 (EST)
Hi GHC people,
I would like to add a primitive to GHC 5.00.2 of the form:
isWHNF :: a -> Bool
I was able to do (something like) this a while ago in 4.06, but have got
stuck trying to do the same with 5.00.2.
Here's what I have tried:
After reading ghc/compiler/prelude/primops.txt:
- added
primop IsHNF "isHNF#" GenPrimOp
a -> Int#
with
strictness = { \ arity -> StrictnessInfo [wwLazy] False }
to ghc/compiler/prelude/primops.txt
- added isHNFzh to ghc/lib/std/PrelGHC.hi-boot
- added
#define isHNFzh(r,a) r=(! closure_THUNK((StgClosure *)a))
to ghc/includes/PrimOps.h
{-
although I think this should be the same as: ???
#define isHNFzh(r,a) r=(closure_HNF((StgClosure *) a))
-}
- I think I need to do something in:
ghc/compiler/nativeGen/StixPrim.lhs
but I have no idea what, I looked at the code in there and got scared,
so I left it alone, although I suspect that was a bad idea.
- I then did: make boot; make all
- everything compiled ok, but I get some serious problems when I try
to use my new primitive:
\begin{code}
module Main where
import GlaExts
import PrelGHC
main = print $ g
g :: Bool
g = fromUnboxedIntAsBoolean (isHNF# ())
fromUnboxedIntAsBoolean :: Int# -> Bool
fromUnboxedIntAsBoolean x
= case x of
1# -> True
_ -> False
\end{code}
When I compile this code with my newly built compiler using:
ghc -ddump-types -fglasgow-exts -package lang
I get:
==================== Interface ====================
TYPE SIGNATURES
Main.fromUnboxedIntAsBoolean :: PrelGHC.Int# -> PrelBase.Bool
Main.g :: PrelBase.Bool
Main.main :: PrelIOBase.IO ()
{-# Generic type constructor details
#-}
ghc-5.00.2: panic! (the `impossible' happened, GHC version 5.00.2):
getRegister(x86,unary primop)
(Prim isHNFzh PrelBase.Z0T{-70-}_closure)
Please report it as a compiler bug to glasgow-haskell-bugs@haskell.org,
or http://sourceforge.net/projects/ghc/.
The file ghc/docs/rts/rts.tex talks of a predicate "isWHNF", however, I cannot
seem to find it anywhere, and suspect that it does not exist anymore.
If anyone could point me in the right direction to solving my problem I would
be very grateful.
Regards,
Bernie.
PS
Unfortunately I clobbered my version for 4.06 with isWHNF added, and now I
can't get it to work anymore.