X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FdeSugar%2FDsForeign.lhs;h=808016ddeebca3a511a02cd8292b682df3fe77e6;hb=0aca2f00f9bddce3624c1c99e9d2373a3a10a6c3;hp=2d4eb35ef59cba261e039509d98c66b4be3fb751;hpb=a7d8f43718b167689c0a4a4c23b33a325e0239f1;p=ghc-hetmet.git diff --git a/ghc/compiler/deSugar/DsForeign.lhs b/ghc/compiler/deSugar/DsForeign.lhs index 2d4eb35..808016d 100644 --- a/ghc/compiler/deSugar/DsForeign.lhs +++ b/ghc/compiler/deSugar/DsForeign.lhs @@ -9,22 +9,29 @@ Expanding out @foreign import@ and @foreign export@ declarations. module DsForeign ( dsForeigns ) where #include "HsVersions.h" +import TcRnMonad -- temp import CoreSyn import DsCCall ( dsCCall, mkFCall, boxResult, unboxArg, resultWrapper ) import DsMonad -import HsSyn ( ForeignDecl(..), ForeignExport(..), +import HsSyn ( ForeignDecl(..), ForeignExport(..), LForeignDecl, ForeignImport(..), CImportSpec(..) ) -import TcHsSyn ( TypecheckedForeignDecl ) +import DataCon ( splitProductType_maybe ) +#ifdef DEBUG +import DataCon ( dataConSourceArity ) +import Type ( isUnLiftedType ) +#endif +import MachOp ( machRepByteWidth, MachRep(..) ) +import SMRep ( argMachRep, primRepToCgRep ) import CoreUtils ( exprType, mkInlineMe ) import Id ( Id, idType, idName, mkSysLocal, setInlinePragma ) -import Literal ( Literal(..) ) +import Literal ( Literal(..), mkStringLit ) import Module ( moduleString ) import Name ( getOccString, NamedThing(..) ) import OccName ( encodeFS ) -import Type ( repType, eqType, typePrimRep ) +import Type ( repType, coreEqType, typePrimRep ) import TcType ( Type, mkFunTys, mkForAllTys, mkTyConApp, mkFunTy, tcSplitTyConApp_maybe, tcSplitForAllTys, tcSplitFunTys, tcTyConAppArgs, @@ -34,17 +41,16 @@ import BasicTypes ( Boxity(..) ) import HscTypes ( ForeignStubs(..) ) import ForeignCall ( ForeignCall(..), CCallSpec(..), Safety(..), playSafe, - CExportSpec(..), + CExportSpec(..), CLabelString, CCallConv(..), ccallConvToInt, ccallConvAttribute ) -import CStrings ( CLabelString ) -import TysWiredIn ( unitTy, stablePtrTyCon, tupleTyCon ) +import TysWiredIn ( unitTy, tupleTyCon ) import TysPrim ( addrPrimTy, mkStablePtrPrimTy, alphaTy ) -import PrimRep ( getPrimRepSizeInBytes ) -import PrelNames ( hasKey, ioTyConKey, newStablePtrName, bindIOName, +import PrelNames ( hasKey, ioTyConKey, stablePtrTyConName, newStablePtrName, bindIOName, checkDotnetResName ) import BasicTypes ( Activation( NeverActive ) ) +import SrcLoc ( Located(..), unLoc ) import Outputable import Maybe ( fromJust ) import FastString @@ -67,7 +73,7 @@ so we reuse the desugaring code in @DsCCall@ to deal with these. type Binding = (Id, CoreExpr) -- No rec/nonrec structure; -- the occurrence analyser will sort it all out -dsForeigns :: [TypecheckedForeignDecl] +dsForeigns :: [LForeignDecl Id] -> DsM (ForeignStubs, [Binding]) dsForeigns [] = returnDs (NoStubs, []) @@ -75,9 +81,11 @@ dsForeigns fos = foldlDs combine (ForeignStubs empty empty [] [], []) fos where combine (ForeignStubs acc_h acc_c acc_hdrs acc_feb, acc_f) - (ForeignImport id _ spec depr loc) - = dsFImport id spec `thenDs` \ (bs, h, c, mbhd) -> - warnDepr depr loc `thenDs` \ _ -> + (L loc (ForeignImport id _ spec depr)) + = traceIf (text "fi start" <+> ppr id) `thenDs` \ _ -> + dsFImport (unLoc id) spec `thenDs` \ (bs, h, c, mbhd) -> + warnDepr depr loc `thenDs` \ _ -> + traceIf (text "fi end" <+> ppr id) `thenDs` \ _ -> returnDs (ForeignStubs (h $$ acc_h) (c $$ acc_c) (addH mbhd acc_hdrs) @@ -85,7 +93,7 @@ dsForeigns fos bs ++ acc_f) combine (ForeignStubs acc_h acc_c acc_hdrs acc_feb, acc_f) - (ForeignExport id _ (CExport (CExportStatic ext_nm cconv)) depr loc) + (L loc (ForeignExport (L _ id) _ (CExport (CExportStatic ext_nm cconv)) depr)) = dsFExport id (idType id) ext_nm cconv False `thenDs` \(h, c, _) -> warnDepr depr loc `thenDs` \_ -> @@ -99,8 +107,8 @@ dsForeigns fos warnDepr False _ = returnDs () warnDepr True loc = dsWarn (loc, msg) - where - msg = ptext SLIT("foreign declaration uses deprecated non-standard syntax") + where + msg = ptext SLIT("foreign declaration uses deprecated non-standard syntax") \end{code} @@ -153,7 +161,7 @@ dsCImport :: Id -> DsM ([Binding], SDoc, SDoc) dsCImport id (CLabel cid) _ _ no_hdrs = resultWrapper (idType id) `thenDs` \ (resTy, foRhs) -> - ASSERT(fromJust resTy `eqType` addrPrimTy) -- typechecker ensures this + ASSERT(fromJust resTy `coreEqType` addrPrimTy) -- typechecker ensures this let rhs = foRhs (mkLit (MachLabel cid Nothing)) in returnDs ([(setImpInline no_hdrs id, rhs)], empty, empty) dsCImport id (CFunction target) cconv safety no_hdrs @@ -234,8 +242,8 @@ dsFCall fn_id fcall no_hdrs topConDs `thenDs` \ topCon -> boxResult maybe_arg_ids augment topCon io_res_ty `thenDs` \ (ccall_result_ty, res_wrapper) -> - getUniqueDs `thenDs` \ ccall_uniq -> - getUniqueDs `thenDs` \ work_uniq -> + newUnique `thenDs` \ ccall_uniq -> + newUnique `thenDs` \ work_uniq -> let -- Build the worker worker_ty = mkForAllTys tvs (mkFunTys (map idType work_arg_ids) ccall_result_ty) @@ -284,13 +292,13 @@ dsFExport :: Id -- Either the exported Id, -- the first argument's stable pointer -> DsM ( SDoc -- contents of Module_stub.h , SDoc -- contents of Module_stub.c - , [Type] -- arguments expected by stub function. + , [Type] -- primitive arguments expected by stub function. ) dsFExport fn_id ty ext_name cconv isDyn = let - (tvs,sans_foralls) = tcSplitForAllTys ty + (_tvs,sans_foralls) = tcSplitForAllTys ty (fe_arg_tys', orig_res_ty) = tcSplitFunTys sans_foralls -- We must use tcSplits here, because we want to see -- the (IO t) in the corner of the type! @@ -353,23 +361,24 @@ dsFExportDynamic id cconv -- hack: need to get at the name of the C stub we're about to generate. fe_nm = mkFastString (moduleString mod_name ++ "_" ++ toCName fe_id) in - dsFExport id export_ty fe_nm cconv True `thenDs` \ (h_code, c_code, stub_args) -> newSysLocalDs arg_ty `thenDs` \ cback -> - dsLookupGlobalId newStablePtrName `thenDs` \ newStablePtrId -> + dsLookupGlobalId newStablePtrName `thenDs` \ newStablePtrId -> + dsLookupTyCon stablePtrTyConName `thenDs` \ stable_ptr_tycon -> let - mk_stbl_ptr_app = mkApps (Var newStablePtrId) [ Type arg_ty, Var cback ] + mk_stbl_ptr_app = mkApps (Var newStablePtrId) [ Type arg_ty, Var cback ] + stable_ptr_ty = mkTyConApp stable_ptr_tycon [arg_ty] + export_ty = mkFunTy stable_ptr_ty arg_ty in - dsLookupGlobalId bindIOName `thenDs` \ bindIOId -> - newSysLocalDs (mkTyConApp stablePtrTyCon [arg_ty]) `thenDs` \ stbl_value -> + dsLookupGlobalId bindIOName `thenDs` \ bindIOId -> + newSysLocalDs stable_ptr_ty `thenDs` \ stbl_value -> + dsFExport id export_ty fe_nm cconv True `thenDs` \ (h_code, c_code, stub_args) -> let - stbl_app cont ret_ty - = mkApps (Var bindIOId) - [ Type (mkTyConApp stablePtrTyCon [arg_ty]) - , Type ret_ty - , mk_stbl_ptr_app - , cont - ] - + stbl_app cont ret_ty = mkApps (Var bindIOId) + [ Type stable_ptr_ty + , Type ret_ty + , mk_stbl_ptr_app + , cont + ] {- The arguments to the external function which will create a little bit of (template) code on the fly @@ -380,17 +389,37 @@ dsFExportDynamic id cconv adj_args = [ mkIntLitInt (ccallConvToInt cconv) , Var stbl_value , mkLit (MachLabel fe_nm mb_sz_args) + , mkLit (mkStringLit arg_type_info) ] -- name of external entry point providing these services. -- (probably in the RTS.) - adjustor = FSLIT("createAdjustor") + adjustor = FSLIT("createAdjustor") - mb_sz_args = - case cconv of - StdCallConv -> Just (sum (map (getPrimRepSizeInBytes . typePrimRep) stub_args)) - _ -> Nothing + arg_type_info = drop 2 $ map (repCharCode.argMachRep + .primRepToCgRep.typePrimRep) + stub_args + repCharCode F32 = 'f' + repCharCode F64 = 'd' + repCharCode I64 = 'l' + repCharCode _ = 'i' + + -- Determine the number of bytes of arguments to the stub function, + -- so that we can attach the '@N' suffix to its label if it is a + -- stdcall on Windows. + mb_sz_args = case cconv of + StdCallConv -> Just (sum (map ty_size stub_args)) + _ -> Nothing + + -- NB. the calculation here isn't strictly speaking correct. + -- We have a primitive Haskell type (eg. Int#, Double#), and + -- we want to know the size, when passed on the C stack, of + -- the associated C type (eg. HsInt, HsDouble). We don't have + -- this information to hand, but we know what GHC's conventions + -- are for passing around the primitive Haskell types, so we + -- use that instead. I hope the two coincide --SDM + ty_size = machRepByteWidth.argMachRep.primRepToCgRep.typePrimRep in - dsCCall adjustor adj_args PlayRisky False io_res_ty `thenDs` \ ccall_adj -> + dsCCall adjustor adj_args PlayRisky io_res_ty `thenDs` \ ccall_adj -> -- PlayRisky: the adjustor doesn't allocate in the Haskell heap or do a callback let ccall_adj_ty = exprType ccall_adj ccall_io_adj = mkLams [stbl_value] $ @@ -411,7 +440,6 @@ dsFExportDynamic id cconv ([arg_ty], io_res_ty) = tcSplitFunTys sans_foralls [res_ty] = tcTyConAppArgs io_res_ty -- Must use tcSplit* to see the (IO t), which is a newtype - export_ty = mkFunTy (mkTyConApp stablePtrTyCon [arg_ty]) arg_ty toCName :: Id -> String toCName i = showSDoc (pprCode CStyle (ppr (idName i))) @@ -434,9 +462,12 @@ mkFExportCBits :: FastString -> Type -> Bool -- True <=> returns an IO type -> CCallConv - -> (SDoc, SDoc, [Type]) + -> (SDoc, + SDoc, + [Type] -- the *primitive* argument types + ) mkFExportCBits c_nm maybe_target arg_htys res_hty is_IO_res_ty cc - = (header_bits, c_bits, all_arg_tys) + = (header_bits, c_bits, all_prim_arg_tys) where -- Create up types and names for the real args arg_cnames, arg_ctys :: [SDoc] @@ -458,11 +489,11 @@ mkFExportCBits c_nm maybe_target arg_htys res_hty is_IO_res_ty cc all_cnames_and_ctys = map fst extra_cnames_and_tys ++ zip arg_cnames arg_ctys - all_arg_tys - = map snd extra_cnames_and_tys ++ arg_htys + all_prim_arg_tys + = map snd extra_cnames_and_tys ++ map getPrimTyOf arg_htys -- stuff to do with the return type of the C function - res_hty_is_unit = res_hty `eqType` unitTy -- Look through any newtypes + res_hty_is_unit = res_hty `coreEqType` unitTy -- Look through any newtypes cResType | res_hty_is_unit = text "void" | otherwise = showStgType res_hty @@ -558,4 +589,18 @@ showFFIType t = getOccString (getName tc) tc = case tcSplitTyConApp_maybe (repType t) of Just (tc,_) -> tc Nothing -> pprPanic "showFFIType" (ppr t) + +-- This function returns the primitive type associated with the boxed +-- type argument to a foreign export (eg. Int ==> Int#). It assumes +-- that all the types we are interested in have a single constructor +-- with a single primitive-typed argument, which is true for all of the legal +-- foreign export argument types (see TcType.legalFEArgTyCon). +getPrimTyOf :: Type -> Type +getPrimTyOf ty = + case splitProductType_maybe (repType ty) of + Just (_, _, data_con, [prim_ty]) -> + ASSERT(dataConSourceArity data_con == 1) + ASSERT2(isUnLiftedType prim_ty, ppr prim_ty) + prim_ty + _other -> pprPanic "DsForeign.getPrimTyOf" (ppr ty) \end{code}