X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FdeSugar%2FCoverage.lhs;h=2136d016750a708321c146409ae3fbe76d3f62b1;hp=d640dad3725c9281a970bae97d4ee76458450ea0;hb=fb6d198f498d4e325a540f28aaa6e1d1530839c3;hpb=6084fb5517da34f65034370a3695e2af3b85ce2b diff --git a/compiler/deSugar/Coverage.lhs b/compiler/deSugar/Coverage.lhs index d640dad..2136d01 100644 --- a/compiler/deSugar/Coverage.lhs +++ b/compiler/deSugar/Coverage.lhs @@ -11,7 +11,7 @@ import HsSyn import Module import Outputable import DynFlags -import Monad +import Control.Monad import SrcLoc import ErrUtils import Name @@ -24,9 +24,9 @@ import HscTypes import StaticFlags import TyCon import FiniteMap +import Maybes import Data.Array -import System.IO (FilePath) import System.Directory ( createDirectoryIfMissing ) import Trace.Hpc.Mix @@ -61,12 +61,20 @@ addCoverageTicksToBinds dflags mod mod_loc tyCons binds = do if "boot" `isSuffixOf` orig_file then return (binds, emptyHpcInfo False, emptyModBreaks) else do + -- Now, we try look for a file generated from a .hsc file to a .hs file, by peeking ahead. + + let top_pos = catMaybes $ foldrBag (\ (L pos _) rest -> srcSpanFileName_maybe pos : rest) [] binds + let orig_file2 = case top_pos of + (file_name:_) + | ".hsc" `isSuffixOf` unpackFS file_name -> unpackFS file_name + _ -> orig_file + let mod_name = moduleNameString (moduleName mod) let (binds1,_,st) = unTM (addTickLHsBinds binds) (TTE - { fileName = mkFastString orig_file + { fileName = mkFastString orig_file2 , declPath = [] , inScope = emptyVarSet , blackList = listToFM [ (getSrcSpan (tyConName tyCon),()) @@ -89,14 +97,14 @@ addCoverageTicksToBinds dflags mod mod_loc tyCons binds = do let tabStop = 1 -- counts as a normal char in GHC's location ranges. createDirectoryIfMissing True hpc_mod_dir - modTime <- getModificationTime orig_file + modTime <- getModificationTime orig_file2 let entries' = [ (hpcPos, box) | (span,_,box) <- entries, hpcPos <- [mkHpcPos span] ] when (length entries' /= tickBoxCount st) $ do panic "the number of .mix entries are inconsistent" - let hashNo = mixHash orig_file modTime tabStop entries' + let hashNo = mixHash orig_file2 modTime tabStop entries' mixCreate hpc_mod_dir mod_name - $ Mix orig_file modTime (toHash hashNo) tabStop entries' + $ Mix orig_file2 modTime (toHash hashNo) tabStop entries' return $ hashNo else do return $ 0 @@ -238,9 +246,9 @@ addTickLHsExprOptAlt oneOfMany (L pos e0) addTickHsExpr e0 addBinTickLHsExpr :: (Bool -> BoxLabel) -> LHsExpr Id -> TM (LHsExpr Id) -addBinTickLHsExpr boxLabel (L pos e0) = do - e1 <- addTickHsExpr e0 - allocBinTickBox boxLabel $ L pos e1 +addBinTickLHsExpr boxLabel (L pos e0) = + allocBinTickBox boxLabel pos $ + addTickHsExpr e0 addTickHsExpr :: HsExpr Id -> TM (HsExpr Id) addTickHsExpr e@(HsVar id) = do freeVar id; return e @@ -270,6 +278,10 @@ addTickHsExpr (SectionR e1 e2) = liftM2 SectionR (addTickLHsExpr e1) (addTickLHsExpr e2) +addTickHsExpr (ExplicitTuple es boxity) = + liftM2 ExplicitTuple + (mapM addTickTupArg es) + (return boxity) addTickHsExpr (HsCase e mgs) = liftM2 HsCase (addTickLHsExpr e) @@ -293,17 +305,13 @@ addTickHsExpr (HsDo cxt stmts last_exp srcloc) = do ListComp -> Just $ BinBox QualBinBox _ -> Nothing addTickHsExpr (ExplicitList ty es) = - liftM2 ExplicitList + liftM2 ExplicitList (return ty) (mapM (addTickLHsExpr) es) addTickHsExpr (ExplicitPArr ty es) = liftM2 ExplicitPArr (return ty) (mapM (addTickLHsExpr) es) -addTickHsExpr (ExplicitTuple es box) = - liftM2 ExplicitTuple - (mapM (addTickLHsExpr) es) - (return box) addTickHsExpr (RecordCon id ty rec_binds) = liftM3 RecordCon (return id) @@ -369,6 +377,10 @@ addTickHsExpr e@(HsType _) = return e -- Others dhould never happen in expression content. addTickHsExpr e = pprPanic "addTickHsExpr" (ppr e) +addTickTupArg :: HsTupArg Id -> TM (HsTupArg Id) +addTickTupArg (Present e) = do { e' <- addTickLHsExpr e; return (Present e') } +addTickTupArg (Missing ty) = return (Missing ty) + addTickMatchGroup :: MatchGroup Id -> TM (MatchGroup Id) addTickMatchGroup (MatchGroup matches ty) = do let isOneOfMany = matchesOneOfMany matches @@ -449,13 +461,15 @@ addTickStmt isGuard (GroupStmt (stmts, binderMap) groupByClause) = do case x of Left a -> f a >>= (return . Left) Right b -> g b >>= (return . Right) -addTickStmt isGuard (RecStmt stmts ids1 ids2 tys dictbinds) = do - liftM5 RecStmt - (addTickLStmts isGuard stmts) - (return ids1) - (return ids2) - (return tys) - (addTickDictBinds dictbinds) +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' <- addTickDictBinds (recS_dicts stmt) + ; return (stmt { recS_stmts = stmts', recS_ret_fn = ret' + , recS_mfix_fn = mfix', recS_bind_fn = bind' + , recS_dicts = dicts' }) } addTick :: Maybe (Bool -> BoxLabel) -> LHsExpr Id -> TM (LHsExpr Id) addTick isGuard e | Just fn <- isGuard = addBinTickLHsExpr fn e @@ -635,7 +649,7 @@ getFileName = fileName `liftM` getEnv sameFileName :: SrcSpan -> TM a -> TM a -> TM a sameFileName pos out_of_scope in_scope = do file_name <- getFileName - case optSrcSpanFileName pos of + case srcSpanFileName_maybe pos of Just file_name2 | file_name == file_name2 -> in_scope _ -> out_of_scope @@ -688,29 +702,28 @@ allocATickBox boxLabel pos fvs | isGoodSrcSpan' pos = ) allocATickBox _boxLabel _pos _fvs = return Nothing -allocBinTickBox :: (Bool -> BoxLabel) -> LHsExpr Id -> TM (LHsExpr Id) -allocBinTickBox boxLabel (L pos e) | isGoodSrcSpan' pos = TM $ \ _env st -> +allocBinTickBox :: (Bool -> BoxLabel) -> SrcSpan -> TM (HsExpr Id) + -> TM (LHsExpr Id) +allocBinTickBox boxLabel pos m + | not opt_Hpc = allocTickBox (ExpBox False) pos m + | isGoodSrcSpan' pos = + do + e <- m + TM $ \ _env st -> let meT = (pos,[],boxLabel True) meF = (pos,[],boxLabel False) meE = (pos,[],ExpBox False) c = tickBoxCount st mes = mixEntries st in - if opt_Hpc - then ( L pos $ HsTick c [] $ L pos $ HsBinTick (c+1) (c+2) (L pos e) + ( L pos $ HsTick c [] $ L pos $ HsBinTick (c+1) (c+2) (L pos e) -- notice that F and T are reversed, -- because we are building the list in -- reverse... , noFVs , st {tickBoxCount=c+3 , mixEntries=meF:meT:meE:mes} ) - else - ( L pos $ HsTick c [] $ L pos e - , noFVs - , st {tickBoxCount=c+1,mixEntries=meE:mes} - ) - -allocBinTickBox _boxLabel e = return e +allocBinTickBox _boxLabel pos m = do e <- m; return (L pos e) isGoodSrcSpan' :: SrcSpan -> Bool isGoodSrcSpan' pos