X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fcmm%2FCmmParse.y;h=27fce3bf88156eb8aef4a706efd55aa89a168f5e;hb=0e08f4df740ea2f48225069bd862d47748d5cde6;hp=840b564a837fb13627802d33eb5b6691856c232d;hpb=d31dfb32ea936c22628b508c28a36c12e631430a;p=ghc-hetmet.git diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 840b564..27fce3b 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -201,30 +201,37 @@ lits :: { [ExtFCode CmmExpr] } cmmproc :: { ExtCode } -- TODO: add real SRT/info tables to parsed Cmm : info maybe_formals '{' body '}' - { do (info_lbl, info) <- $1; - formals <- sequence $2; - stmts <- getCgStmtsEC (loopDecls $4) + { do ((info_lbl, info, live, formals), stmts) <- + getCgStmtsEC' $ loopDecls $ do { + (info_lbl, info, live) <- $1; + formals <- sequence $2; + $4; + return (info_lbl, info, live, formals) } blks <- code (cgStmtsToBlocks stmts) code (emitInfoTableAndCode info_lbl info formals blks) } | info maybe_formals ';' - { do (info_lbl, info) <- $1; + { do (info_lbl, info, live) <- $1; formals <- sequence $2; code (emitInfoTableAndCode info_lbl info formals []) } | NAME maybe_formals '{' body '}' - { do formals <- sequence $2; - stmts <- getCgStmtsEC (loopDecls $4); - blks <- code (cgStmtsToBlocks stmts); + { do (formals, stmts) <- + getCgStmtsEC' $ loopDecls $ do { + formals <- sequence $2; + $4; + return formals } + blks <- code (cgStmtsToBlocks stmts) code (emitProc (CmmNonInfo Nothing) (mkRtsCodeLabelFS $1) formals blks) } -info :: { ExtFCode (CLabel, CmmInfo) } +info :: { ExtFCode (CLabel, CmmInfo, [Maybe LocalReg]) } : 'INFO_TABLE' '(' NAME ',' INT ',' INT ',' INT ',' STRING ',' STRING ')' -- ptrs, nptrs, closure type, description, type { do prof <- profilingInfo $11 $13 return (mkRtsInfoLabelFS $3, CmmInfo prof Nothing (fromIntegral $9) - (ThunkInfo (fromIntegral $5, fromIntegral $7) NoC_SRT)) } + (ThunkInfo (fromIntegral $5, fromIntegral $7) NoC_SRT), + []) } | 'INFO_TABLE_FUN' '(' NAME ',' INT ',' INT ',' INT ',' STRING ',' STRING ',' INT ')' -- ptrs, nptrs, closure type, description, type, fun type @@ -233,7 +240,8 @@ info :: { ExtFCode (CLabel, CmmInfo) } CmmInfo prof Nothing (fromIntegral $9) (FunInfo (fromIntegral $5, fromIntegral $7) NoC_SRT (fromIntegral $15) 0 (ArgSpec 0) - zeroCLit)) } + zeroCLit), + []) } -- we leave most of the fields zero here. This is only used -- to generate the BCO info table in the RTS at the moment. @@ -245,27 +253,31 @@ info :: { ExtFCode (CLabel, CmmInfo) } desc_lit <- code $ mkStringCLit $13 return (mkRtsInfoLabelFS $3, CmmInfo prof Nothing (fromIntegral $11) - (ConstrInfo (fromIntegral $5, fromIntegral $7) (fromIntegral $9) desc_lit)) } + (ConstrInfo (fromIntegral $5, fromIntegral $7) (fromIntegral $9) desc_lit), + []) } | 'INFO_TABLE_SELECTOR' '(' NAME ',' INT ',' INT ',' STRING ',' STRING ')' -- selector, closure type, description, type { do prof <- profilingInfo $9 $11 return (mkRtsInfoLabelFS $3, CmmInfo prof Nothing (fromIntegral $7) - (ThunkSelectorInfo (fromIntegral $5) NoC_SRT)) } + (ThunkSelectorInfo (fromIntegral $5) NoC_SRT), + []) } | 'INFO_TABLE_RET' '(' NAME ',' INT ')' -- closure type (no live regs) { return (mkRtsInfoLabelFS $3, CmmInfo (ProfilingInfo zeroCLit zeroCLit) Nothing (fromIntegral $5) - (ContInfo [] NoC_SRT)) } + (ContInfo [] NoC_SRT), + []) } | 'INFO_TABLE_RET' '(' NAME ',' INT ',' formals0 ')' -- closure type, live regs { do live <- sequence (map (liftM Just) $7) return (mkRtsInfoLabelFS $3, CmmInfo (ProfilingInfo zeroCLit zeroCLit) Nothing (fromIntegral $5) - (ContInfo live NoC_SRT)) } + (ContInfo live NoC_SRT), + live) } body :: { ExtCode } : {- empty -} { return () } @@ -301,10 +313,10 @@ 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 ')' vols ';' - {% foreignCall $3 $1 $4 $6 $8 NoC_SRT } - | maybe_results 'prim' '%' NAME '(' hint_exprs0 ')' vols ';' - {% primCall $1 $4 $6 $8 NoC_SRT } + | maybe_results 'foreign' STRING expr '(' hint_exprs0 ')' safety vols ';' + {% foreignCall $3 $1 $4 $6 $9 $8 } + | maybe_results 'prim' '%' NAME '(' hint_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? | NAME '(' exprs0 ')' ';' @@ -333,6 +345,11 @@ bool_op :: { ExtFCode BoolExpr } | '(' bool_op ')' { $2 } -- This is not C-- syntax. What to do? +safety :: { CmmSafety } + : {- empty -} { CmmUnsafe } -- Default may change soon + | STRING {% parseSafety $1 } + +-- This is not C-- syntax. What to do? vols :: { Maybe [GlobalReg] } : {- empty -} { Nothing } | '[' ']' { Just [] } @@ -618,6 +635,11 @@ callishMachOps = listToUFM $ -- ToDo: the rest, maybe ] +parseSafety :: String -> P CmmSafety +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 @@ -789,6 +811,8 @@ nopEC = code nopC stmtEC stmt = code (stmtC stmt) stmtsEC stmts = code (stmtsC stmts) getCgStmtsEC = code2 getCgStmts' +getCgStmtsEC' = code2 (\m -> getCgStmts' m >>= f) + where f ((decl, b), c) = return ((decl, b), (b, c)) forkLabelledCodeEC ec = do stmts <- getCgStmtsEC ec @@ -816,9 +840,9 @@ foreignCall -> ExtFCode CmmExpr -> [ExtFCode (CmmExpr,MachHint)] -> Maybe [GlobalReg] - -> C_SRT + -> CmmSafety -> P ExtCode -foreignCall conv_string results_code expr_code args_code vols srt +foreignCall conv_string results_code expr_code args_code vols safety = do convention <- case conv_string of "C" -> return CCallConv "C--" -> return CmmCallConv @@ -827,23 +851,39 @@ foreignCall conv_string results_code expr_code args_code vols srt results <- sequence results_code expr <- expr_code args <- sequence args_code - code (emitForeignCall' PlayRisky results - (CmmForeignCall expr convention) args vols srt) where + case convention of + -- Temporary hack so at least some functions are CmmSafe + CmmCallConv -> code (stmtC (CmmCall (CmmForeignCall expr convention) results args safety)) + _ -> case safety of + CmmUnsafe -> + code (emitForeignCall' PlayRisky results + (CmmForeignCall expr convention) args vols NoC_SRT) + CmmSafe srt -> + code (emitForeignCall' (PlaySafe unused) results + (CmmForeignCall expr convention) args vols NoC_SRT) where + unused = panic "not used by emitForeignCall'" primCall :: [ExtFCode (CmmFormal,MachHint)] -> FastString -> [ExtFCode (CmmExpr,MachHint)] -> Maybe [GlobalReg] - -> C_SRT + -> CmmSafety -> P ExtCode -primCall results_code name args_code vols srt +primCall results_code name args_code vols safety = case lookupUFM callishMachOps name of Nothing -> fail ("unknown primitive " ++ unpackFS name) Just p -> return $ do results <- sequence results_code args <- sequence args_code - code (emitForeignCall' PlayRisky results (CmmPrim p) args vols srt) + case safety of + CmmUnsafe -> + code (emitForeignCall' PlayRisky results + (CmmPrim p) args vols NoC_SRT) + CmmSafe srt -> + code (emitForeignCall' (PlaySafe unused) results + (CmmPrim p) args vols NoC_SRT) where + unused = panic "not used by emitForeignCall'" doStore :: MachRep -> ExtFCode CmmExpr -> ExtFCode CmmExpr -> ExtCode doStore rep addr_code val_code