X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2FdeSugar%2FDsForeign.lhs;h=5d47921c7e78b02a1be756c02f630901a14c89ac;hb=80965661715b664b4926fc525d0c89306b92e832;hp=52956a09fff45264bc2f6f7b9782e0f339f0e290;hpb=0065d5ab628975892cea1ec7303f968c3338cbe1;p=ghc-hetmet.git diff --git a/compiler/deSugar/DsForeign.lhs b/compiler/deSugar/DsForeign.lhs index 52956a0..5d47921 100644 --- a/compiler/deSugar/DsForeign.lhs +++ b/compiler/deSugar/DsForeign.lhs @@ -28,25 +28,26 @@ import SMRep ( argMachRep, typeCgRep ) import CoreUtils ( exprType, mkInlineMe ) import Id ( Id, idType, idName, mkSysLocal, setInlinePragma ) import Literal ( Literal(..), mkStringLit ) -import Module ( moduleFS ) +import Module ( moduleNameFS, moduleName ) import Name ( getOccString, NamedThing(..) ) import Type ( repType, coreEqType ) import TcType ( Type, mkFunTys, mkForAllTys, mkTyConApp, - mkFunTy, tcSplitTyConApp_maybe, + mkFunTy, tcSplitTyConApp_maybe, tcSplitIOType_maybe, tcSplitForAllTys, tcSplitFunTys, tcTyConAppArgs, + isBoolTy ) import BasicTypes ( Boxity(..) ) import HscTypes ( ForeignStubs(..) ) import ForeignCall ( ForeignCall(..), CCallSpec(..), - Safety(..), playSafe, + Safety(..), CExportSpec(..), CLabelString, CCallConv(..), ccallConvToInt, ccallConvAttribute ) import TysWiredIn ( unitTy, tupleTyCon ) -import TysPrim ( addrPrimTy, mkStablePtrPrimTy, alphaTy ) -import PrelNames ( hasKey, ioTyConKey, stablePtrTyConName, newStablePtrName, bindIOName, +import TysPrim ( addrPrimTy, mkStablePtrPrimTy, alphaTy, intPrimTy ) +import PrelNames ( stablePtrTyConName, newStablePtrName, bindIOName, checkDotnetResName ) import BasicTypes ( Activation( NeverActive ) ) import SrcLoc ( Located(..), unLoc ) @@ -82,10 +83,9 @@ dsForeigns fos combine stubs (L loc decl) = putSrcSpanDs loc (combine1 stubs decl) combine1 (ForeignStubs acc_h acc_c acc_hdrs acc_feb, acc_f) - (ForeignImport id _ spec depr) + (ForeignImport id _ spec) = traceIf (text "fi start" <+> ppr id) `thenDs` \ _ -> dsFImport (unLoc id) spec `thenDs` \ (bs, h, c, mbhd) -> - warnDepr depr `thenDs` \ _ -> traceIf (text "fi end" <+> ppr id) `thenDs` \ _ -> returnDs (ForeignStubs (h $$ acc_h) (c $$ acc_c) @@ -94,10 +94,9 @@ dsForeigns fos bs ++ acc_f) combine1 (ForeignStubs acc_h acc_c acc_hdrs acc_feb, acc_f) - (ForeignExport (L _ id) _ (CExport (CExportStatic ext_nm cconv)) depr) + (ForeignExport (L _ id) _ (CExport (CExportStatic ext_nm cconv))) = dsFExport id (idType id) ext_nm cconv False `thenDs` \(h, c, _, _) -> - warnDepr depr `thenDs` \_ -> returnDs (ForeignStubs (h $$ acc_h) (c $$ acc_c) acc_hdrs (id:acc_feb), acc_f) @@ -105,11 +104,6 @@ dsForeigns fos addH (Just e) ls | e `elem` ls = ls | otherwise = e:ls - - warnDepr False = returnDs () - warnDepr True = dsWarn msg - where - msg = ptext SLIT("foreign declaration uses deprecated non-standard syntax") \end{code} @@ -253,9 +247,6 @@ dsFCall fn_id fcall no_hdrs wrap_rhs = mkInlineMe (mkLams (tvs ++ args) wrapper_body) in returnDs ([(work_id, work_rhs), (fn_id, wrap_rhs)], empty, empty) - -unsafe_call (CCall (CCallSpec _ _ safety)) = playSafe safety -unsafe_call (DNCall _) = False \end{code} @@ -304,19 +295,12 @@ dsFExport fn_id ty ext_name cconv isDyn -- Look at the result type of the exported function, orig_res_ty -- If it's IO t, return (t, True) -- If it's plain t, return (t, False) - (case tcSplitTyConApp_maybe orig_res_ty of - -- We must use tcSplit here so that we see the (IO t) in - -- the type. [IO t is transparent to plain splitTyConApp.] - - Just (ioTyCon, [res_ty]) - -> ASSERT( ioTyCon `hasKey` ioTyConKey ) - -- The function already returns IO t - returnDs (res_ty, True) - - other -> -- The function returns t - returnDs (orig_res_ty, False) - ) - `thenDs` \ (res_ty, -- t + (case tcSplitIOType_maybe orig_res_ty of + Just (ioTyCon, res_ty) -> returnDs (res_ty, True) + -- The function already returns IO t + Nothing -> returnDs (orig_res_ty, False) + -- The function returns t + ) `thenDs` \ (res_ty, -- t is_IO_res_ty) -> -- Bool returnDs $ mkFExportCBits ext_name @@ -324,26 +308,34 @@ dsFExport fn_id ty ext_name cconv isDyn fe_arg_tys res_ty is_IO_res_ty cconv \end{code} -@foreign export dynamic@ lets you dress up Haskell IO actions -of some fixed type behind an externally callable interface (i.e., -as a C function pointer). Useful for callbacks and stuff. +@foreign import "wrapper"@ (previously "foreign export dynamic") lets +you dress up Haskell IO actions of some fixed type behind an +externally callable interface (i.e., as a C function pointer). Useful +for callbacks and stuff. \begin{verbatim} -foreign export dynamic f :: (Addr -> Int -> IO Int) -> IO Addr +type Fun = Bool -> Int -> IO Int +foreign import "wrapper" f :: Fun -> IO (FunPtr Fun) -- Haskell-visible constructor, which is generated from the above: -- SUP: No check for NULL from createAdjustor anymore??? -f :: (Addr -> Int -> IO Int) -> IO Addr +f :: Fun -> IO (FunPtr Fun) f cback = bindIO (newStablePtr cback) (\StablePtr sp# -> IO (\s1# -> case _ccall_ createAdjustor cconv sp# ``f_helper'' s1# of (# s2#, a# #) -> (# s2#, A# a# #))) -foreign export "f_helper" f_helper :: StablePtr (Addr -> Int -> IO Int) -> Addr -> Int -> IO Int --- `special' foreign export that invokes the closure pointed to by the --- first argument. +foreign import "&f_helper" f_helper :: FunPtr (StablePtr Fun -> Fun) + +-- and the helper in C: + +f_helper(StablePtr s, HsBool b, HsInt i) +{ + rts_evalIO(rts_apply(rts_apply(deRefStablePtr(s), + rts_mkBool(b)), rts_mkInt(i))); +} \end{verbatim} \begin{code} @@ -352,10 +344,10 @@ dsFExportDynamic :: Id -> DsM ([Binding], SDoc, SDoc) dsFExportDynamic id cconv = newSysLocalDs ty `thenDs` \ fe_id -> - getModuleDs `thenDs` \ mod_name -> + getModuleDs `thenDs` \ mod -> let -- hack: need to get at the name of the C stub we're about to generate. - fe_nm = mkFastString (unpackFS (zEncodeFS (moduleFS mod_name)) ++ "_" ++ toCName fe_id) + fe_nm = mkFastString (unpackFS (zEncodeFS (moduleNameFS (moduleName mod))) ++ "_" ++ toCName fe_id) in newSysLocalDs arg_ty `thenDs` \ cback -> dsLookupGlobalId newStablePtrName `thenDs` \ newStablePtrId -> @@ -631,16 +623,19 @@ ret_addr_arg = (text "original_return_addr", text "void*", undefined, typeMachRep addrPrimTy) -- 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). +-- type argument to a foreign export (eg. Int ==> Int#). getPrimTyOf :: Type -> Type -getPrimTyOf ty = - case splitProductType_maybe (repType ty) of +getPrimTyOf ty + | isBoolTy rep_ty = intPrimTy + -- Except for Bool, the types we are interested in have a single constructor + -- with a single primitive-typed argument (see TcType.legalFEArgTyCon). + | otherwise = + case splitProductType_maybe rep_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) + where + rep_ty = repType ty \end{code}