Generating a C call from a MachOp

Johan Tibell johan.tibell at gmail.com
Thu Dec 6 19:13:59 CET 2012


Hi,

I'm trying to implement word2Double#, which I represent as a MachOp I
call MO_UF_Conv (which is very similar to MO_SF_Conv). On some
platform I need to implement this MachOp as a call to a C function.
Here's what I did in the PPC backend (PPC/CodeGen.hs) for example:

getRegister' dflags (CmmMachOp mop [x]) -- unary MachOps
  = case mop of
      MO_UF_Conv from to -> coerceWord2FP from to x

coerceWord2FP :: Width -> Width -> CmmExpr -> NatM Register
coerceWord2FP fromRep toRep x = do
    dflags <- getDynFlags
    (src, src_code) <- getSomeReg x  -- This is not the type of register I need!
    dst <- getNewRegNat (floatSize toRep)
    targetExpr <- cmmMakeDynamicReference dflags addImportNat CallReference lbl
    let target = ForeignTarget targetExpr (ForeignConvention CCallConv
                                           [NoHint] [NoHint]
                                           CmmMayReturn)
    call_code <- genCCall target [src] [dst]
    let code' = src_code `appOL` call_code
    return (Fixed (floatSize toRep) dst code')
  where
    lbl = mkCmmCodeLabel primPackageId (fsLit $ word2FloatLabel toRep)

This doesn't work. The issue is that to make a C call I need
CmmFormals and CmmActuals. I cannot figure out how to get the former,
as I need to get hold of a LocalReg, which I don't see any way of
creating.

I could try to make MO_UF_Conv a CallishMachOp, but then I'll have a
more difficult time implementing this MachOp in e.g. the LLVM backend,
where I don't want to generate a C call but instead output some
instructions.

I could use some pointers.

Cheers,
  Johan



More information about the Glasgow-haskell-users mailing list