X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fcmm%2FCmmParse.y;h=5466e163687ecdb1ae2ce4b4cc6126a92be1533b;hb=1363de59b9b45f4997003d72c18a2f40aeb2031c;hp=50f2c8b08f77621d081d2253afc56c1dfc6c5de0;hpb=805692401866497554a48ce02619121bbdca87c6;p=ghc-hetmet.git diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 50f2c8b..5466e16 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -7,6 +7,13 @@ ----------------------------------------------------------------------------- { +{-# OPTIONS -w #-} +-- The above warning supression flag is a temporary kludge. +-- While working on this module you are encouraged to remove it and fix +-- any warnings in the module. See +-- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings +-- for details + module CmmParse ( parseCmmFile ) where import CgMonad @@ -47,10 +54,9 @@ import Constants import Outputable import Control.Monad +import Data.Array import Data.Char ( ord ) import System.Exit - -#include "HsVersions.h" } %token @@ -192,7 +198,9 @@ static :: { ExtFCode [CmmStatic] } | 'CLOSURE' '(' NAME lits ')' { do lits <- sequence $4; return $ map CmmStaticLit $ - mkStaticClosure (mkRtsInfoLabelFS $3) + mkStaticClosure (mkForeignLabel $3 Nothing True) + -- mkForeignLabel because these are only used + -- for CHARLIKE and INTLIKE closures in the RTS. dontCareCCS (map getLit lits) [] [] [] } -- arrays of closures required for the CHARLIKE & INTLIKE arrays @@ -202,7 +210,7 @@ lits :: { [ExtFCode CmmExpr] } cmmproc :: { ExtCode } -- TODO: add real SRT/info tables to parsed Cmm - : info maybe_formals maybe_gc_block maybe_frame '{' body '}' + : info maybe_formals_without_kinds maybe_gc_block maybe_frame '{' body '}' { do ((entry_ret_label, info, live, formals, gc_block, frame), stmts) <- getCgStmtsEC' $ loopDecls $ do { (entry_ret_label, info, live) <- $1; @@ -214,12 +222,12 @@ cmmproc :: { ExtCode } blks <- code (cgStmtsToBlocks stmts) code (emitInfoTableAndCode entry_ret_label (CmmInfo gc_block frame info) formals blks) } - | info maybe_formals ';' + | info maybe_formals_without_kinds ';' { do (entry_ret_label, info, live) <- $1; formals <- sequence $2; code (emitInfoTableAndCode entry_ret_label (CmmInfo Nothing Nothing info) formals []) } - | NAME maybe_formals maybe_gc_block maybe_frame '{' body '}' + | NAME maybe_formals_without_kinds maybe_gc_block maybe_frame '{' body '}' { do ((formals, gc_block, frame), stmts) <- getCgStmtsEC' $ loopDecls $ do { formals <- sequence $2; @@ -291,7 +299,7 @@ info :: { ExtFCode (CLabel, CmmInfoTable, [Maybe LocalReg]) } (ContInfo [] NoC_SRT), []) } - | 'INFO_TABLE_RET' '(' NAME ',' INT ',' formals0 ')' + | 'INFO_TABLE_RET' '(' NAME ',' INT ',' formals_without_kinds0 ')' -- closure type, live regs { do live <- sequence (map (liftM Just) $7) return (mkRtsRetLabelFS $3, @@ -306,7 +314,7 @@ body :: { ExtCode } decl :: { ExtCode } : type names ';' { mapM_ (newLocal defaultKind $1) $2 } - | STRING type names ';' {% do k <- parseKind $1; + | STRING type names ';' {% do k <- parseGCKind $1; return $ mapM_ (newLocal k $2) $3 } | 'import' names ';' { mapM_ newImport $2 } @@ -333,9 +341,9 @@ stmt :: { ExtCode } -- we tweak the syntax to avoid the conflict. The later -- option is taken here because the other way would require -- multiple levels of expanding and get unwieldy. - | maybe_results 'foreign' STRING expr '(' hint_exprs0 ')' safety vols opt_never_returns ';' + | maybe_results 'foreign' STRING expr '(' cmm_kind_exprs0 ')' safety vols opt_never_returns ';' {% foreignCall $3 $1 $4 $6 $9 $8 $10 } - | maybe_results 'prim' '%' NAME '(' hint_exprs0 ')' safety vols ';' + | maybe_results 'prim' '%' NAME '(' cmm_kind_exprs0 ')' safety vols ';' {% primCall $1 $4 $6 $9 $8 } -- stmt-level macros, stealing syntax from ordinary C-- function calls. -- Perhaps we ought to use the %%-form? @@ -449,23 +457,23 @@ maybe_ty :: { MachRep } : {- empty -} { wordRep } | '::' type { $2 } -maybe_actuals :: { [ExtFCode (CmmExpr, MachHint)] } +maybe_actuals :: { [ExtFCode CmmActual] } : {- empty -} { [] } - | '(' hint_exprs0 ')' { $2 } + | '(' cmm_kind_exprs0 ')' { $2 } -hint_exprs0 :: { [ExtFCode (CmmExpr, MachHint)] } +cmm_kind_exprs0 :: { [ExtFCode CmmActual] } : {- empty -} { [] } - | hint_exprs { $1 } + | cmm_kind_exprs { $1 } -hint_exprs :: { [ExtFCode (CmmExpr, MachHint)] } - : hint_expr { [$1] } - | hint_expr ',' hint_exprs { $1 : $3 } +cmm_kind_exprs :: { [ExtFCode CmmActual] } + : cmm_kind_expr { [$1] } + | cmm_kind_expr ',' cmm_kind_exprs { $1 : $3 } -hint_expr :: { ExtFCode (CmmExpr, MachHint) } - : expr { do e <- $1; return (e, inferHint e) } - | expr STRING {% do h <- parseHint $2; +cmm_kind_expr :: { ExtFCode CmmActual } + : expr { do e <- $1; return (CmmHinted e (inferCmmKind e)) } + | expr STRING {% do h <- parseCmmKind $2; return $ do - e <- $1; return (e,h) } + e <- $1; return (CmmHinted e h) } exprs0 :: { [ExtFCode CmmExpr] } : {- empty -} { [] } @@ -479,20 +487,20 @@ reg :: { ExtFCode CmmExpr } : NAME { lookupName $1 } | GLOBALREG { return (CmmReg (CmmGlobal $1)) } -maybe_results :: { [ExtFCode (CmmFormal, MachHint)] } +maybe_results :: { [ExtFCode CmmFormal] } : {- empty -} { [] } - | '(' hint_lregs ')' '=' { $2 } + | '(' cmm_formals ')' '=' { $2 } -hint_lregs :: { [ExtFCode (CmmFormal, MachHint)] } - : hint_lreg { [$1] } - | hint_lreg ',' { [$1] } - | hint_lreg ',' hint_lregs { $1 : $3 } +cmm_formals :: { [ExtFCode CmmFormal] } + : cmm_formal { [$1] } + | cmm_formal ',' { [$1] } + | cmm_formal ',' cmm_formals { $1 : $3 } -hint_lreg :: { ExtFCode (CmmFormal, MachHint) } - : local_lreg { do e <- $1; return (e, inferHint (CmmReg (CmmLocal e))) } - | STRING local_lreg {% do h <- parseHint $1; +cmm_formal :: { ExtFCode CmmFormal } + : local_lreg { do e <- $1; return (CmmHinted e (inferCmmKind (CmmReg (CmmLocal e)))) } + | STRING local_lreg {% do h <- parseCmmKind $1; return $ do - e <- $2; return (e,h) } + e <- $2; return (CmmHinted e h) } local_lreg :: { ExtFCode LocalReg } : NAME { do e <- lookupName $1; @@ -509,22 +517,22 @@ lreg :: { ExtFCode CmmReg } other -> pprPanic "CmmParse:" (ftext $1 <> text " not a register") } | GLOBALREG { return (CmmGlobal $1) } -maybe_formals :: { [ExtFCode LocalReg] } +maybe_formals_without_kinds :: { [ExtFCode LocalReg] } : {- empty -} { [] } - | '(' formals0 ')' { $2 } + | '(' formals_without_kinds0 ')' { $2 } -formals0 :: { [ExtFCode LocalReg] } +formals_without_kinds0 :: { [ExtFCode LocalReg] } : {- empty -} { [] } - | formals { $1 } + | formals_without_kinds { $1 } -formals :: { [ExtFCode LocalReg] } - : formal ',' { [$1] } - | formal { [$1] } - | formal ',' formals { $1 : $3 } +formals_without_kinds :: { [ExtFCode LocalReg] } + : formal_without_kind ',' { [$1] } + | formal_without_kind { [$1] } + | formal_without_kind ',' formals_without_kinds { $1 : $3 } -formal :: { ExtFCode LocalReg } +formal_without_kind :: { ExtFCode LocalReg } : type NAME { newLocal defaultKind $1 $2 } - | STRING type NAME {% do k <- parseKind $1; + | STRING type NAME {% do k <- parseGCKind $1; return $ newLocal k $2 $3 } maybe_frame :: { ExtFCode (Maybe UpdateFrame) } @@ -592,16 +600,16 @@ exprOp name args_code = exprMacros :: UniqFM ([CmmExpr] -> CmmExpr) exprMacros = listToUFM [ - ( FSLIT("ENTRY_CODE"), \ [x] -> entryCode x ), - ( FSLIT("INFO_PTR"), \ [x] -> closureInfoPtr x ), - ( FSLIT("STD_INFO"), \ [x] -> infoTable x ), - ( FSLIT("FUN_INFO"), \ [x] -> funInfoTable x ), - ( FSLIT("GET_ENTRY"), \ [x] -> entryCode (closureInfoPtr x) ), - ( FSLIT("GET_STD_INFO"), \ [x] -> infoTable (closureInfoPtr x) ), - ( FSLIT("GET_FUN_INFO"), \ [x] -> funInfoTable (closureInfoPtr x) ), - ( FSLIT("INFO_TYPE"), \ [x] -> infoTableClosureType x ), - ( FSLIT("INFO_PTRS"), \ [x] -> infoTablePtrs x ), - ( FSLIT("INFO_NPTRS"), \ [x] -> infoTableNonPtrs x ) + ( fsLit "ENTRY_CODE", \ [x] -> entryCode x ), + ( fsLit "INFO_PTR", \ [x] -> closureInfoPtr x ), + ( fsLit "STD_INFO", \ [x] -> infoTable x ), + ( fsLit "FUN_INFO", \ [x] -> funInfoTable x ), + ( fsLit "GET_ENTRY", \ [x] -> entryCode (closureInfoPtr x) ), + ( fsLit "GET_STD_INFO", \ [x] -> infoTable (closureInfoPtr x) ), + ( fsLit "GET_FUN_INFO", \ [x] -> funInfoTable (closureInfoPtr x) ), + ( fsLit "INFO_TYPE", \ [x] -> infoTableClosureType x ), + ( fsLit "INFO_PTRS", \ [x] -> infoTablePtrs x ), + ( fsLit "INFO_NPTRS", \ [x] -> infoTableNonPtrs x ) ] -- we understand a subset of C-- primitives: @@ -675,24 +683,24 @@ parseSafety "safe" = return (CmmSafe NoC_SRT) parseSafety "unsafe" = return CmmUnsafe parseSafety str = fail ("unrecognised safety: " ++ str) -parseHint :: String -> P MachHint -parseHint "ptr" = return PtrHint -parseHint "signed" = return SignedHint -parseHint "float" = return FloatHint -parseHint str = fail ("unrecognised hint: " ++ str) +parseCmmKind :: String -> P CmmKind +parseCmmKind "ptr" = return PtrHint +parseCmmKind "signed" = return SignedHint +parseCmmKind "float" = return FloatHint +parseCmmKind str = fail ("unrecognised hint: " ++ str) -parseKind :: String -> P Kind -parseKind "ptr" = return KindPtr -parseKind str = fail ("unrecognized kin: " ++ str) +parseGCKind :: String -> P GCKind +parseGCKind "ptr" = return GCKindPtr +parseGCKind str = fail ("unrecognized kin: " ++ str) -defaultKind :: Kind -defaultKind = KindNonPtr +defaultKind :: GCKind +defaultKind = GCKindNonPtr -- labels are always pointers, so we might as well infer the hint -inferHint :: CmmExpr -> MachHint -inferHint (CmmLit (CmmLabel _)) = PtrHint -inferHint (CmmReg (CmmGlobal g)) | isPtrGlobalReg g = PtrHint -inferHint _ = NoHint +inferCmmKind :: CmmExpr -> CmmKind +inferCmmKind (CmmLit (CmmLabel _)) = PtrHint +inferCmmKind (CmmReg (CmmGlobal g)) | isPtrGlobalReg g = PtrHint +inferCmmKind _ = NoHint isPtrGlobalReg Sp = True isPtrGlobalReg SpLim = True @@ -718,43 +726,44 @@ stmtMacro fun args_code = do stmtMacros :: UniqFM ([CmmExpr] -> Code) stmtMacros = listToUFM [ - ( FSLIT("CCS_ALLOC"), \[words,ccs] -> profAlloc words ccs ), - ( FSLIT("CLOSE_NURSERY"), \[] -> emitCloseNursery ), - ( FSLIT("ENTER_CCS_PAP_CL"), \[e] -> enterCostCentrePAP e ), - ( FSLIT("ENTER_CCS_THUNK"), \[e] -> enterCostCentreThunk e ), - ( FSLIT("HP_CHK_GEN"), \[words,liveness,reentry] -> + ( fsLit "CCS_ALLOC", \[words,ccs] -> profAlloc words ccs ), + ( fsLit "CLOSE_NURSERY", \[] -> emitCloseNursery ), + ( fsLit "ENTER_CCS_PAP_CL", \[e] -> enterCostCentrePAP e ), + ( fsLit "ENTER_CCS_THUNK", \[e] -> enterCostCentreThunk e ), + ( fsLit "HP_CHK_GEN", \[words,liveness,reentry] -> hpChkGen words liveness reentry ), - ( FSLIT("HP_CHK_NP_ASSIGN_SP0"), \[e,f] -> hpChkNodePointsAssignSp0 e f ), - ( FSLIT("LOAD_THREAD_STATE"), \[] -> emitLoadThreadState ), - ( FSLIT("LDV_ENTER"), \[e] -> ldvEnter e ), - ( FSLIT("LDV_RECORD_CREATE"), \[e] -> ldvRecordCreate e ), - ( FSLIT("OPEN_NURSERY"), \[] -> emitOpenNursery ), - ( FSLIT("PUSH_UPD_FRAME"), \[sp,e] -> emitPushUpdateFrame sp e ), - ( FSLIT("SAVE_THREAD_STATE"), \[] -> emitSaveThreadState ), - ( FSLIT("SET_HDR"), \[ptr,info,ccs] -> + ( fsLit "HP_CHK_NP_ASSIGN_SP0", \[e,f] -> hpChkNodePointsAssignSp0 e f ), + ( fsLit "LOAD_THREAD_STATE", \[] -> emitLoadThreadState ), + ( fsLit "LDV_ENTER", \[e] -> ldvEnter e ), + ( fsLit "LDV_RECORD_CREATE", \[e] -> ldvRecordCreate e ), + ( fsLit "OPEN_NURSERY", \[] -> emitOpenNursery ), + ( fsLit "PUSH_UPD_FRAME", \[sp,e] -> emitPushUpdateFrame sp e ), + ( fsLit "SAVE_THREAD_STATE", \[] -> emitSaveThreadState ), + ( fsLit "SET_HDR", \[ptr,info,ccs] -> emitSetDynHdr ptr info ccs ), - ( FSLIT("STK_CHK_GEN"), \[words,liveness,reentry] -> + ( fsLit "STK_CHK_GEN", \[words,liveness,reentry] -> stkChkGen words liveness reentry ), - ( FSLIT("STK_CHK_NP"), \[e] -> stkChkNodePoints e ), - ( FSLIT("TICK_ALLOC_PRIM"), \[hdr,goods,slop] -> + ( fsLit "STK_CHK_NP", \[e] -> stkChkNodePoints e ), + ( fsLit "TICK_ALLOC_PRIM", \[hdr,goods,slop] -> tickyAllocPrim hdr goods slop ), - ( FSLIT("TICK_ALLOC_PAP"), \[goods,slop] -> + ( fsLit "TICK_ALLOC_PAP", \[goods,slop] -> tickyAllocPAP goods slop ), - ( FSLIT("TICK_ALLOC_UP_THK"), \[goods,slop] -> + ( fsLit "TICK_ALLOC_UP_THK", \[goods,slop] -> tickyAllocThunk goods slop ), - ( FSLIT("UPD_BH_UPDATABLE"), \[] -> emitBlackHoleCode False ), - ( FSLIT("UPD_BH_SINGLE_ENTRY"), \[] -> emitBlackHoleCode True ), - - ( FSLIT("RET_P"), \[a] -> emitRetUT [(PtrArg,a)]), - ( FSLIT("RET_N"), \[a] -> emitRetUT [(NonPtrArg,a)]), - ( FSLIT("RET_PP"), \[a,b] -> emitRetUT [(PtrArg,a),(PtrArg,b)]), - ( FSLIT("RET_NN"), \[a,b] -> emitRetUT [(NonPtrArg,a),(NonPtrArg,b)]), - ( FSLIT("RET_NP"), \[a,b] -> emitRetUT [(NonPtrArg,a),(PtrArg,b)]), - ( FSLIT("RET_PPP"), \[a,b,c] -> emitRetUT [(PtrArg,a),(PtrArg,b),(PtrArg,c)]), - ( FSLIT("RET_NPP"), \[a,b,c] -> emitRetUT [(NonPtrArg,a),(PtrArg,b),(PtrArg,c)]), - ( FSLIT("RET_NNP"), \[a,b,c] -> emitRetUT [(NonPtrArg,a),(NonPtrArg,b),(PtrArg,c)]), - ( FSLIT("RET_NNNP"), \[a,b,c,d] -> emitRetUT [(NonPtrArg,a),(NonPtrArg,b),(NonPtrArg,c),(PtrArg,d)]), - ( FSLIT("RET_NPNP"), \[a,b,c,d] -> emitRetUT [(NonPtrArg,a),(PtrArg,b),(NonPtrArg,c),(PtrArg,d)]) + ( fsLit "UPD_BH_UPDATABLE", \[] -> emitBlackHoleCode False ), + ( fsLit "UPD_BH_SINGLE_ENTRY", \[] -> emitBlackHoleCode True ), + + ( fsLit "RET_P", \[a] -> emitRetUT [(PtrArg,a)]), + ( fsLit "RET_N", \[a] -> emitRetUT [(NonPtrArg,a)]), + ( fsLit "RET_PP", \[a,b] -> emitRetUT [(PtrArg,a),(PtrArg,b)]), + ( fsLit "RET_NN", \[a,b] -> emitRetUT [(NonPtrArg,a),(NonPtrArg,b)]), + ( fsLit "RET_NP", \[a,b] -> emitRetUT [(NonPtrArg,a),(PtrArg,b)]), + ( fsLit "RET_PPP", \[a,b,c] -> emitRetUT [(PtrArg,a),(PtrArg,b),(PtrArg,c)]), + ( fsLit "RET_NPP", \[a,b,c] -> emitRetUT [(NonPtrArg,a),(PtrArg,b),(PtrArg,c)]), + ( fsLit "RET_NNP", \[a,b,c] -> emitRetUT [(NonPtrArg,a),(NonPtrArg,b),(PtrArg,c)]), + ( fsLit "RET_NNN", \[a,b,c] -> emitRetUT [(NonPtrArg,a),(NonPtrArg,b),(NonPtrArg,c)]), + ( fsLit "RET_NNNP", \[a,b,c,d] -> emitRetUT [(NonPtrArg,a),(NonPtrArg,b),(NonPtrArg,c),(PtrArg,d)]), + ( fsLit "RET_NPNP", \[a,b,c,d] -> emitRetUT [(NonPtrArg,a),(PtrArg,b),(NonPtrArg,c),(PtrArg,d)]) ] @@ -805,7 +814,7 @@ addVarDecl var expr = EC $ \e s -> return ((var, Var expr):s, ()) addLabel :: FastString -> BlockId -> ExtCode addLabel name block_id = EC $ \e s -> return ((name, Label block_id):s, ()) -newLocal :: Kind -> MachRep -> FastString -> ExtFCode LocalReg +newLocal :: GCKind -> MachRep -> FastString -> ExtFCode LocalReg newLocal kind ty name = do u <- code newUnique let reg = LocalReg u ty kind @@ -816,8 +825,8 @@ newLocal kind ty name = do -- classifies these labels as dynamic, hence the code generator emits the -- PIC code for them. newImport :: FastString -> ExtFCode () -newImport name = - addVarDecl name (CmmLit (CmmLabel (mkForeignLabel name Nothing True))) +newImport name + = addVarDecl name (CmmLit (CmmLabel (mkForeignLabel name Nothing True))) newLabel :: FastString -> ExtFCode BlockId newLabel name = do @@ -881,9 +890,9 @@ staticClosure cl_label info payload foreignCall :: String - -> [ExtFCode (CmmFormal,MachHint)] + -> [ExtFCode CmmFormal] -> ExtFCode CmmExpr - -> [ExtFCode (CmmExpr,MachHint)] + -> [ExtFCode CmmActual] -> Maybe [GlobalReg] -> CmmSafety -> CmmReturnInfo @@ -891,6 +900,7 @@ foreignCall foreignCall conv_string results_code expr_code args_code vols safety ret = do convention <- case conv_string of "C" -> return CCallConv + "stdcall" -> return StdCallConv "C--" -> return CmmCallConv _ -> fail ("unknown calling convention: " ++ conv_string) return $ do @@ -901,19 +911,33 @@ foreignCall conv_string results_code expr_code args_code vols safety ret case convention of -- Temporary hack so at least some functions are CmmSafe CmmCallConv -> code (stmtC (CmmCall (CmmCallee expr convention) results args safety ret)) - _ -> case safety of + _ -> + let expr' = adjCallTarget convention expr args in + case safety of CmmUnsafe -> code (emitForeignCall' PlayRisky results - (CmmCallee expr convention) args vols NoC_SRT ret) + (CmmCallee expr' convention) args vols NoC_SRT ret) CmmSafe srt -> code (emitForeignCall' (PlaySafe unused) results - (CmmCallee expr convention) args vols NoC_SRT ret) where + (CmmCallee expr' convention) args vols NoC_SRT ret) where unused = panic "not used by emitForeignCall'" +adjCallTarget :: CCallConv -> CmmExpr -> [CmmHinted CmmExpr] -> CmmExpr +#ifdef mingw32_TARGET_OS +-- On Windows, we have to add the '@N' suffix to the label when making +-- a call with the stdcall calling convention. +adjCallTarget StdCallConv (CmmLit (CmmLabel lbl)) args + = CmmLit (CmmLabel (addLabelSize lbl (sum (map size args)))) + where size (CmmHinted e _) = max wORD_SIZE (machRepByteWidth (cmmExprRep e)) + -- c.f. CgForeignCall.emitForeignCall +#endif +adjCallTarget _ expr _ + = expr + primCall - :: [ExtFCode (CmmFormal,MachHint)] + :: [ExtFCode CmmFormal] -> FastString - -> [ExtFCode (CmmExpr,MachHint)] + -> [ExtFCode CmmActual] -> Maybe [GlobalReg] -> CmmSafety -> P ExtCode @@ -1058,9 +1082,9 @@ doSwitch mb_range scrut arms deflt -- knows about here. initEnv :: Env initEnv = listToUFM [ - ( FSLIT("SIZEOF_StgHeader"), + ( fsLit "SIZEOF_StgHeader", Var (CmmLit (CmmInt (fromIntegral (fixedHdrSize * wORD_SIZE)) wordRep) )), - ( FSLIT("SIZEOF_StgInfoTable"), + ( fsLit "SIZEOF_StgInfoTable", Var (CmmLit (CmmInt (fromIntegral stdInfoTableSizeB) wordRep) )) ] @@ -1080,7 +1104,7 @@ parseCmmFile dflags filename = do let ms = getMessages pst printErrorsAndWarnings dflags ms when (errorsFound dflags ms) $ exitWith (ExitFailure 1) - dumpIfSet_dyn dflags Opt_D_dump_cmm "Cmm" (pprCmms [cmm]) + dumpIfSet_dyn dflags Opt_D_dump_cmm "Cmm" (ppr cmm) return (Just cmm) where no_module = panic "parseCmmFile: no module"