> Although this is only an aesthetic bug, I'd prefer to see no warnings
> from gcc. Given the following module:
>
> ---------------------------------------------------------------------
> module Foo where
>
> import Addr
> import IOExts
> import Monad
>
> bar :: IORef Addr -> Addr -> IO ()
> bar r a = do
> old <- readIORef r
> unless (old == nullAddr) (freeHaskellFunctionPtr old)
> writeIORef r a
> ---------------------------------------------------------------------
>
> Compilation yields:
>
> ---------------------------------------------------------------------
> marutea ~> ghc -fglasgow-exts -O -c Foo.hs
> ghc: module version changed to 1; reason: no old .hi file
> /tmp/ghc28382.hc:28: warning: assignment makes integer from
> pointer without a cast
> /tmp/ghc28382.hc:32: warning: initialization makes pointer
> from integer without a cast
> ---------------------------------------------------------------------
This one is caused by the code generator being a bit short of names for
temporary variables in places, and occasionally having to magic one out of
thin air. The patch below should fix (read: hack around) this problem.
Cheers,
Simon
*** CgCase.lhs 1999/06/28 16:29:45 1.34
--- CgCase.lhs 1999/10/11 09:55:36
***************
*** 63,69 ****
tyConDataCons, tyConFamilySize )
import Type ( Type, typePrimRep, splitAlgTyConApp,
splitTyConApp_maybe, repType )
! import Unique ( Unique, Uniquable(..), mkBuiltinUnique )
import Maybes ( maybeToBool )
import Util
import Outputable
--- 63,69 ----
tyConDataCons, tyConFamilySize )
import Type ( Type, typePrimRep, splitAlgTyConApp,
splitTyConApp_maybe, repType )
! import Unique ( Unique, Uniquable(..), mkPseudoUnique1 )
import Maybes ( maybeToBool )
import Util
import Outputable
***************
*** 144,149 ****
--- 144,154 ----
alternatives (in which case we lookup the tag in the relevant closure
table to get the closure).
+ Being a bit short of uniques for temporary variables here, we use
+ mkPseudoUnique1 to generate a temporary for the tag. We can't use
+ mkBuiltinUnique, because that occasionally clashes with some
+ temporaries generated for _ccall_GC, amongst others (see CgExpr.lhs).
+
\begin{code}
cgCase (StgCon (PrimOp op) args res_ty)
live_in_whole_case live_in_alts bndr srt (StgAlgAlts ty alts
deflt)
***************
*** 152,158 ****
let tag_amode = case op of
TagToEnumOp -> only arg_amodes
! _ -> CTemp (mkBuiltinUnique 1) IntRep
closure = CVal (CIndex (CLbl (mkClosureTblLabel tycon) PtrRep)
tag_amode PtrRep) PtrRep
in
--- 157,163 ----
let tag_amode = case op of
TagToEnumOp -> only arg_amodes
! _ -> CTemp (mkPseudoUnique1{-see above-} 1) IntRep
closure = CVal (CIndex (CLbl (mkClosureTblLabel tycon) PtrRep)
tag_amode PtrRep) PtrRep
in