X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FdeSugar%2FCoverage.lhs;h=fbe1ab9a4537e46489900aadd560d0449764943e;hp=ea41d9869b76237cd587557d5c50922d7c2282dc;hb=b2bd63f99d643f6b3eb30bb72bb9ae26d4183252;hpb=add9b7f13aad3a6ec5fdb4512c79ee9c5d95b3d4 diff --git a/compiler/deSugar/Coverage.lhs b/compiler/deSugar/Coverage.lhs index ea41d98..fbe1ab9 100644 --- a/compiler/deSugar/Coverage.lhs +++ b/compiler/deSugar/Coverage.lhs @@ -5,7 +5,7 @@ \section[Coverage]{@coverage@: the main function} \begin{code} -module Coverage (addCoverageTicksToBinds) where +module Coverage (addCoverageTicksToBinds, hpcInitCode) where import HsSyn import Module @@ -25,6 +25,8 @@ import StaticFlags import TyCon import MonadUtils import Maybes +import CLabel +import Util import Data.Array import System.Directory ( createDirectoryIfMissing ) @@ -299,10 +301,9 @@ addTickHsExpr (HsLet binds e) = liftM2 HsLet (addTickHsLocalBinds binds) -- to think about: !patterns. (addTickLHsExprNeverOrAlways e) -addTickHsExpr (HsDo cxt stmts last_exp srcloc) = do - (stmts', last_exp') <- addTickLStmts' forQual stmts - (addTickLHsExpr last_exp) - return (HsDo cxt stmts' last_exp' srcloc) +addTickHsExpr (HsDo cxt stmts srcloc) + = do { (stmts', _) <- addTickLStmts' forQual stmts (return ()) + ; return (HsDo cxt stmts' srcloc) } where forQual = case cxt of ListComp -> Just $ BinBox QualBinBox @@ -362,6 +363,7 @@ addTickHsExpr (HsWrap w e) = liftM2 HsWrap (return w) (addTickHsExpr e) -- explicitly no tick on inside + addTickHsExpr (HsArrApp e1 e2 ty1 arr_ty lr) = liftM5 HsArrApp (addTickLHsExpr e1) @@ -369,6 +371,7 @@ addTickHsExpr (HsArrApp e1 e2 ty1 arr_ty lr) = (return ty1) (return arr_ty) (return lr) + addTickHsExpr (HsArrForm e fix cmdtop) = liftM3 HsArrForm (addTickLHsExpr e) @@ -420,55 +423,58 @@ addTickLStmts isGuard stmts = do addTickLStmts' :: (Maybe (Bool -> BoxLabel)) -> [LStmt Id] -> TM a -> TM ([LStmt Id], a) addTickLStmts' isGuard lstmts res - = bindLocals binders $ do - lstmts' <- mapM (liftL (addTickStmt isGuard)) lstmts - a <- res - return (lstmts', a) - where - binders = collectLStmtsBinders lstmts + = bindLocals (collectLStmtsBinders lstmts) $ + do { lstmts' <- mapM (liftL (addTickStmt isGuard)) lstmts + ; a <- res + ; return (lstmts', a) } addTickStmt :: (Maybe (Bool -> BoxLabel)) -> Stmt Id -> TM (Stmt Id) +addTickStmt _isGuard (LastStmt e ret) = do + liftM2 LastStmt + (addTickLHsExpr e) + (addTickSyntaxExpr hpcSrcSpan ret) addTickStmt _isGuard (BindStmt pat e bind fail) = do liftM4 BindStmt (addTickLPat pat) (addTickLHsExprAlways e) (addTickSyntaxExpr hpcSrcSpan bind) (addTickSyntaxExpr hpcSrcSpan fail) -addTickStmt isGuard (ExprStmt e bind' ty) = do - liftM3 ExprStmt +addTickStmt isGuard (ExprStmt e bind' guard' ty) = do + liftM4 ExprStmt (addTick isGuard e) (addTickSyntaxExpr hpcSrcSpan bind') + (addTickSyntaxExpr hpcSrcSpan guard') (return ty) addTickStmt _isGuard (LetStmt binds) = do liftM LetStmt (addTickHsLocalBinds binds) -addTickStmt isGuard (ParStmt pairs) = do - liftM ParStmt +addTickStmt isGuard (ParStmt pairs mzipExpr bindExpr returnExpr) = do + liftM4 ParStmt (mapM (addTickStmtAndBinders isGuard) pairs) - -addTickStmt isGuard (TransformStmt stmts ids usingExpr maybeByExpr) = do - liftM4 TransformStmt - (addTickLStmts isGuard stmts) - (return ids) - (addTickLHsExprAlways usingExpr) - (addTickMaybeByLHsExpr maybeByExpr) - -addTickStmt isGuard (GroupStmt stmts binderMap by using) = do - liftM4 GroupStmt - (addTickLStmts isGuard stmts) - (return binderMap) - (fmapMaybeM addTickLHsExprAlways by) - (fmapEitherM addTickLHsExprAlways (addTickSyntaxExpr hpcSrcSpan) using) + (addTickSyntaxExpr hpcSrcSpan mzipExpr) + (addTickSyntaxExpr hpcSrcSpan bindExpr) + (addTickSyntaxExpr hpcSrcSpan returnExpr) + +addTickStmt isGuard stmt@(TransStmt { trS_stmts = stmts + , trS_by = by, trS_using = using + , trS_ret = returnExpr, trS_bind = bindExpr + , trS_fmap = liftMExpr }) = do + t_s <- addTickLStmts isGuard stmts + t_y <- fmapMaybeM addTickLHsExprAlways by + t_u <- addTickLHsExprAlways using + t_f <- addTickSyntaxExpr hpcSrcSpan returnExpr + t_b <- addTickSyntaxExpr hpcSrcSpan bindExpr + t_m <- addTickSyntaxExpr hpcSrcSpan liftMExpr + return $ stmt { trS_stmts = t_s, trS_by = t_y, trS_using = t_u + , trS_ret = t_f, trS_bind = t_b, trS_fmap = t_m } addTickStmt isGuard stmt@(RecStmt {}) = do { stmts' <- addTickLStmts isGuard (recS_stmts stmt) ; ret' <- addTickSyntaxExpr hpcSrcSpan (recS_ret_fn stmt) ; mfix' <- addTickSyntaxExpr hpcSrcSpan (recS_mfix_fn stmt) ; bind' <- addTickSyntaxExpr hpcSrcSpan (recS_bind_fn stmt) - ; dicts' <- addTickEvBinds (recS_dicts stmt) ; return (stmt { recS_stmts = stmts', recS_ret_fn = ret' - , recS_mfix_fn = mfix', recS_bind_fn = bind' - , recS_dicts = dicts' }) } + , recS_mfix_fn = mfix', recS_bind_fn = bind' }) } addTick :: Maybe (Bool -> BoxLabel) -> LHsExpr Id -> TM (LHsExpr Id) addTick isGuard e | Just fn <- isGuard = addBinTickLHsExpr fn e @@ -481,12 +487,6 @@ addTickStmtAndBinders isGuard (stmts, ids) = (addTickLStmts isGuard stmts) (return ids) -addTickMaybeByLHsExpr :: Maybe (LHsExpr Id) -> TM (Maybe (LHsExpr Id)) -addTickMaybeByLHsExpr maybeByExpr = - case maybeByExpr of - Nothing -> return Nothing - Just byExpr -> addTickLHsExprAlways byExpr >>= (return . Just) - addTickHsLocalBinds :: HsLocalBinds Id -> TM (HsLocalBinds Id) addTickHsLocalBinds (HsValBinds binds) = liftM HsValBinds @@ -537,10 +537,128 @@ addTickHsCmdTop (HsCmdTop cmd tys ty syntaxtable) = (return syntaxtable) addTickLHsCmd :: LHsCmd Id -> TM (LHsCmd Id) -addTickLHsCmd x = addTickLHsExpr x +addTickLHsCmd (L pos c0) = do + c1 <- addTickHsCmd c0 + return $ L pos c1 + +addTickHsCmd :: HsCmd Id -> TM (HsCmd Id) +addTickHsCmd (HsLam matchgroup) = + liftM HsLam (addTickCmdMatchGroup matchgroup) +addTickHsCmd (HsApp e1 e2) = + liftM2 HsApp (addTickLHsExprNever e1) (addTickLHsExpr e2) +addTickHsCmd (OpApp e1 c2 fix c3) = + liftM4 OpApp + (addTickLHsExpr e1) + (addTickLHsCmd c2) + (return fix) + (addTickLHsCmd c3) +addTickHsCmd (HsPar e) = liftM HsPar (addTickLHsCmd e) +addTickHsCmd (HsCase e mgs) = + liftM2 HsCase + (addTickLHsExpr e) + (addTickCmdMatchGroup mgs) +addTickHsCmd (HsIf cnd e1 c2 c3) = + liftM3 (HsIf cnd) + (addBinTickLHsExpr (BinBox CondBinBox) e1) + (addTickLHsCmd c2) + (addTickLHsCmd c3) +addTickHsCmd (HsLet binds c) = + bindLocals (collectLocalBinders binds) $ + liftM2 HsLet + (addTickHsLocalBinds binds) -- to think about: !patterns. + (addTickLHsCmd c) +addTickHsCmd (HsDo cxt stmts srcloc) + = do { (stmts', _) <- addTickLCmdStmts' stmts (return ()) + ; return (HsDo cxt stmts' srcloc) } + +addTickHsCmd (HsArrApp e1 e2 ty1 arr_ty lr) = + liftM5 HsArrApp + (addTickLHsExpr e1) + (addTickLHsExpr e2) + (return ty1) + (return arr_ty) + (return lr) +addTickHsCmd (HsArrForm e fix cmdtop) = + liftM3 HsArrForm + (addTickLHsExpr e) + (return fix) + (mapM (liftL (addTickHsCmdTop)) cmdtop) -addTickEvBinds :: TcEvBinds -> TM TcEvBinds -addTickEvBinds x = return x -- No coverage testing for dictionary binding +-- Others should never happen in a command context. +addTickHsCmd e = pprPanic "addTickHsCmd" (ppr e) + +addTickCmdMatchGroup :: MatchGroup Id -> TM (MatchGroup Id) +addTickCmdMatchGroup (MatchGroup matches ty) = do + matches' <- mapM (liftL addTickCmdMatch) matches + return $ MatchGroup matches' ty + +addTickCmdMatch :: Match Id -> TM (Match Id) +addTickCmdMatch (Match pats opSig gRHSs) = + bindLocals (collectPatsBinders pats) $ do + gRHSs' <- addTickCmdGRHSs gRHSs + return $ Match pats opSig gRHSs' + +addTickCmdGRHSs :: GRHSs Id -> TM (GRHSs Id) +addTickCmdGRHSs (GRHSs guarded local_binds) = do + bindLocals binders $ do + local_binds' <- addTickHsLocalBinds local_binds + guarded' <- mapM (liftL addTickCmdGRHS) guarded + return $ GRHSs guarded' local_binds' + where + binders = collectLocalBinders local_binds + +addTickCmdGRHS :: GRHS Id -> TM (GRHS Id) +-- The *guards* are *not* Cmds, although the body is +-- C.f. addTickGRHS for the BinBox stuff +addTickCmdGRHS (GRHS stmts cmd) + = do { (stmts',expr') <- addTickLStmts' (Just $ BinBox $ GuardBinBox) + stmts (addTickLHsCmd cmd) + ; return $ GRHS stmts' expr' } + +addTickLCmdStmts :: [LStmt Id] -> TM [LStmt Id] +addTickLCmdStmts stmts = do + (stmts, _) <- addTickLCmdStmts' stmts (return ()) + return stmts + +addTickLCmdStmts' :: [LStmt Id] -> TM a -> TM ([LStmt Id], a) +addTickLCmdStmts' lstmts res + = bindLocals binders $ do + lstmts' <- mapM (liftL addTickCmdStmt) lstmts + a <- res + return (lstmts', a) + where + binders = collectLStmtsBinders lstmts + +addTickCmdStmt :: Stmt Id -> TM (Stmt Id) +addTickCmdStmt (BindStmt pat c bind fail) = do + liftM4 BindStmt + (addTickLPat pat) + (addTickLHsCmd c) + (return bind) + (return fail) +addTickCmdStmt (LastStmt c ret) = do + liftM2 LastStmt + (addTickLHsCmd c) + (addTickSyntaxExpr hpcSrcSpan ret) +addTickCmdStmt (ExprStmt c bind' guard' ty) = do + liftM4 ExprStmt + (addTickLHsCmd c) + (addTickSyntaxExpr hpcSrcSpan bind') + (addTickSyntaxExpr hpcSrcSpan guard') + (return ty) +addTickCmdStmt (LetStmt binds) = do + liftM LetStmt + (addTickHsLocalBinds binds) +addTickCmdStmt stmt@(RecStmt {}) + = do { stmts' <- addTickLCmdStmts (recS_stmts stmt) + ; ret' <- addTickSyntaxExpr hpcSrcSpan (recS_ret_fn stmt) + ; mfix' <- addTickSyntaxExpr hpcSrcSpan (recS_mfix_fn stmt) + ; bind' <- addTickSyntaxExpr hpcSrcSpan (recS_bind_fn stmt) + ; return (stmt { recS_stmts = stmts', recS_ret_fn = ret' + , recS_mfix_fn = mfix', recS_bind_fn = bind' }) } + +-- Others should never happen in a command context. +addTickCmdStmt stmt = pprPanic "addTickHsCmd" (ppr stmt) addTickHsRecordBinds :: HsRecordBinds Id -> TM (HsRecordBinds Id) addTickHsRecordBinds (HsRecFields fields dd) @@ -673,11 +791,11 @@ allocTickBox boxLabel pos m | isGoodSrcSpan' pos = sameFileName pos (do e <- m; return (L pos e)) $ do (fvs, e) <- getFreeVars m - TM $ \ _env st -> + TM $ \ env st -> let c = tickBoxCount st ids = occEnvElts fvs mes = mixEntries st - me = (pos, declPath _env, map (nameOccName.idName) ids, boxLabel) + me = (pos, declPath env, map (nameOccName.idName) ids, boxLabel) in ( L pos (HsTick c ids (L pos e)) , fvs @@ -690,8 +808,11 @@ allocTickBox _boxLabel pos m = do e <- m; return (L pos e) allocATickBox :: BoxLabel -> SrcSpan -> FreeVars -> TM (Maybe (Int,[Id])) allocATickBox boxLabel pos fvs | isGoodSrcSpan' pos = sameFileName pos - (return Nothing) $ TM $ \ _env st -> - let me = (pos, declPath _env, map (nameOccName.idName) ids, boxLabel) + (return Nothing) $ TM $ \ env st -> + let mydecl_path + | null (declPath env), TopLevelBox x <- boxLabel = x + | otherwise = declPath env + me = (pos, mydecl_path, map (nameOccName.idName) ids, boxLabel) c = tickBoxCount st mes = mixEntries st ids = occEnvElts fvs @@ -708,10 +829,10 @@ allocBinTickBox boxLabel pos m | isGoodSrcSpan' pos = do e <- m - TM $ \ _env st -> - let meT = (pos,declPath _env, [],boxLabel True) - meF = (pos,declPath _env, [],boxLabel False) - meE = (pos,declPath _env, [],ExpBox False) + TM $ \ env st -> + let meT = (pos,declPath env, [],boxLabel True) + meF = (pos,declPath env, [],boxLabel False) + meE = (pos,declPath env, [],ExpBox False) c = tickBoxCount st mes = mixEntries st in @@ -725,26 +846,16 @@ allocBinTickBox boxLabel pos m allocBinTickBox _boxLabel pos m = do e <- m; return (L pos e) isGoodSrcSpan' :: SrcSpan -> Bool -isGoodSrcSpan' pos - | not (isGoodSrcSpan pos) = False - | start == end = False - | otherwise = True - where - start = srcSpanStart pos - end = srcSpanEnd pos +isGoodSrcSpan' pos@(RealSrcSpan _) = srcSpanStart pos /= srcSpanEnd pos +isGoodSrcSpan' (UnhelpfulSpan _) = False mkHpcPos :: SrcSpan -> HpcPos -mkHpcPos pos - | not (isGoodSrcSpan' pos) = panic "bad source span; expected such spans to be filtered out" - | otherwise = hpcPos - where - start = srcSpanStart pos - end = srcSpanEnd pos - hpcPos = toHpcPos ( srcLocLine start - , srcLocCol start - , srcLocLine end - , srcLocCol end - 1 - ) +mkHpcPos pos@(RealSrcSpan s) + | isGoodSrcSpan' pos = toHpcPos (srcSpanStartLine s, + srcSpanStartCol s, + srcSpanEndLine s, + srcSpanEndCol s) +mkHpcPos _ = panic "bad source span; expected such spans to be filtered out" hpcSrcSpan :: SrcSpan hpcSrcSpan = mkGeneralSrcSpan (fsLit "Haskell Program Coverage internals") @@ -772,3 +883,56 @@ mixHash :: FilePath -> Integer -> Int -> [MixEntry] -> Int mixHash file tm tabstop entries = fromIntegral $ hashString (show $ Mix file tm 0 tabstop entries) \end{code} + +%************************************************************************ +%* * +%* initialisation +%* * +%************************************************************************ + +Each module compiled with -fhpc declares an initialisation function of +the form `hpc_init_()`, which is emitted into the _stub.c file +and annotated with __attribute__((constructor)) so that it gets +executed at startup time. + +The function's purpose is to call hs_hpc_module to register this +module with the RTS, and it looks something like this: + +static void hpc_init_Main(void) __attribute__((constructor)); +static void hpc_init_Main(void) +{extern StgWord64 _hpc_tickboxes_Main_hpc[]; + hs_hpc_module("Main",8,1150288664,_hpc_tickboxes_Main_hpc);} + +\begin{code} +hpcInitCode :: Module -> HpcInfo -> SDoc +hpcInitCode _ (NoHpcInfo {}) = empty +hpcInitCode this_mod (HpcInfo tickCount hashNo) + = vcat + [ text "static void hpc_init_" <> ppr this_mod + <> text "(void) __attribute__((constructor));" + , text "static void hpc_init_" <> ppr this_mod <> text "(void)" + , braces (vcat [ + ptext (sLit "extern StgWord64 ") <> tickboxes <> + ptext (sLit "[]") <> semi, + ptext (sLit "hs_hpc_module") <> + parens (hcat (punctuate comma [ + doubleQuotes full_name_str, + int tickCount, -- really StgWord32 + int hashNo, -- really StgWord32 + tickboxes + ])) <> semi + ]) + ] + where + tickboxes = pprCLabel (mkHpcTicksLabel $ this_mod) + + module_name = hcat (map (text.charToC) $ + bytesFS (moduleNameFS (Module.moduleName this_mod))) + package_name = hcat (map (text.charToC) $ + bytesFS (packageIdFS (modulePackageId this_mod))) + full_name_str + | modulePackageId this_mod == mainPackageId + = module_name + | otherwise + = package_name <> char '/' <> module_name +\end{code}