Hi,
I'd like to get some review of these patches to implement a new FFI
import mode. It's best explained by an example:
foreign import prim unsafe "decodeFloat_Int"
local_decodeFloat_Int# :: Float# -> (# Int#, Int# #)
The decodeFloat_Int function is implemented in Cmm code and must follow
ghc's usual out-of-line primop calling convention.
There's a bit more background and motivation here:
http://blog.well-typed.com/2009/06/ghc-primops-and-exorcising-gmp/
It involves small changes in most phases of the compiler and in a few
cases there are some design choices. In particular I'd like to get
feedback on the choice of representation in the Core and STG layers.
In the current patches I use the existing FCall/ForeignCall stuff for
the imported prim functions. I did this rather than trying to add
user-imported prim functions to the PrimOp type because it's pretty
wired in that PrimOp is a simple enumeration. An alternative to what
I've got now might be to unify PrimOp with these extra PrimCall things
(ie have a type containing either), or to make a third kind of IdDetail
in addition to the exiting PrimOpId and FCallId.
The reason that longer term we might not want to stick with using
FCall/ForeignCall is that, as I understand it, after some backend
changes the primop and Haskell function cmm level calling conventions
will be unified and then the foreign import primop could be used at
almost any Haskell function type, not just simple unlifed args and
result.
In the STG layer it's more obvious that we should not be using the
FCall/ForeignCall stuff. The code gen has to treat these prim calls
almost exactly like the existing out-of-line primops. Again, there is
the alternative of unifying PrimOps and these PrimCalls in some middle
data type.
When looking at the code gen patch below, note that unlike the
StgFCallOp, the StgPrimCallOp does not contain a Unique. I do not know
if this is important or not. I did not find a use for the Unique value,
even though like for the C call case we do use an arbitrary user-given
string as a linker symbol name.
The full patch set is here:
http://haskell.org/~duncan/ghc/foreign-import-prim-1.dpatch
Tue Jun 9 11:44:03 BST 2009 Duncan Coutts <[email protected]>
* Add new FFI calling convention "prim"
First in a series of patches to add the feature.
This patch just adds PrimCallConv to the CCallConv type.
Tue Jun 9 11:45:36 BST 2009 Duncan Coutts <[email protected]>
* Lexing and parsing for "foreign import prim"
We only allow simple function label imports, not the normal complicated
business with "wrapper" "dynamic" or data label "&var" imports.
Tue Jun 9 11:48:26 BST 2009 Duncan Coutts <[email protected]>
* Typechecking for "foreign import prim"
The main restriction is that all args and results must be unboxed types.
In particular we allow unboxed tuple results (which is a primary
motivation for the whole feature). The normal rules apply about
"void rep" result types like State#. We only allow "prim" calling
convention for import, not export. The other forms of import, "dynamic",
"wrapper" and data label are banned as a conseqence of checking that the
imported name is a valid C string. We currently require prim imports to
be marked unsafe, though this is essentially arbitrary as the safety
information is unused.
Tue Jun 9 11:59:45 BST 2009 Duncan Coutts <[email protected]>
* Desugaring for "foreign import prim"
Unlike normal foreign imports which desugar into a separate worker and
wrapper, we use just a single wrapper decleration. The representation
in Core of the call is currently as a foreign call. This means the
args are all treated as fully strict. This is ok at the moment because
we restrict the types for foreign import prim to be of unboxed types,
however in future we may want to make prim imports be the normal cmm
calling convention for Haskell functions, in which case we would not
be able to assume all args are strict. At that point it may make more
sense to represent cmm/prim calls distinct from foreign calls, and
more like the we the existing PrimOp calls are handled.
Tue Jun 9 16:11:55 BST 2009 Duncan Coutts <[email protected]>
* Add PrimCall to the STG layer and update Core -> STG translation
It adds a third case to StgOp which already hold StgPrimOp and StgFCallOp.
The code generation for the new StgPrimCallOp case is almost exactly the
same as for out-of-line primops. They now share the tailCallPrim function.
In the Core -> STG translation we map foreign calls using the "prim"
calling convention to the StgPrimCallOp case. This is because in Core we
represent prim calls using the ForeignCall stuff. At the STG level however
the prim calls are really much more like primops than foreign calls.
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc