Skip to content
Snippets Groups Projects
Commit 53b6bdee authored by Ben Gamari's avatar Ben Gamari
Browse files

Coverage: Don't produce ModBreaks if not HscInterpreted

emptyModBreaks contains a bottom and consequently it's important that we
don't use it unless necessary.

(cherry picked from commit f684a7d5)
parent 37c0dd8f
No related branches found
No related tags found
No related merge requests found
......@@ -111,7 +111,7 @@ addTicksToBinds hsc_env mod mod_loc exports tyCons binds
dumpIfSet_dyn dflags Opt_D_dump_ticked "HPC" (pprLHsBinds binds1)
return (binds1, HpcInfo tickCount hashNo, Just modBreaks)
return (binds1, HpcInfo tickCount hashNo, modBreaks)
| otherwise = return (binds, emptyHpcInfo False, Nothing)
......@@ -128,23 +128,23 @@ guessSourceFile binds orig_file =
_ -> orig_file
mkModBreaks :: HscEnv -> Module -> Int -> [MixEntry_] -> IO ModBreaks
mkModBreaks :: HscEnv -> Module -> Int -> [MixEntry_] -> IO (Maybe ModBreaks)
mkModBreaks hsc_env mod count entries
| HscInterpreted <- hscTarget (hsc_dflags hsc_env) = do
| breakpointsEnabled (hsc_dflags hsc_env) = do
breakArray <- GHCi.newBreakArray hsc_env (length entries)
ccs <- mkCCSArray hsc_env mod count entries
let
locsTicks = listArray (0,count-1) [ span | (span,_,_,_) <- entries ]
varsTicks = listArray (0,count-1) [ vars | (_,_,vars,_) <- entries ]
declsTicks = listArray (0,count-1) [ decls | (_,decls,_,_) <- entries ]
return emptyModBreaks
return $ Just $ emptyModBreaks
{ modBreaks_flags = breakArray
, modBreaks_locs = locsTicks
, modBreaks_vars = varsTicks
, modBreaks_decls = declsTicks
, modBreaks_ccs = ccs
}
| otherwise = return emptyModBreaks
| otherwise = return Nothing
mkCCSArray
:: HscEnv -> Module -> Int -> [MixEntry_]
......@@ -1038,7 +1038,7 @@ data TickishType = ProfNotes | HpcTicks | Breakpoints | SourceNotes
coveragePasses :: DynFlags -> [TickishType]
coveragePasses dflags =
ifa (hscTarget dflags == HscInterpreted) Breakpoints $
ifa (breakpointsEnabled dflags) Breakpoints $
ifa (gopt Opt_Hpc dflags) HpcTicks $
ifa (gopt Opt_SccProfilingOn dflags &&
profAuto dflags /= NoProfAuto) ProfNotes $
......@@ -1046,6 +1046,10 @@ coveragePasses dflags =
where ifa f x xs | f = x:xs
| otherwise = xs
-- | Should we produce 'Breakpoint' ticks?
breakpointsEnabled :: DynFlags -> Bool
breakpointsEnabled dflags = hscTarget dflags == HscInterpreted
-- | Tickishs that only make sense when their source code location
-- refers to the current file. This might not always be true due to
-- LINE pragmas in the code - which would confuse at least HPC.
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment