-- | -- Module: Trace.Hpc.Codecov.Lix -- Copyright: (c) 2014 Guillaume Nargeot -- License: BSD3 -- Maintainer: Guillaume Nargeot -- Stability: experimental -- Portability: portable -- -- Functions for converting hpc output to line-based code coverage data. module Trace.Hpc.Codecov.Lix where import Data.List import Data.Ord import Prelude hiding (getLine) import Trace.Hpc.Codecov.Types import Trace.Hpc.Codecov.Util import Trace.Hpc.Mix import Trace.Hpc.Util toHit :: [Bool] -> Hit toHit [] = Irrelevant toHit [x] = if x then Full else None toHit xs | and xs = Full | or xs = Partial | otherwise = None getLine :: MixEntry -> Int getLine = fffst . fromHpcPos . fst where fffst (x, _, _, _) = x toLineHit :: CoverageEntry -> (Int, Bool) toLineHit (entry, cnt, _source) = (getLine entry - 1, cnt > 0) adjust :: CoverageEntry -> CoverageEntry adjust coverageEntry@(mixEntry, _, source) = case (snd mixEntry, source) of (BinBox GuardBinBox False, ["otherwise"]) -> (mixEntry, 1, source) _ -> coverageEntry -- | Convert hpc coverage entries into a line based coverage format toLix :: Int -- ^ Source line count -> [CoverageEntry] -- ^ Mix entries and associated hit count -> Lix -- ^ Line coverage toLix lineCount entries = map toHit (groupByIndex lineCount sortedLineHits) where sortedLineHits = sortBy (comparing fst) lineHits lineHits = map (toLineHit . adjust) entries