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

Looking into Foo.hc shows the problem: An I_ temporary variable is
used to hold an StgAddr. Either another variable should be used or
some casts should be inserted.

---------------------------------------------------------------------
INFO_TABLE_SRT_BITMAP(c1XV_info,c1XV_ret,1,Foo_zdwbar_srt,0,1,RET_SMALL,static 
,IF_,0,0);
IFN_(c1XV_ret) {
EF_(IOExts_zdwwriteIORef_fast3);
I_ _B1_;                          /* !!!!!!!!!!!!!!!!!!!! */
FB_
eqAddrzh(_B1_,(StgAddr)(Sp[1]),(StgAddr)(R1.p[1]));
if (_B1_) {
R1.p=(P_)(Sp[3]);
Sp=Sp+2;
JMP_(IOExts_zdwwriteIORef_fast3);
} else {
_B1_=(StgAddr)(Sp[1]);           /* !!!!!!!!!!!!!!!!!!!! */
Sp[1]=(W_)((P_)&c1XX_info);
Sp=Sp+1;
{
StgAddr _ccall_arg1=_B1_;        /* !!!!!!!!!!!!!!!!!!!! */
do { SaveThreadState();
(freeHaskellFunctionPtr((_ccall_arg1)));
LoadThreadState();} while(0);
}
JMP_(ENTRY_CODE((P_)(*Sp)));
}
FE_
}
---------------------------------------------------------------------

Cheers,
   Sven
-- 
Sven Panne                                        Tel.: +49/89/2178-2235
LMU, Institut fuer Informatik                     FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen              Oettingenstr. 67
mailto:[EMAIL PROTECTED]            D-80538 Muenchen
http://www.informatik.uni-muenchen.de/~Sven.Panne

Reply via email to