Skip to content

Instantly share code, notes, and snippets.

@JustinChristensen
Last active August 21, 2023 02:35
Show Gist options
  • Save JustinChristensen/72e4eae8a8e6e4e4f9be09078770c504 to your computer and use it in GitHub Desktop.
Save JustinChristensen/72e4eae8a8e6e4e4f9be09078770c504 to your computer and use it in GitHub Desktop.
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}
module Main where
import Prelude hiding (readFile, lines, any, drop)
import qualified Prelude as P
import System.IO (stderr)
import System.Exit (exitFailure)
import Text.Megaparsec hiding (State, token, tokens)
import qualified Text.Megaparsec as M (State)
import Text.Megaparsec.Char
import Data.Text (Text, drop, findIndex)
import Data.Text.IO (hPutStrLn, readFile)
import qualified Data.Text as T (unpack, null)
import qualified Data.Text.Read as R (decimal)
import Control.Monad.State (State, evalState, modify, MonadState (get, put))
import Data.Void
import Data.Map (Map)
import qualified Data.Set as S (insert)
import qualified Data.Map as M (fromList, lookup)
import System.Environment (getArgs)
import Data.Int
import GHC.Generics (Generic)
import Data.Time (Day, LocalTime (LocalTime), fromGregorian, TimeOfDay (TimeOfDay))
import Database.PostgreSQL.Simple (ToRow)
import Database.PostgreSQL.Simple.Types (PGArray(..))
import Database.PostgreSQL.Simple.ToField (ToField(..))
import Text.Megaparsec.Char.Lexer (decimal)
import Control.Monad (void)
data Company = Company
{ compcik :: Int32,
name :: Text,
formerName :: Maybe Text,
nameChanged :: Maybe Day,
sics :: PGArray Int16,
eins :: PGArray Text
}
deriving (Generic, ToRow, Show)
data AddressType = Incorporated | Business | Mail deriving (Enum, Show)
instance ToField AddressType where
toField Incorporated = toField @Text "incorp"
toField Business = toField @Text "business"
toField Mail = toField @Text "mail"
data Address = Address
{ addrcik :: Int32,
type_ :: AddressType,
phone :: Maybe Text,
countryCode :: Maybe Text,
stateCode :: Maybe Text,
city :: Maybe Text,
zip :: Maybe Text,
address1 :: Maybe Text,
address2 :: Maybe Text
}
deriving (Generic, ToRow, Show)
data Submission = Submission
{ subcik :: Int32,
accn :: Text,
form :: Text,
fp :: Maybe Text,
period :: Maybe Day,
filed :: Day,
accepted :: LocalTime,
fy :: Maybe Int16,
fyEnd :: Maybe Text,
afs :: Maybe Text,
wksi :: Bool,
amended :: Bool,
detail :: Bool,
file :: Text,
aciks :: PGArray Int32
}
deriving (Generic, ToRow, Show)
usage :: IO ()
usage = do
hPutStrLn stderr "usage: tallow <path>"
exitFailure
data ParserState = ParserState {
header :: Map Text Int
, row :: [M.State Text Void]
} deriving (Show)
type TsvParser = ParsecT Void Text (State ParserState)
advanceTo :: (Char -> Bool) -> TsvParser ()
advanceTo f = do
s <- getInput
case findIndex f s of
Just i -> updateParserState (\st -> st {
stateInput = drop i (stateInput st),
stateOffset = stateOffset st + i
})
Nothing -> fail "could not advance"
field :: TsvParser Text
field = takeWhileP Nothing (not . tsvSep)
tsvSep :: Char -> Bool
tsvSep c = c == '\n' || c == '\t'
parseRowState :: TsvParser [M.State Text Void]
parseRowState = (:) <$> (getParserState <* advance) <*> manyTill (tab *> getParserState <* advance) newline
where advance = advanceTo tsvSep
parseRow :: TsvParser [Text]
parseRow = (:) <$> field <*> manyTill (tab *> field) newline
parseHeader :: TsvParser ()
parseHeader = do
hs <- parseRow
modify $ \ps -> ps { header = M.fromList $ P.zip hs [0..] }
withRow :: TsvParser a -> TsvParser a
withRow p = do
ParserState h _ <- get
r <- parseRowState
st <- getParserState
if length r /= length h
then fail $ "error: row length does not match header length. row:\n" <> show r
else do
put $ ParserState h r
p <* setParserState st
class FromCol a where
col :: Text -> TsvParser a
withCol :: FromCol a => TsvParser a -> Text -> TsvParser a
withCol p s = do
ParserState h r <- get
case M.lookup s h of
Just i -> setParserState (r !! i) *> region reportCol p
Nothing -> fail $ "error: column \"" <> show s <> "\" not found"
where
reportCol (FancyError o errs) = FancyError o $ S.insert (ErrorFail $ "column: " <> T.unpack s) errs
reportCol x = x
instance FromCol Text where
col = withCol $ do
t <- field
if T.null t then fail "error: unexpected empty field"
else pure t
instance FromCol Int16 where
col = withCol decimal
instance FromCol Int32 where
col = withCol decimal
parseN :: Integral a => Int -> TsvParser a
parseN n = do
t <- takeP Nothing n
case R.decimal t of
Right (i, "") -> pure i
Right (_, _) -> fail "unexpected characters for number field"
Left e -> fail (e <> ": " <> T.unpack t)
parseDate :: TsvParser Day
parseDate = try $ fromGregorian <$> (parseN 4 <* dash) <*> (parseN 2 <* dash) <*> parseN 2
where dash = optional $ char '-'
parseTimestamp :: TsvParser LocalTime
parseTimestamp = try $ do
day <- parseDate
void $ char ' '
time <- TimeOfDay <$> (two <* semi) <*> (two <* semi) <*> (fromIntegral <$> two)
pure $ LocalTime day time
where
two = parseN 2
semi = char ':'
instance FromCol Day where
col = withCol parseDate
instance FromCol LocalTime where
col = withCol parseTimestamp
instance FromCol Bool where
col = withCol $ (== "1") <$> field
instance FromCol a => FromCol (Maybe a) where
col t = withCol (optional $ col t) t
parseSubmission :: TsvParser (Company, Address, Address, Address, Submission)
parseSubmission = withRow $ do
let cik_ = col "cik"
company <- Company <$> cik_ <*> col "name" <*> col "former" <*> col "changed" <*> pure (PGArray []) <*> pure (PGArray [])
busAddr <- Address <$> cik_ <*> pure Business <*> col "baph" <*> col "countryba" <*> col "stprba" <*> col "cityba" <*> col "zipba" <*> col "bas1" <*> col "bas2"
mailAddr <- Address <$> cik_ <*> pure Mail <*> pure mempty <*> col "countryma" <*> col "stprma" <*> col "cityma" <*> col "zipma" <*> col "mas1" <*> col "mas2"
incAddr <- Address <$> cik_ <*> pure Incorporated <*> pure mempty <*> col "countryinc" <*> col "stprinc" <*> pure mempty <*> pure mempty <*> pure mempty <*> pure mempty
submission <- Submission
<$> cik_ <*> col "adsh" <*> col "form" <*> col "fp" <*> col "period" <*> col "filed" <*> col "accepted" <*>
col "fy" <*> col "fye" <*> col "afs" <*> col "wksi" <*> col "prevrpt" <*> col "detail" <*> col "instance" <*> pure (PGArray [])
pure (company, busAddr, mailAddr, incAddr, submission)
parseSubmissions :: TsvParser ([Company], [Address], [Submission])
parseSubmissions = do
meof <- optional eof
case meof of
Just _ -> pure ([], [], [])
_ -> do
(company, busAddr, mailAddr, incAddr, submission) <- parseSubmission
(companies, addresses, submissions) <- parseSubmissions
pure (company : companies, busAddr : mailAddr : incAddr : addresses, submission : submissions)
main :: IO ()
main = do
args <- getArgs
if null args then usage else do
let path = head args
contents <- readFile path
let result = evalState (runParserT (parseHeader *> parseSubmissions) path contents) (ParserState mempty mempty)
case result of
Right _ -> pure ()
-- Right records -> print records
Left err -> putStrLn $ errorBundlePretty err
Sun Aug 20 16:20 2023 Time and Allocation Profiling Report (Final)
tallow +RTS -pa -L120 -hd -RTS data/2023q2/sub.txt
total time = 2.58 secs (2584 ticks @ 1000 us, 1 processor)
total alloc = 5,623,699,112 bytes (excludes profiling overheads)
COST CENTRE MODULE SRC %time %alloc ticks bytes
GC GC <built-in> 35.4 0.0 916 1096
advanceTo Main app/Main.hs:(163,1)-(170,39) 17.9 37.4 463 2102732312
withCol Main app/Main.hs:(205,1)-(212,19) 10.4 12.9 268 723092408
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 9.4 15.0 242 844827888
OVERHEAD_of PROFILING <built-in> 7.8 0.1 201 3180072
field Main app/Main.hs:173:1-41 7.0 16.7 180 937969048
parseN Main app/Main.hs:(227,1)-(232,44) 5.5 7.1 142 397642688
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 1.4 3.8 35 214574776
col Main app/Main.hs:(215,3)-(218,15) 1.3 1.6 33 90253752
readChunk Data.Text.Internal.IO src/Data/Text/Internal/IO.hs:(156,1)-(163,10) 0.8 0.2 21 10191696
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 0.7 0.0 18 0
col Main app/Main.hs:258:3-38 0.4 1.3 11 74440112
readTextDevice Data.Text.Internal.IO src/Data/Text/Internal/IO.hs:133:39-64 0.4 0.0 10 1824120
decimal Data.Text.Read src/Data/Text/Read.hs:(62,1)-(66,55) 0.3 1.2 9 65568480
splitAt Data.Text src/Data/Text.hs:(1554,1)-(1558,78) 0.3 0.4 7 23285056
parseRowState Main app/Main.hs:(179,1)-(180,34) 0.2 0.3 6 16675400
parseDate Main app/Main.hs:(235,1)-(236,34) 0.2 1.1 4 61868128
run Data.Text.Array src/Data/Text/Array.hs:181:1-34 0.1 0.2 3 8935040
parseSubmission Main app/Main.hs:(261,1)-(270,56) 0.1 0.0 3 1692808
col Main app/Main.hs:255:3-36 0.1 0.2 3 13050840
SYSTEM SYSTEM <built-in> 0.1 0.0 2 198496
tsvSep Main app/Main.hs:176:1-33 0.1 0.0 2 0
parseTimestamp Main app/Main.hs:(239,1)-(246,19) 0.1 0.1 2 3141776
hGetContents Data.Text.IO src/Data/Text/IO.hs:(135,1)-(149,50) 0.0 0.0 1 944848
parseSubmissions Main app/Main.hs:(273,1)-(280,100) 0.0 0.1 1 7975208
col Main app/Main.hs:224:3-23 0.0 0.2 1 8458704
IDLE IDLE <built-in> 0.0 0.0 0 0
PINNED SYSTEM <built-in> 0.0 0.0 0 0
DONT_CARE MAIN <built-in> 0.0 0.0 0 0
MAIN MAIN <built-in> 0.0 0.0 0 744
CAF GHC.Types <entire-module> 0.0 0.0 0 0
CAF GHC.Tuple <entire-module> 0.0 0.0 0 0
CAF GHC.Prim.Exception <entire-module> 0.0 0.0 0 0
CAF GHC.Prim.Panic <entire-module> 0.0 0.0 0 0
CAF GHC.Classes <entire-module> 0.0 0.0 0 0
CAF GHC.CString <entire-module> 0.0 0.0 0 0
CAF GHC.Num.WordArray <entire-module> 0.0 0.0 0 0
CAF GHC.Num.Primitives <entire-module> 0.0 0.0 0 0
CAF GHC.Num.Backend.GMP <entire-module> 0.0 0.0 0 0
CAF GHC.Num.Integer <entire-module> 0.0 0.0 0 0
CAF GHC.Num.Natural <entire-module> 0.0 0.0 0 0
CAF GHC.Num.BigNat <entire-module> 0.0 0.0 0 0
CAF GHC.Event.Array <entire-module> 0.0 0.0 0 0
CAF GHC.Event.Arr <entire-module> 0.0 0.0 0 0
CAF System.Posix.Types <entire-module> 0.0 0.0 0 0
CAF GHC.Event.Poll <entire-module> 0.0 0.0 0 0
CAF GHC.Event.Manager <entire-module> 0.0 0.0 0 0
CAF GHC.Event.EPoll <entire-module> 0.0 0.0 0 0
CAF GHC.Event.Control <entire-module> 0.0 0.0 0 0
CAF GHC.Event.Unique <entire-module> 0.0 0.0 0 0
CAF GHC.Event.PSQ <entire-module> 0.0 0.0 0 0
CAF GHC.Event.IntVar <entire-module> 0.0 0.0 0 0
CAF GHC.Event.IntTable <entire-module> 0.0 0.0 0 0
CAF GHC.Event.Internal.Types <entire-module> 0.0 0.0 0 0
CAF GHC.Event.Internal <entire-module> 0.0 0.0 0 0
CAF GHC.IO.FD <entire-module> 0.0 0.0 0 16
CAF GHC.Fingerprint <entire-module> 0.0 0.0 0 0
CAF Debug.Trace <entire-module> 0.0 0.0 0 0
CAF Data.Type.Ord <entire-module> 0.0 0.0 0 0
CAF Data.Dynamic <entire-module> 0.0 0.0 0 0
CAF GHC.Event.TimerManager <entire-module> 0.0 0.0 0 0
CAF GHC.Event.Thread <entire-module> 0.0 0.0 0 0
CAF Data.Typeable.Internal <entire-module> 0.0 0.0 0 0
CAF Data.Semigroup.Internal <entire-module> 0.0 0.0 0 0
CAF Data.OldList <entire-module> 0.0 0.0 0 0
CAF Data.Functor.Utils <entire-module> 0.0 0.0 0 0
CAF Control.Monad.ST.Lazy.Imp <entire-module> 0.0 0.0 0 0
CAF Control.Monad.ST.Imp <entire-module> 0.0 0.0 0 0
CAF GHC.IOPort <entire-module> 0.0 0.0 0 0
CAF Unsafe.Coerce <entire-module> 0.0 0.0 0 0
CAF Text.Read.Lex <entire-module> 0.0 0.0 0 0
CAF Text.Read <entire-module> 0.0 0.0 0 0
CAF Text.Printf <entire-module> 0.0 0.0 0 0
CAF Text.ParserCombinators.ReadPrec <entire-module> 0.0 0.0 0 0
CAF Text.ParserCombinators.ReadP <entire-module> 0.0 0.0 0 0
CAF System.Posix.Internals <entire-module> 0.0 0.0 0 0
CAF System.IO <entire-module> 0.0 0.0 0 0
CAF System.Exit <entire-module> 0.0 0.0 0 0
CAF System.Environment <entire-module> 0.0 0.0 0 0
CAF Numeric <entire-module> 0.0 0.0 0 0
CAF GHC.Word <entire-module> 0.0 0.0 0 0
CAF GHC.Weak <entire-module> 0.0 0.0 0 0
CAF GHC.Unicode <entire-module> 0.0 0.0 0 0
CAF GHC.TypeNats <entire-module> 0.0 0.0 0 0
CAF GHC.TypeLits <entire-module> 0.0 0.0 0 0
CAF GHC.TopHandler <entire-module> 0.0 0.0 0 0
CAF GHC.Storable <entire-module> 0.0 0.0 0 0
CAF GHC.Stack.Types <entire-module> 0.0 0.0 0 0
CAF GHC.Stack.CCS <entire-module> 0.0 0.0 0 0
CAF GHC.StableName <entire-module> 0.0 0.0 0 0
CAF GHC.Stable <entire-module> 0.0 0.0 0 0
CAF GHC.Show <entire-module> 0.0 0.0 0 0
CAF GHC.STRef <entire-module> 0.0 0.0 0 0
CAF GHC.ST <entire-module> 0.0 0.0 0 0
CAF GHC.Real <entire-module> 0.0 0.0 0 0
CAF GHC.Read <entire-module> 0.0 0.0 0 0
CAF GHC.Ptr <entire-module> 0.0 0.0 0 0
CAF GHC.Pack <entire-module> 0.0 0.0 0 0
CAF GHC.Num <entire-module> 0.0 0.0 0 0
CAF GHC.MVar <entire-module> 0.0 0.0 0 0
CAF GHC.Maybe <entire-module> 0.0 0.0 0 0
CAF GHC.List <entire-module> 0.0 0.0 0 0
CAF GHC.Ix <entire-module> 0.0 0.0 0 0
CAF GHC.Int <entire-module> 0.0 0.0 0 0
CAF GHC.IORef <entire-module> 0.0 0.0 0 0
CAF GHC.IOArray <entire-module> 0.0 0.0 0 0
CAF GHC.IO.StdHandles <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Unsafe <entire-module> 0.0 0.0 0 0
CAF GHC.IO.IOMode <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Handle.Types <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Handle.Text <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Handle.Internals <entire-module> 0.0 0.0 0 24
CAF GHC.IO.Handle.FD <entire-module> 0.0 0.0 0 34736
CAF GHC.IO.Handle <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Exception <entire-module> 0.0 0.0 0 816
CAF GHC.IO.Encoding.UTF8 <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Encoding.UTF32 <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Encoding.UTF16 <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Encoding.Types <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Encoding.Latin1 <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Encoding.Iconv <entire-module> 0.0 0.0 0 200
CAF GHC.IO.Encoding.Failure <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Encoding <entire-module> 0.0 0.0 0 2976
CAF GHC.IO.Device <entire-module> 0.0 0.0 0 0
CAF GHC.IO.BufferedIO <entire-module> 0.0 0.0 0 0
CAF GHC.IO.Buffer <entire-module> 0.0 0.0 0 0
CAF GHC.IO <entire-module> 0.0 0.0 0 0
CAF GHC.Generics <entire-module> 0.0 0.0 0 0
CAF GHC.ForeignPtr <entire-module> 0.0 0.0 0 0
CAF GHC.Foreign <entire-module> 0.0 0.0 0 0
CAF GHC.Float.RealFracMethods <entire-module> 0.0 0.0 0 0
CAF GHC.Float.ConversionUtils <entire-module> 0.0 0.0 0 0
CAF GHC.Float <entire-module> 0.0 0.0 0 0
CAF GHC.Fingerprint.Type <entire-module> 0.0 0.0 0 0
CAF GHC.Exts <entire-module> 0.0 0.0 0 0
CAF GHC.Exception.Type <entire-module> 0.0 0.0 0 0
CAF GHC.Exception <entire-module> 0.0 0.0 0 0
CAF GHC.Err <entire-module> 0.0 0.0 0 0
CAF GHC.Enum <entire-module> 0.0 0.0 0 0
CAF GHC.Conc.Sync <entire-module> 0.0 0.0 0 0
CAF GHC.Conc.Signal <entire-module> 0.0 0.0 0 640
CAF GHC.Conc.IO <entire-module> 0.0 0.0 0 0
CAF GHC.Char <entire-module> 0.0 0.0 0 0
CAF GHC.Bits <entire-module> 0.0 0.0 0 0
CAF GHC.Base <entire-module> 0.0 0.0 0 0
CAF GHC.Arr <entire-module> 0.0 0.0 0 0
CAF Foreign.Storable <entire-module> 0.0 0.0 0 0
CAF Foreign.Ptr <entire-module> 0.0 0.0 0 0
CAF Foreign.Marshal.Array <entire-module> 0.0 0.0 0 0
CAF Foreign.Marshal.Alloc <entire-module> 0.0 0.0 0 0
CAF Foreign.C.Types <entire-module> 0.0 0.0 0 0
CAF Foreign.C.String <entire-module> 0.0 0.0 0 0
CAF Foreign.C.Error <entire-module> 0.0 0.0 0 0
CAF Data.Void <entire-module> 0.0 0.0 0 0
CAF Data.Version <entire-module> 0.0 0.0 0 0
CAF Data.Unique <entire-module> 0.0 0.0 0 0
CAF Data.Type.Equality <entire-module> 0.0 0.0 0 0
CAF Data.Type.Coercion <entire-module> 0.0 0.0 0 0
CAF Data.Tuple <entire-module> 0.0 0.0 0 0
CAF Data.Traversable <entire-module> 0.0 0.0 0 0
CAF Data.Semigroup <entire-module> 0.0 0.0 0 0
CAF Data.Proxy <entire-module> 0.0 0.0 0 0
CAF Data.Ord <entire-module> 0.0 0.0 0 0
CAF Data.Monoid <entire-module> 0.0 0.0 0 0
CAF Data.Maybe <entire-module> 0.0 0.0 0 0
CAF Data.List.NonEmpty <entire-module> 0.0 0.0 0 0
CAF Data.Functor.Sum <entire-module> 0.0 0.0 0 0
CAF Data.Functor.Product <entire-module> 0.0 0.0 0 0
CAF Data.Functor.Identity <entire-module> 0.0 0.0 0 0
CAF Data.Functor.Const <entire-module> 0.0 0.0 0 0
CAF Data.Functor.Compose <entire-module> 0.0 0.0 0 0
CAF Data.Functor.Contravariant <entire-module> 0.0 0.0 0 0
CAF Data.Functor.Classes <entire-module> 0.0 0.0 0 0
CAF Data.Function <entire-module> 0.0 0.0 0 0
CAF Data.Foldable <entire-module> 0.0 0.0 0 0
CAF Data.Fixed <entire-module> 0.0 0.0 0 0
CAF Data.Either <entire-module> 0.0 0.0 0 0
CAF Data.Data <entire-module> 0.0 0.0 0 0
CAF Data.Complex <entire-module> 0.0 0.0 0 0
CAF Data.Char <entire-module> 0.0 0.0 0 0
CAF Data.Bitraversable <entire-module> 0.0 0.0 0 0
CAF Data.Bifunctor <entire-module> 0.0 0.0 0 0
CAF Data.Bifoldable <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Zip <entire-module> 0.0 0.0 0 0
CAF Control.Monad.IO.Class <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Fix <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Fail <entire-module> 0.0 0.0 0 0
CAF Control.Exception.Base <entire-module> 0.0 0.0 0 0
CAF Control.Category <entire-module> 0.0 0.0 0 0
CAF Control.Arrow <entire-module> 0.0 0.0 0 0
CAF Control.Applicative <entire-module> 0.0 0.0 0 0
CAF Data.Array.Base <entire-module> 0.0 0.0 0 0
CAF Control.DeepSeq <entire-module> 0.0 0.0 0 0
CAF GHC.Lexeme <entire-module> 0.0 0.0 0 0
CAF Language.Haskell.TH.Lib.Internal <entire-module> 0.0 0.0 0 0
CAF Language.Haskell.TH.Syntax <entire-module> 0.0 0.0 0 0
CAF Utils.Containers.Internal.State <entire-module> 0.0 0.0 0 0
runState Utils.Containers.Internal.State src/Utils/Containers/Internal/State.hs:13:28-35 0.0 0.0 0 0
execState Utils.Containers.Internal.State src/Utils/Containers/Internal/State.hs:36:1-34 0.0 0.0 0 0
CAF Utils.Containers.Internal.StrictPair <entire-module> 0.0 0.0 0 0
CAF Utils.Containers.Internal.BitQueue <entire-module> 0.0 0.0 0 0
toListQ Utils.Containers.Internal.BitQueue src/Utils/Containers/Internal/BitQueue.hs:(119,1)-(121,38) 0.0 0.0 0 0
CAF Utils.Containers.Internal.BitUtil <entire-module> 0.0 0.0 0 0
shiftRL Utils.Containers.Internal.BitUtil src/Utils/Containers/Internal/BitUtil.hs:73:1-22 0.0 0.0 0 0
shiftLL Utils.Containers.Internal.BitUtil src/Utils/Containers/Internal/BitUtil.hs:74:1-22 0.0 0.0 0 0
CAF Data.Tree <entire-module> 0.0 0.0 0 0
unfoldTreeM_BF Data.Tree src/Data/Tree.hs:(495,1)-(499,40) 0.0 0.0 0 0
unfoldTreeM Data.Tree src/Data/Tree.hs:(479,1)-(482,22) 0.0 0.0 0 0
unfoldTree Data.Tree src/Data/Tree.hs:465:1-64 0.0 0.0 0 0
unfoldForestM_BF Data.Tree src/Data/Tree.hs:508:1-62 0.0 0.0 0 0
unfoldForestM Data.Tree src/Data/Tree.hs:486:1-46 0.0 0.0 0 0
unfoldForest Data.Tree src/Data/Tree.hs:475:1-35 0.0 0.0 0 0
subForest Data.Tree src/Data/Tree.hs:92:9-17 0.0 0.0 0 0
rootLabel Data.Tree src/Data/Tree.hs:91:9-17 0.0 0.0 0 0
levels Data.Tree src/Data/Tree.hs:(390,1)-(393,41) 0.0 0.0 0 0
foldTree Data.Tree src/Data/Tree.hs:(427,1)-(428,36) 0.0 0.0 0 0
flatten Data.Tree src/Data/Tree.hs:374:1-16 0.0 0.0 0 0
drawTree Data.Tree src/Data/Tree.hs:327:1-26 0.0 0.0 0 0
drawForest Data.Tree src/Data/Tree.hs:348:1-36 0.0 0.0 0 0
CAF Data.Sequence.Internal <entire-module> 0.0 0.0 0 0
|> Data.Sequence.Internal src/Data/Sequence/Internal.hs:1853:1-45 0.0 0.0 0 0
zipWith4 Data.Sequence.Internal src/Data/Sequence/Internal.hs:(4927,1)-(4933,24) 0.0 0.0 0 0
zipWith3 Data.Sequence.Internal src/Data/Sequence/Internal.hs:(4908,1)-(4913,24) 0.0 0.0 0 0
zipWith Data.Sequence.Internal src/Data/Sequence/Internal.hs:(4886,1)-(4890,24) 0.0 0.0 0 0
zip4 Data.Sequence.Internal src/Data/Sequence/Internal.hs:4921:1-21 0.0 0.0 0 0
zip3 Data.Sequence.Internal src/Data/Sequence/Internal.hs:4902:1-20 0.0 0.0 0 0
zip Data.Sequence.Internal src/Data/Sequence/Internal.hs:4879:1-17 0.0 0.0 0 0
viewr Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2284,1)-(2286,42) 0.0 0.0 0 0
viewl Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2217,1)-(2219,42) 0.0 0.0 0 0
update Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2459,1)-(2462,24) 0.0 0.0 0 0
unzipWith Data.Sequence.Internal src/Data/Sequence/Internal.hs:(4702,1)-(4707,11) 0.0 0.0 0 0
unzip Data.Sequence.Internal src/Data/Sequence/Internal.hs:4683:1-26 0.0 0.0 0 0
unfoldr Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2132,1)-(2134,81) 0.0 0.0 0 0
unfoldl Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2138,1)-(2139,81) 0.0 0.0 0 0
traverseWithIndex Data.Sequence.Internal src/Data/Sequence/Internal.hs:(3208,1)-(3277,28) 0.0 0.0 0 0
takeWhileR Data.Sequence.Internal src/Data/Sequence/Internal.hs:4047:1-28 0.0 0.0 0 0
takeWhileL Data.Sequence.Internal src/Data/Sequence/Internal.hs:4039:1-28 0.0 0.0 0 0
take Data.Sequence.Internal src/Data/Sequence/Internal.hs:(3383,1)-(3388,18) 0.0 0.0 0 0
tails Data.Sequence.Internal src/Data/Sequence/Internal.hs:3918:1-66 0.0 0.0 0 0
splitAt Data.Sequence.Internal src/Data/Sequence/Internal.hs:(3709,1)-(3719,27) 0.0 0.0 0 0
spanr Data.Sequence.Internal src/Data/Sequence/Internal.hs:4073:1-26 0.0 0.0 0 0
spanl Data.Sequence.Internal src/Data/Sequence/Internal.hs:4066:1-26 0.0 0.0 0 0
singleton Data.Sequence.Internal src/Data/Sequence/Internal.hs:1696:1-40 0.0 0.0 0 0
scanr1 Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2335,1)-(2337,36) 0.0 0.0 0 0
scanr Data.Sequence.Internal src/Data/Sequence/Internal.hs:2331:1-81 0.0 0.0 0 0
scanl1 Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2325,1)-(2327,36) 0.0 0.0 0 0
scanl Data.Sequence.Internal src/Data/Sequence/Internal.hs:2319:1-81 0.0 0.0 0 0
reverse Data.Sequence.Internal src/Data/Sequence/Internal.hs:4417:1-46 0.0 0.0 0 0
replicateM Data.Sequence.Internal src/Data/Sequence/Internal.hs:1721:1-23 0.0 0.0 0 0
replicateA Data.Sequence.Internal src/Data/Sequence/Internal.hs:(1709,1)-(1711,73) 0.0 0.0 0 0
replicate Data.Sequence.Internal src/Data/Sequence/Internal.hs:(1700,1)-(1702,72) 0.0 0.0 0 0
partition Data.Sequence.Internal src/Data/Sequence/Internal.hs:(4096,1)-(4100,43) 0.0 0.0 0 0
null Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2156,1)-(2157,26) 0.0 0.0 0 0
mapWithIndex Data.Sequence.Internal src/Data/Sequence/Internal.hs:(3060,1)-(3105,28) 0.0 0.0 0 0
lookup Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2379,1)-(2387,23) 0.0 0.0 0 0
liftA2Seq Data.Sequence.Internal src/Data/Sequence/Internal.hs:(598,1)-(617,22) 0.0 0.0 0 0
length Data.Sequence.Internal src/Data/Sequence/Internal.hs:2161:1-26 0.0 0.0 0 0
iterateN Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2146,1)-(2148,71) 0.0 0.0 0 0
intersperse Data.Sequence.Internal src/Data/Sequence/Internal.hs:(892,1)-(894,53) 0.0 0.0 0 0
insertAt Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2635,1)-(2639,22) 0.0 0.0 0 0
inits Data.Sequence.Internal src/Data/Sequence/Internal.hs:3928:1-66 0.0 0.0 0 0
index Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2353,1)-(2358,78) 0.0 0.0 0 0
getElem Data.Sequence.Internal src/Data/Sequence/Internal.hs:1375:27-33 0.0 0.0 0 0
fromList Data.Sequence.Internal src/Data/Sequence/Internal.hs:(4223,1)-(4392,27) 0.0 0.0 0 0
fromFunction Data.Sequence.Internal src/Data/Sequence/Internal.hs:(3321,1)-(3357,28) 0.0 0.0 0 0
fromArray Data.Sequence.Internal src/Data/Sequence/Internal.hs:(3367,1)-(3371,48) 0.0 0.0 0 0
foldMapWithIndex Data.Sequence.Internal src/Data/Sequence/Internal.hs:(3152,1)-(3197,60) 0.0 0.0 0 0
findIndexR Data.Sequence.Internal src/Data/Sequence/Internal.hs:4138:1-44 0.0 0.0 0 0
findIndexL Data.Sequence.Internal src/Data/Sequence/Internal.hs:4133:1-44 0.0 0.0 0 0
filter Data.Sequence.Internal src/Data/Sequence/Internal.hs:4106:1-68 0.0 0.0 0 0
empty Data.Sequence.Internal src/Data/Sequence/Internal.hs:1692:1-29 0.0 0.0 0 0
elemIndicesR Data.Sequence.Internal src/Data/Sequence/Internal.hs:4128:1-36 0.0 0.0 0 0
elemIndicesL Data.Sequence.Internal src/Data/Sequence/Internal.hs:4123:1-36 0.0 0.0 0 0
elemIndexR Data.Sequence.Internal src/Data/Sequence/Internal.hs:4118:1-32 0.0 0.0 0 0
elemIndexL Data.Sequence.Internal src/Data/Sequence/Internal.hs:4113:1-32 0.0 0.0 0 0
dropWhileR Data.Sequence.Internal src/Data/Sequence/Internal.hs:4059:1-28 0.0 0.0 0 0
dropWhileL Data.Sequence.Internal src/Data/Sequence/Internal.hs:4052:1-28 0.0 0.0 0 0
drop Data.Sequence.Internal src/Data/Sequence/Internal.hs:(3545,1)-(3550,21) 0.0 0.0 0 0
deleteAt Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2788,1)-(2790,22) 0.0 0.0 0 0
cycleTaking Data.Sequence.Internal src/Data/Sequence/Internal.hs:(1735,1)-(1739,41) 0.0 0.0 0 0
chunksOf Data.Sequence.Internal src/Data/Sequence/Internal.hs:(3899,1)-(3908,50) 0.0 0.0 0 0
adjust' Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2548,1)-(2552,20) 0.0 0.0 0 0
adjust Data.Sequence.Internal src/Data/Sequence/Internal.hs:(2528,1)-(2531,24) 0.0 0.0 0 0
>< Data.Sequence.Internal src/Data/Sequence/Internal.hs:1889:1-42 0.0 0.0 0 0
<| Data.Sequence.Internal src/Data/Sequence/Internal.hs:1804:1-45 0.0 0.0 0 0
!? Data.Sequence.Internal src/Data/Sequence/Internal.hs:2393:1-18 0.0 0.0 0 0
CAF Data.Set.Internal <entire-module> 0.0 0.0 0 0
valid Data.Set.Internal src/Data/Set/Internal.hs:(2028,1)-(2029,42) 0.0 0.0 0 0
unions Data.Set.Internal src/Data/Set/Internal.hs:813:1-36 0.0 0.0 0 0
union Data.Set.Internal src/Data/Set/Internal.hs:(821,1)-(830,29) 0.0 0.0 0 0
toDescList Data.Set.Internal src/Data/Set/Internal.hs:1055:1-32 0.0 0.0 0 0
toAscList Data.Set.Internal src/Data/Set/Internal.hs:1050:1-24 0.0 0.0 0 0
takeWhileAntitone Data.Set.Internal src/Data/Set/Internal.hs:(1487,1)-(1490,37) 0.0 0.0 0 0
take Data.Set.Internal src/Data/Set/Internal.hs:(1421,1)-(1431,26) 0.0 0.0 0 0
splitMember Data.Set.Internal src/Data/Set/Internal.hs:(1301,1)-(1310,25) 0.0 0.0 0 0
splitAt Data.Set.Internal src/Data/Set/Internal.hs:(1460,1)-(1473,26) 0.0 0.0 0 0
split Data.Set.Internal src/Data/Set/Internal.hs:1286:1-31 0.0 0.0 0 0
spanAntitone Data.Set.Internal src/Data/Set/Internal.hs:(1526,1)-(1531,60) 0.0 0.0 0 0
showTreeWith Data.Set.Internal src/Data/Set/Internal.hs:(1975,1)-(1977,43) 0.0 0.0 0 0
showTree Data.Set.Internal src/Data/Set/Internal.hs:(1935,1)-(1936,29) 0.0 0.0 0 0
powerSet Data.Set.Internal src/Data/Set/Internal.hs:(1840,1)-(1841,82) 0.0 0.0 0 0
partition Data.Set.Internal src/Data/Set/Internal.hs:(921,1)-(932,42) 0.0 0.0 0 0
notMember Data.Set.Internal src/Data/Set/Internal.hs:404:1-32 0.0 0.0 0 0
minView Data.Set.Internal src/Data/Set/Internal.hs:(1632,1)-(1633,58) 0.0 0.0 0 0
merge Data.Set.Internal src/Data/Set/Internal.hs:(1586,1)-(1591,34) 0.0 0.0 0 0
member Data.Set.Internal src/Data/Set/Internal.hs:(389,1)-(395,16) 0.0 0.0 0 0
maxView Data.Set.Internal src/Data/Set/Internal.hs:(1646,1)-(1647,58) 0.0 0.0 0 0
mapMonotonic Data.Set.Internal src/Data/Set/Internal.hs:(961,1)-(962,82) 0.0 0.0 0 0
map Data.Set.Internal src/Data/Set/Internal.hs:945:1-38 0.0 0.0 0 0
lookupMin Data.Set.Internal src/Data/Set/Internal.hs:(769,1)-(770,51) 0.0 0.0 0 0
lookupMax Data.Set.Internal src/Data/Set/Internal.hs:(787,1)-(788,51) 0.0 0.0 0 0
lookupLT Data.Set.Internal src/Data/Set/Internal.hs:(416,1)-(424,58) 0.0 0.0 0 0
lookupLE Data.Set.Internal src/Data/Set/Internal.hs:(457,1)-(467,72) 0.0 0.0 0 0
lookupIndex Data.Set.Internal src/Data/Set/Internal.hs:(1358,1)-(1365,32) 0.0 0.0 0 0
lookupGT Data.Set.Internal src/Data/Set/Internal.hs:(436,1)-(444,61) 0.0 0.0 0 0
lookupGE Data.Set.Internal src/Data/Set/Internal.hs:(480,1)-(490,75) 0.0 0.0 0 0
link Data.Set.Internal src/Data/Set/Internal.hs:(1560,1)-(1565,36) 0.0 0.0 0 0
isSubsetOf Data.Set.Internal src/Data/Set/Internal.hs:(682,1)-(683,43) 0.0 0.0 0 0
isProperSubsetOf Data.Set.Internal src/Data/Set/Internal.hs:(665,1)-(666,44) 0.0 0.0 0 0
intersections Data.Set.Internal src/Data/Set/Internal.hs:(888,1)-(892,46) 0.0 0.0 0 0
intersection Data.Set.Internal src/Data/Set/Internal.hs:(871,1)-(881,30) 0.0 0.0 0 0
insert Data.Set.Internal src/Data/Set/Internal.hs:(520,1)-(532,48) 0.0 0.0 0 0
getIntersection Data.Set.Internal src/Data/Set/Internal.hs:895:41-55 0.0 0.0 0 0
fromList Data.Set.Internal src/Data/Set/Internal.hs:(1094,1)-(1127,86) 0.0 0.0 0 0
fromDistinctDescList Data.Set.Internal src/Data/Set/Internal.hs:(1200,1)-(1214,57) 0.0 0.0 0 0
fromDistinctAscList Data.Set.Internal src/Data/Set/Internal.hs:(1176,1)-(1190,57) 0.0 0.0 0 0
fromDescList Data.Set.Internal src/Data/Set/Internal.hs:1151:1-53 0.0 0.0 0 0
fromAscList Data.Set.Internal src/Data/Set/Internal.hs:1141:1-51 0.0 0.0 0 0
findMin Data.Set.Internal src/Data/Set/Internal.hs:(774,1)-(776,69) 0.0 0.0 0 0
findMax Data.Set.Internal src/Data/Set/Internal.hs:(792,1)-(794,69) 0.0 0.0 0 0
findIndex Data.Set.Internal src/Data/Set/Internal.hs:(1333,1)-(1340,24) 0.0 0.0 0 0
filter Data.Set.Internal src/Data/Set/Internal.hs:(907,1)-(915,22) 0.0 0.0 0 0
elemAt Data.Set.Internal src/Data/Set/Internal.hs:(1381,1)-(1388,18) 0.0 0.0 0 0
dropWhileAntitone Data.Set.Internal src/Data/Set/Internal.hs:(1504,1)-(1507,48) 0.0 0.0 0 0
drop Data.Set.Internal src/Data/Set/Internal.hs:(1442,1)-(1452,26) 0.0 0.0 0 0
disjointUnion Data.Set.Internal src/Data/Set/Internal.hs:1927:1-74 0.0 0.0 0 0
disjoint Data.Set.Internal src/Data/Set/Internal.hs:(742,1)-(750,35) 0.0 0.0 0 0
difference Data.Set.Internal src/Data/Set/Internal.hs:(844,1)-(851,35) 0.0 0.0 0 0
deleteMin Data.Set.Internal src/Data/Set/Internal.hs:(798,1)-(800,31) 0.0 0.0 0 0
deleteMax Data.Set.Internal src/Data/Set/Internal.hs:(804,1)-(806,31) 0.0 0.0 0 0
deleteFindMin Data.Set.Internal src/Data/Set/Internal.hs:(1609,1)-(1611,100) 0.0 0.0 0 0
deleteFindMax Data.Set.Internal src/Data/Set/Internal.hs:(1617,1)-(1619,100) 0.0 0.0 0 0
deleteAt Data.Set.Internal src/Data/Set/Internal.hs:(1402,1)-(1410,22) 0.0 0.0 0 0
delete Data.Set.Internal src/Data/Set/Internal.hs:(572,1)-(583,22) 0.0 0.0 0 0
cartesianProduct Data.Set.Internal src/Data/Set/Internal.hs:(1895,1)-(1898,69) 0.0 0.0 0 0
balanced Data.Set.Internal src/Data/Set/Internal.hs:(2041,1)-(2045,45) 0.0 0.0 0 0
alterF Data.Set.Internal src/Data/Set/Internal.hs:(606,1)-(613,26) 0.0 0.0 0 0
\\ Data.Set.Internal src/Data/Set/Internal.hs:274:1-27 0.0 0.0 0 0
CAF Data.Map.Internal <entire-module> 0.0 0.0 0 0
withoutKeys Data.Map.Internal src/Data/Map/Internal.hs:(1913,1)-(1921,31) 0.0 0.0 0 0
updateWithKey Data.Map.Internal src/Data/Map/Internal.hs:(1081,1)-(1091,38) 0.0 0.0 0 0
updateMinWithKey Data.Map.Internal src/Data/Map/Internal.hs:(1706,1)-(1710,79) 0.0 0.0 0 0
updateMin Data.Map.Internal src/Data/Map/Internal.hs:(1687,1)-(1688,36) 0.0 0.0 0 0
updateMaxWithKey Data.Map.Internal src/Data/Map/Internal.hs:(1718,1)-(1722,79) 0.0 0.0 0 0
updateMax Data.Map.Internal src/Data/Map/Internal.hs:(1696,1)-(1697,36) 0.0 0.0 0 0
updateLookupWithKey Data.Map.Internal src/Data/Map/Internal.hs:(1109,1)-(1124,55) 0.0 0.0 0 0
updateAt Data.Map.Internal src/Data/Map/Internal.hs:(1574,1)-(1584,22) 0.0 0.0 0 0
update Data.Map.Internal src/Data/Map/Internal.hs:1062:1-38 0.0 0.0 0 0
unionsWith Data.Map.Internal src/Data/Map/Internal.hs:(1803,1)-(1804,42) 0.0 0.0 0 0
unions Data.Map.Internal src/Data/Map/Internal.hs:(1790,1)-(1791,34) 0.0 0.0 0 0
unionWithKey Data.Map.Internal src/Data/Map/Internal.hs:(1860,1)-(1869,38) 0.0 0.0 0 0
unionWith Data.Map.Internal src/Data/Map/Internal.hs:(1839,1)-(1848,35) 0.0 0.0 0 0
union Data.Map.Internal src/Data/Map/Internal.hs:(1817,1)-(1825,36) 0.0 0.0 0 0
traverseMaybeWithKey Data.Map.Internal src/Data/Map/Internal.hs:(2999,1)-(3007,37) 0.0 0.0 0 0
toDescList Data.Map.Internal src/Data/Map/Internal.hs:3510:1-50 0.0 0.0 0 0
toAscList Data.Map.Internal src/Data/Map/Internal.hs:3502:1-49 0.0 0.0 0 0
takeWhileAntitone Data.Map.Internal src/Data/Map/Internal.hs:(2893,1)-(2896,37) 0.0 0.0 0 0
take Data.Map.Internal src/Data/Map/Internal.hs:(1504,1)-(1514,26) 0.0 0.0 0 0
splitLookup Data.Map.Internal src/Data/Map/Internal.hs:(3817,1)-(3831,41) 0.0 0.0 0 0
splitAt Data.Map.Internal src/Data/Map/Internal.hs:(1545,1)-(1558,26) 0.0 0.0 0 0
split Data.Map.Internal src/Data/Map/Internal.hs:(3795,1)-(3803,25) 0.0 0.0 0 0
spanAntitone Data.Map.Internal src/Data/Map/Internal.hs:(2932,1)-(2937,63) 0.0 0.0 0 0
restrictKeys Data.Map.Internal src/Data/Map/Internal.hs:(1994,1)-(2004,30) 0.0 0.0 0 0
partitionWithKey Data.Map.Internal src/Data/Map/Internal.hs:(2960,1)-(2973,28) 0.0 0.0 0 0
partition Data.Map.Internal src/Data/Map/Internal.hs:(2948,1)-(2949,36) 0.0 0.0 0 0
notMember Data.Map.Internal src/Data/Map/Internal.hs:605:1-32 0.0 0.0 0 0
missingSubtree Data.Map.Internal src/Data/Map/Internal.hs:2109:5-18 0.0 0.0 0 0
missingKey Data.Map.Internal src/Data/Map/Internal.hs:2110:5-14 0.0 0.0 0 0
minView Data.Map.Internal src/Data/Map/Internal.hs:(1762,1)-(1764,48) 0.0 0.0 0 0
member Data.Map.Internal src/Data/Map/Internal.hs:(586,1)-(592,16) 0.0 0.0 0 0
maxView Data.Map.Internal src/Data/Map/Internal.hs:(1774,1)-(1776,48) 0.0 0.0 0 0
matchedKey Data.Map.Internal src/Data/Map/Internal.hs:2229:5-14 0.0 0.0 0 0
mapWithKey Data.Map.Internal src/Data/Map/Internal.hs:(3071,1)-(3072,85) 0.0 0.0 0 0
mapMaybeWithKey Data.Map.Internal src/Data/Map/Internal.hs:(2989,1)-(2992,62) 0.0 0.0 0 0
mapMaybe Data.Map.Internal src/Data/Map/Internal.hs:2981:1-42 0.0 0.0 0 0
mapKeysWith Data.Map.Internal src/Data/Map/Internal.hs:3170:1-77 0.0 0.0 0 0
mapKeysMonotonic Data.Map.Internal src/Data/Map/Internal.hs:(3195,1)-(3197,64) 0.0 0.0 0 0
mapKeys Data.Map.Internal src/Data/Map/Internal.hs:3153:1-65 0.0 0.0 0 0
mapEitherWithKey Data.Map.Internal src/Data/Map/Internal.hs:(3032,1)-(3040,28) 0.0 0.0 0 0
mapEither Data.Map.Internal src/Data/Map/Internal.hs:(3019,1)-(3020,36) 0.0 0.0 0 0
mapAccumWithKey Data.Map.Internal src/Data/Map/Internal.hs:(3118,1)-(3119,19) 0.0 0.0 0 0
mapAccumRWithKey Data.Map.Internal src/Data/Map/Internal.hs:(3134,1)-(3139,28) 0.0 0.0 0 0
mapAccum Data.Map.Internal src/Data/Map/Internal.hs:(3108,1)-(3109,45) 0.0 0.0 0 0
map Data.Map.Internal src/Data/Map/Internal.hs:(3050,1)-(3052,54) 0.0 0.0 0 0
lookupMin Data.Map.Internal src/Data/Map/Internal.hs:(1623,1)-(1624,55) 0.0 0.0 0 0
lookupMax Data.Map.Internal src/Data/Map/Internal.hs:(1648,1)-(1649,55) 0.0 0.0 0 0
lookupLT Data.Map.Internal src/Data/Map/Internal.hs:(654,1)-(662,66) 0.0 0.0 0 0
lookupLE Data.Map.Internal src/Data/Map/Internal.hs:(697,1)-(707,81) 0.0 0.0 0 0
lookupIndex Data.Map.Internal src/Data/Map/Internal.hs:(1464,1)-(1471,32) 0.0 0.0 0 0
lookupGT Data.Map.Internal src/Data/Map/Internal.hs:(675,1)-(683,68) 0.0 0.0 0 0
lookupGE Data.Map.Internal src/Data/Map/Internal.hs:(721,1)-(731,83) 0.0 0.0 0 0
lookup Data.Map.Internal src/Data/Map/Internal.hs:(568,1)-(574,18) 0.0 0.0 0 0
link2 Data.Map.Internal src/Data/Map/Internal.hs:(3914,1)-(3919,34) 0.0 0.0 0 0
link Data.Map.Internal src/Data/Map/Internal.hs:(3888,1)-(3893,39) 0.0 0.0 0 64
keysSet Data.Map.Internal src/Data/Map/Internal.hs:(3366,1)-(3367,65) 0.0 0.0 0 0
keys Data.Map.Internal src/Data/Map/Internal.hs:3348:1-42 0.0 0.0 0 0
isSubmapOfBy Data.Map.Internal src/Data/Map/Internal.hs:(2780,1)-(2781,41) 0.0 0.0 0 0
isSubmapOf Data.Map.Internal src/Data/Map/Internal.hs:2754:1-42 0.0 0.0 0 0
isProperSubmapOfBy Data.Map.Internal src/Data/Map/Internal.hs:(2836,1)-(2837,40) 0.0 0.0 0 0
isProperSubmapOf Data.Map.Internal src/Data/Map/Internal.hs:(2811,1)-(2812,33) 0.0 0.0 0 0
intersectionWithKey Data.Map.Internal src/Data/Map/Internal.hs:(2035,1)-(2043,39) 0.0 0.0 0 0
intersectionWith Data.Map.Internal src/Data/Map/Internal.hs:(2016,1)-(2024,36) 0.0 0.0 0 0
intersection Data.Map.Internal src/Data/Map/Internal.hs:(1969,1)-(1979,30) 0.0 0.0 0 0
insertWithKey Data.Map.Internal src/Data/Map/Internal.hs:(908,1)-(916,42) 0.0 0.0 0 0
insertWith Data.Map.Internal src/Data/Map/Internal.hs:(853,1)-(865,39) 0.0 0.0 0 0
insertMax Data.Map.Internal src/Data/Map/Internal.hs:(3898,1)-(3902,47) 0.0 0.0 0 0
insertLookupWithKey Data.Map.Internal src/Data/Map/Internal.hs:(962,1)-(974,55) 0.0 0.0 0 0
insert Data.Map.Internal src/Data/Map/Internal.hs:(774,1)-(791,54) 0.0 0.0 0 2904
glue Data.Map.Internal src/Data/Map/Internal.hs:(3926,1)-(3930,86) 0.0 0.0 0 0
fromSet Data.Map.Internal src/Data/Map/Internal.hs:(3385,1)-(3386,73) 0.0 0.0 0 0
fromListWithKey Data.Map.Internal src/Data/Map/Internal.hs:(3480,1)-(3483,39) 0.0 0.0 0 0
fromListWith Data.Map.Internal src/Data/Map/Internal.hs:(3467,1)-(3468,40) 0.0 0.0 0 0
fromList Data.Map.Internal src/Data/Map/Internal.hs:(3423,1)-(3456,89) 0.0 0.0 0 160
fromDistinctDescList Data.Map.Internal src/Data/Map/Internal.hs:(3733,1)-(3747,61) 0.0 0.0 0 0
fromDistinctAscList Data.Map.Internal src/Data/Map/Internal.hs:(3705,1)-(3719,60) 0.0 0.0 0 0
fromDescListWithKey Data.Map.Internal src/Data/Map/Internal.hs:(3676,1)-(3689,36) 0.0 0.0 0 0
fromDescListWith Data.Map.Internal src/Data/Map/Internal.hs:(3633,1)-(3634,44) 0.0 0.0 0 0
fromDescList Data.Map.Internal src/Data/Map/Internal.hs:(3592,1)-(3604,36) 0.0 0.0 0 0
fromAscListWithKey Data.Map.Internal src/Data/Map/Internal.hs:(3649,1)-(3662,36) 0.0 0.0 0 0
fromAscListWith Data.Map.Internal src/Data/Map/Internal.hs:(3617,1)-(3618,43) 0.0 0.0 0 0
fromAscList Data.Map.Internal src/Data/Map/Internal.hs:(3563,1)-(3576,36) 0.0 0.0 0 0
fromArgSet Data.Map.Internal src/Data/Map/Internal.hs:(3394,1)-(3395,80) 0.0 0.0 0 0
findWithDefault Data.Map.Internal src/Data/Map/Internal.hs:(635,1)-(641,13) 0.0 0.0 0 0
findMin Data.Map.Internal src/Data/Map/Internal.hs:(1632,1)-(1634,69) 0.0 0.0 0 0
findMax Data.Map.Internal src/Data/Map/Internal.hs:(1657,1)-(1659,69) 0.0 0.0 0 0
findIndex Data.Map.Internal src/Data/Map/Internal.hs:(1441,1)-(1448,24) 0.0 0.0 0 0
filterWithKey Data.Map.Internal src/Data/Map/Internal.hs:(2860,1)-(2867,31) 0.0 0.0 0 0
filter Data.Map.Internal src/Data/Map/Internal.hs:(2852,1)-(2853,33) 0.0 0.0 0 0
elems Data.Map.Internal src/Data/Map/Internal.hs:3339:1-20 0.0 0.0 0 0
elemAt Data.Map.Internal src/Data/Map/Internal.hs:(1485,1)-(1492,18) 0.0 0.0 0 0
dropWhileAntitone Data.Map.Internal src/Data/Map/Internal.hs:(2910,1)-(2913,51) 0.0 0.0 0 0
drop Data.Map.Internal src/Data/Map/Internal.hs:(1525,1)-(1535,26) 0.0 0.0 0 0
disjoint Data.Map.Internal src/Data/Map/Internal.hs:(2067,1)-(2073,35) 0.0 0.0 0 0
differenceWithKey Data.Map.Internal src/Data/Map/Internal.hs:(1952,1)-(1953,59) 0.0 0.0 0 0
differenceWith Data.Map.Internal src/Data/Map/Internal.hs:(1936,1)-(1937,44) 0.0 0.0 0 0
difference Data.Map.Internal src/Data/Map/Internal.hs:(1890,1)-(1898,30) 0.0 0.0 0 0
delta Data.Map.Internal src/Data/Map/Internal.hs:4007:1-9 0.0 0.0 0 0
deleteMin Data.Map.Internal src/Data/Map/Internal.hs:(1667,1)-(1669,35) 0.0 0.0 0 0
deleteMax Data.Map.Internal src/Data/Map/Internal.hs:(1677,1)-(1679,35) 0.0 0.0 0 0
deleteFindMin Data.Map.Internal src/Data/Map/Internal.hs:(3959,1)-(3961,17) 0.0 0.0 0 0
deleteFindMax Data.Map.Internal src/Data/Map/Internal.hs:(3969,1)-(3971,17) 0.0 0.0 0 0
deleteAt Data.Map.Internal src/Data/Map/Internal.hs:(1596,1)-(1604,22) 0.0 0.0 0 0
delete Data.Map.Internal src/Data/Map/Internal.hs:(993,1)-(1005,26) 0.0 0.0 0 0
compose Data.Map.Internal src/Data/Map/Internal.hs:(2096,1)-(2098,35) 0.0 0.0 0 0
balanceR Data.Map.Internal src/Data/Map/Internal.hs:(4106,1)-(4125,50) 0.0 0.0 0 4512
balanceL Data.Map.Internal src/Data/Map/Internal.hs:(4081,1)-(4100,50) 0.0 0.0 0 4368
balance Data.Map.Internal src/Data/Map/Internal.hs:(4042,1)-(4071,50) 0.0 0.0 0 0
argSet Data.Map.Internal src/Data/Map/Internal.hs:(3375,1)-(3376,70) 0.0 0.0 0 0
alterF Data.Map.Internal src/Data/Map/Internal.hs:1212:1-35 0.0 0.0 0 0
alter Data.Map.Internal src/Data/Map/Internal.hs:(1147,1)-(1159,42) 0.0 0.0 0 0
adjustWithKey Data.Map.Internal src/Data/Map/Internal.hs:(1037,1)-(1045,39) 0.0 0.0 0 0
adjust Data.Map.Internal src/Data/Map/Internal.hs:1021:1-38 0.0 0.0 0 0
CAF Data.Map.Strict.Internal <entire-module> 0.0 0.0 0 0
updateWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(736,1)-(746,38) 0.0 0.0 0 0
updateMinWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(937,1)-(941,79) 0.0 0.0 0 0
updateMin Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(918,1)-(919,36) 0.0 0.0 0 0
updateMaxWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(949,1)-(953,79) 0.0 0.0 0 0
updateMax Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(927,1)-(928,36) 0.0 0.0 0 0
updateLookupWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(764,1)-(776,55) 0.0 0.0 0 0
updateAt Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(896,1)-(906,22) 0.0 0.0 0 0
update Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:717:1-38 0.0 0.0 0 0
unionsWith Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(966,1)-(967,42) 0.0 0.0 0 0
unionWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(998,1)-(1004,38) 0.0 0.0 0 0
unionWith Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(980,1)-(986,35) 0.0 0.0 0 0
traverseMaybeWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1292,1)-(1300,38) 0.0 0.0 0 0
mapWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1364,1)-(1367,60) 0.0 0.0 0 0
mapWhenMissing Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1088,1)-(1090,71) 0.0 0.0 0 0
mapWhenMatched Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1094,1)-(1095,80) 0.0 0.0 0 0
mapMaybeWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1281,1)-(1284,62) 0.0 0.0 0 0
mapMaybe Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:1273:1-42 0.0 0.0 0 0
mapKeysWith Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:1455:1-77 0.0 0.0 0 0
mapEitherWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1325,1)-(1333,28) 0.0 0.0 0 0
mapEither Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1312,1)-(1313,36) 0.0 0.0 0 0
mapAccumWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1420,1)-(1421,19) 0.0 0.0 0 0
mapAccumRWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1436,1)-(1441,37) 0.0 0.0 0 0
mapAccum Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1410,1)-(1411,45) 0.0 0.0 0 0
map Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1343,1)-(1346,70) 0.0 0.0 0 0
intersectionWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1073,1)-(1081,39) 0.0 0.0 0 0
intersectionWith Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1054,1)-(1062,36) 0.0 0.0 0 0
insertWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(588,1)-(599,37) 0.0 0.0 0 0
insertWith Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(543,1)-(551,53) 0.0 0.0 0 0
insertLookupWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(644,1)-(655,59) 0.0 0.0 0 0
insert Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(517,1)-(525,33) 0.0 0.0 0 0
fromSet Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1471,1)-(1472,94) 0.0 0.0 0 0
fromListWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1557,1)-(1560,39) 0.0 0.0 0 0
fromListWith Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1544,1)-(1545,40) 0.0 0.0 0 0
fromList Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1500,1)-(1533,97) 0.0 0.0 0 0
fromDistinctDescList Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1726,1)-(1741,68) 0.0 0.0 0 0
fromDistinctAscList Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1699,1)-(1714,68) 0.0 0.0 0 0
fromDescListWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1671,1)-(1684,36) 0.0 0.0 0 0
fromDescListWith Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1627,1)-(1628,44) 0.0 0.0 0 0
fromDescList Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1599,1)-(1600,40) 0.0 0.0 0 0
fromAscListWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1643,1)-(1656,36) 0.0 0.0 0 0
fromAscListWith Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1613,1)-(1614,43) 0.0 0.0 0 0
fromAscList Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1585,1)-(1586,39) 0.0 0.0 0 0
fromArgSet Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(1480,1)-(1481,88) 0.0 0.0 0 0
findWithDefault Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(477,1)-(483,13) 0.0 0.0 0 0
differenceWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:1039:1-79 0.0 0.0 0 0
differenceWith Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:1024:1-96 0.0 0.0 0 0
alterF Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:860:1-37 0.0 0.0 0 0
alter Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(799,1)-(811,42) 0.0 0.0 0 0
adjustWithKey Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:(691,1)-(700,31) 0.0 0.0 0 0
adjust Data.Map.Strict.Internal src/Data/Map/Strict/Internal.hs:675:1-38 0.0 0.0 0 0
CAF Data.IntSet.Internal <entire-module> 0.0 0.0 0 0
unions Data.IntSet.Internal src/Data/IntSet/Internal.hs:(549,1)-(550,34) 0.0 0.0 0 0
union Data.IntSet.Internal src/Data/IntSet/Internal.hs:(555,1)-(572,15) 0.0 0.0 0 0
toDescList Data.IntSet.Internal src/Data/IntSet/Internal.hs:1179:1-32 0.0 0.0 0 0
toAscList Data.IntSet.Internal src/Data/IntSet/Internal.hs:1174:1-24 0.0 0.0 0 0
takeWhileAntitone Data.IntSet.Internal src/Data/IntSet/Internal.hs:(802,1)-(815,18) 0.0 0.0 0 0
splitMember Data.IntSet.Internal src/Data/IntSet/Internal.hs:(921,1)-(961,32) 0.0 0.0 0 0
split Data.IntSet.Internal src/Data/IntSet/Internal.hs:(887,1)-(916,28) 0.0 0.0 0 0
spanAntitone Data.IntSet.Internal src/Data/IntSet/Internal.hs:(856,1)-(879,28) 0.0 0.0 0 0
size Data.IntSet.Internal src/Data/IntSet/Internal.hs:(334,1)-(338,20) 0.0 0.0 0 0
showTreeWith Data.IntSet.Internal src/Data/IntSet/Internal.hs:(1371,1)-(1373,43) 0.0 0.0 0 0
showTree Data.IntSet.Internal src/Data/IntSet/Internal.hs:(1361,1)-(1362,29) 0.0 0.0 0 0
partition Data.IntSet.Internal src/Data/IntSet/Internal.hs:(775,1)-(789,34) 0.0 0.0 0 0
notMember Data.IntSet.Internal src/Data/IntSet/Internal.hs:355:1-28 0.0 0.0 0 0
minView Data.IntSet.Internal src/Data/IntSet/Internal.hs:(982,1)-(989,32) 0.0 0.0 0 0
member Data.IntSet.Internal src/Data/IntSet/Internal.hs:(344,1)-(351,18) 0.0 0.0 0 0
maxView Data.IntSet.Internal src/Data/IntSet/Internal.hs:(970,1)-(977,32) 0.0 0.0 0 0
mapMonotonic Data.IntSet.Internal src/Data/IntSet/Internal.hs:1068:1-61 0.0 0.0 0 0
map Data.IntSet.Internal src/Data/IntSet/Internal.hs:1052:1-38 0.0 0.0 0 0
lookupLT Data.IntSet.Internal src/Data/IntSet/Internal.hs:(364,1)-(375,34) 0.0 0.0 0 0
lookupLE Data.IntSet.Internal src/Data/IntSet/Internal.hs:(407,1)-(418,34) 0.0 0.0 0 0
lookupGT Data.IntSet.Internal src/Data/IntSet/Internal.hs:(385,1)-(396,34) 0.0 0.0 0 0
lookupGE Data.IntSet.Internal src/Data/IntSet/Internal.hs:(429,1)-(440,34) 0.0 0.0 0 0
isSubsetOf Data.IntSet.Internal src/Data/IntSet/Internal.hs:(694,1)-(706,31) 0.0 0.0 0 0
isProperSubsetOf Data.IntSet.Internal src/Data/IntSet/Internal.hs:(653,1)-(656,17) 0.0 0.0 0 0
intersection Data.IntSet.Internal src/Data/IntSet/Internal.hs:(614,1)-(646,24) 0.0 0.0 0 0
insert Data.IntSet.Internal src/Data/IntSet/Internal.hs:479:1-46 0.0 0.0 0 0
fromList Data.IntSet.Internal src/Data/IntSet/Internal.hs:(1213,1)-(1216,25) 0.0 0.0 0 0
fromAscList Data.IntSet.Internal src/Data/IntSet/Internal.hs:1221:1-26 0.0 0.0 0 0
findMin Data.IntSet.Internal src/Data/IntSet/Internal.hs:(1006,1)-(1013,51) 0.0 0.0 0 0
findMax Data.IntSet.Internal src/Data/IntSet/Internal.hs:(1017,1)-(1024,51) 0.0 0.0 0 0
filter Data.IntSet.Internal src/Data/IntSet/Internal.hs:(762,1)-(771,30) 0.0 0.0 0 0
dropWhileAntitone Data.IntSet.Internal src/Data/IntSet/Internal.hs:(828,1)-(841,18) 0.0 0.0 0 0
disjoint Data.IntSet.Internal src/Data/IntSet/Internal.hs:(722,1)-(754,21) 0.0 0.0 0 0
difference Data.IntSet.Internal src/Data/IntSet/Internal.hs:(580,1)-(605,26) 0.0 0.0 0 0
deleteMin Data.IntSet.Internal src/Data/IntSet/Internal.hs:1032:1-35 0.0 0.0 0 0
deleteMax Data.IntSet.Internal src/Data/IntSet/Internal.hs:1039:1-35 0.0 0.0 0 0
deleteFindMin Data.IntSet.Internal src/Data/IntSet/Internal.hs:995:1-93 0.0 0.0 0 0
deleteFindMax Data.IntSet.Internal src/Data/IntSet/Internal.hs:1001:1-93 0.0 0.0 0 0
delete Data.IntSet.Internal src/Data/IntSet/Internal.hs:495:1-46 0.0 0.0 0 0
alterF Data.IntSet.Internal src/Data/IntSet/Internal.hs:(522,1)-(531,26) 0.0 0.0 0 0
\\ Data.IntSet.Internal src/Data/IntSet/Internal.hs:250:1-27 0.0 0.0 0 0
CAF Data.IntMap.Internal <entire-module> 0.0 0.0 0 0
withoutKeys Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1146,1)-(1172,23) 0.0 0.0 0 0
updateWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(959,1)-(967,27) 0.0 0.0 0 0
updateMinWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2128,1)-(2136,43) 0.0 0.0 0 0
updateMin Data.IntMap.Internal src/Data/IntMap/Internal.hs:2235:1-40 0.0 0.0 0 0
updateMaxWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2144,1)-(2152,43) 0.0 0.0 0 0
updateMax Data.IntMap.Internal src/Data/IntMap/Internal.hs:2227:1-40 0.0 0.0 0 0
updateLookupWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(980,1)-(990,43) 0.0 0.0 0 0
update Data.IntMap.Internal src/Data/IntMap/Internal.hs:(946,1)-(947,31) 0.0 0.0 0 0
unionsWith Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1072,1)-(1073,42) 0.0 0.0 0 0
unions Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1063,1)-(1064,34) 0.0 0.0 0 0
unionWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1099,1)-(1100,84) 0.0 0.0 0 0
unionWith Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1090,1)-(1091,40) 0.0 0.0 0 0
union Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1082,1)-(1083,39) 0.0 0.0 0 0
traverseMaybeWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1864,1)-(1870,50) 0.0 0.0 0 0
toDescList Data.IntMap.Internal src/Data/IntMap/Internal.hs:3148:1-50 0.0 0.0 0 0
toAscList Data.IntMap.Internal src/Data/IntMap/Internal.hs:3140:1-49 0.0 0.0 0 0
takeWhileAntitone Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2637,1)-(2652,18) 0.0 0.0 0 0
splitLookup Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2837,1)-(2859,48) 0.0 0.0 0 0
split Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2788,1)-(2814,28) 0.0 0.0 0 0
spanAntitone Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2695,1)-(2719,28) 0.0 0.0 0 0
size Data.IntMap.Internal src/Data/IntMap/Internal.hs:(550,1)-(554,20) 0.0 0.0 0 0
showTreeWith Data.IntMap.Internal src/Data/IntMap/Internal.hs:(3568,1)-(3570,43) 0.0 0.0 0 0
showTree Data.IntMap.Internal src/Data/IntMap/Internal.hs:(3558,1)-(3559,29) 0.0 0.0 0 0
restrictKeys Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1224,1)-(1250,24) 0.0 0.0 0 0
partitionWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2613,1)-(2624,28) 0.0 0.0 0 0
partition Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2601,1)-(2602,36) 0.0 0.0 0 0
notMember Data.IntMap.Internal src/Data/IntMap/Internal.hs:577:1-32 0.0 0.0 0 0
missingSubtree Data.IntMap.Internal src/Data/IntMap/Internal.hs:1422:5-18 0.0 0.0 0 0
missingKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:1423:5-14 0.0 0.0 0 0
minView Data.IntMap.Internal src/Data/IntMap/Internal.hs:2245:1-62 0.0 0.0 0 0
member Data.IntMap.Internal src/Data/IntMap/Internal.hs:(563,1)-(569,18) 0.0 0.0 0 0
maxView Data.IntMap.Internal src/Data/IntMap/Internal.hs:2240:1-62 0.0 0.0 0 0
matchedKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:1564:5-14 0.0 0.0 0 0
mapWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2432,1)-(2436,24) 0.0 0.0 0 0
mapMaybeWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2735,1)-(2740,27) 0.0 0.0 0 0
mapMaybe Data.IntMap.Internal src/Data/IntMap/Internal.hs:2727:1-42 0.0 0.0 0 0
mapKeysWith Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2545,1)-(2546,63) 0.0 0.0 0 0
mapKeysMonotonic Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2565,1)-(2566,68) 0.0 0.0 0 0
mapKeys Data.IntMap.Internal src/Data/IntMap/Internal.hs:2532:1-65 0.0 0.0 0 0
mapEitherWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2765,1)-(2775,28) 0.0 0.0 0 0
mapEither Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2752,1)-(2753,36) 0.0 0.0 0 0
mapAccumWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2483,1)-(2484,19) 0.0 0.0 0 0
mapAccumRWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2506,1)-(2518,28) 0.0 0.0 0 0
mapAccum Data.IntMap.Internal src/Data/IntMap/Internal.hs:2474:1-48 0.0 0.0 0 0
map Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2412,1)-(2416,26) 0.0 0.0 0 0
lookupMin Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2261,1)-(2268,37) 0.0 0.0 0 0
lookupMax Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2279,1)-(2286,37) 0.0 0.0 0 0
lookupLT Data.IntMap.Internal src/Data/IntMap/Internal.hs:(629,1)-(640,34) 0.0 0.0 0 0
lookupLE Data.IntMap.Internal src/Data/IntMap/Internal.hs:(672,1)-(683,34) 0.0 0.0 0 0
lookupGT Data.IntMap.Internal src/Data/IntMap/Internal.hs:(650,1)-(661,34) 0.0 0.0 0 0
lookupGE Data.IntMap.Internal src/Data/IntMap/Internal.hs:(694,1)-(705,34) 0.0 0.0 0 0
lookup Data.IntMap.Internal src/Data/IntMap/Internal.hs:(583,1)-(589,20) 0.0 0.0 0 0
keysSet Data.IntMap.Internal src/Data/IntMap/Internal.hs:(3072,1)-(3079,60) 0.0 0.0 0 0
keys Data.IntMap.Internal src/Data/IntMap/Internal.hs:3055:1-42 0.0 0.0 0 0
isSubmapOfBy Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2391,1)-(2402,45) 0.0 0.0 0 0
isSubmapOf Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2371,1)-(2372,27) 0.0 0.0 0 0
isProperSubmapOfBy Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2336,1)-(2339,17) 0.0 0.0 0 0
isProperSubmapOf Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2316,1)-(2317,33) 0.0 0.0 0 0
intersectionWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1296,1)-(1297,102) 0.0 0.0 0 0
intersectionWith Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1287,1)-(1288,47) 0.0 0.0 0 0
intersection Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1211,1)-(1212,57) 0.0 0.0 0 0
insertWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(850,1)-(857,33) 0.0 0.0 0 0
insertWith Data.IntMap.Internal src/Data/IntMap/Internal.hs:(835,1)-(836,45) 0.0 0.0 0 0
insertLookupWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(875,1)-(884,49) 0.0 0.0 0 0
insert Data.IntMap.Internal src/Data/IntMap/Internal.hs:(814,1)-(821,24) 0.0 0.0 0 0
fromSet Data.IntMap.Internal src/Data/IntMap/Internal.hs:(3088,1)-(3111,76) 0.0 0.0 0 0
fromListWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(3214,1)-(3217,39) 0.0 0.0 0 0
fromListWith Data.IntMap.Internal src/Data/IntMap/Internal.hs:(3204,1)-(3205,40) 0.0 0.0 0 0
fromList Data.IntMap.Internal src/Data/IntMap/Internal.hs:(3193,1)-(3196,31) 0.0 0.0 0 0
fromDistinctAscList Data.IntMap.Internal src/Data/IntMap/Internal.hs:3257:1-64 0.0 0.0 0 0
fromAscListWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:3247:1-56 0.0 0.0 0 0
fromAscListWith Data.IntMap.Internal src/Data/IntMap/Internal.hs:3236:1-69 0.0 0.0 0 0
fromAscList Data.IntMap.Internal src/Data/IntMap/Internal.hs:3226:1-59 0.0 0.0 0 0
findWithDefault Data.IntMap.Internal src/Data/IntMap/Internal.hs:(612,1)-(619,16) 0.0 0.0 0 0
findMin Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2273,1)-(2275,65) 0.0 0.0 0 0
findMax Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2291,1)-(2293,65) 0.0 0.0 0 0
filterWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2586,1)-(2590,44) 0.0 0.0 0 0
filter Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2578,1)-(2579,33) 0.0 0.0 0 0
elems Data.IntMap.Internal src/Data/IntMap/Internal.hs:3046:1-20 0.0 0.0 0 0
dropWhileAntitone Data.IntMap.Internal src/Data/IntMap/Internal.hs:(2665,1)-(2680,18) 0.0 0.0 0 0
disjoint Data.IntMap.Internal src/Data/IntMap/Internal.hs:(736,1)-(751,49) 0.0 0.0 0 0
differenceWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1133,1)-(1134,39) 0.0 0.0 0 0
differenceWith Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1120,1)-(1121,45) 0.0 0.0 0 0
difference Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1110,1)-(1111,57) 0.0 0.0 0 0
deleteMin Data.IntMap.Internal src/Data/IntMap/Internal.hs:2300:1-35 0.0 0.0 0 0
deleteMax Data.IntMap.Internal src/Data/IntMap/Internal.hs:2307:1-35 0.0 0.0 0 0
deleteFindMin Data.IntMap.Internal src/Data/IntMap/Internal.hs:2257:1-100 0.0 0.0 0 0
deleteFindMax Data.IntMap.Internal src/Data/IntMap/Internal.hs:2251:1-100 0.0 0.0 0 0
delete Data.IntMap.Internal src/Data/IntMap/Internal.hs:(898,1)-(905,19) 0.0 0.0 0 0
compose Data.IntMap.Internal src/Data/IntMap/Internal.hs:(774,1)-(776,35) 0.0 0.0 0 0
alterF Data.IntMap.Internal src/Data/IntMap/Internal.hs:(1046,1)-(1050,23) 0.0 0.0 0 0
alter Data.IntMap.Internal src/Data/IntMap/Internal.hs:(998,1)-(1013,36) 0.0 0.0 0 0
adjustWithKey Data.IntMap.Internal src/Data/IntMap/Internal.hs:(927,1)-(933,27) 0.0 0.0 0 0
adjust Data.IntMap.Internal src/Data/IntMap/Internal.hs:(915,1)-(916,35) 0.0 0.0 0 0
\\ Data.IntMap.Internal src/Data/IntMap/Internal.hs:415:1-27 0.0 0.0 0 0
!? Data.IntMap.Internal src/Data/IntMap/Internal.hs:411:1-21 0.0 0.0 0 0
! Data.IntMap.Internal src/Data/IntMap/Internal.hs:400:1-18 0.0 0.0 0 0
CAF Data.ByteString.Lazy.Internal.Deque <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Builder.RealFloat.Internal <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Builder.RealFloat.D2S <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Builder.RealFloat.F2S <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Builder.Prim.Internal.Base16 <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Builder.Prim.ASCII <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Builder.ASCII <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Builder.Prim.Internal <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Builder.Internal <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Builder.RealFloat <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Builder.Prim <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Builder <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Short.Internal <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Lazy.Internal <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Lazy <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Internal <entire-module> 0.0 0.0 0 0
CAF Data.ByteString.Unsafe <entire-module> 0.0 0.0 0 0
CAF Data.ByteString <entire-module> 0.0 0.0 0 0
CAF Data.Array.Byte <entire-module> 0.0 0.0 0 0
CAF Data.Functor.Reverse <entire-module> 0.0 0.0 0 0
CAF Data.Functor.Constant <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.Writer.Strict <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.Writer.Lazy <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.Writer.CPS <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.State.Strict <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.State.Lazy <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.Select <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.RWS.Strict <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.RWS.Lazy <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.RWS.CPS <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.Reader <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.Maybe <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.List <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.Identity <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.Error <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.Except <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.Cont <entire-module> 0.0 0.0 0 0
CAF Control.Monad.Trans.Accum <entire-module> 0.0 0.0 0 0
CAF Control.Applicative.Lift <entire-module> 0.0 0.0 0 0
CAF Control.Applicative.Backwards <entire-module> 0.0 0.0 0 0
CAF Control.Monad.State.Class <entire-module> 0.0 0.0 0 0
modify' Control.Monad.State.Class Control/Monad/State/Class.hs:(96,1)-(98,13) 0.0 0.0 0 0
modify Control.Monad.State.Class Control/Monad/State/Class.hs:89:1-34 0.0 0.0 0 5672
gets Control.Monad.State.Class Control/Monad/State/Class.hs:(103,1)-(105,16) 0.0 0.0 0 0
CAF Control.Monad.Reader.Class <entire-module> 0.0 0.0 0 0
asks Control.Monad.Reader.Class Control/Monad/Reader/Class.hs:102:1-13 0.0 0.0 0 0
CAF Control.Monad.Error.Class <entire-module> 0.0 0.0 0 0
withError Control.Monad.Error.Class Control/Monad/Error/Class.hs:217:1-69 0.0 0.0 0 0
tryError Control.Monad.Error.Class Control/Monad/Error/Class.hs:210:1-63 0.0 0.0 0 0
modifyError Control.Monad.Error.Class Control/Monad/Error/Class.hs:269:1-71 0.0 0.0 0 0
mapError Control.Monad.Error.Class Control/Monad/Error/Class.hs:228:1-54 0.0 0.0 0 0
liftEither Control.Monad.Error.Class Control/Monad/Error/Class.hs:123:1-35 0.0 0.0 0 0
handleError Control.Monad.Error.Class Control/Monad/Error/Class.hs:222:1-29 0.0 0.0 0 0
CAF Control.Monad.Cont.Class <entire-module> 0.0 0.0 0 0
liftCallCC Control.Monad.Cont.Class Control/Monad/Cont/Class.hs:208:1-73 0.0 0.0 0 0
label_ Control.Monad.Cont.Class Control/Monad/Cont/Class.hs:182:1-30 0.0 0.0 0 0
label Control.Monad.Cont.Class Control/Monad/Cont/Class.hs:175:1-63 0.0 0.0 0 0
CAF Control.Monad.Catch <entire-module> 0.0 0.0 0 0
uninterruptibleMask_ Control.Monad.Catch src/Control/Monad/Catch.hs:778:1-96 0.0 0.0 0 0
tryJust Control.Monad.Catch src/Control/Monad/Catch.hs:837:1-104 0.0 0.0 0 0
try Control.Monad.Catch src/Control/Monad/Catch.hs:831:1-67 0.0 0.0 0 0
onException Control.Monad.Catch src/Control/Monad/Catch.hs:860:1-92 0.0 0.0 0 0
onError Control.Monad.Catch src/Control/Monad/Catch.hs:874:1-102 0.0 0.0 0 0
mask_ Control.Monad.Catch src/Control/Monad/Catch.hs:773:1-66 0.0 0.0 0 0
handleIf Control.Monad.Catch src/Control/Monad/Catch.hs:821:1-49 0.0 0.0 0 0
handleIOError Control.Monad.Catch src/Control/Monad/Catch.hs:813:1-42 0.0 0.0 0 0
handleAll Control.Monad.Catch src/Control/Monad/Catch.hs:817:1-38 0.0 0.0 0 0
finally Control.Monad.Catch src/Control/Monad/Catch.hs:902:1-84 0.0 0.0 0 0
catches Control.Monad.Catch src/Control/Monad/Catch.hs:(847,1)-(851,76) 0.0 0.0 0 0
catchJust Control.Monad.Catch src/Control/Monad/Catch.hs:804:1-78 0.0 0.0 0 0
catchIf Control.Monad.Catch src/Control/Monad/Catch.hs:798:1-81 0.0 0.0 0 0
catchIOError Control.Monad.Catch src/Control/Monad/Catch.hs:792:1-40 0.0 0.0 0 0
catchAll Control.Monad.Catch src/Control/Monad/Catch.hs:786:1-36 0.0 0.0 0 0
bracket_ Control.Monad.Catch src/Control/Monad/Catch.hs:897:1-94 0.0 0.0 0 0
bracketOnError Control.Monad.Catch src/Control/Monad/Catch.hs:(907,1)-(913,16) 0.0 0.0 0 0
bracket Control.Monad.Catch src/Control/Monad/Catch.hs:(890,1)-(892,29) 0.0 0.0 0 0
CAF System.OsPath.Data.ByteString.Short.Internal <entire-module> 0.0 0.0 0 0
writeWord16Array System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(288,1)-(294,29) 0.0 0.0 0 0
word16ToChar System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:65:1-35 0.0 0.0 0 0
useAsCWStringLen System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:221:1-92 0.0 0.0 0 0
useAsCWString System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:213:1-46 0.0 0.0 0 0
unsafeFreezeByteArray System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(102,1)-(104,51) 0.0 0.0 0 0
unpackWord16 System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(259,1)-(265,41) 0.0 0.0 0 0
setByteArray System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(341,1)-(343,35) 0.0 0.0 0 0
packWord16Rev System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:268:1-59 0.0 0.0 0 0
packWord16 System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:245:1-49 0.0 0.0 0 0
packLenWord16Rev System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(271,1)-(278,23) 0.0 0.0 0 0
packLenWord16 System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(248,1)-(255,21) 0.0 0.0 0 0
packCWStringLen System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(201,1)-(203,24) 0.0 0.0 0 0
packCWString System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(190,1)-(192,24) 0.0 0.0 0 0
newPinnedByteArray System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(87,1)-(89,54) 0.0 0.0 0 0
newCWString System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:229:1-43 0.0 0.0 0 0
newByteArray System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(92,1)-(94,54) 0.0 0.0 0 0
moduleErrorMsg System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:242:1-85 0.0 0.0 0 0
moduleErrorIO System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:238:1-68 0.0 0.0 0 0
moduleError System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:450:1-52 0.0 0.0 0 0
isSpace System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:61:1-34 0.0 0.0 0 0
indexWord8Array System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:299:1-65 0.0 0.0 0 0
indexWord16Array System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(307,1)-(310,36) 0.0 0.0 0 0
errorEmptySBS System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:446:1-59 0.0 0.0 0 0
encodeWord16LE# System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(327,1)-(330,53) 0.0 0.0 0 0
decodeWord16LE# System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(334,1)-(336,53) 0.0 0.0 0 0
copyMutableByteArray System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(346,1)-(348,35) 0.0 0.0 0 0
copyByteArray System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(97,1)-(99,35) 0.0 0.0 0 0
copyAddrToByteArray System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(107,1)-(109,35) 0.0 0.0 0 0
compareByteArraysOff System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(460,1)-(461,57) 0.0 0.0 0 0
assertEven System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:(438,1)-(440,114) 0.0 0.0 0 0
asBA System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:78:1-24 0.0 0.0 0 0
_nul System.OsPath.Data.ByteString.Short.Internal System/OsPath/Data/ByteString/Short/Internal.hs:58:1-11 0.0 0.0 0 0
CAF System.OsPath.Encoding.Internal <entire-module> 0.0 0.0 0 0
withFilePathWin System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:264:1-47 0.0 0.0 0 0
withFilePathPosix System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:272:1-86 0.0 0.0 0 0
wNUL System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:349:1-11 0.0 0.0 0 0
utf16le_b_encode System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(195,1)-(224,16) 0.0 0.0 0 0
utf16le_b_decode System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(157,1)-(191,16) 0.0 0.0 0 0
utf16le_b_EF System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(146,1)-(153,12) 0.0 0.0 0 0
utf16le_b_DF System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(136,1)-(143,12) 0.0 0.0 0 0
utf16le_b System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:128:1-44 0.0 0.0 0 0
ucs2le_encode System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(96,1)-(116,16) 0.0 0.0 0 0
ucs2le_decode System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(71,1)-(92,16) 0.0 0.0 0 0
ucs2le_EF System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(60,1)-(67,12) 0.0 0.0 0 0
ucs2le_DF System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(50,1)-(57,12) 0.0 0.0 0 0
ucs2le System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:42:1-38 0.0 0.0 0 0
showEncodingException System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(330,1)-(333,37) 0.0 0.0 0 0
peekFilePathWin System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(267,1)-(269,28) 0.0 0.0 0 0
peekFilePathPosix System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:275:1-82 0.0 0.0 0 0
mkUcs2le System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(45,1)-(47,61) 0.0 0.0 0 0
mkUTF16le_b System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(131,1)-(133,67) 0.0 0.0 0 0
encodeWithTE System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(285,1)-(287,76) 0.0 0.0 0 0
encodeWithBaseWindows System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:315:1-91 0.0 0.0 0 0
encodeWithBasePosix System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:303:1-82 0.0 0.0 0 0
decodeWithTE System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(279,1)-(281,76) 0.0 0.0 0 0
decodeWithBaseWindows System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:309:1-79 0.0 0.0 0 0
decodeWithBasePosix System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:297:1-77 0.0 0.0 0 0
charsToCWchars System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(248,1)-(255,64) 0.0 0.0 0 0
cWcharsToChars_UCS2 System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:231:1-46 0.0 0.0 0 0
cWcharsToChars System.OsPath.Encoding.Internal System/OsPath/Encoding/Internal.hs:(238,1)-(245,19) 0.0 0.0 0 0
CAF System.OsPath.Data.ByteString.Short.Word16 <entire-module> 0.0 0.0 0 0
unsnoc System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(296,1)-(302,38) 0.0 0.0 0 0
unpack System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:199:1-34 0.0 0.0 0 0
unfoldrN System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(423,1)-(438,59) 0.0 0.0 0 0
unfoldr System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(403,1)-(407,52) 0.0 0.0 0 0
uncons2 System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(265,1)-(272,41) 0.0 0.0 0 0
uncons System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(254,1)-(260,37) 0.0 0.0 0 0
takeWhileEnd System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:495:1-59 0.0 0.0 0 0
takeWhile System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:488:1-57 0.0 0.0 0 0
takeEnd System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(477,1)-(482,112) 0.0 0.0 0 0
take System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(456,1)-(462,90) 0.0 0.0 0 0
tail System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(244,1)-(249,76) 0.0 0.0 0 0
splitWith System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(641,1)-(651,44) 0.0 0.0 0 0
splitAt System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(600,1)-(612,12) 0.0 0.0 0 0
split System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:629:1-39 0.0 0.0 0 0
spanEnd System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:592:1-76 0.0 0.0 0 0
span System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:574:1-37 0.0 0.0 0 0
snoc System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(216,1)-(220,30) 0.0 0.0 0 0
singleton System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:189:1-61 0.0 0.0 0 0
reverse System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(327,1)-(338,27) 0.0 0.0 0 0
replicate System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(377,1)-(384,64) 0.0 0.0 0 0
partition System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(821,1)-(847,30) 0.0 0.0 0 0
pack System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:194:1-17 0.0 0.0 0 0
numWord16 System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:207:1-49 0.0 0.0 0 0
map System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(311,1)-(322,27) 0.0 0.0 0 0
last System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(235,1)-(237,58) 0.0 0.0 0 0
isInfixOf System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:656:1-89 0.0 0.0 0 0
init System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(286,1)-(291,78) 0.0 0.0 0 0
index System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(732,1)-(734,51) 0.0 0.0 0 0
head System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(277,1)-(279,40) 0.0 0.0 0 0
foldr1' System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:721:1-112 0.0 0.0 0 0
foldr1 System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:716:1-46 0.0 0.0 0 0
foldr' System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:699:1-54 0.0 0.0 0 0
foldr System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:695:1-48 0.0 0.0 0 0
foldl1' System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:710:1-48 0.0 0.0 0 0
foldl1 System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:705:1-46 0.0 0.0 0 0
foldl' System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:689:1-50 0.0 0.0 0 0
foldl System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:684:1-48 0.0 0.0 0 0
findIndices System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(887,1)-(894,9) 0.0 0.0 0 0
findIndex System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(875,1)-(882,9) 0.0 0.0 0 0
find System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(810,1)-(812,37) 0.0 0.0 0 0
filter System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(778,1)-(801,29) 0.0 0.0 0 0
elemIndices System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:865:1-46 0.0 0.0 0 0
elemIndex System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:859:1-42 0.0 0.0 0 0
elem System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:772:1-85 0.0 0.0 0 0
dropWhileEnd System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:549:1-79 0.0 0.0 0 0
dropWhile System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:539:1-77 0.0 0.0 0 0
dropEnd System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(525,1)-(531,96) 0.0 0.0 0 0
drop System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(504,1)-(511,78) 0.0 0.0 0 0
count System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:869:1-50 0.0 0.0 0 0
cons System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(226,1)-(230,40) 0.0 0.0 0 0
breakSubstring System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(663,1)-(673,22) 0.0 0.0 0 0
breakEnd System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:556:1-73 0.0 0.0 0 0
break System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:564:1-81 0.0 0.0 0 0
any System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(359,1)-(365,9) 0.0 0.0 0 0
all System.OsPath.Data.ByteString.Short.Word16 System/OsPath/Data/ByteString/Short/Word16.hs:(347,1)-(353,9) 0.0 0.0 0 0
CAF System.OsString.Internal.Types <entire-module> 0.0 0.0 0 0
unWW System.OsString.Internal.Types System/OsString/Internal/Types.hs:132:14-17 0.0 0.0 0 0
unWS System.OsString.Internal.Types System/OsString/Internal/Types.hs:69:14-17 0.0 0.0 0 0
unPW System.OsString.Internal.Types System/OsString/Internal/Types.hs:140:14-17 0.0 0.0 0 0
unPS System.OsString.Internal.Types System/OsString/Internal/Types.hs:96:14-17 0.0 0.0 0 0
getWindowsString System.OsString.Internal.Types System/OsString/Internal/Types.hs:59:41-56 0.0 0.0 0 0
getWindowsChar System.OsString.Internal.Types System/OsString/Internal/Types.hs:118:37-50 0.0 0.0 0 0
getPosixString System.OsString.Internal.Types System/OsString/Internal/Types.hs:87:37-50 0.0 0.0 0 0
getPosixChar System.OsString.Internal.Types System/OsString/Internal/Types.hs:124:35-46 0.0 0.0 0 0
getOsString System.OsString.Internal.Types System/OsString/Internal/Types.hs:162:31-41 0.0 0.0 0 0
getOsChar System.OsString.Internal.Types System/OsString/Internal/Types.hs:233:27-35 0.0 0.0 0 0
CAF Data.Binary.Get <entire-module> 0.0 0.0 0 0
skip Data.Binary.Get src/Data/Binary/Get.hs:387:1-75 0.0 0.0 0 0
runGetState Data.Binary.Get src/Data/Binary/Get.hs:(301,1)-(306,81) 0.0 0.0 0 0
runGetOrFail Data.Binary.Get src/Data/Binary/Get.hs:(328,1)-(332,61) 0.0 0.0 0 0
runGetIncremental Data.Binary.Get src/Data/Binary/Get.hs:279:1-57 0.0 0.0 0 0
runGet Data.Binary.Get src/Data/Binary/Get.hs:(340,1)-(345,76) 0.0 0.0 0 0
pushEndOfInput Data.Binary.Get src/Data/Binary/Get.hs:(379,1)-(383,19) 0.0 0.0 0 0
pushChunks Data.Binary.Get src/Data/Binary/Get.hs:(369,1)-(374,44) 0.0 0.0 0 0
pushChunk Data.Binary.Get src/Data/Binary/Get.hs:(355,1)-(359,51) 0.0 0.0 0 0
getRemainingLazyByteString Data.Binary.Get src/Data/Binary/Get.hs:421:1-83 0.0 0.0 0 0
getLazyByteStringNul Data.Binary.Get src/Data/Binary/Get.hs:415:1-80 0.0 0.0 0 0
getLazyByteString Data.Binary.Get src/Data/Binary/Get.hs:392:1-77 0.0 0.0 0 0
CAF Data.Binary.Class <entire-module> 0.0 0.0 0 0
CAF Data.Binary.Builder <entire-module> 0.0 0.0 0 0
putInt64le Data.Binary.Builder src/Data/Binary/Builder.hs:198:1-22 0.0 0.0 0 0
putInt64be Data.Binary.Builder src/Data/Binary/Builder.hs:194:1-22 0.0 0.0 0 0
CAF Data.Binary.Get.Internal <entire-module> 0.0 0.0 0 0
withInputChunks Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:(238,1)-(248,45) 0.0 0.0 0 0
runGetIncremental Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:(156,1)-(157,38) 0.0 0.0 0 0
runCont Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:84:21-27 0.0 0.0 0 0
remaining Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:(369,1)-(375,12) 0.0 0.0 0 0
put Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:394:1-31 0.0 0.0 0 0
lookAheadM Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:(330,1)-(332,47) 0.0 0.0 0 0
lookAheadE Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:(340,1)-(346,35) 0.0 0.0 0 0
lookAhead Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:(317,1)-(322,35) 0.0 0.0 0 0
label Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:(353,1)-(360,10) 0.0 0.0 0 0
isolate Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:(208,1)-(233,57) 0.0 0.0 0 0
isEmpty Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:(256,1)-(259,23) 0.0 0.0 0 0
get Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:390:1-31 0.0 0.0 0 0
failOnEOF Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:251:1-64 0.0 0.0 0 0
bytesRead Data.Binary.Get.Internal src/Data/Binary/Get/Internal.hs:196:1-73 0.0 0.0 0 0
CAF Data.Binary.Put <entire-module> 0.0 0.0 0 0
unPut Data.Binary.Put src/Data/Binary/Put.hs:114:24-28 0.0 0.0 0 0
CAF Data.Text.Internal.Read <entire-module> 0.0 0.0 0 0
runP Data.Text.Internal.Read src/Data/Text/Internal/Read.hs:29:7-10 0.0 0.0 0 0
perhaps Data.Text.Internal.Read src/Data/Text/Internal/Read.hs:(58,1)-(60,44) 0.0 0.0 0 0
hexDigitToInt Data.Text.Internal.Read src/Data/Text/Internal/Read.hs:(63,1)-(71,40) 0.0 0.0 0 0
digitToInt Data.Text.Internal.Read src/Data/Text/Internal/Read.hs:74:1-30 0.0 0.0 0 0
CAF Data.Text.Internal.Lazy.Search <entire-module> 0.0 0.0 0 0
indices Data.Text.Internal.Lazy.Search src/Data/Text/Internal/Lazy/Search.hs:(51,1)-(100,43) 0.0 0.0 0 0
CAF Data.Text.Internal.Lazy.Encoding.Fusion <entire-module> 0.0 0.0 0 0
unstream Data.Text.Internal.Lazy.Encoding.Fusion src/Data/Text/Internal/Lazy/Encoding/Fusion.hs:316:1-42 0.0 0.0 0 0
CAF Data.Text.Internal.Builder.RealFloat.Functions <entire-module> 0.0 0.0 0 0
roundTo Data.Text.Internal.Builder.RealFloat.Functions src/Data/Text/Internal/Builder/RealFloat/Functions.hs:(18,1)-(35,11) 0.0 0.0 0 0
CAF Data.Text.Internal.Builder.Int.Digits <entire-module> 0.0 0.0 0 0
digits Data.Text.Internal.Builder.Int.Digits src/Data/Text/Internal/Builder/Int/Digits.hs:(22,1)-(26,51) 0.0 0.0 0 0
CAF Data.Text.Internal.Builder.Functions <entire-module> 0.0 0.0 0 0
CAF Data.Text.Show <entire-module> 0.0 0.0 0 0
unpackCStringAscii# Data.Text.Show src/Data/Text/Show.hs:(101,1)-(107,25) 0.0 0.0 0 1816
unpackCString# Data.Text.Show src/Data/Text/Show.hs:(66,1)-(88,31) 0.0 0.0 0 0
singleton Data.Text.Show src/Data/Text/Show.hs:(138,1)-(144,18) 0.0 0.0 0 0
addrLen Data.Text.Show src/Data/Text/Show.hs:112:1-45 0.0 0.0 0 0
CAF Data.Text.Unsafe <entire-module> 0.0 0.0 0 0
CAF Data.Text.Read <entire-module> 0.0 0.0 0 0
rational Data.Text.Read src/Data/Text/Read.hs:(143,1)-(144,48) 0.0 0.0 0 0
hexadecimal Data.Text.Read src/Data/Text/Read.hs:(92,1)-(95,30) 0.0 0.0 0 0
double Data.Text.Read src/Data/Text/Read.hs:(159,1)-(161,59) 0.0 0.0 0 0
CAF Data.Text.Lazy.Encoding <entire-module> 0.0 0.0 0 0
encodeUtf8Builder Data.Text.Lazy.Encoding src/Data/Text/Lazy/Encoding.hs:(155,1)-(156,79) 0.0 0.0 0 0
encodeUtf8 Data.Text.Lazy.Encoding src/Data/Text/Lazy/Encoding.hs:149:1-58 0.0 0.0 0 0
decodeUtf8With Data.Text.Lazy.Encoding src/Data/Text/Lazy/Encoding.hs:(110,1)-(117,61) 0.0 0.0 0 0
decodeLatin1 Data.Text.Lazy.Encoding src/Data/Text/Lazy/Encoding.hs:106:1-65 0.0 0.0 0 0
decodeASCII Data.Text.Lazy.Encoding src/Data/Text/Lazy/Encoding.hs:102:1-63 0.0 0.0 0 0
CAF Data.Text.Lazy.Builder.RealFloat <entire-module> 0.0 0.0 0 0
realFloat Data.Text.Lazy.Builder.RealFloat src/Data/Text/Lazy/Builder/RealFloat.hs:45:1-47 0.0 0.0 0 0
formatRealFloat Data.Text.Lazy.Builder.RealFloat src/Data/Text/Lazy/Builder/RealFloat.hs:(62,1)-(120,98) 0.0 0.0 0 0
CAF Data.Text.Lazy.Builder.Int <entire-module> 0.0 0.0 0 0
hexadecimal Data.Text.Lazy.Builder.Int src/Data/Text/Lazy/Builder/Int.hs:(157,1)-(162,64) 0.0 0.0 0 0
decimal Data.Text.Lazy.Builder.Int src/Data/Text/Lazy/Builder/Int.hs:46:1-32 0.0 0.0 0 0
CAF Data.Text.Lazy <entire-module> 0.0 0.0 0 0
transpose Data.Text.Lazy src/Data/Text/Lazy.hs:(654,1)-(655,52) 0.0 0.0 0 0
toChunks Data.Text.Lazy src/Data/Text/Lazy.hs:441:1-35 0.0 0.0 0 0
takeEnd Data.Text.Lazy src/Data/Text/Lazy.hs:(1062,1)-(1071,39) 0.0 0.0 0 0
tails Data.Text.Lazy src/Data/Text/Lazy.hs:(1435,1)-(1438,61) 0.0 0.0 0 0
stripSuffix Data.Text.Lazy src/Data/Text/Lazy.hs:1679:1-68 0.0 0.0 0 0
stripPrefix Data.Text.Lazy src/Data/Text/Lazy.hs:(1628,1)-(1632,52) 0.0 0.0 0 0
splitAt Data.Text.Lazy src/Data/Text/Lazy.hs:(1227,1)-(1237,44) 0.0 0.0 0 0
scanr1 Data.Text.Lazy src/Data/Text/Lazy.hs:(929,1)-(930,50) 0.0 0.0 0 0
scanr Data.Text.Lazy src/Data/Text/Lazy.hs:(923,1)-(924,30) 0.0 0.0 0 0
reverse Data.Text.Lazy src/Data/Text/Lazy.hs:(664,1)-(666,59) 0.0 0.0 0 0
repeat Data.Text.Lazy src/Data/Text/Lazy.hs:(964,1)-(965,16) 0.0 0.0 0 0
lines Data.Text.Lazy src/Data/Text/Lazy.hs:(1527,1)-(1537,81) 0.0 0.0 0 0
iterate Data.Text.Lazy src/Data/Text/Lazy.hs:(1008,1)-(1009,21) 0.0 0.0 0 0
isPrefixOf Data.Text.Lazy src/Data/Text/Lazy.hs:(1572,1)-(1581,23) 0.0 0.0 0 0
isAscii Data.Text.Lazy src/Data/Text/Lazy.hs:892:1-63 0.0 0.0 0 0
inits Data.Text.Lazy src/Data/Text/Lazy.hs:(1427,1)-(1430,57) 0.0 0.0 0 0
groupBy Data.Text.Lazy src/Data/Text/Lazy.hs:(1418,1)-(1422,62) 0.0 0.0 0 0
fromChunks Data.Text.Lazy src/Data/Text/Lazy.hs:437:1-38 0.0 0.0 0 0
dropEnd Data.Text.Lazy src/Data/Text/Lazy.hs:(1104,1)-(1114,39) 0.0 0.0 0 0
cycle Data.Text.Lazy src/Data/Text/Lazy.hs:(997,1)-(999,20) 0.0 0.0 0 0
commonPrefixes Data.Text.Lazy src/Data/Text/Lazy.hs:(1647,1)-(1658,51) 0.0 0.0 0 0
breakOnAll Data.Text.Lazy src/Data/Text/Lazy.hs:(1320,1)-(1327,25) 0.0 0.0 0 0
breakOn Data.Text.Lazy src/Data/Text/Lazy.hs:(1276,1)-(1281,39) 0.0 0.0 0 0
break Data.Text.Lazy src/Data/Text/Lazy.hs:(1335,1)-(1343,64) 0.0 0.0 0 0
CAF Data.Text.Internal.Unsafe <entire-module> 0.0 0.0 0 0
unsafeWithForeignPtr Data.Text.Internal.Unsafe src/Data/Text/Internal/Unsafe.hs:62:1-58 0.0 0.0 0 0
CAF Data.Text.Internal.StrictBuilder <entire-module> 0.0 0.0 0 0
unsafeFromWord8 Data.Text.Internal.StrictBuilder src/Data/Text/Internal/StrictBuilder.hs:(113,1)-(114,55) 0.0 0.0 0 0
unsafeFromByteString Data.Text.Internal.StrictBuilder src/Data/Text/Internal/StrictBuilder.hs:(95,1)-(96,73) 0.0 0.0 0 0
toText Data.Text.Internal.StrictBuilder src/Data/Text/Internal/StrictBuilder.hs:(56,1)-(61,22) 0.0 0.0 0 0
sbWrite Data.Text.Internal.StrictBuilder src/Data/Text/Internal/StrictBuilder.hs:49:5-11 0.0 0.0 0 0
sbLength Data.Text.Internal.StrictBuilder src/Data/Text/Internal/StrictBuilder.hs:48:5-12 0.0 0.0 0 0
fromText Data.Text.Internal.StrictBuilder src/Data/Text/Internal/StrictBuilder.hs:(120,1)-(121,34) 0.0 0.0 0 0
CAF Data.Text.Internal.Lazy.Fusion <entire-module> 0.0 0.0 0 0
unstreamChunks/resize Data.Text.Internal.Lazy.Fusion src/Data/Text/Internal/Lazy/Fusion.hs:(81,72)-(85,38) 0.0 0.0 0 0
unstreamChunks/outer Data.Text.Internal.Lazy.Fusion src/Data/Text/Internal/Lazy/Fusion.hs:(71,15)-(77,43) 0.0 0.0 0 0
unstreamChunks/inner Data.Text.Internal.Lazy.Fusion src/Data/Text/Internal/Lazy/Fusion.hs:(88,17)-(92,59) 0.0 0.0 0 0
CAF Data.Text.Internal.Lazy <entire-module> 0.0 0.0 0 0
strictInvariant Data.Text.Internal.Lazy src/Data/Text/Internal/Lazy.hs:(62,1)-(66,36) 0.0 0.0 0 0
showStructure Data.Text.Internal.Lazy src/Data/Text/Internal/Lazy.hs:(78,1)-(81,57) 0.0 0.0 0 0
lazyInvariant Data.Text.Internal.Lazy src/Data/Text/Internal/Lazy.hs:(70,1)-(74,36) 0.0 0.0 0 0
equal Data.Text.Internal.Lazy src/Data/Text/Internal/Lazy.hs:(125,1)-(135,73) 0.0 0.0 0 0
CAF Data.Text.Internal.IO <entire-module> 0.0 0.0 0 0
otherwise Data.Text.Internal.IO src/Data/Text/Internal/IO.hs:151:43-52 0.0 0.0 0 0
hGetLineWith Data.Text.Internal.IO src/Data/Text/Internal/IO.hs:(44,1)-(46,79) 0.0 0.0 0 0
CAF Data.Text.Internal.Fusion.Types <entire-module> 0.0 0.0 0 0
CAF Data.Text.Internal.Fusion.Size <entire-module> 0.0 0.0 0 0
unionSize Data.Text.Internal.Fusion.Size src/Data/Text/Internal/Fusion/Size.hs:(95,1)-(96,23) 0.0 0.0 0 0
compareSize Data.Text.Internal.Fusion.Size src/Data/Text/Internal/Fusion/Size.hs:(170,1)-(176,32) 0.0 0.0 0 0
charSize Data.Text.Internal.Fusion.Size src/Data/Text/Internal/Fusion/Size.hs:58:1-33 0.0 0.0 0 0
CAF Data.Text.Internal.Fusion.Common <entire-module> 0.0 0.0 0 0
CAF Data.Text.Internal.Fusion.CaseMapping <entire-module> 0.0 0.0 0 0
upperMapping Data.Text.Internal.Fusion.CaseMapping src/Data/Text/Internal/Fusion/CaseMapping.hs:(18,1)-(1646,14) 0.0 0.0 0 0
unI64 Data.Text.Internal.Fusion.CaseMapping src/Data/Text/Internal/Fusion/CaseMapping.hs:14:1-18 0.0 0.0 0 0
titleMapping Data.Text.Internal.Fusion.CaseMapping src/Data/Text/Internal/Fusion/CaseMapping.hs:(3087,1)-(4588,14) 0.0 0.0 0 0
lowerMapping Data.Text.Internal.Fusion.CaseMapping src/Data/Text/Internal/Fusion/CaseMapping.hs:(1649,1)-(3084,14) 0.0 0.0 0 0
foldMapping Data.Text.Internal.Fusion.CaseMapping src/Data/Text/Internal/Fusion/CaseMapping.hs:(4591,1)-(7652,14) 0.0 0.0 0 0
CAF Data.Text.Internal.Fusion <entire-module> 0.0 0.0 0 0
reverse/resize Data.Text.Internal.Fusion src/Data/Text/Internal/Fusion.hs:(198,66)-(203,65) 0.0 0.0 0 0
mapAccumL/resize Data.Text.Internal.Fusion src/Data/Text/Internal/Fusion.hs:(296,63)-(299,52) 0.0 0.0 0 0
CAF Data.Text.Internal.Encoding.Utf8 <entire-module> 0.0 0.0 0 0
utf8RejectState Data.Text.Internal.Encoding.Utf8 src/Data/Text/Internal/Encoding/Utf8.hs:256:1-33 0.0 0.0 0 0
utf8DecodeStart Data.Text.Internal.Encoding.Utf8 src/Data/Text/Internal/Encoding/Utf8.hs:(280,1)-(287,64) 0.0 0.0 0 0
utf8DecodeContinue Data.Text.Internal.Encoding.Utf8 src/Data/Text/Internal/Encoding/Utf8.hs:(291,1)-(298,53) 0.0 0.0 0 0
utf8AcceptState Data.Text.Internal.Encoding.Utf8 src/Data/Text/Internal/Encoding/Utf8.hs:253:1-32 0.0 0.0 0 0
updateDecoderState Data.Text.Internal.Encoding.Utf8 src/Data/Text/Internal/Encoding/Utf8.hs:268:1-54 0.0 0.0 0 0
CAF Data.Text.Internal.Encoding.Fusion <entire-module> 0.0 0.0 0 0
unstream Data.Text.Internal.Encoding.Fusion src/Data/Text/Internal/Encoding/Fusion.hs:(171,1)-(201,21) 0.0 0.0 0 0
CAF Data.Text.Internal.Encoding <entire-module> 0.0 0.0 0 0
validateUtf8More Data.Text.Internal.Encoding src/Data/Text/Internal/Encoding.hs:330:1-55 0.0 0.0 0 0
validateUtf8Chunk Data.Text.Internal.Encoding src/Data/Text/Internal/Encoding.hs:238:1-53 0.0 0.0 0 0
textToStrictBuilder Data.Text.Internal.Encoding src/Data/Text/Internal/Encoding.hs:82:1-33 0.0 0.0 0 0
strictBuilderToText Data.Text.Internal.Encoding src/Data/Text/Internal/Encoding.hs:76:1-31 0.0 0.0 0 0
startUtf8State Data.Text.Internal.Encoding src/Data/Text/Internal/Encoding.hs:111:1-56 0.0 0.0 0 0
getPartialUtf8 Data.Text.Internal.Encoding src/Data/Text/Internal/Encoding.hs:206:1-60 0.0 0.0 0 0
getCompleteLen Data.Text.Internal.Encoding src/Data/Text/Internal/Encoding.hs:202:1-59 0.0 0.0 0 0
decodeUtf8With2 Data.Text.Internal.Encoding src/Data/Text/Internal/Encoding.hs:(506,1)-(531,38) 0.0 0.0 0 0
decodeUtf8With1 Data.Text.Internal.Encoding src/Data/Text/Internal/Encoding.hs:(478,1)-(491,35) 0.0 0.0 0 0
decodeUtf8More Data.Text.Internal.Encoding src/Data/Text/Internal/Encoding.hs:(414,1)-(419,35) 0.0 0.0 0 0
decodeUtf8Chunk Data.Text.Internal.Encoding src/Data/Text/Internal/Encoding.hs:445:1-47 0.0 0.0 0 0
CAF Data.Text.Internal.Builder <entire-module> 0.0 0.0 0 0
toLazyTextWith Data.Text.Internal.Builder src/Data/Text/Internal/Builder.hs:(245,1)-(246,76) 0.0 0.0 0 0
toLazyText Data.Text.Internal.Builder src/Data/Text/Internal/Builder.hs:236:1-42 0.0 0.0 0 0
CAF Data.Text.Internal <entire-module> 0.0 0.0 0 32
textP Data.Text.Internal src/Data/Text/Internal.hs:134:1-12 0.0 0.0 0 0
showText Data.Text.Internal src/Data/Text/Internal.hs:(138,1)-(140,38) 0.0 0.0 0 0
pack Data.Text.Internal src/Data/Text/Internal.hs:(250,1)-(274,33) 0.0 0.0 0 0
firstf Data.Text.Internal src/Data/Text/Internal.hs:(158,1)-(159,32) 0.0 0.0 0 0
empty_ Data.Text.Internal src/Data/Text/Internal.hs:97:1-25 0.0 0.0 0 0
append Data.Text.Internal src/Data/Text/Internal.hs:(103,1)-(115,18) 0.0 0.0 0 0
CAF Data.Text.IO <entire-module> 0.0 0.0 0 48
writeFile Data.Text.IO src/Data/Text/IO.hs:85:1-49 0.0 0.0 0 0
readFile Data.Text.IO src/Data/Text/IO.hs:80:1-55 0.0 0.0 0 19992
putStrLn Data.Text.IO src/Data/Text/IO.hs:309:1-27 0.0 0.0 0 0
putStr Data.Text.IO src/Data/Text/IO.hs:305:1-23 0.0 0.0 0 0
interact Data.Text.IO src/Data/Text/IO.hs:293:1-39 0.0 0.0 0 0
hPutStrLn Data.Text.IO src/Data/Text/IO.hs:286:1-46 0.0 0.0 0 0
hPutStr Data.Text.IO src/Data/Text/IO.hs:(175,1)-(186,56) 0.0 0.0 0 0
hGetLine Data.Text.IO src/Data/Text/IO.hs:170:1-32 0.0 0.0 0 0
hGetChunk Data.Text.IO src/Data/Text/IO.hs:(116,1)-(121,18) 0.0 0.0 0 0
getLine Data.Text.IO src/Data/Text/IO.hs:301:1-24 0.0 0.0 0 0
getContents Data.Text.IO src/Data/Text/IO.hs:297:1-32 0.0 0.0 0 0
appendFile Data.Text.IO src/Data/Text/IO.hs:89:1-51 0.0 0.0 0 0
CAF Data.Text.Foreign <entire-module> 0.0 0.0 0 0
withCStringLen Data.Text.Foreign src/Data/Text/Foreign.hs:191:1-63 0.0 0.0 0 0
withCString Data.Text.Foreign src/Data/Text/Foreign.hs:(165,1)-(169,24) 0.0 0.0 0 0
useAsPtr Data.Text.Foreign src/Data/Text/Foreign.hs:(144,1)-(147,35) 0.0 0.0 0 0
unsafeCopyToPtr Data.Text.Foreign src/Data/Text/Foreign.hs:139:1-87 0.0 0.0 0 0
takeWord8 Data.Text.Foreign src/Data/Text/Foreign.hs:104:1-34 0.0 0.0 0 0
peekCStringLen Data.Text.Foreign src/Data/Text/Foreign.hs:(177,1)-(179,25) 0.0 0.0 0 0
fromPtr0 Data.Text.Foreign src/Data/Text/Foreign.hs:86:1-69 0.0 0.0 0 0
fromPtr Data.Text.Foreign src/Data/Text/Foreign.hs:(74,1)-(78,26) 0.0 0.0 0 0
dropWord8 Data.Text.Foreign src/Data/Text/Foreign.hs:115:1-34 0.0 0.0 0 0
asForeignPtr Data.Text.Foreign src/Data/Text/Foreign.hs:(151,1)-(154,21) 0.0 0.0 0 0
CAF Data.Text.Encoding.Error <entire-module> 0.0 0.0 0 0
strictEncode Data.Text.Encoding.Error src/Data/Text/Encoding/Error.hs:112:1-48 0.0 0.0 0 0
strictDecode Data.Text.Encoding.Error src/Data/Text/Encoding/Error.hs:102:1-48 0.0 0.0 0 0
replace Data.Text.Encoding.Error src/Data/Text/Encoding/Error.hs:120:1-22 0.0 0.0 0 0
lenientDecode Data.Text.Encoding.Error src/Data/Text/Encoding/Error.hs:107:1-33 0.0 0.0 0 0
ignore Data.Text.Encoding.Error src/Data/Text/Encoding/Error.hs:116:1-20 0.0 0.0 0 0
CAF Data.Text.Encoding <entire-module> 0.0 0.0 0 0
streamDecodeUtf8With Data.Text.Encoding src/Data/Text/Encoding.hs:(335,1)-(339,63) 0.0 0.0 0 0
streamDecodeUtf8 Data.Text.Encoding src/Data/Text/Encoding.hs:324:1-52 0.0 0.0 0 0
encodeUtf8 Data.Text.Encoding src/Data/Text/Encoding.hs:(469,1)-(478,36) 0.0 0.0 0 0
decodeUtf8With Data.Text.Encoding src/Data/Text/Encoding.hs:350:1-59 0.0 0.0 0 0
decodeUtf8Lenient Data.Text.Encoding src/Data/Text/Encoding.hs:387:1-48 0.0 0.0 0 0
decodeLatin1 Data.Text.Encoding src/Data/Text/Encoding.hs:(222,1)-(240,31) 0.0 0.0 0 0
decodeASCII Data.Text.Encoding src/Data/Text/Encoding.hs:(201,1)-(207,105) 0.0 0.0 0 0
CAF Data.Text.Array <entire-module> 0.0 0.0 0 0
toList Data.Text.Array src/Data/Text/Array.hs:(170,1)-(172,33) 0.0 0.0 0 0
getSizeofMArray Data.Text.Array src/Data/Text/Array.hs:(138,1)-(142,51) 0.0 0.0 0 0
empty Data.Text.Array src/Data/Text/Array.hs:176:1-38 0.0 0.0 0 32
CAF Data.Text <entire-module> 0.0 0.0 0 0
transpose Data.Text src/Data/Text.hs:1066:1-57 0.0 0.0 0 0
takeEnd Data.Text src/Data/Text.hs:(1427,1)-(1431,24) 0.0 0.0 0 0
tails Data.Text src/Data/Text.hs:(1663,1)-(1664,46) 0.0 0.0 0 0
stripSuffix Data.Text src/Data/Text.hs:(2201,1)-(2203,32) 0.0 0.0 0 0
stripPrefix Data.Text src/Data/Text.hs:(2135,1)-(2137,32) 0.0 0.0 0 0
replace Data.Text src/Data/Text.hs:(804,1)-(825,17) 0.0 0.0 0 0
inits Data.Text src/Data/Text.hs:(1656,1)-(1658,68) 0.0 0.0 0 0
groupBy Data.Text src/Data/Text.hs:(1632,1)-(1638,80) 0.0 0.0 0 0
group Data.Text src/Data/Text.hs:1651:1-20 0.0 0.0 0 0
dropEnd Data.Text src/Data/Text.hs:(1462,1)-(1465,45) 0.0 0.0 0 0
copy Data.Text src/Data/Text.hs:(2229,1)-(2235,17) 0.0 0.0 0 0
concat Data.Text src/Data/Text.hs:(1137,1)-(1148,36) 0.0 0.0 0 698128
CAF Data.Hashable.LowLevel <entire-module> 0.0 0.0 0 0
hashWord64 Data.Hashable.LowLevel src/Data/Hashable/LowLevel.hs:97:1-43 0.0 0.0 0 0
hashPtrWithSalt Data.Hashable.LowLevel src/Data/Hashable/LowLevel.hs:(113,1)-(115,23) 0.0 0.0 0 0
hashInt64 Data.Hashable.LowLevel src/Data/Hashable/LowLevel.hs:96:1-43 0.0 0.0 0 0
hashInt Data.Hashable.LowLevel src/Data/Hashable/LowLevel.hs:(64,1)-(80,31) 0.0 0.0 0 0
hashByteArrayWithSalt Data.Hashable.LowLevel src/Data/Hashable/LowLevel.hs:(129,1)-(131,20) 0.0 0.0 0 0
CAF Data.Hashable.Class <entire-module> 0.0 0.0 0 0
unhashed Data.Hashable.Class src/Data/Hashable/Class.hs:926:1-25 0.0 0.0 0 0
traverseHashed Data.Hashable.Class src/Data/Hashable/Class.hs:972:1-49 0.0 0.0 0 0
mapHashed Data.Hashable.Class src/Data/Hashable/Class.hs:968:1-39 0.0 0.0 0 0
hashedHash Data.Hashable.Class src/Data/Hashable/Class.hs:932:1-27 0.0 0.0 0 0
hashed Data.Hashable.Class src/Data/Hashable/Class.hs:922:1-28 0.0 0.0 0 0
hashWithSalt2 Data.Hashable.Class src/Data/Hashable/Class.hs:285:1-59 0.0 0.0 0 0
hashWithSalt1 Data.Hashable.Class src/Data/Hashable/Class.hs:279:1-45 0.0 0.0 0 0
hashPtr Data.Hashable.Class src/Data/Hashable/Class.hs:776:1-49 0.0 0.0 0 0
defaultLiftHashWithSalt Data.Hashable.Class src/Data/Hashable/Class.hs:291:1-60 0.0 0.0 0 0
defaultHashWithSalt Data.Hashable.Class src/Data/Hashable/Class.hs:301:1-50 0.0 0.0 0 0
defaultHash Data.Hashable.Class src/Data/Hashable/Class.hs:308:1-38 0.0 0.0 0 0
CAF Data.CaseInsensitive.Internal <entire-module> 0.0 0.0 0 0
unsafeMk Data.CaseInsensitive.Internal Data/CaseInsensitive/Internal.hs:106:1-19 0.0 0.0 0 0
traverse Data.CaseInsensitive.Internal Data/CaseInsensitive/Internal.hs:114:1-35 0.0 0.0 0 0
original Data.CaseInsensitive.Internal Data/CaseInsensitive/Internal.hs:89:18-25 0.0 0.0 0 0
mk Data.CaseInsensitive.Internal Data/CaseInsensitive/Internal.hs:97:1-24 0.0 0.0 0 0
map Data.CaseInsensitive.Internal Data/CaseInsensitive/Internal.hs:110:1-25 0.0 0.0 0 0
foldedCase Data.CaseInsensitive.Internal Data/CaseInsensitive/Internal.hs:90:18-27 0.0 0.0 0 0
CAF Math.NumberTheory.Logarithms <entire-module> 0.0 0.0 0 0
wordLog2' Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:147:1-37 0.0 0.0 0 0
wordLog2 Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:(125,1)-(127,51) 0.0 0.0 0 0
naturalLogBase Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:(101,1)-(106,37) 0.0 0.0 0 0
naturalLog2 Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:(111,1)-(113,37) 0.0 0.0 0 0
naturalLog10 Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:(159,1)-(161,31) 0.0 0.0 0 0
integerLogBase' Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:(198,1)-(229,25) 0.0 0.0 0 0
integerLogBase Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:(75,1)-(80,37) 0.0 0.0 0 0
integerLog2' Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:132:1-36 0.0 0.0 0 0
integerLog2 Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:(85,1)-(87,37) 0.0 0.0 0 0
integerLog10' Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:(167,1)-(177,55) 0.0 0.0 0 0
integerLog10 Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:(152,1)-(154,31) 0.0 0.0 0 0
intLog2' Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:142:1-48 0.0 0.0 0 0
intLog2 Math.NumberTheory.Logarithms src/Math/NumberTheory/Logarithms.hs:(118,1)-(120,55) 0.0 0.0 0 0
CAF Data.Primitive.SmallArray <entire-module> 0.0 0.0 0 0
smallArrayFromListN Data.Primitive.SmallArray Data/Primitive/SmallArray.hs:(870,1)-(881,11) 0.0 0.0 0 0
smallArrayFromList Data.Primitive.SmallArray Data/Primitive/SmallArray.hs:885:1-55 0.0 0.0 0 0
runSmallArray Data.Primitive.SmallArray Data/Primitive/SmallArray.hs:407:1-47 0.0 0.0 0 0
emptySmallArray Data.Primitive.SmallArray Data/Primitive/SmallArray.hs:(449,1)-(451,38) 0.0 0.0 0 0
createSmallArray Data.Primitive.SmallArray Data/Primitive/SmallArray.hs:(434,1)-(438,11) 0.0 0.0 0 0
CAF Data.Primitive.PrimArray <entire-module> 0.0 0.0 0 0
traversePrimArray_ Data.Primitive.PrimArray Data/Primitive/PrimArray.hs:(1039,1)-(1043,16) 0.0 0.0 0 0
traversePrimArray Data.Primitive.PrimArray Data/Primitive/PrimArray.hs:(912,1)-(923,29) 0.0 0.0 0 0
runPrimArray Data.Primitive.PrimArray Data/Primitive/PrimArray.hs:1163:1-44 0.0 0.0 0 0
primArrayFromListN Data.Primitive.PrimArray Data/Primitive/PrimArray.hs:(238,1)-(252,29) 0.0 0.0 0 0
primArrayFromList Data.Primitive.PrimArray Data/Primitive/PrimArray.hs:233:1-58 0.0 0.0 0 0
mapMaybePrimArrayA Data.Primitive.PrimArray Data/Primitive/PrimArray.hs:(854,1)-(869,31) 0.0 0.0 0 0
itraversePrimArray_ Data.Primitive.PrimArray Data/Primitive/PrimArray.hs:(1053,1)-(1057,16) 0.0 0.0 0 0
itraversePrimArray Data.Primitive.PrimArray Data/Primitive/PrimArray.hs:(931,1)-(942,29) 0.0 0.0 0 0
filterPrimArrayA Data.Primitive.PrimArray Data/Primitive/PrimArray.hs:(830,1)-(845,31) 0.0 0.0 0 0
emptyPrimArray Data.Primitive.PrimArray Data/Primitive/PrimArray.hs:(282,1)-(284,50) 0.0 0.0 0 0
CAF Data.Primitive.Array <entire-module> 0.0 0.0 0 0
runArray Data.Primitive.Array Data/Primitive/Array.hs:328:1-32 0.0 0.0 0 0
marray# Data.Primitive.Array Data/Primitive/Array.hs:112:5-11 0.0 0.0 0 0
emptyArray Data.Primitive.Array Data/Primitive/Array.hs:(318,1)-(319,74) 0.0 0.0 0 0
createArray Data.Primitive.Array Data/Primitive/Array.hs:(365,1)-(369,11) 0.0 0.0 0 0
arrayFromListN Data.Primitive.Array Data/Primitive/Array.hs:(590,1)-(600,13) 0.0 0.0 0 0
arrayFromList Data.Primitive.Array Data/Primitive/Array.hs:604:1-45 0.0 0.0 0 0
array# Data.Primitive.Array Data/Primitive/Array.hs:69:5-10 0.0 0.0 0 0
CAF Data.Primitive.Types <entire-module> 0.0 0.0 0 0
sizeOf Data.Primitive.Types Data/Primitive/Types.hs:128:1-25 0.0 0.0 0 0
getPrimStorable Data.Primitive.Types Data/Primitive/Types.hs:194:41-55 0.0 0.0 0 0
defaultSetOffAddr# Data.Primitive.Types Data/Primitive/Types.hs:(176,1)-(181,11) 0.0 0.0 0 0
defaultSetByteArray# Data.Primitive.Types Data/Primitive/Types.hs:(165,1)-(170,11) 0.0 0.0 0 0
alignment Data.Primitive.Types Data/Primitive/Types.hs:135:1-31 0.0 0.0 0 0
CAF Data.Primitive.MachDeps <entire-module> 0.0 0.0 0 0
sIZEOF_WORD8 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:95:1-16 0.0 0.0 0 0
sIZEOF_WORD64 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:113:1-17 0.0 0.0 0 0
sIZEOF_WORD32 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:107:1-17 0.0 0.0 0 0
sIZEOF_WORD16 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:101:1-17 0.0 0.0 0 0
sIZEOF_WORD Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:74:1-15 0.0 0.0 0 0
sIZEOF_STABLEPTR Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:89:1-20 0.0 0.0 0 0
sIZEOF_PTR Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:83:1-14 0.0 0.0 0 0
sIZEOF_INT8 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:92:1-15 0.0 0.0 0 0
sIZEOF_INT64 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:110:1-16 0.0 0.0 0 0
sIZEOF_INT32 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:104:1-16 0.0 0.0 0 0
sIZEOF_INT16 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:98:1-16 0.0 0.0 0 0
sIZEOF_INT Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:71:1-14 0.0 0.0 0 0
sIZEOF_FUNPTR Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:86:1-17 0.0 0.0 0 0
sIZEOF_FLOAT Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:80:1-16 0.0 0.0 0 0
sIZEOF_DOUBLE Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:77:1-17 0.0 0.0 0 0
sIZEOF_CHAR Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:68:1-15 0.0 0.0 0 0
aLIGNMENT_WORD8 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:96:1-19 0.0 0.0 0 0
aLIGNMENT_WORD64 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:114:1-20 0.0 0.0 0 0
aLIGNMENT_WORD32 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:108:1-20 0.0 0.0 0 0
aLIGNMENT_WORD16 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:102:1-20 0.0 0.0 0 0
aLIGNMENT_WORD Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:75:1-18 0.0 0.0 0 0
aLIGNMENT_STABLEPTR Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:90:1-23 0.0 0.0 0 0
aLIGNMENT_PTR Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:84:1-17 0.0 0.0 0 0
aLIGNMENT_INT8 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:93:1-18 0.0 0.0 0 0
aLIGNMENT_INT64 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:111:1-19 0.0 0.0 0 0
aLIGNMENT_INT32 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:105:1-19 0.0 0.0 0 0
aLIGNMENT_INT16 Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:99:1-19 0.0 0.0 0 0
aLIGNMENT_INT Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:72:1-17 0.0 0.0 0 0
aLIGNMENT_FUNPTR Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:87:1-20 0.0 0.0 0 0
aLIGNMENT_FLOAT Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:81:1-19 0.0 0.0 0 0
aLIGNMENT_DOUBLE Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:78:1-20 0.0 0.0 0 0
aLIGNMENT_CHAR Data.Primitive.MachDeps Data/Primitive/MachDeps.hs:69:1-18 0.0 0.0 0 0
CAF Control.Monad.Primitive <entire-module> 0.0 0.0 0 0
unsafeDupableInterleave Control.Monad.Primitive Control/Monad/Primitive.hs:368:1-107 0.0 0.0 0 0
noDuplicate Control.Monad.Primitive Control/Monad/Primitive.hs:360:1-57 0.0 0.0 0 0
evalPrim Control.Monad.Primitive Control/Monad/Primitive.hs:356:1-39 0.0 0.0 0 0
CAF Utils <entire-module> 0.0 0.0 0 0
roundTo Utils src/Utils.hs:(27,1)-(45,21) 0.0 0.0 0 0
maxExpt Utils src/Utils.hs:58:1-13 0.0 0.0 0 0
magnitude Utils src/Utils.hs:(86,1)-(91,22) 0.0 0.0 0 0
CAF Data.Text.Lazy.Builder.Scientific <entire-module> 0.0 0.0 0 0
scientificBuilder Data.Text.Lazy.Builder.Scientific src/Data/Text/Lazy/Builder/Scientific.hs:33:1-59 0.0 0.0 0 0
formatScientificBuilder Data.Text.Lazy.Builder.Scientific src/Data/Text/Lazy/Builder/Scientific.hs:(40,1)-(97,82) 0.0 0.0 0 0
CAF Data.Scientific <entire-module> 0.0 0.0 0 0
unsafeFromRational Data.Scientific src/Data/Scientific.hs:(366,1)-(379,28) 0.0 0.0 0 0
toRealFloat Data.Scientific src/Data/Scientific.hs:743:1-47 0.0 0.0 0 0
toRationalRepetend Data.Scientific src/Data/Scientific.hs:(539,1)-(558,17) 0.0 0.0 0 0
toDecimalDigits Data.Scientific src/Data/Scientific.hs:(1103,1)-(1113,48) 0.0 0.0 0 0
toBoundedRealFloat Data.Scientific src/Data/Scientific.hs:(757,1)-(784,27) 0.0 0.0 0 0
toBoundedInteger Data.Scientific src/Data/Scientific.hs:(794,1)-(824,21) 0.0 0.0 0 0
scientificP Data.Scientific src/Data/Scientific.hs:(915,1)-(943,45) 0.0 0.0 0 0
scientific Data.Scientific src/Data/Scientific.hs:188:1-23 0.0 0.0 0 0
normalize Data.Scientific src/Data/Scientific.hs:(1126,1)-(1129,45) 0.0 0.0 0 0
isInteger Data.Scientific src/Data/Scientific.hs:(876,1)-(879,20) 0.0 0.0 0 0
isFloating Data.Scientific src/Data/Scientific.hs:870:1-28 0.0 0.0 0 0
fromRationalRepetendUnlimited Data.Scientific src/Data/Scientific.hs:(467,1)-(490,32) 0.0 0.0 0 0
fromRationalRepetendLimited Data.Scientific src/Data/Scientific.hs:(436,1)-(463,32) 0.0 0.0 0 0
fromRationalRepetend Data.Scientific src/Data/Scientific.hs:(425,1)-(428,55) 0.0 0.0 0 0
fromFloatDigits Data.Scientific src/Data/Scientific.hs:(714,1)-(723,64) 0.0 0.0 0 0
formatScientific Data.Scientific src/Data/Scientific.hs:(1030,1)-(1083,50) 0.0 0.0 0 0
floatingOrInteger Data.Scientific src/Data/Scientific.hs:(854,1)-(859,20) 0.0 0.0 0 0
coefficient Data.Scientific src/Data/Scientific.hs:156:7-17 0.0 0.0 0 0
base10Exponent Data.Scientific src/Data/Scientific.hs:181:7-20 0.0 0.0 0 0
CAF Data.ByteString.Builder.Scientific <entire-module> 0.0 0.0 0 0
scientificBuilder Data.ByteString.Builder.Scientific src/Data/ByteString/Builder/Scientific.hs:39:1-59 0.0 0.0 0 0
formatScientificBuilder Data.ByteString.Builder.Scientific src/Data/ByteString/Builder/Scientific.hs:(46,1)-(107,75) 0.0 0.0 0 0
CAF Text.Megaparsec.State <entire-module> 0.0 0.0 0 0
statePosState Text.Megaparsec.State Text/Megaparsec/State.hs:47:5-17 0.0 0.0 0 0
stateParseErrors Text.Megaparsec.State Text/Megaparsec/State.hs:52:5-20 0.0 0.0 0 0
stateOffset Text.Megaparsec.State Text/Megaparsec/State.hs:43:5-15 0.0 0.0 0 0
stateInput Text.Megaparsec.State Text/Megaparsec/State.hs:39:5-14 0.0 0.0 0 0
pstateTabWidth Text.Megaparsec.State Text/Megaparsec/State.hs:89:5-18 0.0 0.0 0 0
pstateSourcePos Text.Megaparsec.State Text/Megaparsec/State.hs:87:5-19 0.0 0.0 0 0
pstateOffset Text.Megaparsec.State Text/Megaparsec/State.hs:85:5-16 0.0 0.0 0 0
pstateLinePrefix Text.Megaparsec.State Text/Megaparsec/State.hs:91:5-20 0.0 0.0 0 0
pstateInput Text.Megaparsec.State Text/Megaparsec/State.hs:83:5-15 0.0 0.0 0 0
CAF Text.Megaparsec.Lexer <entire-module> 0.0 0.0 0 0
symbol' Text.Megaparsec.Lexer Text/Megaparsec/Lexer.hs:123:1-34 0.0 0.0 0 0
symbol Text.Megaparsec.Lexer Text/Megaparsec/Lexer.hs:111:1-32 0.0 0.0 0 0
space Text.Megaparsec.Lexer Text/Megaparsec/Lexer.hs:(68,1)-(71,44) 0.0 0.0 0 0
lexeme Text.Megaparsec.Lexer Text/Megaparsec/Lexer.hs:87:1-23 0.0 0.0 0 0
CAF Text.Megaparsec.Class <entire-module> 0.0 0.0 0 0
CAF Text.Megaparsec.Stream <entire-module> 0.0 0.0 0 32
unShareInput Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:186:36-47 0.0 0.0 0 0
unNoShareInput Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:261:40-53 0.0 0.0 0 0
CAF Text.Megaparsec.Pos <entire-module> 0.0 0.0 0 0
sourcePosPretty Text.Megaparsec.Pos Text/Megaparsec/Pos.hs:(142,1)-(146,52) 0.0 0.0 0 0
sourceName Text.Megaparsec.Pos Text/Megaparsec/Pos.hs:123:5-14 0.0 0.0 0 0
sourceLine Text.Megaparsec.Pos Text/Megaparsec/Pos.hs:125:5-14 0.0 0.0 0 0
sourceColumn Text.Megaparsec.Pos Text/Megaparsec/Pos.hs:127:5-16 0.0 0.0 0 0
pos1 Text.Megaparsec.Pos Text/Megaparsec/Pos.hs:76:1-14 0.0 0.0 0 0
initialPos Text.Megaparsec.Pos Text/Megaparsec/Pos.hs:136:1-36 0.0 0.0 0 0
defaultTabWidth Text.Megaparsec.Pos Text/Megaparsec/Pos.hs:88:1-25 0.0 0.0 0 0
CAF Text.Megaparsec.Internal <entire-module> 0.0 0.0 0 0
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 0.0 0.0 0 0
runParsecT Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:(675,1)-(680,59) 0.0 0.0 0 176
CAF Text.Megaparsec.Error <entire-module> 0.0 0.0 0 0
showErrorItem Text.Megaparsec.Error Text/Megaparsec/Error.hs:(465,1)-(468,30) 0.0 0.0 0 0
setErrorOffset Text.Megaparsec.Error Text/Megaparsec/Error.hs:(202,1)-(203,50) 0.0 0.0 0 0
parseErrorTextPretty Text.Megaparsec.Error Text/Megaparsec/Error.hs:(445,1)-(456,52) 0.0 0.0 0 0
parseErrorPretty Text.Megaparsec.Error Text/Megaparsec/Error.hs:(430,1)-(431,70) 0.0 0.0 0 0
mapParseError Text.Megaparsec.Error Text/Megaparsec/Error.hs:(188,1)-(189,66) 0.0 0.0 0 0
errorOffset Text.Megaparsec.Error Text/Megaparsec/Error.hs:(195,1)-(196,32) 0.0 0.0 0 0
errorBundlePretty Text.Megaparsec.Error Text/Megaparsec/Error.hs:(366,1)-(418,64) 0.0 0.0 0 0
bundlePosState Text.Megaparsec.Error Text/Megaparsec/Error.hs:250:5-18 0.0 0.0 0 0
bundleErrors Text.Megaparsec.Error Text/Megaparsec/Error.hs:248:5-16 0.0 0.0 0 0
attachSourcePos Text.Megaparsec.Error Text/Megaparsec/Error.hs:(321,1)-(327,38) 0.0 0.0 0 0
CAF Text.Megaparsec.Char.Lexer <entire-module> 0.0 0.0 0 0
skipLineComment Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(95,1)-(96,67) 0.0 0.0 0 0
skipBlockCommentNested Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(125,1)-(129,20) 0.0 0.0 0 0
skipBlockComment Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(108,1)-(111,20) 0.0 0.0 0 0
signed Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(549,1)-(551,56) 0.0 0.0 0 0
scientific Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(473,1)-(477,29) 0.0 0.0 0 0
octal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(421,1)-(427,55) 0.0 0.0 0 0
nonIndented Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:208:1-46 0.0 0.0 0 0
lineFold Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(319,1)-(320,57) 0.0 0.0 0 0
indentGuard Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(188,1)-(193,39) 0.0 0.0 0 0
indentBlock Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(243,1)-(265,16) 0.0 0.0 0 0
incorrectIndent Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(163,1)-(165,35) 0.0 0.0 0 0
hexadecimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(448,1)-(454,56) 0.0 0.0 0 0
float Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(494,1)-(503,9) 0.0 0.0 0 0
charLiteral Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(343,1)-(349,49) 0.0 0.0 0 0
binary Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:(393,1)-(400,39) 0.0 0.0 0 0
CAF Text.Megaparsec <entire-module> 0.0 0.0 0 0
runParserT' Text.Megaparsec Text/Megaparsec.hs:(282,1)-(296,54) 0.0 0.0 0 336
runParserT Text.Megaparsec Text/Megaparsec.hs:268:1-65 0.0 0.0 0 376
runParser' Text.Megaparsec Text/Megaparsec.hs:252:1-42 0.0 0.0 0 0
runParser Text.Megaparsec Text/Megaparsec.hs:238:1-61 0.0 0.0 0 0
parseTest Text.Megaparsec Text/Megaparsec.hs:(217,1)-(220,22) 0.0 0.0 0 0
parseMaybe Text.Megaparsec Text/Megaparsec.hs:(199,1)-(202,21) 0.0 0.0 0 0
parse Text.Megaparsec Text/Megaparsec.hs:187:1-17 0.0 0.0 0 0
match Text.Megaparsec Text/Megaparsec.hs:(592,1)-(602,50) 0.0 0.0 0 0
CAF Data.Tuple.Solo <entire-module> 0.0 0.0 0 0
CAF System.Random.SplitMix.Init <entire-module> 0.0 0.0 0 0
initialSeed System.Random.SplitMix.Init src/System/Random/SplitMix/Init.hs:40:1-26 0.0 0.0 0 0
CAF System.Random.SplitMix32 <entire-module> 0.0 0.0 0 0
unseedSMGen System.Random.SplitMix32 src/System/Random/SplitMix32.hs:349:1-46 0.0 0.0 0 0
splitSMGen System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(199,1)-(203,26) 0.0 0.0 0 0
seedSMGen' System.Random.SplitMix32 src/System/Random/SplitMix32.hs:345:1-30 0.0 0.0 0 0
seedSMGen System.Random.SplitMix32 src/System/Random/SplitMix32.hs:341:1-47 0.0 0.0 0 0
nextWord64 System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(111,1)-(114,28) 0.0 0.0 0 0
nextWord32 System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(105,1)-(107,24) 0.0 0.0 0 0
nextTwoWord32 System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(118,1)-(120,28) 0.0 0.0 0 0
nextInteger System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(155,1)-(158,64) 0.0 0.0 0 0
nextInt System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(124,1)-(130,39) 0.0 0.0 0 0
nextFloat System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(150,1)-(151,63) 0.0 0.0 0 0
nextDouble System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(141,1)-(142,65) 0.0 0.0 0 0
newSMGen System.Random.SplitMix32 src/System/Random/SplitMix32.hs:365:1-48 0.0 0.0 0 0
mkSMGen System.Random.SplitMix32 src/System/Random/SplitMix32.hs:357:1-56 0.0 0.0 0 0
initSMGen System.Random.SplitMix32 src/System/Random/SplitMix32.hs:361:1-37 0.0 0.0 0 0
bitmaskWithRejection64' System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(319,1)-(325,27) 0.0 0.0 0 0
bitmaskWithRejection64 System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(289,1)-(290,58) 0.0 0.0 0 0
bitmaskWithRejection32' System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(300,1)-(306,27) 0.0 0.0 0 0
bitmaskWithRejection32 System.Random.SplitMix32 src/System/Random/SplitMix32.hs:(276,1)-(277,58) 0.0 0.0 0 0
CAF System.Random.SplitMix <entire-module> 0.0 0.0 0 0
unseedSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:369:1-46 0.0 0.0 0 0
splitSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:(225,1)-(229,31) 0.0 0.0 0 0
seedSMGen' System.Random.SplitMix src/System/Random/SplitMix.hs:365:1-30 0.0 0.0 0 0
seedSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:361:1-47 0.0 0.0 0 0
nextWord64 System.Random.SplitMix src/System/Random/SplitMix.hs:(121,1)-(123,29) 0.0 0.0 0 0
nextWord32 System.Random.SplitMix src/System/Random/SplitMix.hs:(129,1)-(136,28) 0.0 0.0 0 0
nextTwoWord32 System.Random.SplitMix src/System/Random/SplitMix.hs:(142,1)-(149,28) 0.0 0.0 0 0
nextInteger System.Random.SplitMix src/System/Random/SplitMix.hs:(181,1)-(184,64) 0.0 0.0 0 0
nextInt System.Random.SplitMix src/System/Random/SplitMix.hs:(153,1)-(157,39) 0.0 0.0 0 0
nextFloat System.Random.SplitMix src/System/Random/SplitMix.hs:(176,1)-(177,63) 0.0 0.0 0 0
nextDouble System.Random.SplitMix src/System/Random/SplitMix.hs:(166,1)-(167,65) 0.0 0.0 0 0
newSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:385:1-48 0.0 0.0 0 0
mkSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:377:1-61 0.0 0.0 0 0
initSMGen System.Random.SplitMix src/System/Random/SplitMix.hs:381:1-36 0.0 0.0 0 0
bitmaskWithRejection64' System.Random.SplitMix src/System/Random/SplitMix.hs:(338,1)-(344,27) 0.0 0.0 0 0
bitmaskWithRejection64 System.Random.SplitMix src/System/Random/SplitMix.hs:(308,1)-(309,58) 0.0 0.0 0 0
bitmaskWithRejection32' System.Random.SplitMix src/System/Random/SplitMix.hs:(319,1)-(325,27) 0.0 0.0 0 0
bitmaskWithRejection32 System.Random.SplitMix src/System/Random/SplitMix.hs:(294,1)-(295,58) 0.0 0.0 0 0
CAF System.Random.GFinite <entire-module> 0.0 0.0 0 0
CAF System.Random.Internal <entire-module> 0.0 0.0 0 0
unStdGen System.Random.Internal src/System/Random/Internal.hs:555:27-34 0.0 0.0 0 0
unStateGen System.Random.Internal src/System/Random/Internal.hs:442:33-42 0.0 0.0 0 0
theStdGen System.Random.Internal src/System/Random/Internal.hs:587:1-64 0.0 0.0 0 0
mkStdGen System.Random.Internal src/System/Random/Internal.hs:583:1-45 0.0 0.0 0 0
CAF System.Random <entire-module> 0.0 0.0 0 0
setStdGen System.Random src/System/Random.hs:489:1-41 0.0 0.0 0 0
randomRIO System.Random src/System/Random.hs:550:1-46 0.0 0.0 0 0
randomIO System.Random src/System/Random.hs:571:1-30 0.0 0.0 0 0
newStdGen System.Random src/System/Random.hs:504:1-55 0.0 0.0 0 0
initStdGen System.Random src/System/Random.hs:366:1-45 0.0 0.0 0 0
getStdRandom System.Random src/System/Random.hs:(527,1)-(528,28) 0.0 0.0 0 0
getStdGen System.Random src/System/Random.hs:496:1-40 0.0 0.0 0 0
CAF Test.QuickCheck.Poly <entire-module> 0.0 0.0 0 0
unOrdC Test.QuickCheck.Poly src/Test/QuickCheck/Poly.hs:146:22-27 0.0 0.0 0 0
unOrdB Test.QuickCheck.Poly src/Test/QuickCheck/Poly.hs:112:22-27 0.0 0.0 0 0
unOrdA Test.QuickCheck.Poly src/Test/QuickCheck/Poly.hs:77:22-27 0.0 0.0 0 0
unC Test.QuickCheck.Poly src/Test/QuickCheck/Poly.hs:59:16-18 0.0 0.0 0 0
unB Test.QuickCheck.Poly src/Test/QuickCheck/Poly.hs:44:16-18 0.0 0.0 0 0
unA Test.QuickCheck.Poly src/Test/QuickCheck/Poly.hs:29:16-18 0.0 0.0 0 0
CAF Test.QuickCheck.Function <entire-module> 0.0 0.0 0 0
functionVoid Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:201:1-20 0.0 0.0 0 0
functionShow Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:194:1-40 0.0 0.0 0 0
functionRealFrac Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:186:1-54 0.0 0.0 0 0
functionPairWith Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:227:1-68 0.0 0.0 0 0
functionMapWith Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:211:1-67 0.0 0.0 0 0
functionMap Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:207:1-38 0.0 0.0 0 0
functionIntegral Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:190:1-55 0.0 0.0 0 0
functionElements Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:182:1-49 0.0 0.0 0 0
functionEitherWith Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:234:1-73 0.0 0.0 0 0
functionBoundedEnum Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:178:1-59 0.0 0.0 0 0
applyFun3 Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:617:1-39 0.0 0.0 0 0
applyFun2 Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:612:1-34 0.0 0.0 0 0
applyFun Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:602:1-22 0.0 0.0 0 0
apply Test.QuickCheck.Function src/Test/QuickCheck/Function.hs:592:1-16 0.0 0.0 0 0
CAF Test.QuickCheck.Random <entire-module> 0.0 0.0 0 0
newQCGen Test.QuickCheck.Random src/Test/QuickCheck/Random.hs:68:1-30 0.0 0.0 0 0
mkQCGen Test.QuickCheck.Random src/Test/QuickCheck/Random.hs:75:1-44 0.0 0.0 0 0
CAF Test.QuickCheck.Gen.Unsafe <entire-module> 0.0 0.0 0 0
promote Test.QuickCheck.Gen.Unsafe src/Test/QuickCheck/Gen/Unsafe.hs:(28,1)-(30,23) 0.0 0.0 0 0
delay Test.QuickCheck.Gen.Unsafe src/Test/QuickCheck/Gen/Unsafe.hs:36:1-37 0.0 0.0 0 0
capture Test.QuickCheck.Gen.Unsafe src/Test/QuickCheck/Gen/Unsafe.hs:51:1-53 0.0 0.0 0 0
CAF Test.QuickCheck.Gen <entire-module> 0.0 0.0 0 0
vectorOf Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:365:1-21 0.0 0.0 0 0
variant Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:103:1-77 0.0 0.0 0 0
unGen Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:60:3-7 0.0 0.0 0 0
suchThatMaybe Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(282,1)-(288,52) 0.0 0.0 0 0
suchThatMap Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(276,1)-(277,46) 0.0 0.0 0 0
suchThat Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(267,1)-(271,63) 0.0 0.0 0 0
sublistOf Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:321:1-58 0.0 0.0 0 0
sized Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:117:1-52 0.0 0.0 0 0
shuffle Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(325,1)-(327,55) 0.0 0.0 0 0
scale Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:144:1-40 0.0 0.0 0 0
sample' Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(236,1)-(237,53) 0.0 0.0 0 0
sample Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(241,1)-(243,22) 0.0 0.0 0 0
resize Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(138,1)-(139,42) 0.0 0.0 0 0
oneof Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(293,1)-(294,50) 0.0 0.0 0 0
listOf1 Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(359,1)-(361,19) 0.0 0.0 0 0
listOf Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(352,1)-(354,19) 0.0 0.0 0 0
infiniteListOf Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:369:1-42 0.0 0.0 0 0
growingElements Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(334,1)-(341,43) 0.0 0.0 0 0
getSize Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:133:1-20 0.0 0.0 0 0
generate Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(230,1)-(232,20) 0.0 0.0 0 0
genFloat Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:256:1-53 0.0 0.0 0 0
genDouble Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:255:1-54 0.0 0.0 0 0
frequency Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(299,1)-(312,58) 0.0 0.0 0 0
elements Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(316,1)-(317,57) 0.0 0.0 0 0
chooseWord64 Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(203,1)-(209,40) 0.0 0.0 0 0
chooseUpTo Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(222,1)-(224,37) 0.0 0.0 0 0
chooseInteger Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(193,1)-(200,65) 0.0 0.0 0 0
chooseInt64 Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(212,1)-(219,49) 0.0 0.0 0 0
chooseInt Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:163:1-33 0.0 0.0 0 0
chooseEnum Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(158,1)-(159,52) 0.0 0.0 0 0
chooseBoundedIntegral Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:(171,1)-(185,31) 0.0 0.0 0 0
chooseAny Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:154:1-53 0.0 0.0 0 0
choose Test.QuickCheck.Gen src/Test/QuickCheck/Gen.hs:150:1-59 0.0 0.0 0 0
CAF Test.QuickCheck.Arbitrary <entire-module> 0.0 0.0 0 0
vector Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1588:1-31 0.0 0.0 0 0
subterms Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:347:1-27 0.0 0.0 0 0
shrinkRealFrac Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:(1250,1)-(1268,28) 0.0 0.0 0 0
shrinkNothing Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1182:1-20 0.0 0.0 0 0
shrinkMapBy Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1199:1-37 0.0 0.0 0 0
shrinkMap Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1195:1-38 0.0 0.0 0 0
shrinkList Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:(473,1)-(488,19) 0.0 0.0 0 0
shrinkIntegral Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:(1203,1)-(1217,39) 0.0 0.0 0 0
shrinkDecimal Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:(1273,1)-(1291,67) 0.0 0.0 0 0
shrinkBoundedEnum Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:(1238,1)-(1245,50) 0.0 0.0 0 0
shrink2 Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:307:1-35 0.0 0.0 0 0
shrink1 Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:295:1-27 0.0 0.0 0 0
recursivelyShrink Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:317:1-54 0.0 0.0 0 0
orderedList Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1592:1-35 0.0 0.0 0 0
infiniteList Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1596:1-39 0.0 0.0 0 0
genericShrink Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:313:1-51 0.0 0.0 0 0
genericCoarbitrary Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1336:1-40 0.0 0.0 0 0
coarbitraryShow Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1575:1-40 0.0 0.0 0 0
coarbitraryReal Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1571:1-46 0.0 0.0 0 0
coarbitraryIntegral Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1567:1-29 0.0 0.0 0 0
coarbitraryEnum Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1579:1-36 0.0 0.0 0 0
arbitraryUnicodeChar Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:(1162,1)-(1168,15) 0.0 0.0 0 0
arbitrarySizedNatural Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:(1092,1)-(1094,42) 0.0 0.0 0 0
arbitrarySizedIntegral Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:(1085,1)-(1087,43) 0.0 0.0 0 0
arbitrarySizedFractional Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:(1102,1)-(1106,50) 0.0 0.0 0 0
arbitrarySizedBoundedIntegral Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:(1138,1)-(1156,45) 0.0 0.0 0 0
arbitraryPrintableChar Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1176:1-53 0.0 0.0 0 0
arbitraryBoundedRandom Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1123:1-51 0.0 0.0 0 0
arbitraryBoundedIntegral Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1118:1-69 0.0 0.0 0 0
arbitraryBoundedEnum Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1127:1-54 0.0 0.0 0 0
arbitraryASCIIChar Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1172:1-46 0.0 0.0 0 0
arbitrary2 Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:304:1-47 0.0 0.0 0 0
arbitrary1 Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:292:1-36 0.0 0.0 0 0
applyArbitrary4 Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1080:1-47 0.0 0.0 0 0
applyArbitrary3 Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1074:1-58 0.0 0.0 0 0
applyArbitrary2 Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1068:1-48 0.0 0.0 0 0
>< Test.QuickCheck.Arbitrary src/Test/QuickCheck/Arbitrary.hs:1364:1-10 0.0 0.0 0 0
CAF Data.Attoparsec.Text.FastSet <entire-module> 0.0 0.0 0 0
set Data.Attoparsec.Text.FastSet internal/Data/Attoparsec/Text/FastSet.hs:105:1-25 0.0 0.0 0 0
member Data.Attoparsec.Text.FastSet internal/Data/Attoparsec/Text/FastSet.hs:(109,1)-(115,52) 0.0 0.0 0 0
fromList Data.Attoparsec.Text.FastSet internal/Data/Attoparsec/Text/FastSet.hs:(83,1)-(94,29) 0.0 0.0 0 0
charClass Data.Attoparsec.Text.FastSet internal/Data/Attoparsec/Text/FastSet.hs:(118,1)-(121,28) 0.0 0.0 0 0
CAF Data.Attoparsec.Text.Buffer <entire-module> 0.0 0.0 0 0
unbufferAt Data.Attoparsec.Text.Buffer internal/Data/Attoparsec/Text/Buffer.hs:(85,1)-(87,26) 0.0 0.0 0 0
unbuffer Data.Attoparsec.Text.Buffer internal/Data/Attoparsec/Text/Buffer.hs:82:1-49 0.0 0.0 0 0
pappend Data.Attoparsec.Text.Buffer internal/Data/Attoparsec/Text/Buffer.hs:(105,1)-(106,55) 0.0 0.0 0 0
lengthCodeUnits Data.Attoparsec.Text.Buffer internal/Data/Attoparsec/Text/Buffer.hs:158:1-29 0.0 0.0 0 0
buffer Data.Attoparsec.Text.Buffer internal/Data/Attoparsec/Text/Buffer.hs:79:1-49 0.0 0.0 0 0
CAF Data.Attoparsec.ByteString.FastSet <entire-module> 0.0 0.0 0 0
set Data.Attoparsec.ByteString.FastSet internal/Data/Attoparsec/ByteString/FastSet.hs:(59,1)-(60,54) 0.0 0.0 0 0
memberWord8 Data.Attoparsec.ByteString.FastSet internal/Data/Attoparsec/ByteString/FastSet.hs:(76,1)-(87,32) 0.0 0.0 0 0
fromSet Data.Attoparsec.ByteString.FastSet internal/Data/Attoparsec/ByteString/FastSet.hs:44:25-31 0.0 0.0 0 0
fromList Data.Attoparsec.ByteString.FastSet internal/Data/Attoparsec/ByteString/FastSet.hs:63:1-23 0.0 0.0 0 0
charClass Data.Attoparsec.ByteString.FastSet internal/Data/Attoparsec/ByteString/FastSet.hs:(109,1)-(112,19) 0.0 0.0 0 0
CAF Data.Attoparsec.ByteString.Buffer <entire-module> 0.0 0.0 0 0
unbuffer Data.Attoparsec.ByteString.Buffer internal/Data/Attoparsec/ByteString/Buffer.hs:89:1-47 0.0 0.0 0 0
pappend Data.Attoparsec.ByteString.Buffer internal/Data/Attoparsec/ByteString/Buffer.hs:(105,1)-(106,78) 0.0 0.0 0 0
buffer Data.Attoparsec.ByteString.Buffer internal/Data/Attoparsec/ByteString/Buffer.hs:86:1-59 0.0 0.0 0 0
CAF Data.Attoparsec.Text.Internal <entire-module> 0.0 0.0 0 0
takeText Data.Attoparsec.Text.Internal Data/Attoparsec/Text/Internal.hs:304:1-35 0.0 0.0 0 0
takeLazyText Data.Attoparsec.Text.Internal Data/Attoparsec/Text/Internal.hs:308:1-43 0.0 0.0 0 0
skip Data.Attoparsec.Text.Internal Data/Attoparsec/Text/Internal.hs:(115,1)-(119,20) 0.0 0.0 0 0
match Data.Attoparsec.Text.Internal Data/Attoparsec/Text/Internal.hs:(525,1)-(528,38) 0.0 0.0 0 0
endOfLine Data.Attoparsec.Text.Internal Data/Attoparsec/Text/Internal.hs:444:1-69 0.0 0.0 0 0
CAF Data.Attoparsec.ByteString.Internal <entire-module> 0.0 0.0 0 0
takeLazyByteString Data.Attoparsec.ByteString.Internal Data/Attoparsec/ByteString/Internal.hs:340:1-49 0.0 0.0 0 0
takeByteString Data.Attoparsec.ByteString.Internal Data/Attoparsec/ByteString/Internal.hs:336:1-41 0.0 0.0 0 0
storable Data.Attoparsec.ByteString.Internal Data/Attoparsec/ByteString/Internal.hs:(142,1)-(148,38) 0.0 0.0 0 0
skip Data.Attoparsec.ByteString.Internal Data/Attoparsec/ByteString/Internal.hs:(123,1)-(127,20) 0.0 0.0 0 0
match Data.Attoparsec.ByteString.Internal Data/Attoparsec/ByteString/Internal.hs:(579,1)-(582,38) 0.0 0.0 0 0
getChunk Data.Attoparsec.ByteString.Internal Data/Attoparsec/ByteString/Internal.hs:(347,1)-(351,23) 0.0 0.0 0 0
endOfLine Data.Attoparsec.ByteString.Internal Data/Attoparsec/ByteString/Internal.hs:496:1-68 0.0 0.0 0 0
CAF Data.Attoparsec.Zepto <entire-module> 0.0 0.0 0 0
CAF Data.Attoparsec.Number <entire-module> 0.0 0.0 0 0
CAF Data.Attoparsec.Internal.Types <entire-module> 0.0 0.0 0 0
runParser Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:111:7-15 0.0 0.0 0 0
fromPos Data.Attoparsec.Internal.Types Data/Attoparsec/Internal/Types.hs:46:21-27 0.0 0.0 0 0
CAF Data.Attoparsec.Internal <entire-module> 0.0 0.0 0 0
prompt Data.Attoparsec.Internal Data/Attoparsec/Internal.hs:(55,1)-(58,45) 0.0 0.0 0 0
endOfInput Data.Attoparsec.Internal Data/Attoparsec/Internal.hs:(110,1)-(117,55) 0.0 0.0 0 0
demandInput_ Data.Attoparsec.Internal Data/Attoparsec/Internal.hs:(85,1)-(91,48) 0.0 0.0 0 0
demandInput Data.Attoparsec.Internal Data/Attoparsec/Internal.hs:(73,1)-(78,41) 0.0 0.0 0 0
compareResults Data.Attoparsec.Internal Data/Attoparsec/Internal.hs:(41,1)-(46,31) 0.0 0.0 0 0
CAF Data.Attoparsec.Combinator <entire-module> 0.0 0.0 0 0
skipMany1 Data.Attoparsec.Combinator Data/Attoparsec/Combinator.hs:228:1-29 0.0 0.0 0 0
skipMany Data.Attoparsec.Combinator Data/Attoparsec/Combinator.hs:(220,1)-(221,40) 0.0 0.0 0 0
sepBy1' Data.Attoparsec.Combinator Data/Attoparsec/Combinator.hs:(175,1)-(176,62) 0.0 0.0 0 0
sepBy1 Data.Attoparsec.Combinator Data/Attoparsec/Combinator.hs:(162,1)-(163,55) 0.0 0.0 0 0
sepBy' Data.Attoparsec.Combinator Data/Attoparsec/Combinator.hs:(150,1)-(151,67) 0.0 0.0 0 0
sepBy Data.Attoparsec.Combinator Data/Attoparsec/Combinator.hs:138:1-68 0.0 0.0 0 0
option Data.Attoparsec.Combinator Data/Attoparsec/Combinator.hs:91:1-25 0.0 0.0 0 0
manyTill' Data.Attoparsec.Combinator Data/Attoparsec/Combinator.hs:(211,1)-(212,62) 0.0 0.0 0 0
manyTill Data.Attoparsec.Combinator Data/Attoparsec/Combinator.hs:(192,1)-(193,55) 0.0 0.0 0 0
choice Data.Attoparsec.Combinator Data/Attoparsec/Combinator.hs:79:1-13 0.0 0.0 0 0
CAF Data.Attoparsec.ByteString.Lazy <entire-module> 0.0 0.0 0 0
parseTest Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:100:1-33 0.0 0.0 0 0
parse Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(89,1)-(96,56) 0.0 0.0 0 0
maybeResult Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(104,1)-(105,32) 0.0 0.0 0 0
eitherResult Data.Attoparsec.ByteString.Lazy Data/Attoparsec/ByteString/Lazy.hs:(109,1)-(111,77) 0.0 0.0 0 0
CAF Data.Attoparsec.ByteString.Char8 <entire-module> 0.0 0.0 0 0
signed Data.Attoparsec.ByteString.Char8 Data/Attoparsec/ByteString/Char8.hs:(470,1)-(472,12) 0.0 0.0 0 0
scientific Data.Attoparsec.ByteString.Char8 Data/Attoparsec/ByteString/Char8.hs:547:1-30 0.0 0.0 0 0
rational Data.Attoparsec.ByteString.Char8 Data/Attoparsec/ByteString/Char8.hs:490:1-36 0.0 0.0 0 0
number Data.Attoparsec.ByteString.Char8 Data/Attoparsec/ByteString/Char8.hs:(535,1)-(540,41) 0.0 0.0 0 0
hexadecimal Data.Attoparsec.ByteString.Char8 Data/Attoparsec/ByteString/Char8.hs:(425,1)-(432,77) 0.0 0.0 0 0
double Data.Attoparsec.ByteString.Char8 Data/Attoparsec/ByteString/Char8.hs:529:1-39 0.0 0.0 0 0
decimal Data.Attoparsec.ByteString.Char8 Data/Attoparsec/ByteString/Char8.hs:(447,1)-(448,49) 0.0 0.0 0 0
<*. Data.Attoparsec.ByteString.Char8 Data/Attoparsec/ByteString/Char8.hs:405:1-25 0.0 0.0 0 0
.*> Data.Attoparsec.ByteString.Char8 Data/Attoparsec/ByteString/Char8.hs:399:1-25 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.AbsoluteTime <entire-module> 0.0 0.0 0 0
taiNominalDayStart Data.Time.Clock.Internal.AbsoluteTime lib/Data/Time/Clock/Internal/AbsoluteTime.hs:31:1-88 0.0 0.0 0 0
taiEpoch Data.Time.Clock.Internal.AbsoluteTime lib/Data/Time/Clock/Internal/AbsoluteTime.hs:28:1-27 0.0 0.0 0 0
diffAbsoluteTime Data.Time.Clock.Internal.AbsoluteTime lib/Data/Time/Clock/Internal/AbsoluteTime.hs:39:1-62 0.0 0.0 0 0
addAbsoluteTime Data.Time.Clock.Internal.AbsoluteTime lib/Data/Time/Clock/Internal/AbsoluteTime.hs:35:1-61 0.0 0.0 0 0
CAF Data.Time.Clock.System <entire-module> 0.0 0.0 0 0
utcToSystemTime Data.Time.Clock.System lib/Data/Time/Clock/System.hs:(46,1)-(61,54) 0.0 0.0 0 0
truncateSystemTimeLeapSecond Data.Time.Clock.System lib/Data/Time/Clock/System.hs:(24,1)-(26,34) 0.0 0.0 0 0
systemToUTCTime Data.Time.Clock.System lib/Data/Time/Clock/System.hs:(30,1)-(42,23) 0.0 0.0 0 0
systemToTAITime Data.Time.Clock.System lib/Data/Time/Clock/System.hs:(68,1)-(71,47) 0.0 0.0 0 0
systemEpochDay Data.Time.Clock.System lib/Data/Time/Clock/System.hs:75:1-40 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.UTCDiff <entire-module> 0.0 0.0 0 0
diffUTCTime Data.Time.Clock.Internal.UTCDiff lib/Data/Time/Clock/Internal/UTCDiff.hs:15:1-71 0.0 0.0 0 0
addUTCTime Data.Time.Clock.Internal.UTCDiff lib/Data/Time/Clock/Internal/UTCDiff.hs:11:1-70 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.POSIXTime <entire-module> 0.0 0.0 0 0
posixDayLength Data.Time.Clock.Internal.POSIXTime lib/Data/Time/Clock/Internal/POSIXTime.hs:9:1-27 0.0 0.0 0 0
CAF Data.Time.Clock.POSIX <entire-module> 0.0 0.0 0 0
utcTimeToPOSIXSeconds Data.Time.Clock.POSIX lib/Data/Time/Clock/POSIX.hs:(42,1)-(43,98) 0.0 0.0 0 0
systemToPOSIXTime Data.Time.Clock.POSIX lib/Data/Time/Clock/POSIX.hs:46:1-83 0.0 0.0 0 0
posixSecondsToUTCTime Data.Time.Clock.POSIX lib/Data/Time/Clock/POSIX.hs:(37,1)-(39,56) 0.0 0.0 0 0
getPOSIXTime Data.Time.Clock.POSIX lib/Data/Time/Clock/POSIX.hs:50:1-51 0.0 0.0 0 0
getCurrentTime Data.Time.Clock.POSIX lib/Data/Time/Clock/POSIX.hs:54:1-53 0.0 0.0 0 0
CAF Data.Time.Calendar.WeekDate <entire-module> 0.0 0.0 0 0
toWeekDate Data.Time.Calendar.WeekDate lib/Data/Time/Calendar/WeekDate.hs:(103,1)-(105,27) 0.0 0.0 0 0
toWeekCalendar Data.Time.Calendar.WeekDate lib/Data/Time/Calendar/WeekDate.hs:(50,1)-(61,79) 0.0 0.0 0 0
showWeekDate Data.Time.Calendar.WeekDate lib/Data/Time/Calendar/WeekDate.hs:(131,1)-(133,31) 0.0 0.0 0 0
fromWeekDateValid Data.Time.Calendar.WeekDate lib/Data/Time/Calendar/WeekDate.hs:(125,1)-(127,63) 0.0 0.0 0 0
fromWeekDate Data.Time.Calendar.WeekDate lib/Data/Time/Calendar/WeekDate.hs:110:1-88 0.0 0.0 0 0
fromWeekCalendarValid Data.Time.Calendar.WeekDate lib/Data/Time/Calendar/WeekDate.hs:(95,1)-(97,72) 0.0 0.0 0 0
fromWeekCalendar Data.Time.Calendar.WeekDate lib/Data/Time/Calendar/WeekDate.hs:(74,1)-(82,71) 0.0 0.0 0 0
CAF Data.Time.Format.Parse.Instances <entire-module> 0.0 0.0 0 0
CAF Data.Time.Format.Parse.Class <entire-module> 0.0 0.0 0 0
timeSubstituteTimeSpecifier Data.Time.Format.Parse.Class lib/Data/Time/Format/Parse/Class.hs:(213,1)-(222,41) 0.0 0.0 0 0
timeParseTimeSpecifier Data.Time.Format.Parse.Class lib/Data/Time/Format/Parse/Class.hs:(139,1)-(210,58) 0.0 0.0 0 0
parseSpecifiers Data.Time.Format.Parse.Class lib/Data/Time/Format/Parse/Class.hs:(69,1)-(100,12) 0.0 0.0 0 0
durationParseTimeSpecifier Data.Time.Format.Parse.Class lib/Data/Time/Format/Parse/Class.hs:(225,1)-(240,58) 0.0 0.0 0 0
CAF Data.Time.Format.Format.Instances <entire-module> 0.0 0.0 0 0
CAF Data.Time.Format.Format.Class <entire-module> 0.0 0.0 0 0
showPaddedFixedFraction Data.Time.Format.Format.Class lib/Data/Time/Format/Format/Class.hs:(92,1)-(100,50) 0.0 0.0 0 0
showPaddedFixed Data.Time.Format.Format.Class lib/Data/Time/Format/Format/Class.hs:(80,1)-(89,21) 0.0 0.0 0 0
formatTime Data.Time.Format.Format.Class lib/Data/Time/Format/Format/Class.hs:(325,1)-(330,59) 0.0 0.0 0 0
formatString Data.Time.Format.Format.Class lib/Data/Time/Format/Format/Class.hs:71:1-95 0.0 0.0 0 0
formatNumberStd Data.Time.Format.Format.Class lib/Data/Time/Format/Format/Class.hs:77:1-44 0.0 0.0 0 0
formatNumber Data.Time.Format.Format.Class lib/Data/Time/Format/Format/Class.hs:74:1-104 0.0 0.0 0 0
formatGeneral Data.Time.Format.Format.Class lib/Data/Time/Format/Format/Class.hs:(67,1)-(68,84) 0.0 0.0 0 0
foWidth Data.Time.Format.Format.Class lib/Data/Time/Format/Format/Class.hs:32:7-13 0.0 0.0 0 0
foPadding Data.Time.Format.Format.Class lib/Data/Time/Format/Format/Class.hs:31:7-15 0.0 0.0 0 0
foLocale Data.Time.Format.Format.Class lib/Data/Time/Format/Format/Class.hs:30:7-14 0.0 0.0 0 0
CAF Data.Time.Format.Locale <entire-module> 0.0 0.0 0 0
wDays Data.Time.Format.Locale lib/Data/Time/Format/Locale.hs:15:7-11 0.0 0.0 0 0
timeFmt Data.Time.Format.Locale lib/Data/Time/Format/Locale.hs:21:29-35 0.0 0.0 0 0
time12Fmt Data.Time.Format.Locale lib/Data/Time/Format/Locale.hs:21:38-46 0.0 0.0 0 0
rfc822DateFormat Data.Time.Format.Locale lib/Data/Time/Format/Locale.hs:97:1-46 0.0 0.0 0 0
months Data.Time.Format.Locale lib/Data/Time/Format/Locale.hs:17:7-12 0.0 0.0 0 0
knownTimeZones Data.Time.Format.Locale lib/Data/Time/Format/Locale.hs:23:7-20 0.0 0.0 0 0
iso8601DateFormat Data.Time.Format.Locale lib/Data/Time/Format/Locale.hs:(89,1)-(93,33) 0.0 0.0 0 0
defaultTimeLocale Data.Time.Format.Locale lib/Data/Time/Format/Locale.hs:(33,1)-(75,9) 0.0 0.0 0 0
dateTimeFmt Data.Time.Format.Locale lib/Data/Time/Format/Locale.hs:21:7-17 0.0 0.0 0 0
dateFmt Data.Time.Format.Locale lib/Data/Time/Format/Locale.hs:21:20-26 0.0 0.0 0 0
amPm Data.Time.Format.Locale lib/Data/Time/Format/Locale.hs:19:7-10 0.0 0.0 0 0
CAF Data.Time.Format.Parse <entire-module> 0.0 0.0 0 0
readSTime Data.Time.Format.Parse lib/Data/Time/Format/Parse.hs:170:1-60 0.0 0.0 0 0
readPTime Data.Time.Format.Parse lib/Data/Time/Format/Parse.hs:212:1-28 0.0 0.0 0 0
parseTimeOrError Data.Time.Format.Parse lib/Data/Time/Format/Parse.hs:(121,1)-(125,70) 0.0 0.0 0 0
parseTimeMultipleM Data.Time.Format.Parse lib/Data/Time/Format/Parse.hs:105:1-46 0.0 0.0 0 0
parseTimeM Data.Time.Format.Parse lib/Data/Time/Format/Parse.hs:72:1-70 0.0 0.0 0 0
CAF Data.Time.LocalTime.Internal.ZonedTime <entire-module> 0.0 0.0 0 0
zonedTimeZone Data.Time.LocalTime.Internal.ZonedTime lib/Data/Time/LocalTime/Internal/ZonedTime.hs:27:7-19 0.0 0.0 0 0
zonedTimeToUTC Data.Time.LocalTime.Internal.ZonedTime lib/Data/Time/LocalTime/Internal/ZonedTime.hs:38:1-57 0.0 0.0 0 0
zonedTimeToLocalTime Data.Time.LocalTime.Internal.ZonedTime lib/Data/Time/LocalTime/Internal/ZonedTime.hs:26:7-26 0.0 0.0 0 0
utcToZonedTime Data.Time.LocalTime.Internal.ZonedTime lib/Data/Time/LocalTime/Internal/ZonedTime.hs:35:1-68 0.0 0.0 0 0
utcToLocalZonedTime Data.Time.LocalTime.Internal.ZonedTime lib/Data/Time/LocalTime/Internal/ZonedTime.hs:(55,1)-(57,34) 0.0 0.0 0 0
getZonedTime Data.Time.LocalTime.Internal.ZonedTime lib/Data/Time/LocalTime/Internal/ZonedTime.hs:(49,1)-(52,34) 0.0 0.0 0 0
CAF Data.Time.LocalTime.Internal.LocalTime <entire-module> 0.0 0.0 0 0
utcToLocalTime Data.Time.LocalTime.Internal.LocalTime lib/Data/Time/LocalTime/Internal/LocalTime.hs:(54,1)-(56,58) 0.0 0.0 0 0
ut1ToLocalTime Data.Time.LocalTime.Internal.LocalTime lib/Data/Time/LocalTime/Internal/LocalTime.hs:(66,1)-(71,56) 0.0 0.0 0 0
localTimeToUTC Data.Time.LocalTime.Internal.LocalTime lib/Data/Time/LocalTime/Internal/LocalTime.hs:(60,1)-(62,44) 0.0 0.0 0 0
localTimeToUT1 Data.Time.LocalTime.Internal.LocalTime lib/Data/Time/LocalTime/Internal/LocalTime.hs:(75,1)-(76,89) 0.0 0.0 0 0
localTimeOfDay Data.Time.LocalTime.Internal.LocalTime lib/Data/Time/LocalTime/Internal/LocalTime.hs:34:7-20 0.0 0.0 0 0
localDay Data.Time.LocalTime.Internal.LocalTime lib/Data/Time/LocalTime/Internal/LocalTime.hs:33:7-14 0.0 0.0 0 0
diffLocalTime Data.Time.LocalTime.Internal.LocalTime lib/Data/Time/LocalTime/Internal/LocalTime.hs:50:1-77 0.0 0.0 0 0
addLocalTime Data.Time.LocalTime.Internal.LocalTime lib/Data/Time/LocalTime/Internal/LocalTime.hs:46:1-71 0.0 0.0 0 0
CAF Data.Time.LocalTime.Internal.CalendarDiffTime <entire-module> 0.0 0.0 0 0
scaleCalendarDiffTime Data.Time.LocalTime.Internal.CalendarDiffTime lib/Data/Time/LocalTime/Internal/CalendarDiffTime.hs:49:1-93 0.0 0.0 0 0
ctTime Data.Time.LocalTime.Internal.CalendarDiffTime lib/Data/Time/LocalTime/Internal/CalendarDiffTime.hs:16:7-12 0.0 0.0 0 0
ctMonths Data.Time.LocalTime.Internal.CalendarDiffTime lib/Data/Time/LocalTime/Internal/CalendarDiffTime.hs:15:7-14 0.0 0.0 0 0
calendarTimeTime Data.Time.LocalTime.Internal.CalendarDiffTime lib/Data/Time/LocalTime/Internal/CalendarDiffTime.hs:45:1-43 0.0 0.0 0 0
calendarTimeDays Data.Time.LocalTime.Internal.CalendarDiffTime lib/Data/Time/LocalTime/Internal/CalendarDiffTime.hs:42:1-89 0.0 0.0 0 0
CAF Data.Time.LocalTime.Internal.TimeOfDay <entire-module> 0.0 0.0 0 0
utcToLocalTimeOfDay Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:(82,1)-(85,24) 0.0 0.0 0 0
todSec Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:38:7-12 0.0 0.0 0 0
todMin Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:36:7-12 0.0 0.0 0 0
todHour Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:34:7-13 0.0 0.0 0 0
timeToTimeOfDay Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:(97,1)-(105,18) 0.0 0.0 0 0
timeToDaysAndTimeOfDay Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:(68,1)-(73,30) 0.0 0.0 0 0
timeOfDayToTime Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:113:1-100 0.0 0.0 0 0
timeOfDayToDayFraction Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:125:1-89 0.0 0.0 0 0
sinceMidnight Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:117:1-31 0.0 0.0 0 0
pastMidnight Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:109:1-30 0.0 0.0 0 0
midnight Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:49:1-26 0.0 0.0 0 0
midday Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:53:1-25 0.0 0.0 0 0
makeTimeOfDayValid Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:(59,1)-(63,28) 0.0 0.0 0 0
localToUTCTimeOfDay Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:89:1-98 0.0 0.0 0 0
daysAndTimeOfDayToTime Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:(77,1)-(78,109) 0.0 0.0 0 0
dayFractionToTimeOfDay Data.Time.LocalTime.Internal.TimeOfDay lib/Data/Time/LocalTime/Internal/TimeOfDay.hs:121:1-69 0.0 0.0 0 0
CAF Data.Time.LocalTime.Internal.TimeZone <entire-module> 0.0 0.0 0 0
utc Data.Time.LocalTime.Internal.TimeZone lib/Data/Time/LocalTime/Internal/TimeZone.hs:78:1-28 0.0 0.0 0 0
timeZoneSummerOnly Data.Time.LocalTime.Internal.TimeZone lib/Data/Time/LocalTime/Internal/TimeZone.hs:31:7-24 0.0 0.0 0 0
timeZoneOffsetString'' Data.Time.LocalTime.Internal.TimeZone lib/Data/Time/LocalTime/Internal/TimeZone.hs:(58,1)-(60,77) 0.0 0.0 0 0
timeZoneOffsetString' Data.Time.LocalTime.Internal.TimeZone lib/Data/Time/LocalTime/Internal/TimeZone.hs:(64,1)-(65,71) 0.0 0.0 0 0
timeZoneOffsetString Data.Time.LocalTime.Internal.TimeZone lib/Data/Time/LocalTime/Internal/TimeZone.hs:69:1-63 0.0 0.0 0 0
timeZoneName Data.Time.LocalTime.Internal.TimeZone lib/Data/Time/LocalTime/Internal/TimeZone.hs:33:7-18 0.0 0.0 0 0
timeZoneMinutes Data.Time.LocalTime.Internal.TimeZone lib/Data/Time/LocalTime/Internal/TimeZone.hs:29:7-21 0.0 0.0 0 0
minutesToTimeZone Data.Time.LocalTime.Internal.TimeZone lib/Data/Time/LocalTime/Internal/TimeZone.hs:43:1-41 0.0 0.0 0 0
hoursToTimeZone Data.Time.LocalTime.Internal.TimeZone lib/Data/Time/LocalTime/Internal/TimeZone.hs:47:1-46 0.0 0.0 0 0
getTimeZone Data.Time.LocalTime.Internal.TimeZone lib/Data/Time/LocalTime/Internal/TimeZone.hs:(148,1)-(150,26) 0.0 0.0 0 0
getCurrentTimeZone Data.Time.LocalTime.Internal.TimeZone lib/Data/Time/LocalTime/Internal/TimeZone.hs:154:1-56 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.CTimespec <entire-module> 0.0 0.0 0 0
realtimeRes Data.Time.Clock.Internal.CTimespec lib/Data/Time/Clock/Internal/CTimespec.hsc:(65,1)-(69,31) 0.0 0.0 0 0
clock_TAI Data.Time.Clock.Internal.CTimespec lib/Data/Time/Clock/Internal/CTimespec.hsc:(57,1)-(59,11) 0.0 0.0 0 0
clockResolution Data.Time.Clock.Internal.CTimespec lib/Data/Time/Clock/Internal/CTimespec.hsc:(72,1)-(76,38) 0.0 0.0 0 0
clockGetTime Data.Time.Clock.Internal.CTimespec lib/Data/Time/Clock/Internal/CTimespec.hsc:(49,1)-(52,5) 0.0 0.0 0 0
clockGetRes Data.Time.Clock.Internal.CTimespec lib/Data/Time/Clock/Internal/CTimespec.hsc:(37,1)-(45,31) 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.UTCTime <entire-module> 0.0 0.0 0 0
utctDayTime Data.Time.Clock.Internal.UTCTime lib/Data/Time/Clock/Internal/UTCTime.hs:28:7-17 0.0 0.0 0 0
utctDay Data.Time.Clock.Internal.UTCTime lib/Data/Time/Clock/Internal/UTCTime.hs:26:7-13 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.SystemTime <entire-module> 0.0 0.0 0 0
systemSeconds Data.Time.Clock.Internal.SystemTime lib/Data/Time/Clock/Internal/SystemTime.hs:39:7-19 0.0 0.0 0 0
systemNanoseconds Data.Time.Clock.Internal.SystemTime lib/Data/Time/Clock/Internal/SystemTime.hs:40:7-23 0.0 0.0 0 0
getTime_resolution Data.Time.Clock.Internal.SystemTime lib/Data/Time/Clock/Internal/SystemTime.hs:88:1-51 0.0 0.0 0 0
getTAISystemTime Data.Time.Clock.Internal.SystemTime lib/Data/Time/Clock/Internal/SystemTime.hs:(90,1)-(93,72) 0.0 0.0 0 0
getSystemTime Data.Time.Clock.Internal.SystemTime lib/Data/Time/Clock/Internal/SystemTime.hs:86:1-49 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.NominalDiffTime <entire-module> 0.0 0.0 0 0
secondsToNominalDiffTime Data.Time.Clock.Internal.NominalDiffTime lib/Data/Time/Clock/Internal/NominalDiffTime.hs:36:1-44 0.0 0.0 0 0
nominalDiffTimeToSeconds Data.Time.Clock.Internal.NominalDiffTime lib/Data/Time/Clock/Internal/NominalDiffTime.hs:42:1-50 0.0 0.0 0 0
nominalDay Data.Time.Clock.Internal.NominalDiffTime lib/Data/Time/Clock/Internal/NominalDiffTime.hs:108:1-18 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.DiffTime <entire-module> 0.0 0.0 0 0
secondsToDiffTime Data.Time.Clock.Internal.DiffTime lib/Data/Time/Clock/Internal/DiffTime.hs:77:1-31 0.0 0.0 0 0
picosecondsToDiffTime Data.Time.Clock.Internal.DiffTime lib/Data/Time/Clock/Internal/DiffTime.hs:81:1-48 0.0 0.0 0 0
diffTimeToPicoseconds Data.Time.Clock.Internal.DiffTime lib/Data/Time/Clock/Internal/DiffTime.hs:85:1-50 0.0 0.0 0 0
CAF Data.Time.Calendar.Week <entire-module> 0.0 0.0 0 0
weekLastDay Data.Time.Calendar.Week lib/Data/Time/Calendar/Week.hs:126:1-75 0.0 0.0 0 0
weekFirstDay Data.Time.Calendar.Week lib/Data/Time/Calendar/Week.hs:109:1-90 0.0 0.0 0 0
weekAllDays Data.Time.Calendar.Week lib/Data/Time/Calendar/Week.hs:92:1-82 0.0 0.0 0 0
firstDayOfWeekOnAfter Data.Time.Calendar.Week lib/Data/Time/Calendar/Week.hs:74:1-83 0.0 0.0 0 0
dayOfWeekDiff Data.Time.Calendar.Week lib/Data/Time/Calendar/Week.hs:70:1-52 0.0 0.0 0 0
dayOfWeek Data.Time.Calendar.Week lib/Data/Time/Calendar/Week.hs:65:1-62 0.0 0.0 0 0
CAF Data.Time.Calendar.Private <entire-module> 0.0 0.0 0 0
showPadded Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:(14,1)-(15,56) 0.0 0.0 0 0
show4 Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:46:1-33 0.0 0.0 0 0
show3 Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:43:1-33 0.0 0.0 0 0
show2Fixed Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:(35,1)-(37,31) 0.0 0.0 0 0
show2 Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:40:1-33 0.0 0.0 0 0
remBy Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:(72,1)-(74,18) 0.0 0.0 0 0
quotRemBy Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:(77,1)-(79,36) 0.0 0.0 0 0
quotBy Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:69:1-55 0.0 0.0 0 0
mod100 Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:49:1-20 0.0 0.0 0 0
div100 Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:52:1-20 0.0 0.0 0 0
clipValid Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:(62,1)-(66,24) 0.0 0.0 0 0
clip Data.Time.Calendar.Private lib/Data/Time/Calendar/Private.hs:(55,1)-(59,14) 0.0 0.0 0 0
CAF Data.Time.Calendar.Gregorian <entire-module> 0.0 0.0 0 0
toGregorian Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:(56,1)-(59,62) 0.0 0.0 0 0
showGregorian Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:(85,1)-(87,32) 0.0 0.0 0 0
gregorianMonthLength Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:91:1-57 0.0 0.0 0 0
fromGregorianValid Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:(79,1)-(81,33) 0.0 0.0 0 0
fromGregorian Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:64:1-104 0.0 0.0 0 0
diffGregorianDurationRollOver Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:(158,1)-(175,60) 0.0 0.0 0 0
diffGregorianDurationClip Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:(136,1)-(153,60) 0.0 0.0 0 0
addGregorianYearsRollOver Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:124:1-65 0.0 0.0 0 0
addGregorianYearsClip Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:119:1-57 0.0 0.0 0 0
addGregorianMonthsRollOver Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:(112,1)-(114,40) 0.0 0.0 0 0
addGregorianMonthsClip Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:(105,1)-(107,40) 0.0 0.0 0 0
addGregorianDurationRollOver Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:132:1-102 0.0 0.0 0 0
addGregorianDurationClip Data.Time.Calendar.Gregorian lib/Data/Time/Calendar/Gregorian.hs:128:1-94 0.0 0.0 0 0
CAF Data.Time.Calendar.Days <entire-module> 0.0 0.0 0 0
toModifiedJulianDay Data.Time.Calendar.Days lib/Data/Time/Calendar/Days.hs:24:7-25 0.0 0.0 0 0
periodToDayValid Data.Time.Calendar.Days lib/Data/Time/Calendar/Days.hs:(100,1)-(102,61) 0.0 0.0 0 0
periodToDay Data.Time.Calendar.Days lib/Data/Time/Calendar/Days.hs:94:1-65 0.0 0.0 0 0
periodLength Data.Time.Calendar.Days lib/Data/Time/Calendar/Days.hs:77:1-83 0.0 0.0 0 0
periodFromDay Data.Time.Calendar.Days lib/Data/Time/Calendar/Days.hs:(85,1)-(88,14) 0.0 0.0 0 0
periodAllDays Data.Time.Calendar.Days lib/Data/Time/Calendar/Days.hs:71:1-55 0.0 0.0 0 0
diffDays Data.Time.Calendar.Days lib/Data/Time/Calendar/Days.hs:52:1-60 0.0 0.0 0 0
addDays Data.Time.Calendar.Days lib/Data/Time/Calendar/Days.hs:49:1-59 0.0 0.0 0 0
CAF Data.Time.Calendar.CalendarDiffDays <entire-module> 0.0 0.0 0 0
scaleCalendarDiffDays Data.Time.Calendar.CalendarDiffDays lib/Data/Time/Calendar/CalendarDiffDays.hs:52:1-81 0.0 0.0 0 0
cdMonths Data.Time.Calendar.CalendarDiffDays lib/Data/Time/Calendar/CalendarDiffDays.hs:12:7-14 0.0 0.0 0 0
cdDays Data.Time.Calendar.CalendarDiffDays lib/Data/Time/Calendar/CalendarDiffDays.hs:13:7-12 0.0 0.0 0 0
calendarYear Data.Time.Calendar.CalendarDiffDays lib/Data/Time/Calendar/CalendarDiffDays.hs:48:1-36 0.0 0.0 0 0
calendarWeek Data.Time.Calendar.CalendarDiffDays lib/Data/Time/Calendar/CalendarDiffDays.hs:42:1-35 0.0 0.0 0 0
calendarMonth Data.Time.Calendar.CalendarDiffDays lib/Data/Time/Calendar/CalendarDiffDays.hs:45:1-36 0.0 0.0 0 0
calendarDay Data.Time.Calendar.CalendarDiffDays lib/Data/Time/Calendar/CalendarDiffDays.hs:39:1-34 0.0 0.0 0 0
CAF Data.Format <entire-module> 0.0 0.0 0 0
specialCaseShowFormat Data.Format lib/Data/Format.hs:(158,1)-(163,24) 0.0 0.0 0 0
specialCaseFormat Data.Format lib/Data/Format.hs:(166,1)-(172,25) 0.0 0.0 0 0
parseReader Data.Format lib/Data/Format.hs:(56,1)-(60,51) 0.0 0.0 0 0
optionalSignFormat Data.Format lib/Data/Format.hs:186:1-72 0.0 0.0 0 0
optionalFormat Data.Format lib/Data/Format.hs:175:1-48 0.0 0.0 0 0
mapMFormat Data.Format lib/Data/Format.hs:(85,1)-(90,28) 0.0 0.0 0 0
mandatorySignFormat Data.Format lib/Data/Format.hs:189:1-65 0.0 0.0 0 0
literalFormat Data.Format lib/Data/Format.hs:155:1-91 0.0 0.0 0 0
integerFormat Data.Format lib/Data/Format.hs:248:1-116 0.0 0.0 0 0
formatShowM Data.Format lib/Data/Format.hs:64:7-17 0.0 0.0 0 0
formatShow Data.Format lib/Data/Format.hs:(72,1)-(75,48) 0.0 0.0 0 0
formatReadP Data.Format lib/Data/Format.hs:66:7-17 0.0 0.0 0 0
formatParseM Data.Format lib/Data/Format.hs:79:1-54 0.0 0.0 0 0
filterFormat Data.Format lib/Data/Format.hs:(93,1)-(104,9) 0.0 0.0 0 0
enumMap Data.Format lib/Data/Format.hs:37:1-32 0.0 0.0 0 0
decimalFormat Data.Format lib/Data/Format.hs:251:1-115 0.0 0.0 0 0
clipFormat Data.Format lib/Data/Format.hs:108:1-61 0.0 0.0 0 0
casesFormat Data.Format lib/Data/Format.hs:(178,1)-(183,31) 0.0 0.0 0 0
CAF Data.Time.Format.ISO8601 <entire-module> 0.0 0.0 0 0
zonedTimeFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(290,1)-(292,58) 0.0 0.0 0 0
yearWeekFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:213:1-64 0.0 0.0 0 0
yearMonthFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:172:1-67 0.0 0.0 0 0
yearFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:176:1-24 0.0 0.0 0 0
withUTCDesignator Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:261:1-45 0.0 0.0 0 0
withTimeDesignator Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:257:1-46 0.0 0.0 0 0
weekDateFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:209:1-113 0.0 0.0 0 0
utcTimeFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(296,1)-(297,100) 0.0 0.0 0 0
timeOffsetFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(265,1)-(277,81) 0.0 0.0 0 0
timeOfDayFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:226:1-111 0.0 0.0 0 0
timeOfDayAndOffsetFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:281:1-73 0.0 0.0 0 0
timeAndOffsetFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:305:1-55 0.0 0.0 0 0
recurringIntervalFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(370,1)-(372,97) 0.0 0.0 0 0
parseFormatExtension Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:80:1-63 0.0 0.0 0 0
ordinalDateFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:201:1-83 0.0 0.0 0 0
localTimeFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(285,1)-(286,118) 0.0 0.0 0 0
isoMakeTimeOfDayValid Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(160,1)-(161,54) 0.0 0.0 0 0
iso8601Show Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:380:1-38 0.0 0.0 0 0
iso8601ParseM Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:384:1-42 0.0 0.0 0 0
intervalFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:366:1-30 0.0 0.0 0 0
hourMinuteFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(234,1)-(243,85) 0.0 0.0 0 0
hourFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(247,1)-(253,51) 0.0 0.0 0 0
formatReadPExtension Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:76:1-90 0.0 0.0 0 0
expandedYearWeekFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:222:1-86 0.0 0.0 0 0
expandedYearMonthFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:189:1-73 0.0 0.0 0 0
expandedYearFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:193:1-40 0.0 0.0 0 0
expandedWeekDateFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(217,1)-(218,109) 0.0 0.0 0 0
expandedOrdinalDateFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:205:1-105 0.0 0.0 0 0
expandedCenturyFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:197:1-59 0.0 0.0 0 0
expandedCalendarFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(184,1)-(185,106) 0.0 0.0 0 0
durationTimeFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(325,1)-(336,109) 0.0 0.0 0 0
durationDaysFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:321:1-98 0.0 0.0 0 0
dayAndTimeFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:301:1-58 0.0 0.0 0 0
centuryFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:180:1-46 0.0 0.0 0 0
calendarFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:168:1-110 0.0 0.0 0 0
alternativeDurationTimeFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(351,1)-(362,77) 0.0 0.0 0 0
alternativeDurationDaysFormat Data.Time.Format.ISO8601 lib/Data/Time/Format/ISO8601.hs:(340,1)-(347,73) 0.0 0.0 0 0
CAF Data.Time.Calendar.Quarter <entire-module> 0.0 0.0 0 0
monthQuarter Data.Time.Calendar.Quarter lib/Data/Time/Calendar/Quarter.hs:129:1-69 0.0 0.0 0 0
monthOfYearQuarter Data.Time.Calendar.Quarter lib/Data/Time/Calendar/Quarter.hs:(122,1)-(125,25) 0.0 0.0 0 0
diffQuarters Data.Time.Calendar.Quarter lib/Data/Time/Calendar/Quarter.hs:109:1-48 0.0 0.0 0 0
dayQuarter Data.Time.Calendar.Quarter lib/Data/Time/Calendar/Quarter.hs:133:1-22 0.0 0.0 0 0
addQuarters Data.Time.Calendar.Quarter lib/Data/Time/Calendar/Quarter.hs:106:1-47 0.0 0.0 0 0
CAF Data.Time.Calendar.Month <entire-module> 0.0 0.0 0 0
fromYearMonthValid Data.Time.Calendar.Month lib/Data/Time/Calendar/Month.hs:(80,1)-(82,28) 0.0 0.0 0 0
fromMonthDayValid Data.Time.Calendar.Month lib/Data/Time/Calendar/Month.hs:95:1-36 0.0 0.0 0 0
diffMonths Data.Time.Calendar.Month lib/Data/Time/Calendar/Month.hs:69:1-42 0.0 0.0 0 0
addMonths Data.Time.Calendar.Month lib/Data/Time/Calendar/Month.hs:66:1-41 0.0 0.0 0 0
CAF Data.Time.Calendar.OrdinalDate <entire-module> 0.0 0.0 0 0
toOrdinalDate Data.Time.Calendar.OrdinalDate lib/Data/Time/Calendar/OrdinalDate.hs:(12,1)-(23,57) 0.0 0.0 0 0
sundayStartWeek Data.Time.Calendar.OrdinalDate lib/Data/Time/Calendar/OrdinalDate.hs:(99,1)-(103,26) 0.0 0.0 0 0
showOrdinalDate Data.Time.Calendar.OrdinalDate lib/Data/Time/Calendar/OrdinalDate.hs:(77,1)-(79,31) 0.0 0.0 0 0
mondayStartWeek Data.Time.Calendar.OrdinalDate lib/Data/Time/Calendar/OrdinalDate.hs:(89,1)-(93,26) 0.0 0.0 0 0
isLeapYear Data.Time.Calendar.OrdinalDate lib/Data/Time/Calendar/OrdinalDate.hs:83:1-87 0.0 0.0 0 0
fromSundayStartWeekValid Data.Time.Calendar.OrdinalDate lib/Data/Time/Calendar/OrdinalDate.hs:(198,1)-(219,40) 0.0 0.0 0 0
fromSundayStartWeek Data.Time.Calendar.OrdinalDate lib/Data/Time/Calendar/OrdinalDate.hs:(176,1)-(187,33) 0.0 0.0 0 0
fromOrdinalDateValid Data.Time.Calendar.OrdinalDate lib/Data/Time/Calendar/OrdinalDate.hs:(61,1)-(73,34) 0.0 0.0 0 0
fromOrdinalDate Data.Time.Calendar.OrdinalDate lib/Data/Time/Calendar/OrdinalDate.hs:(28,1)-(46,20) 0.0 0.0 0 0
fromMondayStartWeekValid Data.Time.Calendar.OrdinalDate lib/Data/Time/Calendar/OrdinalDate.hs:(140,1)-(161,40) 0.0 0.0 0 0
fromMondayStartWeek Data.Time.Calendar.OrdinalDate lib/Data/Time/Calendar/OrdinalDate.hs:(118,1)-(129,33) 0.0 0.0 0 0
CAF Data.Time.Calendar.MonthDay <entire-module> 0.0 0.0 0 0
monthLength Data.Time.Calendar.MonthDay lib/Data/Time/Calendar/MonthDay.hs:85:1-66 0.0 0.0 0 0
monthAndDayToDayOfYearValid Data.Time.Calendar.MonthDay lib/Data/Time/Calendar/MonthDay.hs:(47,1)-(60,55) 0.0 0.0 0 0
monthAndDayToDayOfYear Data.Time.Calendar.MonthDay lib/Data/Time/Calendar/MonthDay.hs:(31,1)-(42,27) 0.0 0.0 0 0
dayOfYearToMonthAndDay Data.Time.Calendar.MonthDay lib/Data/Time/Calendar/MonthDay.hs:(65,1)-(75,9) 0.0 0.0 0 0
CAF Data.Tagged <entire-module> 0.0 0.0 0 0
untag Data.Tagged src/Data/Tagged.hs:456:1-16 0.0 0.0 0 0
unTagged Data.Tagged src/Data/Tagged.hs:110:31-38 0.0 0.0 0 0
reproxy Data.Tagged src/Data/Tagged.hs:505:1-17 0.0 0.0 0 0
CAF Data.Bifoldable1 <entire-module> 0.0 0.0 0 0
CAF Data.Foldable1 <entire-module> 0.0 0.0 0 0
minimumBy Data.Foldable1 src/Data/Foldable1.hs:(355,1)-(358,31) 0.0 0.0 0 0
maximumBy Data.Foldable1 src/Data/Foldable1.hs:(345,1)-(348,31) 0.0 0.0 0 0
intercalate1 Data.Foldable1 src/Data/Foldable1.hs:311:1-38 0.0 0.0 0 0
foldrMapM1 Data.Foldable1 src/Data/Foldable1.hs:(323,1)-(328,34) 0.0 0.0 0 0
foldrM1 Data.Foldable1 src/Data/Foldable1.hs:319:1-27 0.0 0.0 0 0
foldlMapM1 Data.Foldable1 src/Data/Foldable1.hs:(337,1)-(338,28) 0.0 0.0 0 0
foldlM1 Data.Foldable1 src/Data/Foldable1.hs:333:1-27 0.0 0.0 0 0
CAF Data.Fix <entire-module> 0.0 0.0 0 0
wrapNu Data.Fix src/Data/Fix.hs:382:1-33 0.0 0.0 0 0
wrapMu Data.Fix src/Data/Fix.hs:315:1-45 0.0 0.0 0 0
wrapFix Data.Fix src/Data/Fix.hs:176:1-13 0.0 0.0 0 0
unwrapNu Data.Fix src/Data/Fix.hs:393:1-37 0.0 0.0 0 0
unwrapMu Data.Fix src/Data/Fix.hs:326:1-31 0.0 0.0 0 0
unwrapFix Data.Fix src/Data/Fix.hs:187:1-17 0.0 0.0 0 0
unfoldNu Data.Fix src/Data/Fix.hs:371:1-13 0.0 0.0 0 0
unfoldMu Data.Fix src/Data/Fix.hs:304:1-40 0.0 0.0 0 0
unfoldFixM Data.Fix src/Data/Fix.hs:417:1-58 0.0 0.0 0 0
unfoldFix Data.Fix src/Data/Fix.hs:165:1-45 0.0 0.0 0 0
unMu Data.Fix src/Data/Fix.hs:267:21-24 0.0 0.0 0 0
unFix Data.Fix src/Data/Fix.hs:139:23-27 0.0 0.0 0 0
refoldM Data.Fix src/Data/Fix.hs:422:1-63 0.0 0.0 0 0
refold Data.Fix src/Data/Fix.hs:402:1-39 0.0 0.0 0 0
hyloM Data.Fix src/Data/Fix.hs:458:1-15 0.0 0.0 0 0
hylo Data.Fix src/Data/Fix.hs:440:1-13 0.0 0.0 0 0
hoistNu Data.Fix src/Data/Fix.hs:355:1-45 0.0 0.0 0 0
hoistMu Data.Fix src/Data/Fix.hs:289:1-47 0.0 0.0 0 0
hoistFix' Data.Fix src/Data/Fix.hs:148:1-57 0.0 0.0 0 0
hoistFix Data.Fix src/Data/Fix.hs:144:1-56 0.0 0.0 0 0
foldNu Data.Fix src/Data/Fix.hs:364:1-44 0.0 0.0 0 0
foldMu Data.Fix src/Data/Fix.hs:297:1-23 0.0 0.0 0 0
foldFixM Data.Fix src/Data/Fix.hs:412:1-52 0.0 0.0 0 0
foldFix Data.Fix src/Data/Fix.hs:157:1-45 0.0 0.0 0 0
cataM Data.Fix src/Data/Fix.hs:446:1-16 0.0 0.0 0 0
cata Data.Fix src/Data/Fix.hs:430:1-14 0.0 0.0 0 0
anaM Data.Fix src/Data/Fix.hs:452:1-17 0.0 0.0 0 0
ana Data.Fix src/Data/Fix.hs:435:1-15 0.0 0.0 0 0
CAF Data.DList.DNonEmpty.Internal <entire-module> 0.0 0.0 0 0
unfoldr Data.DList.DNonEmpty.Internal Data/DList/DNonEmpty/Internal.hs:(354,1)-(357,41) 0.0 0.0 0 0
toDList Data.DList.DNonEmpty.Internal Data/DList/DNonEmpty/Internal.hs:171:1-36 0.0 0.0 0 0
fromList Data.DList.DNonEmpty.Internal Data/DList/DNonEmpty/Internal.hs:(207,1)-(208,63) 0.0 0.0 0 0
CAF Data.DList.Internal <entire-module> 0.0 0.0 0 0
unsafeApplyDList Data.DList.Internal Data/DList/Internal.hs:101:32-47 0.0 0.0 0 0
unfoldr Data.DList.Internal Data/DList/Internal.hs:(429,1)-(432,41) 0.0 0.0 0 0
CAF WithIndex <entire-module> 0.0 0.0 0 0
runIndexing WithIndex src/WithIndex.hs:694:35-45 0.0 0.0 0 0
itraverseListOff WithIndex src/WithIndex.hs:(274,1)-(275,87) 0.0 0.0 0 0
getTraversed WithIndex src/WithIndex.hs:654:37-48 0.0 0.0 0 0
getSequenced WithIndex src/WithIndex.hs:676:37-48 0.0 0.0 0 0
CAF Data.HashSet.Internal <entire-module> 0.0 0.0 0 0
toMap Data.HashSet.Internal Data/HashSet/Internal.hs:270:1-13 0.0 0.0 0 0
singleton Data.HashSet.Internal Data/HashSet/Internal.hs:262:1-40 0.0 0.0 0 0
member Data.HashSet.Internal Data/HashSet/Internal.hs:(348,1)-(350,30) 0.0 0.0 0 0
keysSet Data.HashSet.Internal Data/HashSet/Internal.hs:286:1-29 0.0 0.0 0 0
isSubsetOf Data.HashSet.Internal Data/HashSet/Internal.hs:300:1-70 0.0 0.0 0 0
intersection Data.HashSet.Internal Data/HashSet/Internal.hs:395:1-67 0.0 0.0 0 0
insert Data.HashSet.Internal Data/HashSet/Internal.hs:358:1-42 0.0 0.0 0 0
fromMap Data.HashSet.Internal Data/HashSet/Internal.hs:277:1-17 0.0 0.0 0 0
empty Data.HashSet.Internal Data/HashSet/Internal.hs:255:1-23 0.0 0.0 0 0
difference Data.HashSet.Internal Data/HashSet/Internal.hs:386:1-63 0.0 0.0 0 0
delete Data.HashSet.Internal Data/HashSet/Internal.hs:368:1-39 0.0 0.0 0 0
asMap Data.HashSet.Internal Data/HashSet/Internal.hs:113:7-11 0.0 0.0 0 0
CAF Data.HashMap.Internal.Strict <entire-module> 0.0 0.0 0 0
update Data.HashMap.Internal.Strict Data/HashMap/Internal/Strict.hs:296:1-24 0.0 0.0 0 0
singleton Data.HashMap.Internal.Strict Data/HashMap/Internal/Strict.hs:170:1-33 0.0 0.0 0 0
intersectionWithKey Data.HashMap.Internal.Strict Data/HashMap/Internal/Strict.hs:628:1-93 0.0 0.0 0 0
intersectionWith Data.HashMap.Internal.Strict Data/HashMap/Internal/Strict.hs:620:1-62 0.0 0.0 0 0
insertWith Data.HashMap.Internal.Strict Data/HashMap/Internal/Strict.hs:(191,1)-(219,76) 0.0 0.0 0 0
insert Data.HashMap.Internal.Strict Data/HashMap/Internal/Strict.hs:179:1-27 0.0 0.0 0 0
fromList Data.HashMap.Internal.Strict Data/HashMap/Internal/Strict.hs:638:1-70 0.0 0.0 0 0
differenceWith Data.HashMap.Internal.Strict Data/HashMap/Internal/Strict.hs:(608,1)-(612,75) 0.0 0.0 0 0
alterF Data.HashMap.Internal.Strict Data/HashMap/Internal/Strict.hs:(330,1)-(335,35) 0.0 0.0 0 0
alter Data.HashMap.Internal.Strict Data/HashMap/Internal/Strict.hs:(308,1)-(311,27) 0.0 0.0 0 0
adjust Data.HashMap.Internal.Strict Data/HashMap/Internal/Strict.hs:(266,1)-(289,23) 0.0 0.0 0 0
CAF Data.HashMap.Internal.List <entire-module> 0.0 0.0 0 0
unorderedCompare Data.HashMap.Internal.List Data/HashMap/Internal/List.hs:(68,1)-(79,101) 0.0 0.0 0 0
isPermutationBy Data.HashMap.Internal.List Data/HashMap/Internal/List.hs:(40,1)-(52,25) 0.0 0.0 0 0
deleteBy Data.HashMap.Internal.List Data/HashMap/Internal/List.hs:(83,1)-(84,83) 0.0 0.0 0 0
CAF Data.HashMap.Internal.Array <entire-module> 0.0 0.0 0 0
unsafeSameArray Data.HashMap.Internal.Array Data/HashMap/Internal/Array.hs:(136,1)-(137,59) 0.0 0.0 0 0
unMArray Data.HashMap.Internal.Array Data/HashMap/Internal/Array.hs:158:7-14 0.0 0.0 0 0
unArray Data.HashMap.Internal.Array Data/HashMap/Internal/Array.hs:126:7-13 0.0 0.0 0 0
toList Data.HashMap.Internal.Array Data/HashMap/Internal/Array.hs:534:1-21 0.0 0.0 0 0
sameArray1 Data.HashMap.Internal.Array Data/HashMap/Internal/Array.hs:(140,1)-(151,23) 0.0 0.0 0 0
new_ Data.HashMap.Internal.Array Data/HashMap/Internal/Array.hs:208:1-28 0.0 0.0 0 0
fromList' Data.HashMap.Internal.Array Data/HashMap/Internal/Array.hs:(511,1)-(520,44) 0.0 0.0 0 0
fromList Data.HashMap.Internal.Array Data/HashMap/Internal/Array.hs:(499,1)-(508,43) 0.0 0.0 0 0
copyM Data.HashMap.Internal.Array Data/HashMap/Internal/Array.hs:(306,1)-(311,26) 0.0 0.0 0 0
copy Data.HashMap.Internal.Array Data/HashMap/Internal/Array.hs:(297,1)-(302,30) 0.0 0.0 0 0
CAF Data.HashMap.Internal <entire-module> 0.0 0.0 0 0
updateOrConcatWithKey Data.HashMap.Internal Data/HashMap/Internal.hs:(2307,1)-(2334,15) 0.0 0.0 0 0
update Data.HashMap.Internal Data/HashMap/Internal.hs:1231:1-24 0.0 0.0 0 0
unsafeInsert Data.HashMap.Internal Data/HashMap/Internal.hs:(888,1)-(918,76) 0.0 0.0 0 0
union Data.HashMap.Internal Data/HashMap/Internal.hs:1522:1-23 0.0 0.0 0 0
size Data.HashMap.Internal Data/HashMap/Internal.hs:(581,1)-(587,49) 0.0 0.0 0 0
singleton Data.HashMap.Internal Data/HashMap/Internal.hs:569:1-37 0.0 0.0 0 0
null Data.HashMap.Internal Data/HashMap/Internal.hs:(576,1)-(577,16) 0.0 0.0 0 0
member Data.HashMap.Internal Data/HashMap/Internal.hs:(592,1)-(594,19) 0.0 0.0 0 0
mapKeys Data.HashMap.Internal Data/HashMap/Internal.hs:1746:1-65 0.0 0.0 0 0
isSubmapOfBy Data.HashMap.Internal Data/HashMap/Internal.hs:(1440,1)-(1484,45) 0.0 0.0 0 0
isSubmapOf Data.HashMap.Internal Data/HashMap/Internal.hs:1412:1-42 0.0 0.0 0 0
intersectionWithKey Data.HashMap.Internal Data/HashMap/Internal.hs:1790:1-74 0.0 0.0 0 0
intersectionWith Data.HashMap.Internal Data/HashMap/Internal.hs:1783:1-62 0.0 0.0 0 0
intersection Data.HashMap.Internal Data/HashMap/Internal.hs:1776:1-49 0.0 0.0 0 0
insertNewKey Data.HashMap.Internal Data/HashMap/Internal.hs:(814,1)-(838,66) 0.0 0.0 0 0
insertModifying Data.HashMap.Internal Data/HashMap/Internal.hs:(970,1)-(1008,74) 0.0 0.0 0 0
insertKeyExists Data.HashMap.Internal Data/HashMap/Internal.hs:(852,1)-(874,30) 0.0 0.0 0 0
insert' Data.HashMap.Internal Data/HashMap/Internal.hs:(772,1)-(803,76) 0.0 0.0 0 0
insert Data.HashMap.Internal Data/HashMap/Internal.hs:768:1-37 0.0 0.0 0 0
hash Data.HashMap.Internal Data/HashMap/Internal.hs:180:1-28 0.0 0.0 0 0
fromList Data.HashMap.Internal Data/HashMap/Internal.hs:2174:1-63 0.0 0.0 0 0
findWithDefault Data.HashMap.Internal Data/HashMap/Internal.hs:(718,1)-(720,17) 0.0 0.0 0 0
equalKeys1 Data.HashMap.Internal Data/HashMap/Internal.hs:(466,1)-(478,37) 0.0 0.0 0 0
equalKeys Data.HashMap.Internal Data/HashMap/Internal.hs:(482,1)-(494,39) 0.0 0.0 0 0
empty Data.HashMap.Internal Data/HashMap/Internal.hs:565:1-13 0.0 0.0 0 0
differenceWith Data.HashMap.Internal Data/HashMap/Internal.hs:(1766,1)-(1770,70) 0.0 0.0 0 0
difference Data.HashMap.Internal Data/HashMap/Internal.hs:(1754,1)-(1758,29) 0.0 0.0 0 0
deleteKeyExists Data.HashMap.Internal Data/HashMap/Internal.hs:(1137,1)-(1174,32) 0.0 0.0 0 0
delete' Data.HashMap.Internal Data/HashMap/Internal.hs:(1077,1)-(1125,23) 0.0 0.0 0 0
delete Data.HashMap.Internal Data/HashMap/Internal.hs:1073:1-33 0.0 0.0 0 0
compose Data.HashMap.Internal Data/HashMap/Internal.hs:(1680,1)-(1682,35) 0.0 0.0 0 0
bitsPerSubkey Data.HashMap.Internal Data/HashMap/Internal.hs:2383:1-17 0.0 0.0 0 0
alterF Data.HashMap.Internal Data/HashMap/Internal.hs:(1267,1)-(1273,31) 0.0 0.0 0 0
alter Data.HashMap.Internal Data/HashMap/Internal.hs:(1245,1)-(1248,27) 0.0 0.0 0 0
adjust# Data.HashMap.Internal Data/HashMap/Internal.hs:(1192,1)-(1224,23) 0.0 0.0 0 0
! Data.HashMap.Internal Data/HashMap/Internal.hs:(738,1)-(740,63) 0.0 0.0 0 0
CAF Data.Stream.Monadic <entire-module> 0.0 0.0 0 0
unBox Data.Stream.Monadic src/Data/Stream/Monadic.hs:123:20-24 0.0 0.0 0 0
catMaybes Data.Stream.Monadic src/Data/Stream/Monadic.hs:723:1-23 0.0 0.0 0 0
CAF Data.Vector.Generic.New <entire-module> 0.0 0.0 0 0
CAF Data.Vector.Storable.Mutable <entire-module> 0.0 0.0 0 0
unsafeCoerceMVector Data.Vector.Storable.Mutable src/Data/Vector/Storable/Mutable.hs:126:1-34 0.0 0.0 0 0
CAF Data.Vector.Primitive.Mutable <entire-module> 0.0 0.0 0 0
unsafeCoerceMVector Data.Vector.Primitive.Mutable src/Data/Vector/Primitive/Mutable.hs:106:1-34 0.0 0.0 0 0
CAF Data.Vector.Generic <entire-module> 0.0 0.0 0 0
liftReadsPrec Data.Vector.Generic src/Data/Vector/Generic.hs:2624:1-61 0.0 0.0 0 0
imapM Data.Vector.Generic src/Data/Vector/Generic.hs:1117:1-71 0.0 0.0 0 0
gunfold Data.Vector.Generic src/Data/Vector/Generic.hs:(2655,1)-(2657,22) 0.0 0.0 0 0
concatNE Data.Vector.Generic src/Data/Vector/Generic.hs:752:1-35 0.0 0.0 0 0
cmpBy Data.Vector.Generic src/Data/Vector/Generic.hs:2601:1-54 0.0 0.0 0 0
CAF Data.Vector.Internal.Check <entire-module> 0.0 0.0 0 0
internalError Data.Vector.Internal.Check src/Data/Vector/Internal/Check.hs:(88,1)-(92,13) 0.0 0.0 0 0
CAF Data.Vector <entire-module> 0.0 0.0 0 0
cmpBy Data.Vector src/Data/Vector.hs:2114:1-15 0.0 0.0 0 0
CAF Data.Vector.Mutable <entire-module> 0.0 0.0 0 0
CAF Data.Vector.Storable <entire-module> 0.0 0.0 0 0
unsafeCoerceVector Data.Vector.Storable src/Data/Vector/Storable.hs:223:1-33 0.0 0.0 0 0
cmpBy Data.Vector.Storable src/Data/Vector/Storable.hs:1827:1-15 0.0 0.0 0 0
CAF Data.Vector.Primitive <entire-module> 0.0 0.0 0 0
unsafeCoerceVector Data.Vector.Primitive src/Data/Vector/Primitive.hs:212:1-33 0.0 0.0 0 0
cmpBy Data.Vector.Primitive src/Data/Vector/Primitive.hs:1781:1-15 0.0 0.0 0 0
CAF Data.Vector.Generic.Base <entire-module> 0.0 0.0 0 0
CAF Data.Vector.Generic.Mutable <entire-module> 0.0 0.0 0 0
nextPermutation Data.Vector.Generic.Mutable src/Data/Vector/Generic/Mutable.hs:(1232,1)-(1250,24) 0.0 0.0 0 0
CAF Data.Vector.Generic.Mutable.Base <entire-module> 0.0 0.0 0 0
CAF Data.Vector.Fusion.Bundle.Monadic <entire-module> 0.0 0.0 0 0
sVector Data.Vector.Fusion.Bundle.Monadic src/Data/Vector/Fusion/Bundle/Monadic.hs:131:30-36 0.0 0.0 0 0
sSize Data.Vector.Fusion.Bundle.Monadic src/Data/Vector/Fusion/Bundle/Monadic.hs:132:30-34 0.0 0.0 0 0
sElems Data.Vector.Fusion.Bundle.Monadic src/Data/Vector/Fusion/Bundle/Monadic.hs:129:30-35 0.0 0.0 0 0
sChunks Data.Vector.Fusion.Bundle.Monadic src/Data/Vector/Fusion/Bundle/Monadic.hs:130:30-36 0.0 0.0 0 0
CAF Data.Vector.Fusion.Bundle.Size <entire-module> 0.0 0.0 0 0
upperBound Data.Vector.Fusion.Bundle.Size src/Data/Vector/Fusion/Bundle/Size.hs:(129,1)-(131,30) 0.0 0.0 0 0
toMax Data.Vector.Fusion.Bundle.Size src/Data/Vector/Fusion/Bundle/Size.hs:(118,1)-(120,25) 0.0 0.0 0 0
lowerBound Data.Vector.Fusion.Bundle.Size src/Data/Vector/Fusion/Bundle/Size.hs:(124,1)-(125,24) 0.0 0.0 0 0
CAF Data.Vector.Fusion.Util <entire-module> 0.0 0.0 0 0
unId Data.Vector.Fusion.Util src/Data/Vector/Fusion/Util.hs:25:21-24 0.0 0.0 0 0
CAF Data.Functor.WithIndex.Instances <entire-module> 0.0 0.0 0 0
CAF Data.Bifunctor.Assoc <entire-module> 0.0 0.0 0 0
CAF Data.These.Combinators <entire-module> 0.0 0.0 0 0
unassocThese Data.These.Combinators src/Data/These/Combinators.hs:164:1-22 0.0 0.0 0 0
swapThese Data.These.Combinators src/Data/These/Combinators.hs:131:1-16 0.0 0.0 0 0
mapThis Data.These.Combinators src/Data/These/Combinators.hs:(271,1)-(272,22) 0.0 0.0 0 0
mapThese Data.These.Combinators src/Data/These/Combinators.hs:(279,1)-(280,26) 0.0 0.0 0 0
mapThere Data.These.Combinators src/Data/These/Combinators.hs:112:1-17 0.0 0.0 0 0
mapThat Data.These.Combinators src/Data/These/Combinators.hs:(275,1)-(276,22) 0.0 0.0 0 0
mapHere Data.These.Combinators src/Data/These/Combinators.hs:108:1-15 0.0 0.0 0 0
justThis Data.These.Combinators src/Data/These/Combinators.hs:(212,1)-(213,27) 0.0 0.0 0 0
justThese Data.These.Combinators src/Data/These/Combinators.hs:(220,1)-(221,31) 0.0 0.0 0 0
justThere Data.These.Combinators src/Data/These/Combinators.hs:(207,1)-(209,30) 0.0 0.0 0 0
justThat Data.These.Combinators src/Data/These/Combinators.hs:(216,1)-(217,27) 0.0 0.0 0 0
justHere Data.These.Combinators src/Data/These/Combinators.hs:(191,1)-(193,29) 0.0 0.0 0 0
isThis Data.These.Combinators src/Data/These/Combinators.hs:251:1-27 0.0 0.0 0 0
isThese Data.These.Combinators src/Data/These/Combinators.hs:257:1-28 0.0 0.0 0 0
isThat Data.These.Combinators src/Data/These/Combinators.hs:254:1-27 0.0 0.0 0 0
hasThere Data.These.Combinators src/Data/These/Combinators.hs:264:1-29 0.0 0.0 0 0
hasHere Data.These.Combinators src/Data/These/Combinators.hs:261:1-27 0.0 0.0 0 0
catThis Data.These.Combinators src/Data/These/Combinators.hs:229:1-27 0.0 0.0 0 0
catThese Data.These.Combinators src/Data/These/Combinators.hs:237:1-29 0.0 0.0 0 0
catThere Data.These.Combinators src/Data/These/Combinators.hs:243:1-29 0.0 0.0 0 0
catThat Data.These.Combinators src/Data/These/Combinators.hs:233:1-27 0.0 0.0 0 0
catHere Data.These.Combinators src/Data/These/Combinators.hs:240:1-27 0.0 0.0 0 0
bitraverseThese Data.These.Combinators src/Data/These/Combinators.hs:116:1-28 0.0 0.0 0 0
bimapThese Data.These.Combinators src/Data/These/Combinators.hs:104:1-18 0.0 0.0 0 0
assocThese Data.These.Combinators src/Data/These/Combinators.hs:148:1-18 0.0 0.0 0 0
CAF Data.These <entire-module> 0.0 0.0 0 0
undistrThesePair Data.These src/Data/These.hs:(197,1)-(205,48) 0.0 0.0 0 0
undistrPairThese Data.These src/Data/These.hs:(214,1)-(216,55) 0.0 0.0 0 0
these Data.These src/Data/These.hs:(118,1)-(120,33) 0.0 0.0 0 0
partitionThese Data.These src/Data/These.hs:(141,1)-(147,36) 0.0 0.0 0 0
partitionHereThere Data.These src/Data/These.hs:(153,1)-(159,36) 0.0 0.0 0 0
partitionEithersNE Data.These src/Data/These.hs:(178,1)-(184,34) 0.0 0.0 0 0
mergeTheseWith Data.These src/Data/These.hs:133:1-53 0.0 0.0 0 0
mergeThese Data.These src/Data/These.hs:129:1-24 0.0 0.0 0 0
fromThese Data.These src/Data/These.hs:(124,1)-(125,14) 0.0 0.0 0 0
distrThesePair Data.These src/Data/These.hs:(192,1)-(194,56) 0.0 0.0 0 0
distrPairThese Data.These src/Data/These.hs:(209,1)-(211,51) 0.0 0.0 0 0
CAF Data.Functor.These <entire-module> 0.0 0.0 0 0
CAF Data.Semialign.Internal <entire-module> 0.0 0.0 0 0
unzipDefault Data.Semialign.Internal src/Data/Semialign/Internal.hs:345:1-39 0.0 0.0 0 0
salign Data.Semialign.Internal src/Data/Semialign/Internal.hs:862:1-36 0.0 0.0 0 0
rpadZipWith Data.Semialign.Internal src/Data/Semialign/Internal.hs:882:1-48 0.0 0.0 0 0
rpadZip Data.Semialign.Internal src/Data/Semialign/Internal.hs:886:1-25 0.0 0.0 0 0
padZipWith Data.Semialign.Internal src/Data/Semialign/Internal.hs:870:1-47 0.0 0.0 0 0
padZip Data.Semialign.Internal src/Data/Semialign/Internal.hs:866:1-64 0.0 0.0 0 0
oops Data.Semialign.Internal src/Data/Semialign/Internal.hs:85:1-50 0.0 0.0 0 0
lpadZipWith Data.Semialign.Internal src/Data/Semialign/Internal.hs:874:1-70 0.0 0.0 0 0
lpadZip Data.Semialign.Internal src/Data/Semialign/Internal.hs:878:1-25 0.0 0.0 0 0
alignVectorWith Data.Semialign.Internal src/Data/Semialign/Internal.hs:782:1-68 0.0 0.0 0 0
CAF Data.Strict.Either <entire-module> 0.0 0.0 0 0
rights Data.Strict.Either src/Data/Strict/Either.hs:133:1-29 0.0 0.0 0 0
partitionEithers Data.Strict.Either src/Data/Strict/Either.hs:(137,1)-(141,30) 0.0 0.0 0 0
lefts Data.Strict.Either src/Data/Strict/Either.hs:129:1-27 0.0 0.0 0 0
isRight Data.Strict.Either src/Data/Strict/Either.hs:(112,1)-(113,25) 0.0 0.0 0 0
isLeft Data.Strict.Either src/Data/Strict/Either.hs:(106,1)-(107,23) 0.0 0.0 0 0
fromRight Data.Strict.Either src/Data/Strict/Either.hs:(124,1)-(125,64) 0.0 0.0 0 0
fromLeft Data.Strict.Either src/Data/Strict/Either.hs:(118,1)-(119,62) 0.0 0.0 0 0
either Data.Strict.Either src/Data/Strict/Either.hs:(100,1)-(101,26) 0.0 0.0 0 0
CAF Data.Strict.Maybe <entire-module> 0.0 0.0 0 0
maybeToList Data.Strict.Maybe src/Data/Strict/Maybe.hs:(136,1)-(137,28) 0.0 0.0 0 0
maybe Data.Strict.Maybe src/Data/Strict/Maybe.hs:(126,1)-(127,24) 0.0 0.0 0 0
mapMaybe Data.Strict.Maybe src/Data/Strict/Maybe.hs:(145,1)-(150,22) 0.0 0.0 0 0
listToMaybe Data.Strict.Maybe src/Data/Strict/Maybe.hs:(131,1)-(132,31) 0.0 0.0 0 0
isNothing Data.Strict.Maybe src/Data/Strict/Maybe.hs:(106,1)-(107,25) 0.0 0.0 0 0
isJust Data.Strict.Maybe src/Data/Strict/Maybe.hs:(101,1)-(102,21) 0.0 0.0 0 0
fromMaybe Data.Strict.Maybe src/Data/Strict/Maybe.hs:(119,1)-(120,24) 0.0 0.0 0 0
fromJust Data.Strict.Maybe src/Data/Strict/Maybe.hs:(112,1)-(113,21) 0.0 0.0 0 0
catMaybes Data.Strict.Maybe src/Data/Strict/Maybe.hs:141:1-33 0.0 0.0 0 0
CAF Data.Strict.Tuple <entire-module> 0.0 0.0 0 0
zip Data.Strict.Tuple src/Data/Strict/Tuple.hs:146:1-29 0.0 0.0 0 0
unzip Data.Strict.Tuple src/Data/Strict/Tuple.hs:(150,1)-(152,11) 0.0 0.0 0 0
uncurry Data.Strict.Tuple src/Data/Strict/Tuple.hs:138:1-27 0.0 0.0 0 0
swap Data.Strict.Tuple src/Data/Strict/Tuple.hs:142:1-24 0.0 0.0 0 0
snd Data.Strict.Tuple src/Data/Strict/Tuple.hs:130:1-17 0.0 0.0 0 0
fst Data.Strict.Tuple src/Data/Strict/Tuple.hs:126:1-17 0.0 0.0 0 0
curry Data.Strict.Tuple src/Data/Strict/Tuple.hs:134:1-25 0.0 0.0 0 0
CAF Data.Strict.These <entire-module> 0.0 0.0 0 0
undistrThesePair Data.Strict.These src/Data/Strict/These.hs:(190,1)-(198,48) 0.0 0.0 0 0
undistrPairThese Data.Strict.These src/Data/Strict/These.hs:(207,1)-(209,55) 0.0 0.0 0 0
these Data.Strict.These src/Data/Strict/These.hs:(113,1)-(115,33) 0.0 0.0 0 0
partitionThese Data.Strict.These src/Data/Strict/These.hs:(136,1)-(142,36) 0.0 0.0 0 0
partitionHereThere Data.Strict.These src/Data/Strict/These.hs:(147,1)-(153,36) 0.0 0.0 0 0
partitionEithersNE Data.Strict.These src/Data/Strict/These.hs:(171,1)-(177,34) 0.0 0.0 0 0
mergeTheseWith Data.Strict.These src/Data/Strict/These.hs:128:1-53 0.0 0.0 0 0
mergeThese Data.Strict.These src/Data/Strict/These.hs:124:1-24 0.0 0.0 0 0
fromThese Data.Strict.These src/Data/Strict/These.hs:(119,1)-(120,14) 0.0 0.0 0 0
distrThesePair Data.Strict.These src/Data/Strict/These.hs:(185,1)-(187,56) 0.0 0.0 0 0
distrPairThese Data.Strict.These src/Data/Strict/These.hs:(202,1)-(204,51) 0.0 0.0 0 0
CAF Data.Strict.Classes <entire-module> 0.0 0.0 0 0
CAF Data.Text.Short.Internal <entire-module> 0.0 0.0 0 0
unsnoc Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(969,1)-(977,27) 0.0 0.0 0 0
uncons Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(945,1)-(953,23) 0.0 0.0 0 0
toText Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:668:1-98 0.0 0.0 0 0
toString Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(523,1)-(530,16) 0.0 0.0 0 0
toShortByteString Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:498:1-35 0.0 0.0 0 0
toByteString Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:504:1-48 0.0 0.0 0 0
toBuilder Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:510:1-50 0.0 0.0 0 0
stripSuffix Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(1056,1)-(1060,28) 0.0 0.0 0 0
stripPrefix Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(1015,1)-(1017,30) 0.0 0.0 0 0
splitAtEnd Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(908,1)-(915,18) 0.0 0.0 0 0
splitAt Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(879,1)-(885,22) 0.0 0.0 0 0
split Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(400,1)-(408,21) 0.0 0.0 0 0
spanEnd Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(471,1)-(473,27) 0.0 0.0 0 0
span Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(458,1)-(460,27) 0.0 0.0 0 0
snoc Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(1498,1)-(1508,45) 0.0 0.0 0 0
singleton Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:1465:1-30 0.0 0.0 0 0
reverse Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(1161,1)-(1176,23) 0.0 0.0 0 0
replicate Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(1136,1)-(1148,14) 0.0 0.0 0 0
null Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:280:1-35 0.0 0.0 0 0
length Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:294:1-102 0.0 0.0 0 0
isValidUtf8 Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:813:1-107 0.0 0.0 0 0
isSuffixOf Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(1033,1)-(1042,20) 0.0 0.0 0 0
isPrefixOf Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(993,1)-(1001,20) 0.0 0.0 0 0
isAscii Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(315,1)-(317,19) 0.0 0.0 0 0
intersperse Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(1074,1)-(1096,47) 0.0 0.0 0 0
intercalate Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(1113,1)-(1117,50) 0.0 0.0 0 0
indexMaybe Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(833,1)-(837,105) 0.0 0.0 0 0
indexEndMaybe Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(851,1)-(855,109) 0.0 0.0 0 0
fromText Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(706,1)-(707,99) 0.0 0.0 0 0
fromString Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(690,1)-(696,28) 0.0 0.0 0 0
fromShortByteStringUnsafe Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:764:1-37 0.0 0.0 0 0
fromShortByteString Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(748,1)-(752,22) 0.0 0.0 0 0
fromByteStringUnsafe Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:787:1-46 0.0 0.0 0 0
fromByteString Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:774:1-50 0.0 0.0 0 0
foldr1 Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(646,1)-(654,16) 0.0 0.0 0 0
foldr Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(622,1)-(629,16) 0.0 0.0 0 0
foldl1' Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(599,1)-(608,40) 0.0 0.0 0 0
foldl1 Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(571,1)-(580,40) 0.0 0.0 0 0
foldl' Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(586,1)-(593,16) 0.0 0.0 0 0
foldl Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(547,1)-(554,16) 0.0 0.0 0 0
findIndex Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(370,1)-(380,16) 0.0 0.0 0 0
find Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(346,1)-(356,16) 0.0 0.0 0 0
filter Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(1194,1)-(1220,53) 0.0 0.0 0 0
dropAround Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(1232,1)-(1242,17) 0.0 0.0 0 0
cons Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:(1480,1)-(1490,51) 0.0 0.0 0 0
all Data.Text.Short.Internal src/Data/Text/Short/Internal.hs:334:1-49 0.0 0.0 0 0
CAF Data.Time.Calendar.Quarter.Compat <entire-module> 0.0 0.0 0 0
toYearQuarter Data.Time.Calendar.Quarter.Compat src/Data/Time/Calendar/Quarter/Compat.hs:31:1-40 0.0 0.0 0 0
fromYearQuarter Data.Time.Calendar.Quarter.Compat src/Data/Time/Calendar/Quarter/Compat.hs:27:1-29 0.0 0.0 0 0
CAF Data.Time.Calendar.Month.Compat <entire-module> 0.0 0.0 0 0
toYearMonth Data.Time.Calendar.Month.Compat src/Data/Time/Calendar/Month/Compat.hs:34:1-36 0.0 0.0 0 0
toMonthDay Data.Time.Calendar.Month.Compat src/Data/Time/Calendar/Month/Compat.hs:42:1-34 0.0 0.0 0 0
fromYearMonth Data.Time.Calendar.Month.Compat src/Data/Time/Calendar/Month/Compat.hs:30:1-25 0.0 0.0 0 0
fromMonthDay Data.Time.Calendar.Month.Compat src/Data/Time/Calendar/Month/Compat.hs:38:1-23 0.0 0.0 0 0
CAF Data.UUID.Types.Internal.Builder <entire-module> 0.0 0.0 0 0
CAF Data.UUID.Types.Internal <entire-module> 0.0 0.0 0 0
unpack Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:(179,1)-(194,7) 0.0 0.0 0 0
toWords64 Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:152:1-36 0.0 0.0 0 0
toWords Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:(124,1)-(129,25) 0.0 0.0 0 0
toText Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:379:1-38 0.0 0.0 0 0
toString Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:(352,1)-(370,34) 0.0 0.0 0 0
toList Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:(269,1)-(273,48) 0.0 0.0 0 0
toLazyASCIIBytes Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:(473,1)-(479,18) 0.0 0.0 0 0
toByteString Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:308:1-31 0.0 0.0 0 0
toASCIIBytes Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:386:1-55 0.0 0.0 0 0
time_mid Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:165:9-16 0.0 0.0 0 0
time_low Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:164:9-16 0.0 0.0 0 0
time_hi_and_version Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:166:9-27 0.0 0.0 0 0
pack Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:(197,1)-(205,59) 0.0 0.0 0 0
null Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:289:1-15 0.0 0.0 0 0
node_5 Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:174:9-14 0.0 0.0 0 0
node_4 Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:173:9-14 0.0 0.0 0 0
node_3 Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:172:9-14 0.0 0.0 0 0
node_2 Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:171:9-14 0.0 0.0 0 0
node_1 Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:170:9-14 0.0 0.0 0 0
node_0 Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:169:9-14 0.0 0.0 0 0
nil Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:297:1-14 0.0 0.0 0 0
fromWords64 Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:160:1-18 0.0 0.0 0 0
fromWords Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:141:1-60 0.0 0.0 0 0
fromText Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:375:1-40 0.0 0.0 0 0
fromString Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:(319,1)-(321,53) 0.0 0.0 0 0
fromLazyASCIIBytes Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:(483,1)-(490,22) 0.0 0.0 0 0
fromByteString Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:302:1-37 0.0 0.0 0 0
fromASCIIBytes Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:(437,1)-(469,39) 0.0 0.0 0 0
clock_seq_low Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:168:9-21 0.0 0.0 0 0
clock_seq_hi_res Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:167:9-24 0.0 0.0 0 0
buildFromWords Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:(262,1)-(264,48) 0.0 0.0 0 0
buildFromBytes Data.UUID.Types.Internal src/Data/UUID/Types/Internal.hs:(255,1)-(258,36) 0.0 0.0 0 0
CAF Witherable <entire-module> 0.0 0.0 0 0
unwrapFoldable Witherable src/Witherable.hs:707:47-60 0.0 0.0 0 0
<&?> Witherable src/Witherable.hs:619:1-25 0.0 0.0 0 0
<$?> Witherable src/Witherable.hs:607:1-17 0.0 0.0 0 0
CAF Data.Aeson.Parser.Time <entire-module> 0.0 0.0 0 0
run Data.Aeson.Parser.Time src/Data/Aeson/Parser/Time.hs:(31,1)-(33,32) 0.0 0.0 0 0
CAF Data.Aeson.KeyMap <entire-module> 0.0 0.0 0 0
unionWithKey Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:293:1-68 0.0 0.0 0 0
unionWith Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:289:1-62 0.0 0.0 0 0
union Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:285:1-50 0.0 0.0 0 0
traverseWithKey Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:242:1-65 0.0 0.0 0 0
traverse Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:237:1-50 0.0 0.0 0 0
toMapText Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:602:1-58 0.0 0.0 0 0
toMap Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:321:1-16 0.0 0.0 0 0
toList Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:264:1-28 0.0 0.0 0 0
toHashMapText Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:592:1-62 0.0 0.0 0 0
toHashMap Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:313:1-31 0.0 0.0 0 0
toAscList Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:275:1-34 0.0 0.0 0 0
size Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:157:1-24 0.0 0.0 0 0
singleton Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:161:1-40 0.0 0.0 0 0
null Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:153:1-24 0.0 0.0 0 0
member Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:165:1-34 0.0 0.0 0 0
mapWithKey Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:211:1-51 0.0 0.0 0 0
mapMaybeWithKey Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:355:1-61 0.0 0.0 0 0
mapMaybe Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:351:1-47 0.0 0.0 0 0
map Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:205:1-10 0.0 0.0 0 0
lookup Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:189:1-38 0.0 0.0 0 0
keys Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:309:1-24 0.0 0.0 0 0
intersectionWithKey Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:305:1-82 0.0 0.0 0 0
intersectionWith Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:301:1-76 0.0 0.0 0 0
intersection Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:297:1-64 0.0 0.0 0 0
insertWith Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:201:1-61 0.0 0.0 0 0
insert Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:195:1-51 0.0 0.0 0 0
fromMapText Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:608:1-62 0.0 0.0 0 0
fromMap Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:325:1-16 0.0 0.0 0 0
fromListWith Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:248:1-44 0.0 0.0 0 0
fromList Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:258:1-30 0.0 0.0 0 0
fromHashMapText Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:596:1-66 0.0 0.0 0 0
fromHashMap Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:317:1-33 0.0 0.0 0 0
foldrWithKey Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:232:1-48 0.0 0.0 0 0
foldr' Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:220:1-38 0.0 0.0 0 0
foldr Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:217:1-36 0.0 0.0 0 0
foldl' Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:226:1-38 0.0 0.0 0 0
foldl Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:223:1-36 0.0 0.0 0 0
foldMapWithKey Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:214:1-50 0.0 0.0 0 0
filterWithKey Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:347:1-57 0.0 0.0 0 0
filter Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:343:1-43 0.0 0.0 0 0
empty Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:149:1-22 0.0 0.0 0 0
elems Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:270:1-26 0.0 0.0 0 0
difference Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:280:1-72 0.0 0.0 0 0
delete Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:169:1-43 0.0 0.0 0 0
alterF Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:174:1-50 0.0 0.0 0 0
alignWithKey Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:588:1-68 0.0 0.0 0 0
alignWith Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:584:1-63 0.0 0.0 0 0
!? Data.Aeson.KeyMap src/Data/Aeson/KeyMap.hs:580:1-21 0.0 0.0 0 0
CAF Data.Aeson.Parser.UnescapePure <entire-module> 0.0 0.0 0 0
unescapeText Data.Aeson.Parser.UnescapePure src-pure/Data/Aeson/Parser/UnescapePure.hs:32:1-60 0.0 0.0 0 0
CAF Data.Attoparsec.Time.Internal <entire-module> 0.0 0.0 0 0
toTimeOfDay64 Data.Attoparsec.Time.Internal attoparsec-iso8601/src/Data/Attoparsec/Time/Internal.hs:51:1-68 0.0 0.0 0 0
toPico Data.Attoparsec.Time.Internal attoparsec-iso8601/src/Data/Attoparsec/Time/Internal.hs:27:1-16 0.0 0.0 0 0
fromPico Data.Attoparsec.Time.Internal attoparsec-iso8601/src/Data/Attoparsec/Time/Internal.hs:31:1-24 0.0 0.0 0 0
diffTimeOfDay64 Data.Attoparsec.Time.Internal attoparsec-iso8601/src/Data/Attoparsec/Time/Internal.hs:(43,1)-(48,55) 0.0 0.0 0 0
CAF Data.Attoparsec.Time <entire-module> 0.0 0.0 0 0
zonedTime Data.Attoparsec.Time attoparsec-iso8601/src/Data/Attoparsec/Time.hs:196:1-74 0.0 0.0 0 0
year Data.Attoparsec.Time attoparsec-iso8601/src/Data/Attoparsec/Time.hs:(93,1)-(98,26) 0.0 0.0 0 0
utcTime Data.Attoparsec.Time attoparsec-iso8601/src/Data/Attoparsec/Time.hs:(176,1)-(182,51) 0.0 0.0 0 0
timeZone Data.Attoparsec.Time attoparsec-iso8601/src/Data/Attoparsec/Time.hs:(141,1)-(164,33) 0.0 0.0 0 0
timeOfDay Data.Attoparsec.Time attoparsec-iso8601/src/Data/Attoparsec/Time.hs:(110,1)-(116,28) 0.0 0.0 0 0
quarter Data.Attoparsec.Time attoparsec-iso8601/src/Data/Attoparsec/Time.hs:(75,1)-(85,24) 0.0 0.0 0 0
month Data.Attoparsec.Time attoparsec-iso8601/src/Data/Attoparsec/Time.hs:(65,1)-(69,73) 0.0 0.0 0 0
localTime Data.Attoparsec.Time attoparsec-iso8601/src/Data/Attoparsec/Time.hs:(170,1)-(171,53) 0.0 0.0 0 0
day Data.Attoparsec.Time attoparsec-iso8601/src/Data/Attoparsec/Time.hs:(54,1)-(59,74) 0.0 0.0 0 0
CAF Data.Aeson.Types.ToJSON <entire-module> 0.0 0.0 0 0
toJSONKeyText Data.Aeson.Types.ToJSON src/Data/Aeson/Types/ToJSON.hs:514:1-49 0.0 0.0 0 0
toJSONKeyKey Data.Aeson.Types.ToJSON src/Data/Aeson/Types/ToJSON.hs:520:1-44 0.0 0.0 0 0
genericToJSONKey Data.Aeson.Types.ToJSON src/Data/Aeson/Types/ToJSON.hs:561:1-92 0.0 0.0 0 0
genericToJSON Data.Aeson.Types.ToJSON src/Data/Aeson/Types/ToJSON.hs:191:1-49 0.0 0.0 0 0
genericToEncoding Data.Aeson.Types.ToJSON src/Data/Aeson/Types/ToJSON.hs:206:1-53 0.0 0.0 0 0
genericLiftToJSON Data.Aeson.Types.ToJSON src/Data/Aeson/Types/ToJSON.hs:199:1-69 0.0 0.0 0 0
genericLiftToEncoding Data.Aeson.Types.ToJSON src/Data/Aeson/Types/ToJSON.hs:214:1-73 0.0 0.0 0 0
contramapToJSONKeyFunction Data.Aeson.Types.ToJSON src/Data/Aeson/Types/ToJSON.hs:(539,1)-(541,56) 0.0 0.0 0 0
CAF Data.Aeson.Types.Internal <entire-module> 0.0 0.0 0 0
unwrapUnaryRecords Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:779:7-24 0.0 0.0 0 0
tagSingleConstructors Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:782:7-27 0.0 0.0 0 0
tagFieldName Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:808:20-31 0.0 0.0 0 0
sumEncoding Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:777:7-17 0.0 0.0 0 0
rejectUnknownFields Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:785:7-25 0.0 0.0 0 0
prependFailure Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:692:1-37 0.0 0.0 0 0
parserThrowError Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:(698,1)-(699,34) 0.0 0.0 0 0
parserCatchError Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:(705,1)-(706,62) 0.0 0.0 0 0
parseFail Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:364:1-16 0.0 0.0 0 0
omitNothingFields Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:728:7-23 0.0 0.0 0 0
modifyFailure Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:(682,1)-(683,36) 0.0 0.0 0 0
keyModifier Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:849:7-17 0.0 0.0 0 0
isEmptyArray Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:(569,1)-(570,22) 0.0 0.0 0 0
fromDotNetTime Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:517:7-20 0.0 0.0 0 0
formatRelativePath Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:(619,1)-(642,25) 0.0 0.0 0 0
formatPath Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:614:1-48 0.0 0.0 0 0
formatError Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:609:1-68 0.0 0.0 0 0
fieldLabelModifier Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:717:7-24 0.0 0.0 0 0
emptyObject Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:574:1-29 0.0 0.0 0 0
emptyArray Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:564:1-26 0.0 0.0 0 0
defaultTaggedObject Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:(908,1)-(911,23) 0.0 0.0 0 0
defaultOptions Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:(888,1)-(897,18) 0.0 0.0 0 0
defaultJSONKeyOptions Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:921:1-41 0.0 0.0 0 0
contentsFieldName Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:809:20-36 0.0 0.0 0 0
constructorTagModifier Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:720:7-28 0.0 0.0 0 0
camelTo2 Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:(950,1)-(956,33) 0.0 0.0 0 0
camelTo Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:(933,1)-(943,66) 0.0 0.0 0 0
allNullaryToStringTag Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:723:7-27 0.0 0.0 0 0
<?> Data.Aeson.Types.Internal src/Data/Aeson/Types/Internal.hs:670:1-74 0.0 0.0 0 0
CAF Data.Aeson.Types.Generic <entire-module> 0.0 0.0 0 0
unTagged2 Data.Aeson.Types.Generic src/Data/Aeson/Types/Generic.hs:73:50-58 0.0 0.0 0 0
CAF Data.Aeson.Types.FromJSON <entire-module> 0.0 0.0 0 0
withText Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(708,1)-(709,76) 0.0 0.0 0 0
withScientific Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(736,1)-(737,71) 0.0 0.0 0 0
withObject Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(697,1)-(698,78) 0.0 0.0 0 0
withEmbeddedJSON Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(797,1)-(802,73) 0.0 0.0 0 0
withBool Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(792,1)-(793,75) 0.0 0.0 0 0
withArray Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(719,1)-(720,75) 0.0 0.0 0 0
unexpected Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:547:1-57 0.0 0.0 0 0
typeMismatch Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(537,1)-(538,75) 0.0 0.0 0 0
parseOptionalFieldWith Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(239,1)-(242,32) 0.0 0.0 0 0
parseIndexedJSON Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:173:1-52 0.0 0.0 0 0
parseFieldMaybe' Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:851:1-24 0.0 0.0 0 0
parseFieldMaybe Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:847:1-23 0.0 0.0 0 0
parseField Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:843:1-17 0.0 0.0 0 0
mapFromJSONKeyFunction Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:488:1-29 0.0 0.0 0 0
ifromJSON Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:810:1-28 0.0 0.0 0 0
genericParseJSON Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:267:1-60 0.0 0.0 0 0
genericLiftParseJSON Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:275:1-80 0.0 0.0 0 0
genericFromJSONKey Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(508,1)-(514,87) 0.0 0.0 0 0
fromJSONKeyCoerce Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:471:1-37 0.0 0.0 0 0
fromJSON Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:806:1-26 0.0 0.0 0 0
explicitParseFieldMaybe' Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(869,1)-(871,39) 0.0 0.0 0 0
explicitParseFieldMaybe Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(863,1)-(865,59) 0.0 0.0 0 0
explicitParseField Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:(857,1)-(859,30) 0.0 0.0 0 0
coerceFromJSONKeyFunction Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:479:1-34 0.0 0.0 0 0
.:? Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:830:1-41 0.0 0.0 0 0
.:! Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:839:1-42 0.0 0.0 0 0
.: Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:820:1-35 0.0 0.0 0 0
.!= Data.Aeson.Types.FromJSON src/Data/Aeson/Types/FromJSON.hs:888:1-39 0.0 0.0 0 0
CAF Data.Aeson.Internal.Text <entire-module> 0.0 0.0 0 0
unsafeDecodeASCII Data.Aeson.Internal.Text src/Data/Aeson/Internal/Text.hs:(29,1)-(30,69) 0.0 0.0 0 0
CAF Data.Aeson.Internal.Integer <entire-module> 0.0 0.0 0 0
bsToIntegerSimple Data.Aeson.Internal.Integer src/Data/Aeson/Internal/Integer.hs:(20,1)-(21,45) 0.0 0.0 0 0
bsToInteger Data.Aeson.Internal.Integer src/Data/Aeson/Internal/Integer.hs:(13,1)-(17,19) 0.0 0.0 0 0
CAF Data.Aeson.Encoding.Builder <entire-module> 0.0 0.0 0 0
unquoted Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:114:1-47 0.0 0.0 0 0
text Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:110:1-49 0.0 0.0 0 0
string Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:(122,1)-(123,66) 0.0 0.0 0 0
scientific Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:(145,1)-(149,24) 0.0 0.0 0 0
quote Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:118:1-41 0.0 0.0 0 0
object Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:(97,1)-(102,61) 0.0 0.0 0 0
null_ Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:78:1-56 0.0 0.0 0 0
encodeToBuilder Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:(69,1)-(74,37) 0.0 0.0 0 0
emptyObject_ Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:155:1-51 0.0 0.0 0 0
emptyArray_ Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:152:1-50 0.0 0.0 0 0
bool Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:(82,1)-(83,72) 0.0 0.0 0 0
array Data.Aeson.Encoding.Builder src/Data/Aeson/Encoding/Builder.hs:(87,1)-(93,57) 0.0 0.0 0 0
CAF Data.Aeson.Parser.Internal <entire-module> 0.0 0.0 0 0
value' Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:278:1-39 0.0 0.0 0 0
value Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:194:1-37 0.0 0.0 0 0
parseListNoDup Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:(269,1)-(274,31) 0.0 0.0 0 0
jstring Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:316:1-45 0.0 0.0 0 0
jsonNoDup' Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:312:1-37 0.0 0.0 0 0
jsonNoDup Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:256:1-35 0.0 0.0 0 0
jsonLast' Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:303:1-57 0.0 0.0 0 0
jsonLast Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:247:1-56 0.0 0.0 0 0
jsonEOF' Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:437:1-43 0.0 0.0 0 0
jsonEOF Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:432:1-41 0.0 0.0 0 0
jsonAccum' Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:308:1-45 0.0 0.0 0 0
jsonAccum Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:252:1-44 0.0 0.0 0 0
json' Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:121:1-14 0.0 0.0 0 0
json Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:104:1-12 0.0 0.0 0 0
fromListAccum Data.Aeson.Parser.Internal src/Data/Aeson/Parser/Internal.hs:(264,1)-(265,83) 0.0 0.0 0 0
CAF Data.Aeson.Key <entire-module> 0.0 0.0 0 0
toText Data.Aeson.Key src/Data/Aeson/Key.hs:54:1-14 0.0 0.0 0 0
toString Data.Aeson.Key src/Data/Aeson/Key.hs:48:1-29 0.0 0.0 0 0
toShortText Data.Aeson.Key src/Data/Aeson/Key.hs:68:1-33 0.0 0.0 0 0
fromText Data.Aeson.Key src/Data/Aeson/Key.hs:51:1-14 0.0 0.0 0 0
fromString Data.Aeson.Key src/Data/Aeson/Key.hs:45:1-25 0.0 0.0 0 0
fromShortText Data.Aeson.Key src/Data/Aeson/Key.hs:72:1-31 0.0 0.0 0 0
CAF Data.Aeson.Encoding.Internal <entire-module> 0.0 0.0 0 0
zonedTime Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:437:1-46 0.0 0.0 0 0
wrapObject Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:183:1-59 0.0 0.0 0 0
wrapArray Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:180:1-62 0.0 0.0 0 0
wordText Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:382:1-42 0.0 0.0 0 0
word8Text Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:370:1-44 0.0 0.0 0 0
word8 Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:303:1-29 0.0 0.0 0 0
word64Text Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:379:1-46 0.0 0.0 0 0
word64 Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:312:1-31 0.0 0.0 0 0
word32Text Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:376:1-46 0.0 0.0 0 0
word32 Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:309:1-31 0.0 0.0 0 0
word16Text Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:373:1-46 0.0 0.0 0 0
word16 Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:306:1-31 0.0 0.0 0 0
word Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:315:1-27 0.0 0.0 0 0
value Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:444:1-37 0.0 0.0 0 0
utcTime Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:431:1-42 0.0 0.0 0 0
unsafeToEncoding Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:102:1-27 0.0 0.0 0 0
timeOfDay Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:434:1-46 0.0 0.0 0 0
text Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:253:1-25 0.0 0.0 0 0
string Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:269:1-29 0.0 0.0 0 0
shortText Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:(262,1)-(266,44) 0.0 0.0 0 0
scientificText Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:412:1-52 0.0 0.0 0 0
scientific Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:341:1-37 0.0 0.0 0 0
retagEncoding Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:109:1-39 0.0 0.0 0 0
quarter Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:425:1-42 0.0 0.0 0 0
pair' Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:145:1-75 0.0 0.0 0 0
openCurly Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:280:1-35 0.0 0.0 0 0
openBracket Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:278:1-35 0.0 0.0 0 0
null_ Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:186:1-25 0.0 0.0 0 0
nullEncoding Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:171:1-57 0.0 0.0 0 0
month Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:422:1-38 0.0 0.0 0 0
localTime Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:428:1-46 0.0 0.0 0 0
lazyText Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:(256,1)-(258,65) 0.0 0.0 0 0
key Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:250:1-23 0.0 0.0 0 0
integerText Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:385:1-48 0.0 0.0 0 0
integer Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:318:1-33 0.0 0.0 0 0
intText Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:367:1-40 0.0 0.0 0 0
int8Text Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:355:1-42 0.0 0.0 0 0
int8 Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:288:1-27 0.0 0.0 0 0
int64Text Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:364:1-44 0.0 0.0 0 0
int64 Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:297:1-29 0.0 0.0 0 0
int32Text Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:361:1-44 0.0 0.0 0 0
int32 Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:294:1-29 0.0 0.0 0 0
int16Text Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:358:1-44 0.0 0.0 0 0
int16 Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:291:1-29 0.0 0.0 0 0
int Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:300:1-25 0.0 0.0 0 0
fromEncoding Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:90:7-18 0.0 0.0 0 0
floatText Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:(388,1)-(390,54) 0.0 0.0 0 0
float Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:321:1-51 0.0 0.0 0 0
emptyObject_ Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:177:1-39 0.0 0.0 0 0
emptyArray_ Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:174:1-37 0.0 0.0 0 0
empty Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:228:1-23 0.0 0.0 0 0
econcat Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:231:1-26 0.0 0.0 0 0
doubleText Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:(407,1)-(409,55) 0.0 0.0 0 0
double Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:338:1-53 0.0 0.0 0 0
day Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:419:1-34 0.0 0.0 0 0
comma Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:276:1-35 0.0 0.0 0 0
colon Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:277:1-35 0.0 0.0 0 0
closeCurly Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:281:1-35 0.0 0.0 0 0
closeBracket Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:279:1-35 0.0 0.0 0 0
bool Data.Aeson.Encoding.Internal src/Data/Aeson/Encoding/Internal.hs:(189,1)-(190,29) 0.0 0.0 0 0
CAF Data.Aeson <entire-module> 0.0 0.0 0 0
encodeFile Data.Aeson src/Data/Aeson.hs:185:1-39 0.0 0.0 0 0
encode Data.Aeson src/Data/Aeson.hs:181:1-46 0.0 0.0 0 0
decodeFileStrict' Data.Aeson src/Data/Aeson.hs:261:1-51 0.0 0.0 0 0
decodeFileStrict Data.Aeson src/Data/Aeson.hs:223:1-49 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.Time.Internal.Printer <entire-module> 0.0 0.0 0 0
zonedTime Database.PostgreSQL.Simple.Time.Internal.Printer src/Database/PostgreSQL/Simple/Time/Internal/Printer.hs:(120,1)-(121,38) 0.0 0.0 0 0
utcTime Database.PostgreSQL.Simple.Time.Internal.Printer src/Database/PostgreSQL/Simple/Time/Internal/Printer.hs:(112,1)-(113,68) 0.0 0.0 0 0
timeZone Database.PostgreSQL.Simple.Time.Internal.Printer src/Database/PostgreSQL/Simple/Time/Internal/Printer.hs:(103,1)-(109,68) 0.0 0.0 0 0
timeOfDay Database.PostgreSQL.Simple.Time.Internal.Printer src/Database/PostgreSQL/Simple/Time/Internal/Printer.hs:(93,1)-(100,52) 0.0 0.0 0 0
nominalDiffTime Database.PostgreSQL.Simple.Time.Internal.Printer src/Database/PostgreSQL/Simple/Time/Internal/Printer.hs:(125,1)-(127,62) 0.0 0.0 0 0
localTime Database.PostgreSQL.Simple.Time.Internal.Printer src/Database/PostgreSQL/Simple/Time/Internal/Printer.hs:(116,1)-(117,45) 0.0 0.0 0 0
day Database.PostgreSQL.Simple.Time.Internal.Printer src/Database/PostgreSQL/Simple/Time/Internal/Printer.hs:(88,1)-(90,78) 0.0 0.0 0 0
calendarDiffTime Database.PostgreSQL.Simple.Time.Internal.Printer src/Database/PostgreSQL/Simple/Time/Internal/Printer.hs:(130,1)-(135,15) 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.Time.Internal.Parser <entire-module> 0.0 0.0 0 0
zonedTime Database.PostgreSQL.Simple.Time.Internal.Parser src/Database/PostgreSQL/Simple/Time/Internal/Parser.hs:196:1-74 0.0 0.0 0 0
utcTime Database.PostgreSQL.Simple.Time.Internal.Parser src/Database/PostgreSQL/Simple/Time/Internal/Parser.hs:(175,1)-(184,41) 0.0 0.0 0 0
timeZoneHMS Database.PostgreSQL.Simple.Time.Internal.Parser src/Database/PostgreSQL/Simple/Time/Internal/Parser.hs:(120,1)-(144,30) 0.0 0.0 0 0
timeZone Database.PostgreSQL.Simple.Time.Internal.Parser src/Database/PostgreSQL/Simple/Time/Internal/Parser.hs:(93,1)-(113,33) 0.0 0.0 0 0
timeOfDay Database.PostgreSQL.Simple.Time.Internal.Parser src/Database/PostgreSQL/Simple/Time/Internal/Parser.hs:(61,1)-(70,28) 0.0 0.0 0 0
localToUTCTimeOfDayHMS Database.PostgreSQL.Simple.Time.Internal.Parser src/Database/PostgreSQL/Simple/Time/Internal/Parser.hs:(147,1)-(162,35) 0.0 0.0 0 0
localTime Database.PostgreSQL.Simple.Time.Internal.Parser src/Database/PostgreSQL/Simple/Time/Internal/Parser.hs:(169,1)-(170,53) 0.0 0.0 0 0
day Database.PostgreSQL.Simple.Time.Internal.Parser src/Database/PostgreSQL/Simple/Time/Internal/Parser.hs:(45,1)-(49,63) 0.0 0.0 0 0
calendarDiffTime Database.PostgreSQL.Simple.Time.Internal.Parser src/Database/PostgreSQL/Simple/Time/Internal/Parser.hs:(202,1)-(204,36) 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.Time.Implementation <entire-module> 0.0 0.0 0 0
zonedTimestampToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:164:1-63 0.0 0.0 0 0
zonedTimeToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:148:1-46 0.0 0.0 0 0
utcTimestampToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:161:1-59 0.0 0.0 0 0
utcTimeToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:145:1-42 0.0 0.0 0 0
unboundedToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:(154,1)-(158,45) 0.0 0.0 0 0
timeZoneToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:142:1-44 0.0 0.0 0 0
timeOfDayToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:139:1-46 0.0 0.0 0 0
parseZonedTimestamp Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:73:1-69 0.0 0.0 0 0
parseZonedTime Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:58:1-59 0.0 0.0 0 0
parseUTCTimestamp Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:70:1-67 0.0 0.0 0 0
parseUTCTime Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:55:1-57 0.0 0.0 0 0
parseTimeOfDay Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:67:1-59 0.0 0.0 0 0
parseLocalTimestamp Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:76:1-69 0.0 0.0 0 0
parseLocalTime Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:61:1-59 0.0 0.0 0 0
parseDay Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:64:1-47 0.0 0.0 0 0
parseDate Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:79:1-49 0.0 0.0 0 0
parseCalendarDiffTime Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:82:1-73 0.0 0.0 0 0
nominalDiffTimeToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:173:1-46 0.0 0.0 0 0
localToUTCTimeOfDayHMS Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:(117,1)-(118,60) 0.0 0.0 0 0
localTimestampToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:167:1-63 0.0 0.0 0 0
localTimeToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:151:1-46 0.0 0.0 0 0
getZonedTimestamp Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:124:1-45 0.0 0.0 0 0
getZonedTime Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:121:1-27 0.0 0.0 0 0
getUnbounded Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:(85,1)-(88,32) 0.0 0.0 0 0
getUTCTimestamp Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:130:1-41 0.0 0.0 0 0
getUTCTime Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:127:1-23 0.0 0.0 0 0
getTimeZoneHMS Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:(111,1)-(114,50) 0.0 0.0 0 0
getTimeZone Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:106:1-43 0.0 0.0 0 0
getTimeOfDay Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:97:1-27 0.0 0.0 0 0
getLocalTimestamp Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:103:1-45 0.0 0.0 0 0
getLocalTime Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:100:1-27 0.0 0.0 0 0
getDay Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:91:1-15 0.0 0.0 0 0
getDate Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:94:1-29 0.0 0.0 0 0
getCalendarDiffTime Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:133:1-41 0.0 0.0 0 0
dayToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:136:1-34 0.0 0.0 0 0
dateToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:170:1-48 0.0 0.0 0 0
calendarDiffTimeToBuilder Database.PostgreSQL.Simple.Time.Implementation src/Database/PostgreSQL/Simple/Time/Implementation.hs:176:1-48 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.Compat <entire-module> 0.0 0.0 0 0
toPico Database.PostgreSQL.Simple.Compat src/Database/PostgreSQL/Simple/Compat.hs:81:1-16 0.0 0.0 0 0
toByteString Database.PostgreSQL.Simple.Compat src/Database/PostgreSQL/Simple/Compat.hs:73:1-46 0.0 0.0 0 0
fromPico Database.PostgreSQL.Simple.Compat src/Database/PostgreSQL/Simple/Compat.hs:84:1-24 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.Types <entire-module> 0.0 0.0 0 0
fromQuery Database.PostgreSQL.Simple.Types src/Database/PostgreSQL/Simple/Types.hs:81:7-15 0.0 0.0 0 0
fromPGArray Database.PostgreSQL.Simple.Types src/Database/PostgreSQL/Simple/Types.hs:185:30-40 0.0 0.0 0 0
fromIdentifier Database.PostgreSQL.Simple.Types src/Database/PostgreSQL/Simple/Types.hs:157:34-47 0.0 0.0 0 0
fromBinary Database.PostgreSQL.Simple.Types src/Database/PostgreSQL/Simple/Types.hs:153:28-37 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.ToField <entire-module> 0.0 0.0 0 0
toJSONField Database.PostgreSQL.Simple.ToField src/Database/PostgreSQL/Simple/ToField.hs:327:1-35 0.0 0.0 0 0
inQuotes Database.PostgreSQL.Simple.ToField src/Database/PostgreSQL/Simple/ToField.hs:(333,1)-(334,26) 0.0 0.0 0 0
CAF Main <entire-module> 0.0 0.0 0 624
zip Main app/Main.hs:56:5-7 0.0 0.0 0 0
wksi Main app/Main.hs:73:5-8 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 0.0 0.0 0 1933496
usage Main app/Main.hs:(151,1)-(153,13) 0.0 0.0 0 0
type_ Main app/Main.hs:51:5-9 0.0 0.0 0 0
toField Main app/Main.hs:(45,3)-(47,37) 0.0 0.0 0 0
toEnum Main app/Main.hs:42:61-64 0.0 0.0 0 0
succ Main app/Main.hs:42:61-64 0.0 0.0 0 0
subcik Main app/Main.hs:63:5-10 0.0 0.0 0 0
stateCode Main app/Main.hs:54:5-13 0.0 0.0 0 0
sics Main app/Main.hs:37:5-8 0.0 0.0 0 0
showsPrec Main app/Main.hs:40:29-32 0.0 0.0 0 0
showsPrec Main app/Main.hs:42:67-70 0.0 0.0 0 0
showsPrec Main app/Main.hs:60:29-32 0.0 0.0 0 0
showsPrec Main app/Main.hs:79:29-32 0.0 0.0 0 0
showsPrec Main app/Main.hs:158:15-18 0.0 0.0 0 0
row Main app/Main.hs:157:5-7 0.0 0.0 0 0
pred Main app/Main.hs:42:61-64 0.0 0.0 0 0
phone Main app/Main.hs:52:5-9 0.0 0.0 0 0
period Main app/Main.hs:67:5-10 0.0 0.0 0 0
parseRow Main app/Main.hs:183:1-60 0.0 0.0 0 80
parseHeader Main app/Main.hs:(186,1)-(188,61) 0.0 0.0 0 48
nameChanged Main app/Main.hs:36:5-15 0.0 0.0 0 0
name Main app/Main.hs:34:5-8 0.0 0.0 0 0
main Main app/Main.hs:(283,1)-(292,50) 0.0 0.0 0 1872
header Main app/Main.hs:156:5-10 0.0 0.0 0 0
fyEnd Main app/Main.hs:71:5-9 0.0 0.0 0 0
fy Main app/Main.hs:70:5-6 0.0 0.0 0 0
fromEnum Main app/Main.hs:42:61-64 0.0 0.0 0 0
fp Main app/Main.hs:66:5-6 0.0 0.0 0 0
formerName Main app/Main.hs:35:5-14 0.0 0.0 0 0
form Main app/Main.hs:65:5-8 0.0 0.0 0 0
filed Main app/Main.hs:68:5-9 0.0 0.0 0 0
file Main app/Main.hs:76:5-8 0.0 0.0 0 0
enumFromThen Main app/Main.hs:42:61-64 0.0 0.0 0 0
enumFrom Main app/Main.hs:42:61-64 0.0 0.0 0 0
eins Main app/Main.hs:38:5-8 0.0 0.0 0 0
detail Main app/Main.hs:75:5-10 0.0 0.0 0 0
countryCode Main app/Main.hs:53:5-15 0.0 0.0 0 0
compcik Main app/Main.hs:33:5-11 0.0 0.0 0 0
col Main app/Main.hs:221:3-23 0.0 0.0 0 1691888
col Main app/Main.hs:249:3-25 0.0 0.1 0 5075664
col Main app/Main.hs:252:3-30 0.0 0.0 0 1691888
city Main app/Main.hs:55:5-8 0.0 0.0 0 0
amended Main app/Main.hs:74:5-11 0.0 0.0 0 0
afs Main app/Main.hs:72:5-7 0.0 0.0 0 0
address2 Main app/Main.hs:58:5-12 0.0 0.0 0 0
address1 Main app/Main.hs:57:5-12 0.0 0.0 0 0
addrcik Main app/Main.hs:50:5-11 0.0 0.0 0 0
aciks Main app/Main.hs:77:5-9 0.0 0.0 0 0
accn Main app/Main.hs:64:5-8 0.0 0.0 0 0
accepted Main app/Main.hs:69:5-12 0.0 0.0 0 0
individual inherited
COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc ticks bytes
MAIN MAIN <built-in> 422 0 0.0 0.0 100.0 100.0 0 744
CAF Main <entire-module> 843 0 0.0 0.0 0.0 0.0 0 624
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 912 2 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:255:3-36 1098 1 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:221:3-23 1073 1 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:252:3-30 1030 1 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 961 1 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 919 1 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 897 1 0.0 0.0 0.0 0.0 0 0
field Main app/Main.hs:173:1-41 860 1 0.0 0.0 0.0 0.0 0 0
lookup Data.Map.Internal src/Data/Map/Internal.hs:(568,1)-(574,18) 906 1 0.0 0.0 0.0 0.0 0 0
main Main app/Main.hs:(283,1)-(292,50) 844 1 0.0 0.0 0.0 0.0 0 88
parseDate Main app/Main.hs:(235,1)-(236,34) 971 1 0.0 0.0 0.0 0.0 0 80
parseN Main app/Main.hs:(227,1)-(232,44) 974 2 0.0 0.0 0.0 0.0 0 0
parseHeader Main app/Main.hs:(186,1)-(188,61) 854 1 0.0 0.0 0.0 0.0 0 0
modify Control.Monad.State.Class Control/Monad/State/Class.hs:89:1-34 890 0 0.0 0.0 0.0 0.0 0 2592
parseRow Main app/Main.hs:183:1-60 857 1 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 879 1 0.0 0.0 0.0 0.0 0 16
advanceTo Main app/Main.hs:(163,1)-(170,39) 882 1 0.0 0.0 0.0 0.0 0 0
parseSubmission Main app/Main.hs:(261,1)-(270,56) 874 1 0.0 0.0 0.0 0.0 0 1104
unpackCStringAscii# Data.Text.Show src/Data/Text/Show.hs:(101,1)-(107,25) 907 32 0.0 0.0 0.0 0.0 0 1816
addrLen Data.Text.Show src/Data/Text/Show.hs:112:1-45 908 32 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 936 22 0.0 0.0 0.0 0.0 0 5136
withCol Main app/Main.hs:(205,1)-(212,19) 937 22 0.0 0.0 0.0 0.0 0 880
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 942 22 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:221:3-23 1074 0 0.0 0.0 0.0 0.0 0 184
withCol Main app/Main.hs:(205,1)-(212,19) 1075 1 0.0 0.0 0.0 0.0 0 40
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 1080 1 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 962 0 0.0 0.0 0.0 0.0 0 368
withCol Main app/Main.hs:(205,1)-(212,19) 963 2 0.0 0.0 0.0 0.0 0 80
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 968 2 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 946 0 0.0 0.0 0.0 0.0 0 3496
withCol Main app/Main.hs:(205,1)-(212,19) 947 19 0.0 0.0 0.0 0.0 0 760
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 952 19 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 875 1 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:255:3-36 1099 0 0.0 0.0 0.0 0.0 0 552
withCol Main app/Main.hs:(205,1)-(212,19) 1100 3 0.0 0.0 0.0 0.0 0 120
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 1105 3 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:252:3-30 1031 0 0.0 0.0 0.0 0.0 0 184
withCol Main app/Main.hs:(205,1)-(212,19) 1032 1 0.0 0.0 0.0 0.0 0 40
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 1037 1 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 1000 0 0.0 0.0 0.0 0.0 0 184
withCol Main app/Main.hs:(205,1)-(212,19) 1001 1 0.0 0.0 0.0 0.0 0 40
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 1006 1 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 920 0 0.0 0.0 0.0 0.0 0 736
withCol Main app/Main.hs:(205,1)-(212,19) 921 4 0.0 0.0 0.0 0.0 0 160
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 926 4 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 898 0 0.0 0.0 0.0 0.0 0 184
withCol Main app/Main.hs:(205,1)-(212,19) 899 1 0.0 0.0 0.0 0.0 0 40
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 909 1 0.0 0.0 0.0 0.0 0 0
parseSubmissions Main app/Main.hs:(273,1)-(280,100) 871 1 0.0 0.0 0.0 0.0 0 0
parseTimestamp Main app/Main.hs:(239,1)-(246,19) 1040 1 0.0 0.0 0.0 0.0 0 40
parseN Main app/Main.hs:(227,1)-(232,44) 1052 1 0.0 0.0 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.ToField <entire-module> 842 0 0.0 0.0 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.Types <entire-module> 841 0 0.0 0.0 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.Compat <entire-module> 840 0 0.0 0.0 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.Time.Implementation <entire-module> 839 0 0.0 0.0 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.Time.Internal.Parser <entire-module> 838 0 0.0 0.0 0.0 0.0 0 0
CAF Database.PostgreSQL.Simple.Time.Internal.Printer <entire-module> 837 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson <entire-module> 836 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Encoding.Internal <entire-module> 835 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Key <entire-module> 834 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Parser.Internal <entire-module> 833 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Encoding.Builder <entire-module> 832 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Internal.Integer <entire-module> 831 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Internal.Text <entire-module> 830 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Types.FromJSON <entire-module> 829 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Types.Generic <entire-module> 828 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Types.Internal <entire-module> 827 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Types.ToJSON <entire-module> 826 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.Time <entire-module> 825 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.Time.Internal <entire-module> 824 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Parser.UnescapePure <entire-module> 823 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.KeyMap <entire-module> 822 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Aeson.Parser.Time <entire-module> 821 0 0.0 0.0 0.0 0.0 0 0
CAF Witherable <entire-module> 820 0 0.0 0.0 0.0 0.0 0 0
CAF Data.UUID.Types.Internal <entire-module> 819 0 0.0 0.0 0.0 0.0 0 0
CAF Data.UUID.Types.Internal.Builder <entire-module> 818 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.Month.Compat <entire-module> 817 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.Quarter.Compat <entire-module> 816 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Short.Internal <entire-module> 815 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Strict.Classes <entire-module> 814 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Strict.These <entire-module> 813 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Strict.Tuple <entire-module> 812 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Strict.Maybe <entire-module> 811 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Strict.Either <entire-module> 810 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Semialign.Internal <entire-module> 809 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.These <entire-module> 808 0 0.0 0.0 0.0 0.0 0 0
CAF Data.These <entire-module> 807 0 0.0 0.0 0.0 0.0 0 0
CAF Data.These.Combinators <entire-module> 806 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Bifunctor.Assoc <entire-module> 805 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.WithIndex.Instances <entire-module> 804 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Fusion.Util <entire-module> 803 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Fusion.Bundle.Size <entire-module> 802 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Fusion.Bundle.Monadic <entire-module> 801 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Generic.Mutable.Base <entire-module> 800 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Generic.Mutable <entire-module> 799 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Generic.Base <entire-module> 798 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Primitive <entire-module> 797 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Storable <entire-module> 796 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Mutable <entire-module> 795 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector <entire-module> 794 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Internal.Check <entire-module> 793 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Generic <entire-module> 792 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Primitive.Mutable <entire-module> 791 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Storable.Mutable <entire-module> 790 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Vector.Generic.New <entire-module> 789 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Stream.Monadic <entire-module> 788 0 0.0 0.0 0.0 0.0 0 0
CAF Data.HashMap.Internal <entire-module> 787 0 0.0 0.0 0.0 0.0 0 0
CAF Data.HashMap.Internal.Array <entire-module> 786 0 0.0 0.0 0.0 0.0 0 0
CAF Data.HashMap.Internal.List <entire-module> 785 0 0.0 0.0 0.0 0.0 0 0
CAF Data.HashMap.Internal.Strict <entire-module> 784 0 0.0 0.0 0.0 0.0 0 0
CAF Data.HashSet.Internal <entire-module> 783 0 0.0 0.0 0.0 0.0 0 0
CAF WithIndex <entire-module> 782 0 0.0 0.0 0.0 0.0 0 0
CAF Data.DList.Internal <entire-module> 781 0 0.0 0.0 0.0 0.0 0 0
CAF Data.DList.DNonEmpty.Internal <entire-module> 780 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Fix <entire-module> 779 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Foldable1 <entire-module> 778 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Bifoldable1 <entire-module> 777 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Tagged <entire-module> 776 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.MonthDay <entire-module> 775 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.OrdinalDate <entire-module> 774 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.Month <entire-module> 773 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.Quarter <entire-module> 772 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Format.ISO8601 <entire-module> 771 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Format <entire-module> 770 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.CalendarDiffDays <entire-module> 769 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.Days <entire-module> 768 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.Gregorian <entire-module> 767 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.Private <entire-module> 766 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.Week <entire-module> 765 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.DiffTime <entire-module> 764 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.NominalDiffTime <entire-module> 763 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.SystemTime <entire-module> 762 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.UTCTime <entire-module> 761 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.CTimespec <entire-module> 760 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.LocalTime.Internal.TimeZone <entire-module> 759 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.LocalTime.Internal.TimeOfDay <entire-module> 758 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.LocalTime.Internal.CalendarDiffTime <entire-module> 757 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.LocalTime.Internal.LocalTime <entire-module> 756 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.LocalTime.Internal.ZonedTime <entire-module> 755 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Format.Parse <entire-module> 754 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Format.Locale <entire-module> 753 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Format.Format.Class <entire-module> 752 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Format.Format.Instances <entire-module> 751 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Format.Parse.Class <entire-module> 750 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Format.Parse.Instances <entire-module> 749 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Calendar.WeekDate <entire-module> 748 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Clock.POSIX <entire-module> 747 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.POSIXTime <entire-module> 746 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.UTCDiff <entire-module> 745 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Clock.System <entire-module> 744 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Time.Clock.Internal.AbsoluteTime <entire-module> 743 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.ByteString.Char8 <entire-module> 742 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.ByteString.Lazy <entire-module> 741 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.Combinator <entire-module> 740 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.Internal <entire-module> 739 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.Internal.Types <entire-module> 738 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.Number <entire-module> 737 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.Zepto <entire-module> 736 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.ByteString.Internal <entire-module> 735 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.Text.Internal <entire-module> 734 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.ByteString.Buffer <entire-module> 733 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.ByteString.FastSet <entire-module> 732 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.Text.Buffer <entire-module> 731 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Attoparsec.Text.FastSet <entire-module> 730 0 0.0 0.0 0.0 0.0 0 0
CAF Test.QuickCheck.Arbitrary <entire-module> 729 0 0.0 0.0 0.0 0.0 0 0
CAF Test.QuickCheck.Gen <entire-module> 728 0 0.0 0.0 0.0 0.0 0 0
CAF Test.QuickCheck.Gen.Unsafe <entire-module> 727 0 0.0 0.0 0.0 0.0 0 0
CAF Test.QuickCheck.Random <entire-module> 726 0 0.0 0.0 0.0 0.0 0 0
CAF Test.QuickCheck.Function <entire-module> 725 0 0.0 0.0 0.0 0.0 0 0
CAF Test.QuickCheck.Poly <entire-module> 724 0 0.0 0.0 0.0 0.0 0 0
CAF System.Random <entire-module> 723 0 0.0 0.0 0.0 0.0 0 0
CAF System.Random.Internal <entire-module> 722 0 0.0 0.0 0.0 0.0 0 0
CAF System.Random.GFinite <entire-module> 721 0 0.0 0.0 0.0 0.0 0 0
CAF System.Random.SplitMix <entire-module> 720 0 0.0 0.0 0.0 0.0 0 0
CAF System.Random.SplitMix32 <entire-module> 719 0 0.0 0.0 0.0 0.0 0 0
CAF System.Random.SplitMix.Init <entire-module> 718 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Tuple.Solo <entire-module> 717 0 0.0 0.0 0.0 0.0 0 0
CAF Text.Megaparsec <entire-module> 716 0 0.0 0.0 0.0 0.0 0 0
CAF Text.Megaparsec.Char.Lexer <entire-module> 715 0 0.0 0.0 0.0 0.0 0 0
CAF Text.Megaparsec.Error <entire-module> 714 0 0.0 0.0 0.0 0.0 0 0
CAF Text.Megaparsec.Internal <entire-module> 713 0 0.0 0.0 0.0 0.0 0 0
CAF Text.Megaparsec.Pos <entire-module> 712 0 0.0 0.0 0.0 0.0 0 0
CAF Text.Megaparsec.Stream <entire-module> 711 0 0.0 0.0 0.0 0.0 0 32
CAF Text.Megaparsec.Class <entire-module> 710 0 0.0 0.0 0.0 0.0 0 0
CAF Text.Megaparsec.Lexer <entire-module> 709 0 0.0 0.0 0.0 0.0 0 0
CAF Text.Megaparsec.State <entire-module> 708 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder.Scientific <entire-module> 707 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Scientific <entire-module> 706 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Lazy.Builder.Scientific <entire-module> 705 0 0.0 0.0 0.0 0.0 0 0
CAF Utils <entire-module> 704 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Primitive <entire-module> 703 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Primitive.MachDeps <entire-module> 702 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Primitive.Types <entire-module> 701 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Primitive.Array <entire-module> 700 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Primitive.PrimArray <entire-module> 699 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Primitive.SmallArray <entire-module> 698 0 0.0 0.0 0.0 0.0 0 0
CAF Math.NumberTheory.Logarithms <entire-module> 697 0 0.0 0.0 0.0 0.0 0 0
CAF Data.CaseInsensitive.Internal <entire-module> 696 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Hashable.Class <entire-module> 695 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Hashable.LowLevel <entire-module> 694 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text <entire-module> 693 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Array <entire-module> 692 0 0.0 0.0 0.0 0.0 0 0
empty Data.Text.Array src/Data/Text/Array.hs:176:1-38 863 1 0.0 0.0 0.0 0.0 0 32
CAF Data.Text.Encoding <entire-module> 691 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Encoding.Error <entire-module> 690 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Foreign <entire-module> 689 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.IO <entire-module> 688 0 0.0 0.0 0.0 0.0 0 48
CAF Data.Text.Internal <entire-module> 687 0 0.0 0.0 0.0 0.0 0 32
empty_ Data.Text.Internal src/Data/Text/Internal.hs:97:1-25 981 1 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Builder <entire-module> 686 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Encoding <entire-module> 685 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Encoding.Fusion <entire-module> 684 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Encoding.Utf8 <entire-module> 683 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Fusion <entire-module> 682 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Fusion.CaseMapping <entire-module> 681 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Fusion.Common <entire-module> 680 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Fusion.Size <entire-module> 679 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Fusion.Types <entire-module> 678 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.IO <entire-module> 677 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Lazy <entire-module> 676 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Lazy.Fusion <entire-module> 675 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.StrictBuilder <entire-module> 674 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Unsafe <entire-module> 673 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Lazy <entire-module> 672 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Lazy.Builder.Int <entire-module> 671 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Lazy.Builder.RealFloat <entire-module> 670 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Lazy.Encoding <entire-module> 669 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Read <entire-module> 668 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Unsafe <entire-module> 667 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Show <entire-module> 666 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Builder.Functions <entire-module> 665 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Builder.Int.Digits <entire-module> 664 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Builder.RealFloat.Functions <entire-module> 663 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Lazy.Encoding.Fusion <entire-module> 662 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Lazy.Search <entire-module> 661 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Text.Internal.Read <entire-module> 660 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Binary.Put <entire-module> 659 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Binary.Get.Internal <entire-module> 658 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Binary.Builder <entire-module> 657 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Binary.Class <entire-module> 656 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Binary.Get <entire-module> 655 0 0.0 0.0 0.0 0.0 0 0
CAF System.OsString.Internal.Types <entire-module> 654 0 0.0 0.0 0.0 0.0 0 0
CAF System.OsPath.Data.ByteString.Short.Word16 <entire-module> 653 0 0.0 0.0 0.0 0.0 0 0
CAF System.OsPath.Encoding.Internal <entire-module> 652 0 0.0 0.0 0.0 0.0 0 0
CAF System.OsPath.Data.ByteString.Short.Internal <entire-module> 651 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Catch <entire-module> 650 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Cont.Class <entire-module> 649 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Error.Class <entire-module> 648 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Reader.Class <entire-module> 647 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.State.Class <entire-module> 646 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Applicative.Backwards <entire-module> 645 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Applicative.Lift <entire-module> 644 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.Accum <entire-module> 643 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.Cont <entire-module> 642 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.Except <entire-module> 641 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.Error <entire-module> 640 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.Identity <entire-module> 639 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.List <entire-module> 638 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.Maybe <entire-module> 637 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.Reader <entire-module> 636 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.RWS.CPS <entire-module> 635 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.RWS.Lazy <entire-module> 634 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.RWS.Strict <entire-module> 633 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.Select <entire-module> 632 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.State.Lazy <entire-module> 631 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.State.Strict <entire-module> 630 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.Writer.CPS <entire-module> 629 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.Writer.Lazy <entire-module> 628 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Trans.Writer.Strict <entire-module> 627 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.Constant <entire-module> 626 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.Reverse <entire-module> 625 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Array.Byte <entire-module> 624 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString <entire-module> 623 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Unsafe <entire-module> 622 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Internal <entire-module> 621 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Lazy <entire-module> 620 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Lazy.Internal <entire-module> 619 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Short.Internal <entire-module> 618 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder <entire-module> 617 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder.Prim <entire-module> 616 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder.RealFloat <entire-module> 615 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder.Internal <entire-module> 614 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder.Prim.Internal <entire-module> 613 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder.ASCII <entire-module> 612 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder.Prim.ASCII <entire-module> 611 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder.Prim.Internal.Base16 <entire-module> 610 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder.RealFloat.F2S <entire-module> 609 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder.RealFloat.D2S <entire-module> 608 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Builder.RealFloat.Internal <entire-module> 607 0 0.0 0.0 0.0 0.0 0 0
CAF Data.ByteString.Lazy.Internal.Deque <entire-module> 606 0 0.0 0.0 0.0 0.0 0 0
CAF Data.IntMap.Internal <entire-module> 605 0 0.0 0.0 0.0 0.0 0 0
CAF Data.IntSet.Internal <entire-module> 604 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Map.Strict.Internal <entire-module> 603 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Map.Internal <entire-module> 602 0 0.0 0.0 0.0 0.0 0 0
delta Data.Map.Internal src/Data/Map/Internal.hs:4007:1-9 893 1 0.0 0.0 0.0 0.0 0 0
CAF Data.Set.Internal <entire-module> 601 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Sequence.Internal <entire-module> 600 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Tree <entire-module> 599 0 0.0 0.0 0.0 0.0 0 0
CAF Utils.Containers.Internal.BitUtil <entire-module> 598 0 0.0 0.0 0.0 0.0 0 0
CAF Utils.Containers.Internal.BitQueue <entire-module> 597 0 0.0 0.0 0.0 0.0 0 0
CAF Utils.Containers.Internal.StrictPair <entire-module> 596 0 0.0 0.0 0.0 0.0 0 0
CAF Utils.Containers.Internal.State <entire-module> 595 0 0.0 0.0 0.0 0.0 0 0
CAF Language.Haskell.TH.Syntax <entire-module> 594 0 0.0 0.0 0.0 0.0 0 0
CAF Language.Haskell.TH.Lib.Internal <entire-module> 593 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Lexeme <entire-module> 592 0 0.0 0.0 0.0 0.0 0 0
CAF Control.DeepSeq <entire-module> 591 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Array.Base <entire-module> 590 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Applicative <entire-module> 589 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Arrow <entire-module> 588 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Category <entire-module> 587 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Exception.Base <entire-module> 586 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Fail <entire-module> 585 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Fix <entire-module> 584 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.IO.Class <entire-module> 583 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.Zip <entire-module> 582 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Bifoldable <entire-module> 581 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Bifunctor <entire-module> 580 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Bitraversable <entire-module> 579 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Char <entire-module> 578 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Complex <entire-module> 577 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Data <entire-module> 576 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Either <entire-module> 575 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Fixed <entire-module> 574 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Foldable <entire-module> 573 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Function <entire-module> 572 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.Classes <entire-module> 571 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.Contravariant <entire-module> 570 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.Compose <entire-module> 569 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.Const <entire-module> 568 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.Identity <entire-module> 567 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.Product <entire-module> 566 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.Sum <entire-module> 565 0 0.0 0.0 0.0 0.0 0 0
CAF Data.List.NonEmpty <entire-module> 564 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Maybe <entire-module> 563 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Monoid <entire-module> 562 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Ord <entire-module> 561 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Proxy <entire-module> 560 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Semigroup <entire-module> 559 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Traversable <entire-module> 558 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Tuple <entire-module> 557 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Type.Coercion <entire-module> 556 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Type.Equality <entire-module> 555 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Unique <entire-module> 554 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Version <entire-module> 553 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Void <entire-module> 552 0 0.0 0.0 0.0 0.0 0 0
CAF Foreign.C.Error <entire-module> 551 0 0.0 0.0 0.0 0.0 0 0
CAF Foreign.C.String <entire-module> 550 0 0.0 0.0 0.0 0.0 0 0
CAF Foreign.C.Types <entire-module> 549 0 0.0 0.0 0.0 0.0 0 0
CAF Foreign.Marshal.Alloc <entire-module> 548 0 0.0 0.0 0.0 0.0 0 0
CAF Foreign.Marshal.Array <entire-module> 547 0 0.0 0.0 0.0 0.0 0 0
CAF Foreign.Ptr <entire-module> 546 0 0.0 0.0 0.0 0.0 0 0
CAF Foreign.Storable <entire-module> 545 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Arr <entire-module> 544 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Base <entire-module> 543 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Bits <entire-module> 542 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Char <entire-module> 541 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Conc.IO <entire-module> 540 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Conc.Signal <entire-module> 539 0 0.0 0.0 0.0 0.0 0 640
CAF GHC.Conc.Sync <entire-module> 538 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Enum <entire-module> 537 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Err <entire-module> 536 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Exception <entire-module> 535 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Exception.Type <entire-module> 534 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Exts <entire-module> 533 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Fingerprint.Type <entire-module> 532 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Float <entire-module> 531 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Float.ConversionUtils <entire-module> 530 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Float.RealFracMethods <entire-module> 529 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Foreign <entire-module> 528 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.ForeignPtr <entire-module> 527 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Generics <entire-module> 526 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO <entire-module> 525 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Buffer <entire-module> 524 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.BufferedIO <entire-module> 523 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Device <entire-module> 522 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Encoding <entire-module> 521 0 0.0 0.0 0.0 0.0 0 2976
CAF GHC.IO.Encoding.Failure <entire-module> 520 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Encoding.Iconv <entire-module> 519 0 0.0 0.0 0.0 0.0 0 200
CAF GHC.IO.Encoding.Latin1 <entire-module> 518 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Encoding.Types <entire-module> 517 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Encoding.UTF16 <entire-module> 516 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Encoding.UTF32 <entire-module> 515 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Encoding.UTF8 <entire-module> 514 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Exception <entire-module> 513 0 0.0 0.0 0.0 0.0 0 816
CAF GHC.IO.Handle <entire-module> 512 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Handle.FD <entire-module> 511 0 0.0 0.0 0.0 0.0 0 34736
CAF GHC.IO.Handle.Internals <entire-module> 510 0 0.0 0.0 0.0 0.0 0 24
CAF GHC.IO.Handle.Text <entire-module> 509 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Handle.Types <entire-module> 508 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.IOMode <entire-module> 507 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.Unsafe <entire-module> 506 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.StdHandles <entire-module> 505 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IOArray <entire-module> 504 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IORef <entire-module> 503 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Int <entire-module> 502 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Ix <entire-module> 501 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.List <entire-module> 500 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Maybe <entire-module> 499 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.MVar <entire-module> 498 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Num <entire-module> 497 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Pack <entire-module> 496 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Ptr <entire-module> 495 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Read <entire-module> 494 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Real <entire-module> 493 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.ST <entire-module> 492 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.STRef <entire-module> 491 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Show <entire-module> 490 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Stable <entire-module> 489 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.StableName <entire-module> 488 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Stack.CCS <entire-module> 487 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Stack.Types <entire-module> 486 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Storable <entire-module> 485 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.TopHandler <entire-module> 484 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.TypeLits <entire-module> 483 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.TypeNats <entire-module> 482 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Unicode <entire-module> 481 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Weak <entire-module> 480 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Word <entire-module> 479 0 0.0 0.0 0.0 0.0 0 0
CAF Numeric <entire-module> 478 0 0.0 0.0 0.0 0.0 0 0
CAF System.Environment <entire-module> 477 0 0.0 0.0 0.0 0.0 0 0
CAF System.Exit <entire-module> 476 0 0.0 0.0 0.0 0.0 0 0
CAF System.IO <entire-module> 475 0 0.0 0.0 0.0 0.0 0 0
CAF System.Posix.Internals <entire-module> 474 0 0.0 0.0 0.0 0.0 0 0
CAF Text.ParserCombinators.ReadP <entire-module> 473 0 0.0 0.0 0.0 0.0 0 0
CAF Text.ParserCombinators.ReadPrec <entire-module> 472 0 0.0 0.0 0.0 0.0 0 0
CAF Text.Printf <entire-module> 471 0 0.0 0.0 0.0 0.0 0 0
CAF Text.Read <entire-module> 470 0 0.0 0.0 0.0 0.0 0 0
CAF Text.Read.Lex <entire-module> 469 0 0.0 0.0 0.0 0.0 0 0
CAF Unsafe.Coerce <entire-module> 468 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IOPort <entire-module> 467 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.ST.Imp <entire-module> 466 0 0.0 0.0 0.0 0.0 0 0
CAF Control.Monad.ST.Lazy.Imp <entire-module> 465 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Functor.Utils <entire-module> 464 0 0.0 0.0 0.0 0.0 0 0
CAF Data.OldList <entire-module> 463 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Semigroup.Internal <entire-module> 462 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Typeable.Internal <entire-module> 461 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.Thread <entire-module> 460 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.TimerManager <entire-module> 459 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Dynamic <entire-module> 458 0 0.0 0.0 0.0 0.0 0 0
CAF Data.Type.Ord <entire-module> 457 0 0.0 0.0 0.0 0.0 0 0
CAF Debug.Trace <entire-module> 456 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Fingerprint <entire-module> 455 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.IO.FD <entire-module> 454 0 0.0 0.0 0.0 0.0 0 16
CAF GHC.Event.Internal <entire-module> 453 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.Internal.Types <entire-module> 452 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.IntTable <entire-module> 451 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.IntVar <entire-module> 450 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.PSQ <entire-module> 449 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.Unique <entire-module> 448 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.Control <entire-module> 447 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.EPoll <entire-module> 446 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.Manager <entire-module> 445 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.Poll <entire-module> 444 0 0.0 0.0 0.0 0.0 0 0
CAF System.Posix.Types <entire-module> 443 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.Arr <entire-module> 442 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Event.Array <entire-module> 441 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Num.BigNat <entire-module> 440 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Num.Natural <entire-module> 439 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Num.Integer <entire-module> 438 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Num.Backend.GMP <entire-module> 437 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Num.Primitives <entire-module> 436 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Num.WordArray <entire-module> 435 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.CString <entire-module> 434 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Classes <entire-module> 433 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Prim.Panic <entire-module> 432 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Prim.Exception <entire-module> 431 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Tuple <entire-module> 430 0 0.0 0.0 0.0 0.0 0 0
CAF GHC.Types <entire-module> 429 0 0.0 0.0 0.0 0.0 0 0
DONT_CARE MAIN <built-in> 425 0 0.0 0.0 0.0 0.0 0 0
GC GC <built-in> 427 0 35.4 0.0 35.4 0.0 916 1096
IDLE IDLE <built-in> 423 0 0.0 0.0 0.0 0.0 0 0
OVERHEAD_of PROFILING <built-in> 426 0 7.8 0.1 7.8 0.1 201 3180072
PINNED SYSTEM <built-in> 424 0 0.0 0.0 0.0 0.0 0 0
SYSTEM SYSTEM <built-in> 428 0 0.1 0.0 0.1 0.0 2 198496
main Main app/Main.hs:(283,1)-(292,50) 845 0 0.0 0.0 56.7 99.9 0 1784
readFile Data.Text.IO src/Data/Text/IO.hs:80:1-55 846 1 0.0 0.0 1.4 0.4 0 19992
hGetContents Data.Text.IO src/Data/Text/IO.hs:(135,1)-(149,50) 847 1 0.0 0.0 1.4 0.4 1 944848
readChunk Data.Text.Internal.IO src/Data/Text/Internal/IO.hs:(156,1)-(163,10) 848 4364 0.8 0.2 1.2 0.2 21 10191696
readTextDevice Data.Text.Internal.IO src/Data/Text/Internal/IO.hs:133:39-64 849 4364 0.4 0.0 0.4 0.0 10 1824120
concat Data.Text src/Data/Text.hs:(1137,1)-(1148,36) 862 1 0.0 0.0 0.1 0.2 0 698128
run Data.Text.Array src/Data/Text/Array.hs:181:1-34 864 1 0.1 0.2 0.1 0.2 3 8935040
runParserT Text.Megaparsec Text/Megaparsec.hs:268:1-65 850 1 0.0 0.0 55.3 99.5 0 376
runParserT' Text.Megaparsec Text/Megaparsec.hs:(282,1)-(296,54) 851 1 0.0 0.0 55.3 99.5 0 336
runParsecT Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:(675,1)-(680,59) 852 1 0.0 0.0 55.3 99.5 0 176
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 853 2 0.0 0.0 0.0 0.0 0 0
parseHeader Main app/Main.hs:(186,1)-(188,61) 855 0 0.0 0.0 55.3 99.5 0 48
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 856 1 0.0 0.0 0.0 0.0 0 0
parseRow Main app/Main.hs:183:1-60 858 0 0.0 0.0 55.3 99.5 0 80
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 859 2 0.0 0.0 0.0 0.0 0 0
field Main app/Main.hs:173:1-41 861 0 7.0 16.7 55.3 99.5 180 937969048
tsvSep Main app/Main.hs:176:1-33 865 6732472 0.0 0.0 0.0 0.0 0 0
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 867 82175 0.0 0.0 0.0 0.0 0 0
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 866 322 0.0 0.0 0.0 0.0 0 0
unShareInput Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:186:36-47 868 72 0.0 0.0 0.0 0.0 0 0
modify Control.Monad.State.Class Control/Monad/State/Class.hs:89:1-34 869 1 0.0 0.0 48.4 82.9 0 3080
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 870 5 0.0 0.0 0.0 0.0 0 0
fromList Data.Map.Internal src/Data/Map/Internal.hs:(3423,1)-(3456,89) 891 1 0.0 0.0 0.0 0.0 0 160
insert Data.Map.Internal src/Data/Map/Internal.hs:(774,1)-(791,54) 894 33 0.0 0.0 0.0 0.0 0 2904
balanceL Data.Map.Internal src/Data/Map/Internal.hs:(4081,1)-(4100,50) 896 71 0.0 0.0 0.0 0.0 0 4368
balanceR Data.Map.Internal src/Data/Map/Internal.hs:(4106,1)-(4125,50) 895 71 0.0 0.0 0.0 0.0 0 4512
link Data.Map.Internal src/Data/Map/Internal.hs:(3888,1)-(3893,39) 892 1 0.0 0.0 0.0 0.0 0 64
parseSubmissions Main app/Main.hs:(273,1)-(280,100) 872 0 0.0 0.1 48.4 82.9 1 7975208
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 873 181258 0.0 0.0 0.0 0.0 0 0
parseSubmission Main app/Main.hs:(261,1)-(270,56) 876 0 0.1 0.0 48.3 82.7 3 1691704
col Main app/Main.hs:255:3-36 1101 0 0.1 0.2 0.7 1.3 3 13050288
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1108 90627 0.0 0.0 0.0 0.0 0 0
withCol Main app/Main.hs:(205,1)-(212,19) 1102 0 0.1 0.1 0.5 1.1 2 7251920
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1103 90642 0.0 0.0 0.0 0.0 0 0
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 1106 0 0.5 1.0 0.5 1.0 12 54857240
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1107 996879 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 1109 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 1110 0 0.0 0.0 0.0 0.0 0 0
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 1111 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1112 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1113 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1114 0 0.0 0.0 0.0 0.0 0 592
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1117 3 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 1115 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 1116 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:252:3-30 1033 0 0.0 0.0 2.7 4.5 0 1691704
withCol Main app/Main.hs:(205,1)-(212,19) 1034 0 0.1 0.0 2.7 4.5 2 2417520
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1035 30214 0.0 0.0 0.0 0.0 0 0
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 1038 0 0.1 0.2 2.6 4.5 3 13774360
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1039 241666 0.0 0.0 0.0 0.0 0 0
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 1062 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1063 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1064 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1065 0 0.0 0.0 0.0 0.0 0 176
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1072 1 0.0 0.0 0.0 0.0 0 0
parseTimestamp Main app/Main.hs:(239,1)-(246,19) 1041 0 0.1 0.1 2.5 4.2 2 3141736
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1042 60418 0.0 0.0 0.0 0.0 0 0
parseDate Main app/Main.hs:(235,1)-(236,34) 1043 0 0.0 0.3 1.3 2.4 0 15467008
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1044 151045 0.0 0.0 0.0 0.0 0 0
parseN Main app/Main.hs:(227,1)-(232,44) 1045 0 1.0 1.8 1.3 2.1 25 99327208
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1046 906270 0.0 0.0 0.0 0.0 0 0
unShareInput Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:186:36-47 1051 181254 0.0 0.0 0.0 0.0 0 0
decimal Data.Text.Read src/Data/Text/Read.hs:(62,1)-(66,55) 1050 90627 0.2 0.3 0.2 0.3 4 14500320
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 1049 90627 0.0 0.0 0.0 0.0 1 0
splitAt Data.Text src/Data/Text.hs:(1554,1)-(1558,78) 1047 90627 0.1 0.1 0.1 0.1 2 5800128
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 1048 90627 0.0 0.0 0.0 0.0 1 0
parseN Main app/Main.hs:(227,1)-(232,44) 1053 0 1.0 1.4 1.1 1.8 26 79993432
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1054 664598 0.0 0.0 0.0 0.0 0 0
unShareInput Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:186:36-47 1060 120836 0.0 0.0 0.0 0.0 0 0
decimal Data.Text.Read src/Data/Text/Read.hs:(62,1)-(66,55) 1058 90627 0.0 0.3 0.0 0.3 1 14500320
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 1057 90627 0.0 0.0 0.0 0.0 0 0
splitAt Data.Text src/Data/Text.hs:(1554,1)-(1558,78) 1055 90627 0.1 0.1 0.1 0.1 2 4833440
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 1056 90627 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 1144 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 1145 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 1061 0 0.0 0.0 0.0 0.0 0 0
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 1066 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1067 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1068 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1069 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 1070 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 1071 0 0.0 0.0 0.0 0.0 0 0
parseDate Main app/Main.hs:(235,1)-(236,34) 1059 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 1002 0 0.0 0.0 1.5 2.4 0 1691704
withCol Main app/Main.hs:(205,1)-(212,19) 1003 0 0.0 0.0 1.5 2.4 1 2417520
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1004 30214 0.0 0.0 0.0 0.0 0 0
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 1007 0 0.0 0.2 1.5 2.3 1 13774344
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1008 241666 0.0 0.0 0.0 0.0 0 0
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 1019 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1020 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1021 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1022 0 0.0 0.0 0.0 0.0 0 176
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1029 1 0.0 0.0 0.0 0.0 0 0
parseDate Main app/Main.hs:(235,1)-(236,34) 1009 0 0.1 0.3 1.5 2.1 2 15467008
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1010 151045 0.0 0.0 0.0 0.0 0 0
parseN Main app/Main.hs:(227,1)-(232,44) 1011 0 1.2 1.5 1.4 1.8 30 82168480
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1012 785434 0.0 0.0 0.0 0.0 0 0
decimal Data.Text.Read src/Data/Text/Read.hs:(62,1)-(66,55) 1016 90627 0.1 0.3 0.1 0.3 3 14500320
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 1015 90627 0.0 0.0 0.0 0.0 0 0
splitAt Data.Text src/Data/Text.hs:(1554,1)-(1558,78) 1013 90627 0.1 0.1 0.1 0.1 3 4833440
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 1014 90627 0.0 0.0 0.0 0.0 0 0
unShareInput Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:186:36-47 1017 60418 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 1018 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 1143 0 0.0 0.0 0.0 0.0 0 0
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 1023 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1024 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1025 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1026 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 1027 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 1028 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 938 0 0.4 1.3 13.7 21.4 11 74434976
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 945 1329196 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:221:3-23 1076 0 0.0 0.0 0.7 0.9 0 1691704
withCol Main app/Main.hs:(205,1)-(212,19) 1077 0 0.1 0.1 0.7 0.9 3 7574216
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1078 30214 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 1155 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:252:3-30 1093 0 0.0 0.0 0.0 0.0 0 0
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 1081 0 0.4 0.4 0.6 0.8 10 19774840
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1082 332293 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 1147 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:252:3-30 1146 0 0.0 0.0 0.0 0.0 0 0
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 1083 0 0.2 0.4 0.2 0.4 5 23707416
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1084 173272 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1085 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1086 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1087 0 0.0 0.0 0.0 0.0 0 208
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 1096 1 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 1095 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:252:3-30 1094 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 1088 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1089 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1090 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1091 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 1092 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 964 0 0.0 0.1 3.1 4.5 0 3383408
withCol Main app/Main.hs:(205,1)-(212,19) 965 0 0.2 0.4 3.1 4.5 6 22048768
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 966 453127 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 1135 0 0.0 0.0 0.0 0.0 0 0
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 969 0 0.4 0.6 2.9 4.1 10 31432704
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 970 634383 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 983 0 0.0 0.0 0.0 0.0 0 0
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 984 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 985 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 986 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 987 0 0.0 0.0 0.0 0.0 0 656
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 988 14 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 999 0 0.0 0.0 0.0 0.0 0 0
parseDate Main app/Main.hs:(235,1)-(236,34) 972 0 0.1 0.6 2.5 3.5 2 30934032
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 973 302090 0.0 0.0 0.0 0.0 0 0
parseN Main app/Main.hs:(227,1)-(232,44) 975 0 2.4 2.4 2.4 3.0 61 136153568
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 976 1281988 0.0 0.0 0.0 0.0 0 0
decimal Data.Text.Read src/Data/Text/Read.hs:(62,1)-(66,55) 980 152366 0.0 0.4 0.0 0.4 1 22067520
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 979 152366 0.0 0.0 0.0 0.0 0 0
splitAt Data.Text src/Data/Text.hs:(1554,1)-(1558,78) 977 152366 0.0 0.1 0.0 0.1 0 7818048
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 978 152366 0.0 0.0 0.0 0.0 0 0
unShareInput Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:186:36-47 982 91948 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1127 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1128 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1129 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 1130 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1131 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1132 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1133 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 1134 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1136 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1137 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1138 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 1139 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 948 0 1.0 1.3 7.9 10.7 26 74782512
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 955 1147942 0.0 0.0 0.0 0.0 0 0
withCol Main app/Main.hs:(205,1)-(212,19) 949 0 1.3 1.8 6.9 9.3 34 98752520
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 950 1150910 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:221:3-23 1153 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 1152 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 1140 0 0.0 0.0 0.0 0.0 0 0
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 953 0 5.6 7.6 5.6 7.6 145 426293120
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 954 8749095 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 1141 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:221:3-23 1097 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 991 0 0.0 0.0 0.0 0.0 0 0
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 956 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 957 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 958 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 959 0 0.0 0.0 0.0 0.0 0 4128
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 960 59 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 992 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 993 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 994 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 995 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 996 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1123 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1124 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1125 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 1126 0 0.0 0.0 0.0 0.0 0 0
withCol Main app/Main.hs:(205,1)-(212,19) 939 0 0.3 0.9 1.6 4.0 9 53167840
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 940 664598 0.0 0.0 0.0 0.0 0 0
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 943 0 1.2 3.0 1.2 3.0 32 170137088
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 944 4652186 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 922 0 0.3 0.3 1.1 1.9 7 15467008
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 929 241672 0.0 0.0 0.0 0.0 0 0
withCol Main app/Main.hs:(205,1)-(212,19) 923 0 0.2 0.5 0.9 1.7 4 29726624
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 924 362510 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 1154 0 0.0 0.0 0.0 0.0 0 0
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 927 0 0.7 1.1 0.7 1.1 18 63557728
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 928 1329182 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 1142 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:255:3-36 1118 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 930 0 0.0 0.0 0.0 0.0 0 0
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 931 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 932 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 933 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 934 0 0.0 0.0 0.0 0.0 0 1208
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 935 12 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 998 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1148 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1149 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1150 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 1151 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 1119 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 1120 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 1121 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 1122 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:224:3-23 900 0 0.0 0.2 1.9 4.9 1 8458520
withCol Main app/Main.hs:(205,1)-(212,19) 901 0 0.3 0.4 1.9 4.7 7 22241288
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 902 332481 0.0 0.0 0.0 0.0 0 0
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 910 0 0.4 0.9 1.6 4.3 11 51226464
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 911 1177959 0.0 0.0 0.0 0.0 0 0
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 913 0 1.2 3.4 1.2 3.4 30 190867360
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 914 755225 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 989 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 997 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 990 0 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 915 0 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 916 0 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 917 0 0.0 0.0 0.0 0.0 0 632
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 918 10 0.0 0.0 0.0 0.0 0 0
withRow Main app/Main.hs:(191,1)-(199,28) 877 0 0.0 0.0 26.6 46.2 0 1933496
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 878 30211 0.0 0.0 0.0 0.0 0 0
parseRowState Main app/Main.hs:(179,1)-(180,34) 880 0 0.2 0.3 26.6 46.2 6 16675384
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 881 181254 0.0 0.0 0.0 0.0 0 0
advanceTo Main app/Main.hs:(163,1)-(170,39) 883 0 17.9 37.4 26.4 45.9 463 2102724536
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 884 18276458 0.0 0.0 0.0 0.0 0 0
tsvSep Main app/Main.hs:176:1-33 886 8934783 0.1 0.0 0.1 0.0 2 0
stateInput Text.Megaparsec.State Text/Megaparsec/State.hs:39:5-14 885 2175048 0.0 0.0 0.0 0.0 0 0
stateOffset Text.Megaparsec.State Text/Megaparsec/State.hs:43:5-15 887 1087524 0.0 0.0 0.0 0.0 0 0
unShareInput Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:186:36-47 889 1087524 0.0 0.0 0.0 0.0 0 0
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 888 938010 0.6 0.0 0.6 0.0 16 0
col Main app/Main.hs:224:3-23 903 0 0.0 0.0 7.7 8.5 0 0
withCol Main app/Main.hs:(205,1)-(212,19) 904 0 7.7 8.5 7.7 8.5 200 477492032
unParser Text.Megaparsec.Internal Text/Megaparsec/Internal.hs:126:5-12 905 5709486 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:255:3-36 1104 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:252:3-30 1036 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 1005 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:258:3-38 941 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:221:3-23 1079 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:249:3-25 967 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 951 0 0.0 0.0 0.0 0.0 0 0
col Main app/Main.hs:(215,3)-(218,15) 925 0 0.0 0.0 0.0 0.0 0 0
region Text.Megaparsec Text/Megaparsec.hs:(388,1)-(397,23) 1156 0 0.0 0.0 0.0 0.0 0 0
decimal Text.Megaparsec.Char.Lexer Text/Megaparsec/Char/Lexer.hs:365:1-32 1157 0 0.0 0.0 0.0 0.0 0 0
stateParseErrors Text.Megaparsec.State Text/Megaparsec/State.hs:52:5-20 1158 1 0.0 0.0 0.0 0.0 0 0
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}
module Main where
import Prelude hiding (readFile, lines, any, drop)
import qualified Prelude as P
import System.IO (stderr)
import System.Exit (exitFailure)
import Text.Megaparsec hiding (State, token, tokens)
import qualified Text.Megaparsec as M (State)
import Text.Megaparsec.Char
import Data.Text (Text, drop, findIndex)
import Data.Text.IO (hPutStrLn, readFile)
import qualified Data.Text as T (unpack, null)
import qualified Data.Text.Read as R (decimal)
import Control.Monad.State (State, evalState, modify, MonadState (get, put))
import Data.Void
import Data.Map (Map)
import qualified Data.Set as S (insert)
import qualified Data.Map as M (fromList, lookup)
import System.Environment (getArgs)
import Data.Int
import GHC.Generics (Generic)
import Data.Time (Day, LocalTime (LocalTime), fromGregorian, TimeOfDay (TimeOfDay))
import Database.PostgreSQL.Simple (ToRow)
import Database.PostgreSQL.Simple.Types (PGArray(..))
import Database.PostgreSQL.Simple.ToField (ToField(..))
import Text.Megaparsec.Char.Lexer (decimal)
import Control.Monad (void)
data Company = Company
{ compcik :: Int32,
name :: Text,
formerName :: Maybe Text,
nameChanged :: Maybe Day,
sics :: PGArray Int16,
eins :: PGArray Text
}
deriving (Generic, ToRow, Show)
data AddressType = Incorporated | Business | Mail deriving (Enum, Show)
instance ToField AddressType where
toField Incorporated = toField @Text "incorp"
toField Business = toField @Text "business"
toField Mail = toField @Text "mail"
data Address = Address
{ addrcik :: Int32,
type_ :: AddressType,
phone :: Maybe Text,
countryCode :: Maybe Text,
stateCode :: Maybe Text,
city :: Maybe Text,
zip :: Maybe Text,
address1 :: Maybe Text,
address2 :: Maybe Text
}
deriving (Generic, ToRow, Show)
data Submission = Submission
{ subcik :: Int32,
accn :: Text,
form :: Text,
fp :: Maybe Text,
period :: Maybe Day,
filed :: Day,
accepted :: LocalTime,
fy :: Maybe Int16,
fyEnd :: Maybe Text,
afs :: Maybe Text,
wksi :: Bool,
amended :: Bool,
detail :: Bool,
file :: Text,
aciks :: PGArray Int32
}
deriving (Generic, ToRow, Show)
usage :: IO ()
usage = do
hPutStrLn stderr "usage: tallow <path>"
exitFailure
data ParserState = ParserState {
header :: Map Text Int
, row :: [M.State Text Void]
} deriving (Show)
type TsvParser = ParsecT Void Text (State ParserState)
advanceTo :: (Char -> Bool) -> TsvParser ()
advanceTo f = do
s <- getInput
case findIndex f s of
Just i -> updateParserState (\st -> st {
stateInput = drop i (stateInput st),
stateOffset = stateOffset st + i
})
Nothing -> fail "could not advance"
field :: TsvParser Text
field = takeWhileP Nothing (not . tsvSep)
tsvSep :: Char -> Bool
tsvSep c = c == '\n' || c == '\t'
parseRowState :: TsvParser [M.State Text Void]
parseRowState = (:) <$> (getParserState <* advance) <*> manyTill (tab *> getParserState <* advance) newline
where advance = advanceTo tsvSep
parseRowStates :: TsvParser ()
parseRowStates = do
meof <- optional eof
case meof of
Just _ -> pure ()
_ -> do
void parseRowState
parseRowStates
parseRow :: TsvParser [Text]
parseRow = (:) <$> field <*> manyTill (tab *> field) newline
parseHeader :: TsvParser ()
parseHeader = do
hs <- parseRow
modify $ \ps -> ps { header = M.fromList $ P.zip hs [0..] }
withRow :: TsvParser a -> TsvParser a
withRow p = do
ParserState h _ <- get
r <- parseRowState
st <- getParserState
if length r /= length h
then fail $ "error: row length does not match header length. row:\n" <> show r
else do
put $ ParserState h r
p <* setParserState st
class FromCol a where
col :: Text -> TsvParser a
withCol :: FromCol a => TsvParser a -> Text -> TsvParser a
withCol p s = do
ParserState h r <- get
case M.lookup s h of
Just i -> setParserState (r !! i) *> region reportCol p
Nothing -> fail $ "error: column \"" <> show s <> "\" not found"
where
reportCol (FancyError o errs) = FancyError o $ S.insert (ErrorFail $ "column: " <> T.unpack s) errs
reportCol x = x
instance FromCol Text where
col = withCol $ do
t <- field
if T.null t then fail "error: unexpected empty field"
else pure t
instance FromCol Int16 where
col = withCol decimal
instance FromCol Int32 where
col = withCol decimal
parseN :: Integral a => Int -> TsvParser a
parseN n = do
t <- takeP Nothing n
case R.decimal t of
Right (!i, "") -> pure i
Right (_, _) -> fail "unexpected characters for number field"
Left e -> fail (e <> ": " <> T.unpack t)
parseDate :: TsvParser Day
parseDate = try $ fromGregorian <$> (parseN 4 <* dash) <*> (parseN 2 <* dash) <*> parseN 2
where dash = optional $ char '-'
parseTimestamp :: TsvParser LocalTime
parseTimestamp = try $ do
day <- parseDate
void $ char ' '
time <- TimeOfDay <$> (two <* semi) <*> (two <* semi) <*> (fromIntegral <$> two)
pure $ LocalTime day time
where
two = parseN 2
semi = char ':'
instance FromCol Day where
col = withCol parseDate
instance FromCol LocalTime where
col = withCol parseTimestamp
instance FromCol Bool where
col = withCol $ (== "1") <$> field
instance FromCol a => FromCol (Maybe a) where
col t = withCol (optional $ col t) t
parseSubmission :: TsvParser (Company, Address, Address, Address, Submission)
parseSubmission = withRow $ do
let cik_ = col "cik"
company <- Company <$> cik_ <*> col "name" <*> col "former" <*> col "changed" <*> pure (PGArray []) <*> pure (PGArray [])
busAddr <- Address <$> cik_ <*> pure Business <*> col "baph" <*> col "countryba" <*> col "stprba" <*> col "cityba" <*> col "zipba" <*> col "bas1" <*> col "bas2"
mailAddr <- Address <$> cik_ <*> pure Mail <*> pure mempty <*> col "countryma" <*> col "stprma" <*> col "cityma" <*> col "zipma" <*> col "mas1" <*> col "mas2"
incAddr <- Address <$> cik_ <*> pure Incorporated <*> pure mempty <*> col "countryinc" <*> col "stprinc" <*> pure mempty <*> pure mempty <*> pure mempty <*> pure mempty
submission <- Submission
<$> cik_ <*> col "adsh" <*> col "form" <*> col "fp" <*> col "period" <*> col "filed" <*> col "accepted" <*>
col "fy" <*> col "fye" <*> col "afs" <*> col "wksi" <*> col "prevrpt" <*> col "detail" <*> col "instance" <*> pure (PGArray [])
pure (company, busAddr, mailAddr, incAddr, submission)
parseSubmissions :: TsvParser ([Company], [Address], [Submission])
parseSubmissions = do
meof <- optional eof
case meof of
Just _ -> pure ([], [], [])
_ -> do
(company, busAddr, mailAddr, incAddr, submission) <- parseSubmission
(companies, addresses, submissions) <- parseSubmissions
pure (company : companies, busAddr : mailAddr : incAddr : addresses, submission : submissions)
main :: IO ()
main = do
args <- getArgs
if null args then usage else do
let path = head args
contents <- readFile path
-- let result = evalState (runParserT (parseHeader *> parseSubmissions) path contents) (ParserState mempty mempty)
-- case result of
-- Right (companies, addresses, submissions) -> print ("companies: " <> show (length companies) <> ", addresses: " <> show (length addresses) <> ", submissions: " <> show (length submissions))
-- Left err -> putStrLn $ errorBundlePretty err
let result = evalState (runParserT parseRowStates path contents) (ParserState mempty mempty)
case result of
Right () -> putStrLn "it worked!"
Left err -> putStrLn $ errorBundlePretty err
Sun Aug 20 20:44 2023 Time and Allocation Profiling Report (Final)
tallow +RTS -pa -L120 -hd -RTS data/2023q2/sub.txt
total time = 0.50 secs (500 ticks @ 1000 us, 1 processor)
total alloc = 2,126,388,384 bytes (excludes profiling overheads)
COST CENTRE MODULE SRC %time %alloc ticks bytes
advanceTo Main app/Main.hs:(95,1)-(102,39) 84.0 97.8 420 2078866176
measureOff Data.Text src/Data/Text.hs:(1408,1)-(1410,70) 3.4 0.0 17 0
readTextDevice Data.Text.Internal.IO src/Data/Text/Internal/IO.hs:133:39-64 3.2 0.1 16 1824120
GC GC <built-in> 2.8 0.0 14 1096
readChunk Data.Text.Internal.IO src/Data/Text/Internal/IO.hs:(156,1)-(163,10) 2.6 0.5 13 10191696
tsvSep Main app/Main.hs:108:1-33 1.8 0.0 9 0
OVERHEAD_of PROFILING <built-in> 0.8 0.0 4 35640
run Data.Text.Array src/Data/Text/Array.hs:181:1-34 0.4 0.4 2 8935040
parseRowState Main app/Main.hs:(111,1)-(112,34) 0.4 0.8 2 16675952
SYSTEM SYSTEM <built-in> 0.2 0.0 1 165744
concat Data.Text src/Data/Text.hs:(1137,1)-(1148,36) 0.2 0.0 1 698128
parseRowStates Main app/Main.hs:(115,1)-(121,20) 0.2 0.4 1 7975472
IDLE IDLE <built-in> 0.0 0.0 0 0
PINNED SYSTEM <built-in> 0.0 0.0 0 0
DONT_CARE MAIN <built-in> 0.0 0.0 0 0
MAIN MAIN <built-in> 0.0 0.0 0 728
CAF GHC.Types <entire-module> 0.0 0.0 0 0
CAF GHC.Tuple <entire-module> 0.0 0.0 0 0
CAF GHC.Prim.Exception <entire-module> 0.0 0.0 0 0
CAF GHC.Prim.Panic <entire-module> 0.0 0.0 0 0
CAF GHC.Classes <entire-module> 0.0 0.0 0 0
CAF GHC.CString <entire-module> 0.0 0.0 0 0
CAF GHC.Num.WordArray <entire-module> 0.0 0.0 0 0
CAF GHC.Num.Primitives <entire-module> 0.0 0.0 0 0
advanceTo :: (Char -> Bool) -> TsvParser ()
advanceTo f = updateParserState (\st ->
let ip = stateInput st
rest = dropWhile (not . f) ip
-- o = stateOffset st
-- d = T.length ip - T.length rest
in st {
stateInput = rest
-- stateOffset = o + d
})
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment