X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2FdeSugar%2FDsForeign.lhs;h=10e072e0d3ec28c2ef2fdd53afc88acf0ac456c2;hb=a8427a4125e9b78e88a487eeabf018f1c6e8bc08;hp=46fc0747a2742feeea33ea4dcfe13441045db691;hpb=61d2625ae2e6a4cdae2ffc92df828905e81c24cc;p=ghc-hetmet.git diff --git a/compiler/deSugar/DsForeign.lhs b/compiler/deSugar/DsForeign.lhs index 46fc074..10e072e 100644 --- a/compiler/deSugar/DsForeign.lhs +++ b/compiler/deSugar/DsForeign.lhs @@ -1,9 +1,9 @@ % +% (c) The University of Glasgow 2006 % (c) The AQUA Project, Glasgow University, 1998 % -\section[DsCCall]{Desugaring \tr{foreign} declarations} -Expanding out @foreign import@ and @foreign export@ declarations. +Desugaring foreign declarations (see also DsCCall). \begin{code} module DsForeign ( dsForeigns ) where @@ -13,47 +13,33 @@ import TcRnMonad -- temp import CoreSyn -import DsCCall ( dsCCall, mkFCall, boxResult, unboxArg, resultWrapper ) +import DsCCall import DsMonad -import HsSyn ( ForeignDecl(..), ForeignExport(..), LForeignDecl, - ForeignImport(..), CImportSpec(..) ) -import DataCon ( splitProductType_maybe ) -#ifdef DEBUG -import DataCon ( dataConSourceArity ) -import Type ( isUnLiftedType ) -#endif -import MachOp ( machRepByteWidth, MachRep(..) ) -import SMRep ( argMachRep, typeCgRep ) -import CoreUtils ( exprType, mkInlineMe ) -import Id ( Id, idType, idName, mkSysLocal, setInlinePragma ) -import Literal ( Literal(..), mkStringLit ) -import Module ( moduleNameFS, moduleName ) -import Name ( getOccString, NamedThing(..) ) -import Type ( repType, coreEqType ) -import TcType ( Type, mkFunTys, mkForAllTys, mkTyConApp, - mkFunTy, tcSplitTyConApp_maybe, tcSplitIOType_maybe, - tcSplitForAllTys, tcSplitFunTys, tcTyConAppArgs, - isBoolTy - ) - -import BasicTypes ( Boxity(..) ) -import HscTypes ( ForeignStubs(..) ) -import ForeignCall ( ForeignCall(..), CCallSpec(..), - Safety(..), - CExportSpec(..), CLabelString, - CCallConv(..), ccallConvToInt, - ccallConvAttribute - ) -import TysWiredIn ( unitTy, tupleTyCon ) -import TysPrim ( addrPrimTy, mkStablePtrPrimTy, alphaTy, intPrimTy ) -import PrelNames ( stablePtrTyConName, newStablePtrName, bindIOName, - checkDotnetResName ) -import BasicTypes ( Activation( NeverActive ) ) -import SrcLoc ( Located(..), unLoc ) +import HsSyn +import DataCon +import MachOp +import SMRep +import CoreUtils +import Id +import Literal +import Module +import Name +import Type +import Coercion +import TcType + +import HscTypes +import ForeignCall +import TysWiredIn +import TysPrim +import PrelNames +import BasicTypes +import SrcLoc import Outputable -import Maybe ( fromJust, isNothing ) import FastString + +import Data.Maybe \end{code} Desugaring of @foreign@ declarations is naturally split up into @@ -83,10 +69,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) @@ -95,10 +80,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) @@ -106,11 +90,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} @@ -303,8 +282,9 @@ dsFExport fn_id ty ext_name cconv isDyn -- If it's IO t, return (t, True) -- If it's plain t, return (t, False) (case tcSplitIOType_maybe orig_res_ty of - Just (ioTyCon, res_ty) -> returnDs (res_ty, True) + Just (ioTyCon, res_ty, co) -> returnDs (res_ty, True) -- The function already returns IO t + -- ToDo: what about the coercion? Nothing -> returnDs (orig_res_ty, False) -- The function returns t ) `thenDs` \ (res_ty, -- t @@ -331,7 +311,7 @@ f :: Fun -> IO (FunPtr Fun) f cback = bindIO (newStablePtr cback) (\StablePtr sp# -> IO (\s1# -> - case _ccall_ createAdjustor cconv sp# ``f_helper'' s1# of + case _ccall_ createAdjustor cconv sp# ``f_helper'' s1# of (# s2#, a# #) -> (# s2#, A# a# #))) foreign import "&f_helper" f_helper :: FunPtr (StablePtr Fun -> Fun) @@ -360,7 +340,6 @@ dsFExportDynamic id cconv dsLookupGlobalId newStablePtrName `thenDs` \ newStablePtrId -> dsLookupTyCon stablePtrTyConName `thenDs` \ stable_ptr_tycon -> let - 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 @@ -369,12 +348,6 @@ dsFExportDynamic id cconv dsFExport id export_ty fe_nm cconv True `thenDs` \ (h_code, c_code, arg_reps, args_size) -> let - 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 @@ -405,15 +378,19 @@ dsFExportDynamic id cconv _ -> Nothing in - dsCCall adjustor adj_args PlayRisky io_res_ty `thenDs` \ ccall_adj -> + dsCCall adjustor adj_args PlayRisky (mkTyConApp io_tc [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] $ - Note (Coerce io_res_ty ccall_adj_ty) - ccall_adj - io_app = mkLams tvs $ - mkLams [cback] $ - stbl_app ccall_io_adj res_ty + + let io_app = mkLams tvs $ + Lam cback $ + mkCoerceI (mkSymCoI co) $ + mkApps (Var bindIOId) + [ Type stable_ptr_ty + , Type res_ty + , mkApps (Var newStablePtrId) [ Type arg_ty, Var cback ] + , Lam stbl_value ccall_adj + ] + fed = (id `setInlinePragma` NeverActive, io_app) -- Never inline the f.e.d. function, because the litlit -- might not be in scope in other modules. @@ -421,11 +398,12 @@ dsFExportDynamic id cconv returnDs ([fed], h_code, c_code) where - ty = idType id - (tvs,sans_foralls) = tcSplitForAllTys ty - ([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 + ty = idType id + (tvs,sans_foralls) = tcSplitForAllTys ty + ([arg_ty], fn_res_ty) = tcSplitFunTys sans_foralls + Just (io_tc, res_ty, co) = tcSplitIOType_maybe fn_res_ty + -- Must have an IO type; hence Just + -- co : fn_res_ty ~ IO res_ty toCName :: Id -> String toCName i = showSDoc (pprCode CStyle (ppr (idName i))) @@ -466,7 +444,7 @@ mkFExportCBits c_nm maybe_target arg_htys res_hty is_IO_res_ty cc MachRep)] -- the MachRep arg_info = [ (text ('a':show n), showStgType ty, ty, typeMachRep (getPrimTyOf ty)) - | (ty,n) <- zip arg_htys [1..] ] + | (ty,n) <- zip arg_htys [1::Int ..] ] -- add some auxiliary args; the stable ptr in the wrapper case, and -- a slot for the dummy return address in the wrapper + ccall case