Hello, I'm trying to do safe ccall from cmm (see below for the code). It seems to work, but -dcmm-lint is not satisfied:
/opt/ghc-7.8.2/bin/ghc --make -o test hs.hs cmm.cmm c.c -dcmm-lint -fforce-recomp Cmm lint error: in basic block c4 in assignment: _c1::I32 = R1; Reg ty: I32 Rhs ty: I64 Program was: {offset c5: _c0::I64 = R1; _c2::I64 = c_test; _c3::I32 = %MO_UU_Conv_W64_W32(_c0::I64); I64[(young<c4> + 8)] = c4; foreign call "ccall" arg hints: [] result hints: [] (_c2::I64)(...) returns to c4 args: ([_c3::I32]) ress: ([_c1::I32])ret_args: 8ret_off: 8; c4: _c1::I32 = R1; R1 = %MO_SS_Conv_W32_W64(_c1::I32); call (P64[(old + 8)])(R1) args: 8, res: 0, upd: 8; } <no location info>: Compilation had errors The same code without "safe" annotation passes cmm lint. Is it my error or ghc bug? How can I do safe ccall in cmm correctly? Here is the code: == c.c == #include <assert.h> int c_test(int i) { assert(i == 1); return 2; } == cmm.cmm #include "Cmm.h" cmm_test(W_ i) { CInt i1; (i1) = ccall c_test(W_TO_INT(i)) "safe"; return (TO_W_(i1)); } == hs.hs == {-# LANGUAGE GHCForeignImportPrim #-} {-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE UnliftedFFITypes #-} import GHC.Prim import GHC.Types import Control.Exception foreign import prim "cmm_test" test :: Int# -> Int# main :: IO () main = do let i1 = test 1# assert (I# i1 == 2) (return ()) Thanks, Yuras _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs