X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2FdeSugar%2FCoverage.lhs;h=95b70f091a5ab33bf7939e8abc5e58a0ac8000ed;hb=34c8d0312071f7d0f4d221a997d3408c653ef9e5;hp=d894523de3cfaebf0f7530b7ccde95b2f6166c48;hpb=4e0c994eb1613c62e94069642d7acdb2e69b773b;p=ghc-hetmet.git diff --git a/compiler/deSugar/Coverage.lhs b/compiler/deSugar/Coverage.lhs index d894523..95b70f0 100644 --- a/compiler/deSugar/Coverage.lhs +++ b/compiler/deSugar/Coverage.lhs @@ -99,7 +99,7 @@ addCoverageTicksToBinds dflags mod mod_loc tyCons binds = createDirectoryIfMissing True hpc_mod_dir modTime <- getModificationTime orig_file2 let entries' = [ (hpcPos, box) - | (span,_,box) <- entries, hpcPos <- [mkHpcPos span] ] + | (span,_,_,box) <- entries, hpcPos <- [mkHpcPos span] ] when (length entries' /= tickBoxCount st) $ do panic "the number of .mix entries are inconsistent" let hashNo = mixHash orig_file2 modTime tabStop entries' @@ -113,13 +113,16 @@ addCoverageTicksToBinds dflags mod mod_loc tyCons binds = breakArray <- newBreakArray $ length entries let locsTicks = listArray (0,tickBoxCount st-1) - [ span | (span,_,_) <- entries ] + [ span | (span,_,_,_) <- entries ] varsTicks = listArray (0,tickBoxCount st-1) - [ vars | (_,vars,_) <- entries ] + [ vars | (_,_,vars,_) <- entries ] + declsTicks= listArray (0,tickBoxCount st-1) + [ decls | (_,decls,_,_) <- entries ] modBreaks = emptyModBreaks { modBreaks_flags = breakArray , modBreaks_locs = locsTicks , modBreaks_vars = varsTicks + , modBreaks_decls = declsTicks } doIfSet_dyn dflags Opt_D_dump_hpc $ do @@ -359,18 +362,6 @@ 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) - (addTickLHsExpr e2) - (return ty1) - (return arr_ty) - (return lr) -addTickHsExpr (HsArrForm e fix cmdtop) = - liftM3 HsArrForm - (addTickLHsExpr e) - (return fix) - (mapM (liftL (addTickHsCmdTop)) cmdtop) addTickHsExpr e@(HsType _) = return e @@ -462,10 +453,8 @@ addTickStmt isGuard stmt@(RecStmt {}) ; 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 @@ -534,10 +523,120 @@ 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 last_exp srcloc) = do + (stmts', last_exp') <- addTickLCmdStmts' stmts (addTickLHsCmd last_exp) + return (HsDo cxt stmts' last_exp' srcloc) + where +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) + +-- 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) +addTickCmdGRHS (GRHS stmts cmd) = do + (stmts',expr') <- addTickLCmdStmts' 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 (ExprStmt c bind' ty) = do + liftM3 ExprStmt + (addTickLHsCmd c) + (return bind') + (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' }) } -addTickEvBinds :: TcEvBinds -> TM TcEvBinds -addTickEvBinds x = return x -- No coverage testing for dictionary binding +-- Others should never happen in a command context. +addTickCmdStmt stmt = pprPanic "addTickHsCmd" (ppr stmt) addTickHsRecordBinds :: HsRecordBinds Id -> TM (HsRecordBinds Id) addTickHsRecordBinds (HsRecFields fields dd) @@ -670,11 +769,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, map (nameOccName.idName) ids, boxLabel) + me = (pos, declPath env, map (nameOccName.idName) ids, boxLabel) in ( L pos (HsTick c ids (L pos e)) , fvs @@ -687,8 +786,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, 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 @@ -705,10 +807,10 @@ allocBinTickBox boxLabel pos m | isGoodSrcSpan' pos = do e <- m - TM $ \ _env st -> - let meT = (pos,[],boxLabel True) - meF = (pos,[],boxLabel False) - meE = (pos,[],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 @@ -757,7 +859,7 @@ matchesOneOfMany lmatches = sum (map matchCount lmatches) > 1 \begin{code} -type MixEntry_ = (SrcSpan, [OccName], BoxLabel) +type MixEntry_ = (SrcSpan, [String], [OccName], BoxLabel) -- For the hash value, we hash everything: the file name, -- the timestamp of the original source file, the tab stop,