Skip to content

Instantly share code, notes, and snippets.

@adept
Last active November 28, 2017 00:04
Show Gist options
  • Save adept/ec929fe714a7dd7c307bf8e8f8472aba to your computer and use it in GitHub Desktop.
Save adept/ec929fe714a7dd7c307bf8e8f8472aba to your computer and use it in GitHub Desktop.
Data.Decimal is slow in common cases
{-# LANGUAGE DeriveDataTypeable #-}
-- | Decimal numbers are represented as @m*10^(-e)@ where
-- @m@ and @e@ are integers. The exponent @e@ is an unsigned Word8. Hence
-- the smallest value that can be represented is @10^-255@.
--
-- Unary arithmetic results have the exponent of the argument.
-- Addition and subtraction results have an exponent equal to the
-- maximum of the exponents of the arguments. Other operators have
-- exponents sufficient to show the exact result, up to a limit of
-- 255:
--
-- > 0.15 * 0.15 :: Decimal = 0.0225
-- > (1/3) :: Decimal = 0.33333333333333...
-- > decimalPlaces (1/3) = 255
--
-- While @(/)@ is defined, you don't normally want to use it. Instead
-- The functions "divide" and "allocate" will split a decimal amount
-- into lists of results which are guaranteed to sum to the original
-- number. This is a useful property when doing financial arithmetic.
--
-- The arithmetic on mantissas is always done using @Integer@, regardless of
-- the type of @DecimalRaw@ being manipulated. In practice it is strongly
-- recommended that @Decimal@ be used, with other types being used only where
-- necessary (e.g. to conform to a network protocol). For instance
-- @(1/3) :: DecimalRaw Int@ does not give the right answer.
module Data.Decimal (
-- ** Decimal Values
DecimalRaw (..),
Decimal,
realFracToDecimal,
decimalConvert,
unsafeDecimalConvert,
roundTo,
(*.),
divide,
allocate,
eitherFromRational,
normalizeDecimal
) where
import Control.DeepSeq
import Data.Char
import Data.Ratio
import Data.Word
import Data.Typeable
import Text.ParserCombinators.ReadP
-- | Raw decimal arithmetic type constructor. A decimal value consists of an
-- integer mantissa and a negative exponent which is interpreted as the number
-- of decimal places. The value stored in a @Decimal d@ is therefore equal to:
--
-- > decimalMantissa d / (10 ^ decimalPlaces d)
--
-- The "Show" instance will add trailing zeros, so @show $ Decimal 3 1500@
-- will return \"1.500\". Conversely the "Read" instance will use the decimal
-- places to determine the precision.
--
-- Regardless of the type of the arguments, all mantissa arithmetic is done
-- using @Integer@ types, so application developers do not need to worry about
-- overflow in the internal algorithms. However the result of each operator
-- will be converted to the mantissa type without checking for overflow.
data DecimalRaw i = Decimal {
decimalPlaces :: ! Word8,
decimalMantissa :: ! i}
deriving (Typeable)
-- | Arbitrary precision decimal type. Programs should do decimal
-- arithmetic with this type and only convert to other instances of
-- "DecimalRaw" where required by an external interface.
--
-- Using this type is also faster because it avoids repeated conversions
-- to and from @Integer@.
type Decimal = DecimalRaw Integer
instance (NFData i) => NFData (DecimalRaw i) where
rnf (Decimal _ i) = rnf i
instance (Integral i) => Enum (DecimalRaw i) where
succ x = x + 1
pred x = x - 1
toEnum = fromIntegral
fromEnum = fromIntegral . decimalMantissa . roundTo 0
enumFrom = iterate (+1)
enumFromThen x1 x2 = let dx = x2 - x1 in iterate (+dx) x1
enumFromTo x1 x2 = takeWhile (<= x2) $ iterate (+1) x1
enumFromThenTo x1 x2 x3 = takeWhile (<= x3) $ enumFromThen x1 x2
-- | Convert a real fractional value into a Decimal of the appropriate
-- precision.
realFracToDecimal :: (Integral i, RealFrac r) => Word8 -> r -> DecimalRaw i
realFracToDecimal e r = Decimal e $ round (r * (10^e))
-- Internal function to divide and return the nearest integer. Rounds 0.5 away from zero.
divRound :: (Integral a) => a -> a -> a
divRound n1 n2 = if abs r * 2 >= abs n2 then n + signum n1 else n
where (n, r) = n1 `quotRem` n2
-- | Convert a @DecimalRaw@ from one base representation to another. Does
-- not check for overflow in the new representation. Only use after
-- using "roundTo" to put an upper value on the exponent, or to convert
-- to a larger representation.
unsafeDecimalConvert :: (Integral a, Integral b) => DecimalRaw a -> DecimalRaw b
unsafeDecimalConvert (Decimal e n) = Decimal e $ fromIntegral n
-- | Convert a @DecimalRaw@ from one base to another. Returns @Nothing@ if
-- this would cause arithmetic overflow.
decimalConvert :: (Integral a, Integral b, Bounded b) =>
DecimalRaw a -> Maybe (DecimalRaw b)
decimalConvert (Decimal e n) =
let n1 :: Integer
n1 = fromIntegral n
n2 = fromIntegral n -- Of type b.
ub = fromIntegral $ max maxBound n2 -- Can't say "maxBound :: b", so do this instead.
lb = fromIntegral $ min minBound n2
in if lb <= n1 && n1 <= ub then Just $ Decimal e n2 else Nothing
-- | Round a @DecimalRaw@ to a specified number of decimal places.
-- If the value ends in @5@ then it is rounded away from zero.
roundTo :: (Integral i) => Word8 -> DecimalRaw i -> DecimalRaw i
roundTo d (Decimal _ 0) = Decimal d 0
roundTo d (Decimal e n) = Decimal d $ fromIntegral n1
where
n1 = case compare d e of
LT -> n `divRound` divisor
EQ -> n
GT -> n * multiplier
divisor = 10 ^ (e-d)
multiplier = 10 ^ (d-e)
-- Round the two DecimalRaw values to the largest exponent.
roundMax :: (Integral i) => DecimalRaw i -> DecimalRaw i -> (Word8, i, i)
roundMax (Decimal _ 0) (Decimal _ 0) = (0,0,0)
roundMax (Decimal e1 n1) (Decimal _ 0) = (e1,n1,0)
roundMax (Decimal _ 0) (Decimal e2 n2) = (e2,0,n2)
roundMax d1@(Decimal e1 n1_) d2@(Decimal e2 n2_)
| e1 == e2 = (e1, n1_, n2_)
| otherwise = (e, n1, n2)
where
e = max e1 e2
(Decimal _ n1) = roundTo e d1
(Decimal _ n2) = roundTo e d2
instance (Integral i, Show i) => Show (DecimalRaw i) where
showsPrec _ (Decimal e n)
| e == 0 = ((signStr ++ strN) ++)
| otherwise = (concat [signStr, intPart, ".", fracPart] ++)
where
strN = show $ abs n
signStr = if n < 0 then "-" else ""
len = length strN
padded = replicate (fromIntegral e + 1 - len) '0' ++ strN
(intPart, fracPart) = splitAt (max 1 (len - fromIntegral e)) padded
instance (Integral i, Read i) => Read (DecimalRaw i) where
readsPrec _ = readP_to_S readDecimalP
-- | Parse a Decimal value. Used for the Read instance.
readDecimalP :: (Integral i, Read i) => ReadP (DecimalRaw i)
readDecimalP = do
s1 <- myOpt '+' $ char '-' +++ char '+'
intPart <- munch1 isDigit
fractPart <- myOpt "" $ do
_ <- char '.'
munch1 isDigit
expPart <- myOpt 0 $ do
_ <- char 'e' +++ char 'E'
s2 <- myOpt '+' $ char '-' +++ char '+'
fmap (applySign s2 . strToInt) $ munch1 isDigit
let n = applySign s1 $ strToInt $ intPart ++ fractPart
e = length fractPart - expPart
if e < 0
then return $ Decimal 0 $ n * 10 ^ negate e
else if e < 256
then return $ Decimal (fromIntegral e) n
else pfail
where
strToInt :: (Integral n) => String -> n
strToInt = foldl (\t v -> 10 * t + v) 0 . map (fromIntegral . subtract (ord '0') . ord)
applySign '-' v = negate v
applySign _ v = v
myOpt d p = p <++ return d
instance (Integral i) => Eq (DecimalRaw i) where
d1 == d2 = n1 == n2 where (_, n1, n2) = roundMax d1 d2
instance (Integral i) => Ord (DecimalRaw i) where
compare d1 d2 = compare n1 n2 where (_, n1, n2) = roundMax d1 d2
instance (Integral i) => Num (DecimalRaw i) where
d1 + d2 = Decimal e $ fromIntegral (n1 + n2)
where (e, n1, n2) = roundMax d1 d2
d1 - d2 = Decimal e $ fromIntegral (n1 - n2)
where (e, n1, n2) = roundMax d1 d2
d1 * d2 = normalizeDecimal $ realFracToDecimal maxBound $ toRational d1 * toRational d2
abs (Decimal e n) = Decimal e $ abs n
signum (Decimal _ n) = fromIntegral $ signum n
fromInteger n = Decimal 0 $ fromIntegral n
instance (Integral i) => Real (DecimalRaw i) where
toRational (Decimal e n) = fromIntegral n % (10 ^ e)
instance (Integral i) => Fractional (DecimalRaw i) where
fromRational r =
let
v :: Decimal
v = normalizeDecimal $ realFracToDecimal maxBound r
in unsafeDecimalConvert v
a / b = fromRational $ toRational a / toRational b
instance (Integral i) => RealFrac (DecimalRaw i) where
properFraction a = (rnd, fromRational rep)
where
(rnd, rep) = properFraction $ toRational a
-- | Divide a @DecimalRaw@ value into one or more portions. The portions
-- will be approximately equal, and the sum of the portions is guaranteed to
-- be the original value.
--
-- The portions are represented as a list of pairs. The first part of each
-- pair is the number of portions, and the second part is the portion value.
-- Hence 10 dollars divided 3 ways will produce @[(2, 3.33), (1, 3.34)]@.
divide :: Decimal -> Int -> [(Int, Decimal)]
divide (Decimal e n) d
| d > 0 =
case n `divMod` fromIntegral d of
(result, 0) -> [(d, Decimal e result)]
(result, r) -> [(d - fromIntegral r,
Decimal e result),
(fromIntegral r, Decimal e (result+1))]
| otherwise = error "Data.Decimal.divide: Divisor must be > 0."
-- | Allocate a @DecimalRaw@ value proportionately with the values in a list.
-- The allocated portions are guaranteed to add up to the original value.
--
-- Some of the allocations may be zero or negative, but the sum of the list
-- must not be zero. The allocation is intended to be as close as possible
-- to the following:
--
-- > let result = allocate d parts
-- > in all (== d / sum parts) $ zipWith (/) result parts
allocate :: Decimal -> [Integer] -> [Decimal]
allocate (Decimal e n) ps
| total == 0 =
error "Data.Decimal.allocate: allocation list must not sum to zero."
| otherwise = map (Decimal e) $ zipWith (-) ts (tail ts)
where
ts = map fst $ scanl nxt (n, total) ps
nxt (n1, t1) p1 = (n1 - (n1 * p1) `zdiv` t1, t1 - p1)
zdiv 0 0 = 0
zdiv x y = x `divRound` y
total = sum ps
-- | Multiply a @DecimalRaw@ by a @RealFrac@ value.
(*.) :: (Integral i, RealFrac r) => DecimalRaw i -> r -> DecimalRaw i
(Decimal e m) *. d = Decimal e $ round $ fromIntegral m * d
-- | Count the divisors, i.e. the count of 2 divisors in 18 is 1 because 18 = 2 * 3 * 3
factorN :: (Integral a)
=> a -- ^ Denominator base
-> a -- ^ dividing value
-> (a, a) -- ^ The count of divisors and the result of division
factorN d val = factorN' val 0
where
factorN' 1 acc = (acc, 1)
factorN' v acc = if md == 0
then factorN' vd (acc + 1)
else (acc, v)
where
(vd, md) = v `divMod` d
-- | Try to convert Rational to Decimal with absolute precision
-- return string with fail description if not converted
eitherFromRational :: (Integral i) => Rational -> Either String (DecimalRaw i)
eitherFromRational r = if done == 1
then do
wres <- we
return $ Decimal wres (fromIntegral m)
else Left $ show r ++ " has no decimal denominator"
where
den = denominator r
num = numerator r
(f2, rest) = factorN 2 den
(f5, done) = factorN 5 rest
e = max f2 f5
m = num * ((10^e) `div` den)
we = if e > fromIntegral (maxBound :: Word8)
then Left $ show e ++ " is too big ten power to represent as Decimal"
else Right $ fromIntegral e
-- | Reduce the exponent of the decimal number to the minimal possible value
normalizeDecimal :: (Integral i) => DecimalRaw i -> DecimalRaw i
normalizeDecimal r = case eitherFromRational $ toRational r of
Right x -> x
Left e -> error $ "Impossible happened: " ++ e
This file has been truncated, but you can view the full file.
Mon Nov 27 23:59 2017 Time and Allocation Profiling Report (Final)
hledgerprof +RTS -p -RTS balance
total time = 12.87 secs (12868 ticks @ 1000 us, 1 processor)
total alloc = 9,178,410,648 bytes (excludes profiling overheads)
COST CENTRE MODULE SRC %time %alloc
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 4.8 4.6
try Text.Megaparsec Text/Megaparsec.hs:1127:3-49 4.0 3.3
compareText.go Data.Text Data/Text.hs:(416,5)-(422,33) 3.9 0.0
compare Text.Megaparsec.Pos Text/Megaparsec/Pos.hs:127:31-33 3.6 0.4
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 3.6 2.7
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 3.3 7.4
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 3.3 4.3
roundMax Data.Decimal Data/Decimal.hs:(143,1)-(152,35) 3.2 3.3
return Text.Megaparsec Text/Megaparsec.hs:352:3-15 3.1 1.5
datep.maybedate Hledger.Read.Common Hledger/Read/Common.hs:245:7-63 2.6 2.4
take1_ Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:231:3-19 2.3 7.9
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 2.1 2.5
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 2.1 1.2
descriptionp Hledger.Read.Common Hledger/Read/Common.hs:219:1-46 1.8 3.4
normaliseHelper.(...) Hledger.Data.Amount Hledger/Data/Amount.hs:(403,5)-(407,26) 1.8 4.2
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 1.7 1.1
postingp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(563,1)-(586,4) 1.5 1.3
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 1.1 1.4
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 1.1 0.8
advance1 Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:229:3-34 1.1 0.9
accountnamep Hledger.Read.Common Hledger/Read/Common.hs:(328,1)-(340,65) 0.8 1.4
showAmountHelper Hledger.Data.Amount Hledger/Data/Amount.hs:(278,1)-(289,25) 0.6 1.1
sumSimilarAmountsUsingFirstPrice Hledger.Data.Amount Hledger/Data/Amount.hs:(451,1)-(452,77) 0.4 1.0
compareText Data.Text Data/Text.hs:(412,1)-(422,33) 0.4 2.7
compareText.go.(...) Data.Text Data/Text.hs:422:13-33 0.4 2.6
compareText.go.(...) Data.Text Data/Text.hs:421:13-33 0.4 2.6
similarAmountsOp Hledger.Data.Amount Hledger/Data/Amount.hs:(179,1)-(182,80) 0.3 1.2
individual inherited
COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc
MAIN MAIN <built-in> 11990 0 0.0 0.0 100.0 100.0
CAF System.Console.Terminfo.Base <entire-module> 13471 0 0.0 0.0 0.0 0.0
CAF GHC.Conc.Signal <entire-module> 12095 0 0.0 0.0 0.0 0.0
CAF GHC.IO.Encoding <entire-module> 12077 0 0.0 0.0 0.0 0.0
CAF GHC.IO.Encoding.Iconv <entire-module> 12075 0 0.0 0.0 0.0 0.0
CAF GHC.IO.Exception <entire-module> 12069 0 0.0 0.0 0.0 0.0
CAF GHC.IO.FD <entire-module> 12068 0 0.0 0.0 0.0 0.0
CAF GHC.IO.Handle.FD <entire-module> 12066 0 0.0 0.0 0.0 0.0
CAF GHC.IO.Handle.Internals <entire-module> 12065 0 0.0 0.0 0.0 0.0
CAF Text.Printf <entire-module> 12025 0 0.0 0.0 0.0 0.0
CAF Text.Read.Lex <entire-module> 12023 0 0.0 0.0 0.0 0.0
CAF GHC.Event.Thread <entire-module> 12017 0 0.0 0.0 0.0 0.0
CAF GHC.Event.Poll <entire-module> 12006 0 0.0 0.0 0.0 0.0
CAF:$fAlternativeParsecT1 Text.Megaparsec <no location info> 15770 0 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 24286 1 0.0 0.0 0.0 0.0
CAF:$fAlternativeParsecT2 Text.Parsec.Prim <no location info> 13225 0 0.0 0.0 0.0 0.0
pure Text.Parsec.Prim Text/Parsec/Prim.hs:193:5-17 80423 1 0.0 0.0 0.0 0.0
CAF:$fAlternativeParsecT_$cfmap Text.Megaparsec Text/Megaparsec.hs:316:3-6 15753 0 0.0 0.0 0.0 0.0
fmap Text.Megaparsec Text/Megaparsec.hs:316:3-13 24273 1 0.0 0.0 0.0 0.0
CAF:$fApplicativeId4 Data.Vector.Fusion.Util <no location info> 14640 0 0.0 0.0 0.0 0.0
pure Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:31:3-11 74127 1 0.0 0.0 0.0 0.0
CAF:$fBoundedStatus_$cmaxBound Hledger.Data.Types Hledger/Data/Types.hs:190:20-26 19960 0 0.0 0.0 0.0 0.0
maxBound Hledger.Data.Types Hledger/Data/Types.hs:190:20-26 25110 1 0.0 0.0 0.0 0.0
CAF:$fBoundedStatus_$cminBound Hledger.Data.Types Hledger/Data/Types.hs:190:20-26 19961 0 0.0 0.0 0.0 0.0
minBound Hledger.Data.Types Hledger/Data/Types.hs:190:20-26 25109 1 0.0 0.0 0.0 0.0
CAF:$fEqMixedAmount1 Hledger.Data.Types <no location info> 19991 0 0.0 0.0 0.0 0.0
/= Hledger.Data.Types Hledger/Data/Types.hs:174:48-49 74253 1 0.0 0.0 0.0 0.0
CAF:$fFractionalDecimalRaw11 Data.Decimal <no location info> 16605 0 0.0 0.0 0.0 0.0
fromRational Data.Decimal Data/Decimal.hs:(220,3)-(224,30) 76434 0 0.0 0.0 0.0 0.0
fromRational.v Data.Decimal Data/Decimal.hs:223:9-59 76435 0 0.0 0.0 0.0 0.0
normalizeDecimal Data.Decimal Data/Decimal.hs:(314,1)-(316,48) 76436 0 0.0 0.0 0.0 0.0
toRational Data.Decimal Data/Decimal.hs:217:5-56 76437 0 0.0 0.0 0.0 0.0
CAF:$fHashableText0_$chash Data.Hashable.Class Data/Hashable/Class.hs:622:10-24 15127 0 0.0 0.0 0.0 0.0
hash Data.Hashable.Class Data/Hashable/Class.hs:233:5-35 77349 1 0.0 0.0 0.0 0.0
CAF:$fIsStringText_$cfromString Data.Text Data/Text.hs:354:5-14 13167 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24306 1 0.0 0.0 0.0 0.0
CAF:$fMonadId1 Data.Vector.Fusion.Util <no location info> 14642 0 0.0 0.0 0.0 0.0
return Data.Vector.Fusion.Util Data/Vector/Fusion/Util.hs:35:3-15 74126 1 0.0 0.0 0.0 0.0
CAF:$fMonoidCharMap2 Data.IntMap.CharMap2 <no location info> 16146 0 0.0 0.0 0.0 0.0
mempty Data.IntMap.CharMap2 Data/IntMap/CharMap2.hs:22:3-25 81657 1 0.0 0.0 0.0 0.0
CAF:$fMonoidJournal_$cmempty Hledger.Data.Journal Hledger/Data/Journal.hs:158:3-8 21300 0 0.0 0.0 0.0 0.0
mempty Hledger.Data.Journal Hledger/Data/Journal.hs:158:3-22 32916 1 0.0 0.0 0.0 0.0
CAF:$fMonoidText_$c<> Data.Text Data/Text.hs:341:5-8 13129 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24591 1 0.0 0.0 0.0 0.0
CAF:$fMonoidText_$cmappend Data.Text Data/Text.hs:347:5-11 13130 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24590 1 0.0 0.0 0.0 0.0
CAF:$fNumAmount1 Hledger.Data.Amount <no location info> 21971 0 0.0 0.0 0.0 0.0
negate Hledger.Data.Amount Hledger/Data/Amount.hs:147:5-52 75156 0 0.0 0.0 0.0 0.0
fromInteger Data.Decimal Data/Decimal.hs:214:5-46 75157 1 0.0 0.0 0.0 0.0
CAF:$fNumAmount_$c+ Hledger.Data.Amount Hledger/Data/Amount.hs:148:5-7 21992 0 0.0 0.0 0.0 0.0
+ Hledger.Data.Amount Hledger/Data/Amount.hs:148:5-55 74842 1 0.0 0.0 0.0 0.0
CAF:$fNumAmount_$c- Hledger.Data.Amount Hledger/Data/Amount.hs:149:5-7 21993 0 0.0 0.0 0.0 0.0
- Hledger.Data.Amount Hledger/Data/Amount.hs:149:5-55 77521 1 0.0 0.0 0.0 0.0
CAF:$fNumSize_$c- Data.Text.Internal.Fusion.Size Data/Text/Internal/Fusion/Size.hs:80:5-7 12934 0 0.0 0.0 0.0 0.0
- Data.Text.Internal.Fusion.Size Data/Text/Internal/Fusion/Size.hs:80:5-22 76807 1 0.0 0.0 0.0 0.0
CAF:$fNumSize_$cfromInteger Data.Text.Internal.Fusion.Size Data/Text/Internal/Fusion/Size.hs:83:5-15 12924 0 0.0 0.0 0.0 0.0
fromInteger Data.Text.Internal.Fusion.Size Data/Text/Internal/Fusion/Size.hs:(83,5)-(84,42) 76810 1 0.0 0.0 0.0 0.0
CAF:$fOrdMixedAmount7 Hledger.Data.Types <no location info> 19983 0 0.0 0.0 0.0 0.0
compare Hledger.Data.Types Hledger/Data/Types.hs:174:51-53 78504 1 0.0 0.0 0.0 0.0
CAF:$fOrdPos7 Text.Megaparsec.Pos <no location info> 15454 0 0.0 0.0 0.0 0.0
compare Text.Megaparsec.Pos Text/Megaparsec/Pos.hs:53:23-25 24364 1 0.0 0.0 0.0 0.0
CAF:$fOrdText_$ccompare Data.Text Data/Text.hs:331:5-11 13114 0 0.0 0.0 0.0 0.0
compare Data.Text Data/Text.hs:331:5-25 74313 1 0.0 0.0 0.0 0.0
CAF:$fPrimMonadST1_r3vo Control.Monad.Primitive <no location info> 13859 0 0.0 0.0 0.0 0.0
primitive Control.Monad.Primitive Control/Monad/Primitive.hs:152:3-16 74143 1 0.0 0.0 0.0 0.0
CAF:$fRegexOptionsRegexCompOptionExecOption_$cdefaultCompOpt Text.Regex.TDFA.Common Text/Regex/TDFA/Common.hs:149:3-16 16533 0 0.0 0.0 0.0 0.0
defaultCompOpt Text.Regex.TDFA.Common Text/Regex/TDFA/Common.hs:(149,3)-(154,31) 80808 1 0.0 0.0 0.0 0.0
CAF:$fRegexOptionsRegexCompOptionExecOption_$cdefaultExecOpt Text.Regex.TDFA.Common Text/Regex/TDFA/Common.hs:155:3-16 16534 0 0.0 0.0 0.0 0.0
defaultExecOpt Text.Regex.TDFA.Common Text/Regex/TDFA/Common.hs:155:3-55 81005 1 0.0 0.0 0.0 0.0
CAF:$fStreamText5 Text.Megaparsec.Stream <no location info> 15421 0 0.0 0.0 0.0 0.0
take1_ Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:231:3-19 24257 1 0.0 0.0 0.0 0.0
CAF:accountLeafName Hledger.Data.AccountName Hledger/Data/AccountName.hs:40:1-15 22256 0 0.0 0.0 0.0 0.0
accountLeafName Hledger.Data.AccountName Hledger/Data/AccountName.hs:40:1-46 81170 1 0.0 0.0 0.0 0.0
CAF:accountNameComponents Hledger.Data.AccountName Hledger/Data/AccountName.hs:34:1-21 22255 0 0.0 0.0 0.0 0.0
accountNameComponents Hledger.Data.AccountName Hledger/Data/AccountName.hs:34:1-41 28080 1 0.0 0.0 0.0 0.0
CAF:accountNameFromComponents Hledger.Data.AccountName Hledger/Data/AccountName.hs:37:1-25 22257 0 0.0 0.0 0.0 0.0
accountNameFromComponents Hledger.Data.AccountName Hledger/Data/AccountName.hs:37:1-49 28078 1 0.0 0.0 0.0 0.0
CAF:accountNameWithPostingType1 Hledger.Data.Posting <no location info> 20758 0 0.0 0.0 0.0 0.0
accountNameWithPostingType Hledger.Data.Posting Hledger/Data/Posting.hs:(250,1)-(252,77) 76936 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 76937 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 76938 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 76939 1 0.0 0.0 0.0 0.0
CAF:accountNameWithPostingType10 Hledger.Data.Posting <no location info> 20754 0 0.0 0.0 0.0 0.0
accountNameWithPostingType Hledger.Data.Posting Hledger/Data/Posting.hs:(250,1)-(252,77) 76802 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 76803 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 76804 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 76805 1 0.0 0.0 0.0 0.0
CAF:accountNameWithPostingType11 Hledger.Data.Posting <no location info> 20753 0 0.0 0.0 0.0 0.0
CAF:accountNameWithPostingType2 Hledger.Data.Posting <no location info> 20741 0 0.0 0.0 0.0 0.0
CAF:accountNameWithPostingType4 Hledger.Data.Posting <no location info> 20757 0 0.0 0.0 0.0 0.0
accountNameWithPostingType Hledger.Data.Posting Hledger/Data/Posting.hs:(250,1)-(252,77) 76932 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 76933 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 76934 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 76935 1 0.0 0.0 0.0 0.0
CAF:accountNameWithPostingType5 Hledger.Data.Posting <no location info> 20756 0 0.0 0.0 0.0 0.0
CAF:accountNameWithPostingType7 Hledger.Data.Posting <no location info> 20755 0 0.0 0.0 0.0 0.0
accountNameWithPostingType Hledger.Data.Posting Hledger/Data/Posting.hs:(250,1)-(252,77) 76813 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 76814 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 76815 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 76816 1 0.0 0.0 0.0 0.0
CAF:accountNameWithPostingType8 Hledger.Data.Posting <no location info> 20738 0 0.0 0.0 0.0 0.0
CAF:accountdirectivep_r71nj Hledger.Read.JournalReader <no location info> 17744 0 0.0 0.0 0.0 0.0
accountdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(233,1)-(239,51) 25365 1 0.0 0.0 0.0 0.0
CAF:accountnamep1 Hledger.Read.Common <no location info> 18612 0 0.0 0.0 0.0 0.0
accountnamep Hledger.Read.Common Hledger/Read/Common.hs:(328,1)-(340,65) 27975 1 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 27976 1 0.0 0.0 0.0 0.0
CAF:accountnamep11 Hledger.Read.Common <no location info> 18605 0 0.0 0.0 0.0 0.0
accountnamep Hledger.Read.Common Hledger/Read/Common.hs:(328,1)-(340,65) 28015 0 0.0 0.0 0.0 0.0
accountnamep.singlespace Hledger.Read.Common Hledger/Read/Common.hs:338:7-92 28016 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 28017 1 0.0 0.0 0.0 0.0
CAF:accountnamep12 Hledger.Read.Common <no location info> 18604 0 0.0 0.0 0.0 0.0
accountnamep Hledger.Read.Common Hledger/Read/Common.hs:(328,1)-(340,65) 28024 0 0.0 0.0 0.0 0.0
accountnamep.singlespace Hledger.Read.Common Hledger/Read/Common.hs:338:7-92 28025 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 28026 1 0.0 0.0 0.0 0.0
CAF:accountnamep13 Hledger.Read.Common <no location info> 18603 0 0.0 0.0 0.0 0.0
return Text.Megaparsec Text/Megaparsec.hs:352:3-15 28032 1 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 28033 1 0.0 0.0 0.0 0.0
CAF:accountnamep15 Hledger.Read.Common <no location info> 18400 0 0.0 0.0 0.0 0.0
accountnamep Hledger.Read.Common Hledger/Read/Common.hs:(328,1)-(340,65) 28027 0 0.0 0.0 0.0 0.0
accountnamep.singlespace Hledger.Read.Common Hledger/Read/Common.hs:338:7-92 28028 0 0.0 0.0 0.0 0.0
notFollowedBy Text.Megaparsec Text/Megaparsec.hs:870:3-36 28029 1 0.0 0.0 0.0 0.0
CAF:accountnamep16 Hledger.Read.Common <no location info> 18399 0 0.0 0.0 0.0 0.0
accountnamep Hledger.Read.Common Hledger/Read/Common.hs:(328,1)-(340,65) 28018 0 0.0 0.0 0.0 0.0
accountnamep.singlespace Hledger.Read.Common Hledger/Read/Common.hs:338:7-92 28019 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 28020 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 28021 1 0.0 0.0 0.0 0.0
CAF:accountnamep4 Hledger.Read.Common <no location info> 18610 0 0.0 0.0 0.0 0.0
accountnamep Hledger.Read.Common Hledger/Read/Common.hs:(328,1)-(340,65) 27979 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 27980 1 0.0 0.0 0.0 0.0
CAF:accountnamep6 Hledger.Read.Common <no location info> 18609 0 0.0 0.0 0.0 0.0
accountnamep Hledger.Read.Common Hledger/Read/Common.hs:(328,1)-(340,65) 27989 0 0.0 0.0 0.0 0.0
CAF:accountnamep7 Hledger.Read.Common <no location info> 18608 0 0.0 0.0 0.0 0.0
accountnamep Hledger.Read.Common Hledger/Read/Common.hs:(328,1)-(340,65) 27990 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 27993 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 27991 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 27992 1 0.0 0.0 0.0 0.0
CAF:accountnamep8 Hledger.Read.Common <no location info> 18607 0 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 27997 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 27998 1 0.0 0.0 0.0 0.0
CAF:accountnamep9 Hledger.Read.Common <no location info> 18606 0 0.0 0.0 0.0 0.0
accountnamep Hledger.Read.Common Hledger/Read/Common.hs:(328,1)-(340,65) 28010 0 0.0 0.0 0.0 0.0
accountnamep.singlespace Hledger.Read.Common Hledger/Read/Common.hs:338:7-92 28011 1 0.0 0.0 0.0 0.0
try Text.Megaparsec Text/Megaparsec.hs:868:3-26 28012 1 0.0 0.0 0.0 0.0
CAF:accountsFromPostings10 Hledger.Data.Account <no location info> 22315 0 0.0 0.0 0.0 0.0
accountsFromPostings Hledger.Data.Account Hledger/Data/Account.hs:(64,1)-(78,18) 78624 0 0.0 0.0 0.0 0.0
accountsFromPostings.summed Hledger.Data.Account Hledger/Data/Account.hs:69:5-79 78625 0 0.0 0.0 0.0 0.0
accountsFromPostings.summed.\ Hledger.Data.Account Hledger/Data/Account.hs:69:40-70 78626 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 78627 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 78628 0 0.0 0.0 0.0 0.0
fromInteger Data.Decimal Data/Decimal.hs:214:5-46 78651 1 0.0 0.0 0.0 0.0
CAF:accountsFromPostings6 Hledger.Data.Account <no location info> 22320 0 0.0 0.0 0.0 0.0
accountsFromPostings Hledger.Data.Account Hledger/Data/Account.hs:(64,1)-(78,18) 78416 0 0.0 0.0 0.0 0.0
accountsFromPostings.nametree Hledger.Data.Account Hledger/Data/Account.hs:70:5-67 78417 0 0.0 0.0 0.0 0.0
treeFromPaths Hledger.Utils.Tree Hledger/Utils/Tree.hs:85:1-62 78418 1 0.0 0.0 0.0 0.0
CAF:accountsFromPostings8 Hledger.Data.Account <no location info> 22317 0 0.0 0.0 0.0 0.0
accountsFromPostings Hledger.Data.Account Hledger/Data/Account.hs:(64,1)-(78,18) 78611 0 0.0 0.0 0.0 0.0
accountsFromPostings.summed Hledger.Data.Account Hledger/Data/Account.hs:69:5-79 78612 0 0.0 0.0 0.0 0.0
accountsFromPostings.summed.\ Hledger.Data.Account Hledger/Data/Account.hs:69:40-70 78613 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 78614 1 0.0 0.0 0.0 0.0
CAF:accountsFromPostings9 Hledger.Data.Account <no location info> 22316 0 0.0 0.0 0.0 0.0
accountsFromPostings Hledger.Data.Account Hledger/Data/Account.hs:(64,1)-(78,18) 78619 0 0.0 0.0 0.0 0.0
accountsFromPostings.summed Hledger.Data.Account Hledger/Data/Account.hs:69:5-79 78620 0 0.0 0.0 0.0 0.0
accountsFromPostings.summed.\ Hledger.Data.Account Hledger/Data/Account.hs:69:40-70 78621 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 78622 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 78623 1 0.0 0.0 0.0 0.0
CAF:accountsmode Hledger.Cli.Commands.Accounts Hledger/Cli/Commands/Accounts.hs:35:1-12 23184 0 0.0 0.0 0.0 0.0
accountsmode Hledger.Cli.Commands.Accounts Hledger/Cli/Commands/Accounts.hs:(35,1)-(50,23) 24104 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24105 1 0.0 0.0 0.0 0.0
CAF:accountsmode36 Hledger.Cli.Commands.Accounts <no location info> 23164 0 0.0 0.0 0.0 0.0
CAF:accountsmode43 Hledger.Cli.Commands.Accounts <no location info> 23166 0 0.0 0.0 0.0 0.0
CAF:accountsmode_aliases Hledger.Cli.Commands.Accounts Hledger/Cli/Commands/Accounts.hs:50:9-15 23165 0 0.0 0.0 0.0 0.0
accountsmode Hledger.Cli.Commands.Accounts Hledger/Cli/Commands/Accounts.hs:(35,1)-(50,23) 24106 0 0.0 0.0 0.0 0.0
accountsmode.aliases Hledger.Cli.Commands.Accounts Hledger/Cli/Commands/Accounts.hs:50:9-23 24107 1 0.0 0.0 0.0 0.0
CAF:acctsep Hledger.Data.AccountName Hledger/Data/AccountName.hs:28:1-7 22254 0 0.0 0.0 0.0 0.0
acctsep Hledger.Data.AccountName Hledger/Data/AccountName.hs:28:1-30 28082 1 0.0 0.0 0.0 0.0
singleton_ Data.Text.Show Data/Text/Show.hs:(81,1)-(88,18) 28084 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 28088 1 0.0 0.0 0.0 0.0
singleton_.x Data.Text.Show Data/Text/Show.hs:(83,9)-(85,25) 28089 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 28090 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 28091 1 0.0 0.0 0.0 0.0
singleton_.d Data.Text.Show Data/Text/Show.hs:88:9-18 28085 1 0.0 0.0 0.0 0.0
singleton_.len Data.Text.Show Data/Text/Show.hs:(86,9)-(87,31) 28086 1 0.0 0.0 0.0 0.0
singleton_.x Data.Text.Show Data/Text/Show.hs:(83,9)-(85,25) 28087 1 0.0 0.0 0.0 0.0
CAF:acctsepchar Hledger.Data.AccountName Hledger/Data/AccountName.hs:25:1-11 22253 0 0.0 0.0 0.0 0.0
acctsepchar Hledger.Data.AccountName Hledger/Data/AccountName.hs:25:1-17 28083 1 0.0 0.0 0.0 0.0
CAF:activitymode Hledger.Cli.Commands.Activity Hledger/Cli/Commands/Activity.hs:22:1-12 23161 0 0.0 0.0 0.0 0.0
activitymode Hledger.Cli.Commands.Activity Hledger/Cli/Commands/Activity.hs:(22,1)-(31,20) 24108 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24109 1 0.0 0.0 0.0 0.0
CAF:activitymode9 Hledger.Cli.Commands.Activity <no location info> 23157 0 0.0 0.0 0.0 0.0
CAF:activitymode_aliases Hledger.Cli.Commands.Activity Hledger/Cli/Commands/Activity.hs:31:9-15 23156 0 0.0 0.0 0.0 0.0
activitymode Hledger.Cli.Commands.Activity Hledger/Cli/Commands/Activity.hs:(22,1)-(31,20) 24110 0 0.0 0.0 0.0 0.0
activitymode.aliases Hledger.Cli.Commands.Activity Hledger/Cli/Commands/Activity.hs:31:9-20 24111 1 0.0 0.0 0.0 0.0
CAF:addmode Hledger.Cli.Commands.Add Hledger/Cli/Commands/Add.hs:48:1-7 23019 0 0.0 0.0 0.0 0.0
addmode Hledger.Cli.Commands.Add Hledger/Cli/Commands/Add.hs:(48,1)-(58,2) 24112 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24113 1 0.0 0.0 0.0 0.0
CAF:addmode23 Hledger.Cli.Commands.Add <no location info> 23010 0 0.0 0.0 0.0 0.0
CAF:addonExtensions Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:689:1-15 23637 0 0.0 0.0 0.0 0.0
addonExtensions Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(689,1)-(701,3) 24331 1 0.0 0.0 0.0 0.0
CAF:aliasdirectivep_r71p7 Hledger.Read.JournalReader <no location info> 17814 0 0.0 0.0 0.0 0.0
aliasdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(321,1)-(325,23) 25302 1 0.0 0.0 0.0 0.0
CAF:aliasesFromOpts Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:489:1-15 23580 0 0.0 0.0 0.0 0.0
aliasesFromOpts Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(489,1)-(490,41) 78484 1 0.0 0.0 0.0 0.0
CAF:amount Hledger.Data.Amount Hledger/Data/Amount.hs:154:1-6 21983 0 0.0 0.0 0.0 0.0
amount Hledger.Data.Amount Hledger/Data/Amount.hs:154:1-98 74267 1 0.0 0.0 0.0 0.0
CAF:amount1 Hledger.Data.Amount <no location info> 21962 0 0.0 0.0 0.0 0.0
amount Hledger.Data.Amount Hledger/Data/Amount.hs:154:1-98 74290 0 0.0 0.0 0.0 0.0
fromInteger Data.Decimal Data/Decimal.hs:214:5-46 74291 1 0.0 0.0 0.0 0.0
CAF:amount3 Hledger.Data.Amount <no location info> 21963 0 0.0 0.0 0.0 0.0
amount Hledger.Data.Amount Hledger/Data/Amount.hs:154:1-98 74825 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 74826 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 74827 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 74828 1 0.0 0.0 0.0 0.0
CAF:amountstyle Hledger.Data.Amount Hledger/Data/Amount.hs:129:1-11 21982 0 0.0 0.0 0.0 0.0
amountstyle Hledger.Data.Amount Hledger/Data/Amount.hs:129:1-54 74463 1 0.0 0.0 0.0 0.0
CAF:anonymiseByOpts2 Hledger.Cli.Utils <no location info> 23507 0 0.0 0.0 0.0 0.0
CAF:appendNewOrbit_r5lXS Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:381:3-16 16262 0 0.0 0.0 0.0 0.0
assemble Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(345,1)-(357,71) 81610 0 0.0 0.0 0.0 0.0
assemble.oneInstruction Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(346,3)-(357,71) 81611 0 0.0 0.0 0.0 0.0
enterOrbit Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(378,1)-(388,70) 81612 0 0.0 0.0 0.0 0.0
enterOrbit.appendNewOrbit Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:381:3-70 81613 1 0.0 0.0 0.0 0.0
CAF:applyaccountdirectivep_r71nC Hledger.Read.JournalReader <no location info> 17754 0 0.0 0.0 0.0 0.0
applyaccountdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(308,1)-(313,26) 25387 1 0.0 0.0 0.0 0.0
CAF:assemble_r5iBH Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:345:1-8 16265 0 0.0 0.0 0.0 0.0
assemble Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(345,1)-(357,71) 81361 1 0.0 0.0 0.0 0.0
CAF:assignmentPostings Hledger.Data.Transaction Hledger/Data/Transaction.hs:334:1-18 20221 0 0.0 0.0 0.0 0.0
assignmentPostings Hledger.Data.Transaction Hledger/Data/Transaction.hs:334:1-52 74247 1 0.0 0.0 0.0 0.0
CAF:balancedVirtualPostings Hledger.Data.Transaction Hledger/Data/Transaction.hs:340:1-23 20211 0 0.0 0.0 0.0 0.0
balancedVirtualPostings Hledger.Data.Transaction Hledger/Data/Transaction.hs:340:1-62 74746 1 0.0 0.0 0.0 0.0
CAF:balancemode Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:268:1-11 23003 0 0.0 0.0 0.0 0.0
balancemode Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:(268,1)-(296,29) 24114 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24115 1 0.0 0.0 0.0 0.0
CAF:balancemode165 Hledger.Cli.Commands.Balance <no location info> 22998 0 0.0 0.0 0.0 0.0
CAF:balancemode167 Hledger.Cli.Commands.Balance <no location info> 22997 0 0.0 0.0 0.0 0.0
CAF:balancemode172 Hledger.Cli.Commands.Balance <no location info> 23001 0 0.0 0.0 0.0 0.0
balancemode Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:(268,1)-(296,29) 24450 0 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24451 0 0.0 0.0 0.0 0.0
headDef Safe Safe.hs:134:1-37 24452 1 0.0 0.0 0.0 0.0
CAF:balancemode173 Hledger.Cli.Commands.Balance <no location info> 23000 0 0.0 0.0 0.0 0.0
balancemode Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:(268,1)-(296,29) 24453 0 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24454 0 0.0 0.0 0.0 0.0
headDef Safe Safe.hs:134:1-37 24455 0 0.0 0.0 0.0 0.0
headMay Safe Safe.hs:130:1-27 24456 0 0.0 0.0 0.0 0.0
liftMay Safe.Util Safe/Util.hs:20:1-69 24457 1 0.0 0.0 0.0 0.0
CAF:balancemode174 Hledger.Cli.Commands.Balance <no location info> 22885 0 0.0 0.0 0.0 0.0
CAF:balancemode_aliases Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:296:9-15 22999 0 0.0 0.0 0.0 0.0
balancemode Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:(268,1)-(296,29) 24411 0 0.0 0.0 0.0 0.0
balancemode.aliases Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:296:9-29 24412 1 0.0 0.0 0.0 0.0
CAF:balancesheet18 Hledger.Cli.Commands.Balancesheet <no location info> 22871 0 0.0 0.0 0.0 0.0
CAF:balancesheet20 Hledger.Cli.Commands.Balancesheet <no location info> 22870 0 0.0 0.0 0.0 0.0
CAF:balancesheetSpec Hledger.Cli.Commands.Balancesheet Hledger/Cli/Commands/Balancesheet.hs:22:1-16 22878 0 0.0 0.0 0.0 0.0
balancesheetSpec Hledger.Cli.Commands.Balancesheet Hledger/Cli/Commands/Balancesheet.hs:(22,1)-(36,1) 24117 1 0.0 0.0 0.0 0.0
CAF:balancesheetequity23 Hledger.Cli.Commands.Balancesheetequity <no location info> 22858 0 0.0 0.0 0.0 0.0
CAF:balancesheetequity25 Hledger.Cli.Commands.Balancesheetequity <no location info> 22857 0 0.0 0.0 0.0 0.0
CAF:balancesheetequitySpec Hledger.Cli.Commands.Balancesheetequity Hledger/Cli/Commands/Balancesheetequity.hs:20:1-22 22867 0 0.0 0.0 0.0 0.0
balancesheetequitySpec Hledger.Cli.Commands.Balancesheetequity Hledger/Cli/Commands/Balancesheetequity.hs:(20,1)-(34,1) 24121 1 0.0 0.0 0.0 0.0
CAF:balancesheetequitymode Hledger.Cli.Commands.Balancesheetequity Hledger/Cli/Commands/Balancesheetequity.hs:37:1-22 22868 0 0.0 0.0 0.0 0.0
balancesheetequitymode Hledger.Cli.Commands.Balancesheetequity Hledger/Cli/Commands/Balancesheetequity.hs:37:1-74 24120 1 0.0 0.0 0.0 0.0
compoundBalanceCommandMode Hledger.Cli.CompoundBalanceCommand Hledger/Cli/CompoundBalanceCommand.hs:(48,1)-(82,33) 24122 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24123 1 0.0 0.0 0.0 0.0
CAF:balancesheetmode Hledger.Cli.Commands.Balancesheet Hledger/Cli/Commands/Balancesheet.hs:39:1-16 22879 0 0.0 0.0 0.0 0.0
balancesheetmode Hledger.Cli.Commands.Balancesheet Hledger/Cli/Commands/Balancesheet.hs:39:1-62 24116 1 0.0 0.0 0.0 0.0
compoundBalanceCommandMode Hledger.Cli.CompoundBalanceCommand Hledger/Cli/CompoundBalanceCommand.hs:(48,1)-(82,33) 24118 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24119 1 0.0 0.0 0.0 0.0
CAF:boolopt Hledger.Data.RawOptions Hledger/Data/RawOptions.hs:45:1-7 20731 0 0.0 0.0 0.0 0.0
boolopt Hledger.Data.RawOptions Hledger/Data/RawOptions.hs:45:1-19 25094 1 0.0 0.0 0.0 0.0
CAF:builtinCommandNames Hledger.Cli.Commands Hledger/Cli/Commands.hs:106:1-19 23468 0 0.0 0.0 0.0 0.0
builtinCommandNames Hledger.Cli.Commands Hledger/Cli/Commands.hs:106:1-65 24409 1 0.0 0.0 0.0 0.0
modeNames System.Console.CmdArgs.Explicit.Type System/Console/CmdArgs/Explicit/Type.hs:89:6-14 24410 22 0.0 0.0 0.0 0.0
CAF:builtinCommands Hledger.Cli.Commands Hledger/Cli/Commands.hs:79:1-15 23467 0 0.0 0.0 0.0 0.0
builtinCommands Hledger.Cli.Commands Hledger/Cli/Commands.hs:(79,1)-(102,3) 24099 1 0.0 0.0 0.0 0.0
CAF:builtinCommands25 Hledger.Cli.Commands <no location info> 23465 0 0.0 0.0 0.0 0.0
builtinCommands Hledger.Cli.Commands Hledger/Cli/Commands.hs:(79,1)-(102,3) 24193 0 0.0 0.0 0.0 0.0
testmode Hledger.Cli.Commands Hledger/Cli/Commands.hs:(215,1)-(226,2) 24194 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24195 1 0.0 0.0 0.0 0.0
CAF:builtinCommands59 Hledger.Cli.Commands <no location info> 23419 0 0.0 0.0 0.0 0.0
CAF:cacheLineIntBits Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:66:1-16 15326 0 0.0 0.0 0.0 0.0
cacheLineIntBits Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:66:1-52 77354 1 0.0 0.0 0.0 0.0
log2 Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:(292,1)-(295,37) 77355 1 0.0 0.0 0.0 0.0
log2.go Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:(294,5)-(295,37) 77357 7 0.0 0.0 0.0 0.0
CAF:cacheLineIntBits1 Data.HashTable.Internal.Utils <no location info> 15325 0 0.0 0.0 0.0 0.0
cacheLineIntBits Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:66:1-52 77356 0 0.0 0.0 0.0 0.0
CAF:cacheLineSize Data.HashTable.Internal.IntArray src/Data/HashTable/Internal/IntArray.hs:80:1-13 15368 0 0.0 0.0 0.0 0.0
cacheLineSize Data.HashTable.Internal.IntArray src/Data/HashTable/Internal/IntArray.hs:80:1-18 74238 1 0.0 0.0 0.0 0.0
CAF:cacheLineSize Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:48:1-13 15314 0 0.0 0.0 0.0 0.0
cacheLineSize Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:48:1-18 74222 1 0.0 0.0 0.0 0.0
CAF:cashflow12 Hledger.Cli.Commands.Cashflow <no location info> 22848 0 0.0 0.0 0.0 0.0
CAF:cashflow14 Hledger.Cli.Commands.Cashflow <no location info> 22847 0 0.0 0.0 0.0 0.0
CAF:cashflowSpec Hledger.Cli.Commands.Cashflow Hledger/Cli/Commands/Cashflow.hs:25:1-12 22853 0 0.0 0.0 0.0 0.0
cashflowSpec Hledger.Cli.Commands.Cashflow Hledger/Cli/Commands/Cashflow.hs:(25,1)-(37,1) 24125 1 0.0 0.0 0.0 0.0
CAF:cashflowmode Hledger.Cli.Commands.Cashflow Hledger/Cli/Commands/Cashflow.hs:40:1-12 22854 0 0.0 0.0 0.0 0.0
cashflowmode Hledger.Cli.Commands.Cashflow Hledger/Cli/Commands/Cashflow.hs:40:1-54 24124 1 0.0 0.0 0.0 0.0
compoundBalanceCommandMode Hledger.Cli.CompoundBalanceCommand Hledger/Cli/CompoundBalanceCommand.hs:(48,1)-(82,33) 24126 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24127 1 0.0 0.0 0.0 0.0
CAF:checkdatesmode Hledger.Cli.Commands.Checkdates Hledger/Cli/Commands/Checkdates.hs:17:1-14 22841 0 0.0 0.0 0.0 0.0
checkdatesmode Hledger.Cli.Commands.Checkdates Hledger/Cli/Commands/Checkdates.hs:(17,1)-(29,33) 24128 1 0.0 0.0 0.0 0.0
hledgerCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(264,1)-(277,9) 24129 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24131 1 0.0 0.0 0.0 0.0
parseHelpTemplate Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(248,1)-(256,60) 24130 1 0.0 0.0 0.0 0.0
parseHelpTemplate.names Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:253:9-23 24132 1 0.0 0.0 0.0 0.0
CAF:checkdupesmode Hledger.Cli.Commands.Checkdupes Hledger/Cli/Commands/Checkdupes.hs:19:1-14 22830 0 0.0 0.0 0.0 0.0
checkdupesmode Hledger.Cli.Commands.Checkdupes Hledger/Cli/Commands/Checkdupes.hs:(19,1)-(29,15) 24133 1 0.0 0.0 0.0 0.0
hledgerCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(264,1)-(277,9) 24134 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24136 1 0.0 0.0 0.0 0.0
parseHelpTemplate Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(248,1)-(256,60) 24135 1 0.0 0.0 0.0 0.0
parseHelpTemplate.names Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:253:9-23 24137 1 0.0 0.0 0.0 0.0
CAF:choice' Hledger.Utils.Parse Hledger/Utils/Parse.hs:34:1-7 16774 0 0.0 0.0 0.0 0.0
choice' Hledger.Utils.Parse Hledger/Utils/Parse.hs:34:1-26 24327 1 0.0 0.0 0.0 0.0
CAF:choiceInState Hledger.Utils.Parse Hledger/Utils/Parse.hs:39:1-13 16787 0 0.0 0.0 0.0 0.0
choiceInState Hledger.Utils.Parse Hledger/Utils/Parse.hs:39:1-32 26800 1 0.0 0.0 0.0 0.0
CAF:cleanWin_r5iBD Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:219:1-8 16266 0 0.0 0.0 0.0 0.0
cleanWin Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:219:1-25 81630 1 0.0 0.0 0.0 0.0
CAF:cliptopleft1 Hledger.Utils.String <no location info> 16681 0 0.0 0.0 0.0 0.0
CAF:codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-5 18636 0 0.0 0.0 0.0 0.0
codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-106 27738 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 27739 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 27740 1 0.0 0.0 0.0 0.0
CAF:codep1 Hledger.Read.Common <no location info> 18635 0 0.0 0.0 0.0 0.0
codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-106 27780 0 0.0 0.0 0.0 0.0
return Text.Megaparsec Text/Megaparsec.hs:352:3-15 27781 1 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 27782 1 0.0 0.0 0.0 0.0
CAF:codep2 Hledger.Read.Common <no location info> 18634 0 0.0 0.0 0.0 0.0
codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-106 27744 0 0.0 0.0 0.0 0.0
try Text.Megaparsec Text/Megaparsec.hs:868:3-26 27745 1 0.0 0.0 0.0 0.0
CAF:codep20 Hledger.Read.Common <no location info> 18622 0 0.0 0.0 0.0 0.0
codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-106 27772 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 27773 1 0.0 0.0 0.0 0.0
CAF:codep26 Hledger.Read.Common <no location info> 18402 0 0.0 0.0 0.0 0.0
codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-106 27749 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 27750 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 27758 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 27759 1 0.0 0.0 0.0 0.0
CAF:codep27 Hledger.Read.Common <no location info> 18401 0 0.0 0.0 0.0 0.0
codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-106 27754 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 27755 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 27756 1 0.0 0.0 0.0 0.0
CAF:codep4 Hledger.Read.Common <no location info> 18633 0 0.0 0.0 0.0 0.0
codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-106 27747 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 27748 1 0.0 0.0 0.0 0.0
CAF:codep5 Hledger.Read.Common <no location info> 18632 0 0.0 0.0 0.0 0.0
codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-106 27768 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 27769 1 0.0 0.0 0.0 0.0
CAF:codep6 Hledger.Read.Common <no location info> 18631 0 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 33388 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 33389 1 0.0 0.0 0.0 0.0
CAF:codep7 Hledger.Read.Common <no location info> 18623 0 0.0 0.0 0.0 0.0
codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-106 27770 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 27771 1 0.0 0.0 0.0 0.0
CAF:color1 Hledger.Utils.Color <no location info> 16812 0 0.0 0.0 0.0 0.0
color Hledger.Utils.Color Hledger/Utils/Color.hs:19:1-80 81711 0 0.0 0.0 0.0 0.0
setSGRCode System.Console.ANSI.Codes System/Console/ANSI/Codes.hs:151:1-46 81712 0 0.0 0.0 0.0 0.0
csi System.Console.ANSI.Codes System/Console/ANSI/Codes.hs:66:1-75 81713 1 0.0 0.0 0.0 0.0
CAF:commentp Hledger.Read.Common Hledger/Read/Common.hs:682:1-8 18493 0 0.0 0.0 0.0 0.0
commentp Hledger.Read.Common Hledger/Read/Common.hs:682:1-35 25956 1 0.0 0.0 0.0 0.0
commentStartingWithp Hledger.Read.Common Hledger/Read/Common.hs:(690,1)-(696,19) 25957 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 25962 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 25966 1 0.0 0.0 0.0 0.0
CAF:commentp'_r5LA2 Hledger.Read.Common <no location info> 18882 0 0.0 0.0 0.0 0.0
followingcommentandtagsp Hledger.Read.Common Hledger/Read/Common.hs:(645,1)-(677,39) 28533 0 0.0 0.0 0.0 0.0
followingcommentandtagsp.commentp' Hledger.Read.Common Hledger/Read/Common.hs:653:9-65 28534 1 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 28535 1 0.0 0.0 0.0 0.0
CAF:commentp1 Hledger.Read.Common <no location info> 18492 0 0.0 0.0 0.0 0.0
CAF:commodityStylesFromAmounts_samecomm Hledger.Data.Journal Hledger/Data/Journal.hs:755:5-12 21269 0 0.0 0.0 0.0 0.0
commodityStylesFromAmounts Hledger.Data.Journal Hledger/Data/Journal.hs:(753,1)-(757,79) 74443 0 0.0 0.0 0.0 0.0
commodityStylesFromAmounts.samecomm Hledger.Data.Journal Hledger/Data/Journal.hs:755:5-55 74444 1 0.0 0.0 0.0 0.0
CAF:commoditysymbolp1 Hledger.Read.Common <no location info> 18553 0 0.0 0.0 0.0 0.0
commoditysymbolp Hledger.Read.Common Hledger/Read/Common.hs:452:1-93 25606 1 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 25607 1 0.0 0.0 0.0 0.0
CAF:commoditysymbolp11 Hledger.Read.Common <no location info> 18548 0 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 25610 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 25611 1 0.0 0.0 0.0 0.0
CAF:commoditysymbolp12 Hledger.Read.Common <no location info> 18546 0 0.0 0.0 0.0 0.0
quotedcommoditysymbolp Hledger.Read.Common Hledger/Read/Common.hs:(455,1)-(459,19) 25612 1 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 25613 1 0.0 0.0 0.0 0.0
CAF:commoditysymbolp16 Hledger.Read.Common <no location info> 18541 0 0.0 0.0 0.0 0.0
quotedcommoditysymbolp Hledger.Read.Common Hledger/Read/Common.hs:(455,1)-(459,19) 25616 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 25617 1 0.0 0.0 0.0 0.0
CAF:compOpt Hledger.Utils.Regex Hledger/Utils/Regex.hs:78:1-7 16743 0 0.0 0.0 0.0 0.0
compOpt Hledger.Utils.Regex Hledger/Utils/Regex.hs:78:1-24 80807 1 0.0 0.0 0.0 0.0
CAF:concatAccountNames1 Hledger.Data.Posting <no location info> 20761 0 0.0 0.0 0.0 0.0
concatAccountNames Hledger.Data.Posting Hledger/Data/Posting.hs:(263,1)-(264,97) 74505 0 0.0 0.0 0.0 0.0
concat Data.Text Data/Text.hs:(897,1)-(909,36) 74506 1 0.0 0.0 0.0 0.0
concat.ts' Data.Text Data/Text.hs:902:5-34 74507 1 0.0 0.0 0.0 0.0
CAF:cs_r4Lkh Text.Regex.TDFA.ReadRegex <no location info> 15834 0 0.0 0.0 0.0 0.0
CAF:cshowAmount1 Hledger.Data.Amount <no location info> 21970 0 0.0 0.0 0.0 0.0
isNegativeAmount Hledger.Data.Amount Hledger/Data/Amount.hs:209:1-44 79043 0 0.0 0.0 0.0 0.0
fromInteger Data.Decimal Data/Decimal.hs:214:5-46 79044 1 0.0 0.0 0.0 0.0
CAF:d_r42ZE Hledger.Query <no location info> 19071 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24580 0 0.0 0.0 0.0 0.0
words''.prefixedQuotedPattern Hledger.Query Hledger/Query.hs:(190,7)-(198,40) 24581 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24582 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24583 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24584 1 0.0 0.0 0.0 0.0
CAF:datep1 Hledger.Read.Common <no location info> 18745 0 0.0 0.0 0.0 0.0
datep Hledger.Read.Common Hledger/Read/Common.hs:(228,1)-(249,28) 26456 1 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26457 1 0.0 0.0 0.0 0.0
CAF:datesepchar1 Hledger.Data.Dates <no location info> 21694 0 0.0 0.0 0.0 0.0
datesepchar Hledger.Data.Dates Hledger/Data/Dates.hs:664:1-32 27520 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 27521 1 0.0 0.0 0.0 0.0
CAF:datesepchars Hledger.Data.Dates Hledger/Data/Dates.hs:662:1-12 21514 0 0.0 0.0 0.0 0.0
datesepchars Hledger.Data.Dates Hledger/Data/Dates.hs:662:1-20 27524 1 0.0 0.0 0.0 0.0
CAF:debugLevel Hledger.Utils.Debug Hledger/Utils/Debug.hs:63:1-10 16807 0 0.0 0.0 0.0 0.0
debugLevel Hledger.Utils.Debug Hledger/Utils/Debug.hs:(63,1)-(72,36) 23990 1 0.0 0.0 0.0 0.0
CAF:debugLevel1 Hledger.Utils.Debug <no location info> 16806 0 0.0 0.0 0.0 0.0
CAF:debugLevel_args Hledger.Utils.Debug Hledger/Utils/Debug.hs:72:7-10 16805 0 0.0 0.0 0.0 0.0
debugLevel Hledger.Utils.Debug Hledger/Utils/Debug.hs:(63,1)-(72,36) 23991 0 0.0 0.0 0.0 0.0
debugLevel.args Hledger.Utils.Debug Hledger/Utils/Debug.hs:72:7-36 23992 1 0.0 0.0 0.0 0.0
CAF:decodeRawOpts Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:378:1-13 23680 0 0.0 0.0 0.0 0.0
decodeRawOpts Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:378:1-67 24080 1 0.0 0.0 0.0 0.0
CAF:defCommandMode11 Hledger.Cli.CliOptions <no location info> 23728 0 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24425 0 0.0 0.0 0.0 0.0
argsFlag Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:168:1-70 24426 1 0.0 0.0 0.0 0.0
flagArg System.Console.CmdArgs.Explicit.Type System/Console/CmdArgs/Explicit/Type.hs:261:1-35 24427 1 0.0 0.0 0.0 0.0
CAF:defCommandMode_name1 Hledger.Cli.CliOptions <no location info> 23562 0 0.0 0.0 0.0 0.0
CAF:defMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:185:1-7 23723 0 0.0 0.0 0.0 0.0
defMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(185,1)-(200,2) 24097 1 0.0 0.0 0.0 0.0
CAF:defaultBalanceLineFormat Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:606:1-24 23666 0 0.0 0.0 0.0 0.0
defaultBalanceLineFormat Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(606,1)-(611,5) 78838 1 0.0 0.0 0.0 0.0
CAF:defaultBalanceLineFormat10 Hledger.Cli.CliOptions <no location info> 23665 0 0.0 0.0 0.0 0.0
CAF:defaultJournal12 Hledger.Read <no location info> 18977 0 0.0 0.0 0.0 0.0
defaultJournalPath Hledger.Read Hledger/Read.hs:(103,1)-(113,58) 25128 1 0.0 0.0 0.0 0.0
CAF:defaultOutputFormat Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:522:1-19 23668 0 0.0 0.0 0.0 0.0
defaultOutputFormat Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:522:1-27 78178 1 0.0 0.0 0.0 0.0
CAF:defaultSplitter Data.List.Split.Internals src/Data/List/Split/Internals.hs:58:1-15 16588 0 0.0 0.0 0.0 0.0
defaultSplitter Data.List.Split.Internals src/Data/List/Split/Internals.hs:(58,1)-(63,28) 24031 1 0.0 0.0 0.0 0.0
CAF:defaultTotalFieldWidth_r1V9Q Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:474:1-22 22922 0 0.0 0.0 0.0 0.0
defaultTotalFieldWidth Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:474:1-27 83278 1 0.0 0.0 0.0 0.0
CAF:defaultyeardirectivep1 Hledger.Read.JournalReader <no location info> 17841 0 0.0 0.0 0.0 0.0
defaultyeardirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(371,1)-(377,12) 26280 1 0.0 0.0 0.0 0.0
CAF:defaultyeardirectivep10 Hledger.Read.JournalReader <no location info> 17829 0 0.0 0.0 0.0 0.0
defaultyeardirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(371,1)-(377,12) 26287 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26288 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 26289 1 0.0 0.0 0.0 0.0
CAF:defaultyeardirectivep3 Hledger.Read.JournalReader <no location info> 17832 0 0.0 0.0 0.0 0.0
defaultyeardirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(371,1)-(377,12) 26285 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26286 1 0.0 0.0 0.0 0.0
CAF:defaultyeardirectivep4 Hledger.Read.JournalReader <no location info> 17831 0 0.0 0.0 0.0 0.0
defaultyeardirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(371,1)-(377,12) 26291 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26292 1 0.0 0.0 0.0 0.0
CAF:defaultyeardirectivep5 Hledger.Read.JournalReader <no location info> 17830 0 0.0 0.0 0.0 0.0
defaultyeardirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(371,1)-(377,12) 26295 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26296 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 26297 1 0.0 0.0 0.0 0.0
CAF:defcliopts Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:363:1-10 23673 0 0.0 0.0 0.0 0.0
defcliopts Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(363,1)-(374,16) 24075 1 0.0 0.0 0.0 0.0
CAF:defreportopts Hledger.Reports.ReportOptions Hledger/Reports/ReportOptions.hs:114:1-13 17396 0 0.0 0.0 0.0 0.0
defreportopts Hledger.Reports.ReportOptions Hledger/Reports/ReportOptions.hs:(114,1)-(140,7) 24076 1 0.0 0.0 0.0 0.0
CAF:descriptionp1 Hledger.Read.Common <no location info> 18616 0 0.0 0.0 0.0 0.0
descriptionp Hledger.Read.Common Hledger/Read/Common.hs:219:1-46 27791 1 0.0 0.0 0.0 0.0
CAF:descriptionp2 Hledger.Read.Common <no location info> 18615 0 0.0 0.0 0.0 0.0
descriptionp Hledger.Read.Common Hledger/Read/Common.hs:219:1-46 27794 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 27795 1 0.0 0.0 0.0 0.0
CAF:descriptionp4 Hledger.Read.Common <no location info> 18614 0 0.0 0.0 0.0 0.0
CAF:digits Hledger.Data.Amount Hledger/Data/Amount.hs:211:1-6 21978 0 0.0 0.0 0.0 0.0
digits Hledger.Data.Amount Hledger/Data/Amount.hs:211:1-30 75335 1 0.0 0.0 0.0 0.0
CAF:directivep1 Hledger.Read.JournalReader <no location info> 18040 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25236 1 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 25237 1 0.0 0.0 0.0 0.0
CAF:doInternalChecks Data.Vector.Internal.Check Data/Vector/Internal/Check.hs:71:1-16 14647 0 0.0 0.0 0.0 0.0
doInternalChecks Data.Vector.Internal.Check Data/Vector/Internal/Check.hs:71:1-24 74140 1 0.0 0.0 0.0 0.0
CAF:doUnsafeChecks Data.Vector.Internal.Check Data/Vector/Internal/Check.hs:64:1-14 14646 0 0.0 0.0 0.0 0.0
doUnsafeChecks Data.Vector.Internal.Check Data/Vector/Internal/Check.hs:64:1-22 74120 1 0.0 0.0 0.0 0.0
CAF:doubleQuotedPattern_r430s Hledger.Query <no location info> 19091 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24893 0 0.0 0.0 0.0 0.0
words''.doubleQuotedPattern Hledger.Query Hledger/Query.hs:202:7-124 24894 1 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 24895 1 0.0 0.0 0.0 0.0
CAF:dropBlanks Data.List.Split.Internals src/Data/List/Split/Internals.hs:352:1-10 16591 0 0.0 0.0 0.0 0.0
dropBlanks Data.List.Split.Internals src/Data/List/Split/Internals.hs:352:1-54 27568 1 0.0 0.0 0.0 0.0
CAF:ds10_r71tZ Hledger.Read.JournalReader <no location info> 18015 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26543 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26544 0 0.0 0.0 0.0 0.0
periodictransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(430,1)-(435,50) 26545 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26546 1 0.0 0.0 0.0 0.0
CAF:ds11_r71u8 Hledger.Read.JournalReader <no location info> 18020 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26508 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26509 0 0.0 0.0 0.0 0.0
modifiertransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(422,1)-(427,49) 26510 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26511 1 0.0 0.0 0.0 0.0
CAF:ds12_r71ud Hledger.Read.JournalReader <no location info> 18025 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 37032 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 37033 0 0.0 0.0 0.0 0.0
transactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(439,1)-(453,107) 37034 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 37035 1 0.0 0.0 0.0 0.0
CAF:ds13_r71ue Hledger.Read.JournalReader <no location info> 18026 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 27621 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 27622 0 0.0 0.0 0.0 0.0
transactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(439,1)-(453,107) 27623 0 0.0 0.0 0.0 0.0
lookAhead Text.Megaparsec Text/Megaparsec.hs:(1128,3)-(1129,34) 27624 1 0.0 0.0 0.0 0.0
CAF:ds14_r71uT Hledger.Read.JournalReader <no location info> 18039 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25262 0 0.0 0.0 0.0 0.0
includedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(180,1)-(211,59) 25263 1 0.0 0.0 0.0 0.0
CAF:ds1_r2kXi Hledger.Data.Amount <no location info> 21937 0 0.0 0.0 0.0 0.0
showAmountHelper Hledger.Data.Amount Hledger/Data/Amount.hs:(278,1)-(289,25) 75293 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 75294 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 75295 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 75296 1 0.0 0.0 0.0 0.0
CAF:ds1_r431X Hledger.Query <no location info> 19137 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25057 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25058 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25059 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25060 1 0.0 0.0 0.0 0.0
CAF:ds2_r71tk Hledger.Read.JournalReader <no location info> 17982 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26336 0 0.0 0.0 0.0 0.0
commodityconversiondirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(408,1)-(417,11) 26337 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26338 1 0.0 0.0 0.0 0.0
CAF:ds3_r71tn Hledger.Read.JournalReader <no location info> 17985 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26322 0 0.0 0.0 0.0 0.0
commodityconversiondirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(408,1)-(417,11) 26323 1 0.0 0.0 0.0 0.0
CAF:ds4_r5Lz4 Hledger.Read.Common <no location info> 18830 0 0.0 0.0 0.0 0.0
postingdatesp Hledger.Read.Common Hledger/Read/Common.hs:(772,1)-(778,35) 28832 0 0.0 0.0 0.0 0.0
postingdatesp.nonp Hledger.Read.Common Hledger/Read/Common.hs:(775,7)-(776,42) 28833 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 28834 1 0.0 0.0 0.0 0.0
CAF:ds4_r71tp Hledger.Read.JournalReader <no location info> 17987 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26313 0 0.0 0.0 0.0 0.0
defaultcommoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(380,1)-(385,50) 26314 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26315 1 0.0 0.0 0.0 0.0
CAF:ds5_r71ts Hledger.Read.JournalReader <no location info> 17990 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26299 0 0.0 0.0 0.0 0.0
defaultcommoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(380,1)-(385,50) 26300 1 0.0 0.0 0.0 0.0
CAF:ds6_r71tD Hledger.Read.JournalReader <no location info> 17997 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26120 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 26121 0 0.0 0.0 0.0 0.0
commoditydirectivemultilinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(272,1)-(281,46) 26122 1 0.0 0.0 0.0 0.0
CAF:ds7_r71tJ Hledger.Read.JournalReader <no location info> 18000 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25439 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25440 0 0.0 0.0 0.0 0.0
commoditydirectiveonelinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(259,1)-(266,75) 25441 1 0.0 0.0 0.0 0.0
CAF:ds8_r71tK Hledger.Read.JournalReader <no location info> 18001 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25432 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25433 0 0.0 0.0 0.0 0.0
try Text.Megaparsec Text/Megaparsec.hs:1127:3-49 25434 1 0.0 0.0 0.0 0.0
CAF:ds9_r71tL Hledger.Read.JournalReader <no location info> 18002 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25426 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25427 1 0.0 0.0 0.0 0.0
CAF:ds_r2kXw Hledger.Data.Amount <no location info> 21949 0 0.0 0.0 0.0 0.0
normaliseHelper Hledger.Data.Amount Hledger/Data/Amount.hs:(395,1)-(415,32) 75243 0 0.0 0.0 0.0 0.0
normaliseHelper.newzero Hledger.Data.Amount Hledger/Data/Amount.hs:(400,5)-(402,29) 75244 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 75245 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 75246 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 75247 1 0.0 0.0 0.0 0.0
CAF:ds_r56gd Hledger.Reports.ReportOptions <no location info> 17454 0 0.0 0.0 0.0 0.0
CAF:ds_rAXE Hledger.Cli.CliOptions <no location info> 23568 0 0.0 0.0 0.0 0.0
CAF:elemMask Data.HashTable.Internal.IntArray src/Data/HashTable/Internal/IntArray.hs:69:1-8 15367 0 0.0 0.0 0.0 0.0
elemMask Data.HashTable.Internal.IntArray src/Data/HashTable/Internal/IntArray.hs:69:1-17 77358 1 0.0 0.0 0.0 0.0
CAF:empty Data.Text.Array Data/Text/Array.hs:173:1-5 13112 0 0.0 0.0 0.0 0.0
empty Data.Text.Array Data/Text/Array.hs:173:1-38 24259 1 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24260 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24261 1 0.0 0.0 0.0 0.0
CAF:empty Data.Text.Internal Data/Text/Internal.hs:82:1-5 13004 0 0.0 0.0 0.0 0.0
CAF:emptyMarker Data.HashTable.ST.Cuckoo src/Data/HashTable/ST/Cuckoo.hs:769:1-11 15382 0 0.0 0.0 0.0 0.0
emptyMarker Data.HashTable.ST.Cuckoo src/Data/HashTable/ST/Cuckoo.hs:769:1-15 77381 1 0.0 0.0 0.0 0.0
CAF:emptyTree1 Hledger.Utils.Tree <no location info> 16625 0 0.0 0.0 0.0 0.0
emptyTree Hledger.Utils.Tree Hledger/Utils/Tree.hs:75:1-21 78563 1 0.0 0.0 0.0 0.0
CAF:emptyorcommentlinep1 Hledger.Read.Common <no location info> 18505 0 0.0 0.0 0.0 0.0
emptyorcommentlinep Hledger.Read.Common Hledger/Read/Common.hs:(612,1)-(614,11) 26581 1 0.0 0.0 0.0 0.0
CAF:endaliasesdirectivep_r71nT Hledger.Read.JournalReader <no location info> 17767 0 0.0 0.0 0.0 0.0
endaliasesdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(352,1)-(354,21) 25325 1 0.0 0.0 0.0 0.0
CAF:endapplyaccountdirectivep_r71nK Hledger.Read.JournalReader <no location info> 17760 0 0.0 0.0 0.0 0.0
endapplyaccountdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(316,1)-(318,18) 26161 1 0.0 0.0 0.0 0.0
CAF:endtagdirectivep_r71o5 Hledger.Read.JournalReader <no location info> 17775 0 0.0 0.0 0.0 0.0
endtagdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(365,1)-(368,11) 26235 1 0.0 0.0 0.0 0.0
CAF:eolof Hledger.Utils.Parse Hledger/Utils/Parse.hs:83:1-5 16786 0 0.0 0.0 0.0 0.0
eolof Hledger.Utils.Parse Hledger/Utils/Parse.hs:83:1-38 27064 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 27065 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 27066 1 0.0 0.0 0.0 0.0
CAF:eolof1 Hledger.Utils.Parse <no location info> 16757 0 0.0 0.0 0.0 0.0
eolof Hledger.Utils.Parse Hledger/Utils/Parse.hs:83:1-38 27075 0 0.0 0.0 0.0 0.0
eof Text.Megaparsec Text/Megaparsec.hs:873:3-26 27076 1 0.0 0.0 0.0 0.0
CAF:eolof3 Hledger.Utils.Parse <no location info> 16785 0 0.0 0.0 0.0 0.0
eolof Hledger.Utils.Parse Hledger/Utils/Parse.hs:83:1-38 27069 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 27070 1 0.0 0.0 0.0 0.0
CAF:eolof4 Hledger.Utils.Parse <no location info> 16758 0 0.0 0.0 0.0 0.0
return Text.Megaparsec Text/Megaparsec.hs:352:3-15 27100 1 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 27101 1 0.0 0.0 0.0 0.0
CAF:eolof5 Hledger.Utils.Parse <no location info> 16779 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 26725 1 0.0 0.0 0.0 0.0
CAF:equitymode Hledger.Cli.Commands.Equity Hledger/Cli/Commands/Equity.hs:16:1-10 22817 0 0.0 0.0 0.0 0.0
equitymode Hledger.Cli.Commands.Equity Hledger/Cli/Commands/Equity.hs:(16,1)-(59,33) 24138 1 0.0 0.0 0.0 0.0
hledgerCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(264,1)-(277,9) 24139 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24141 1 0.0 0.0 0.0 0.0
parseHelpTemplate Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(248,1)-(256,60) 24140 1 0.0 0.0 0.0 0.0
parseHelpTemplate.names Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:253:9-23 24142 1 0.0 0.0 0.0 0.0
CAF:eta10_r71sD Hledger.Read.JournalReader <no location info> 17959 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25462 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25463 0 0.0 0.0 0.0 0.0
commoditydirectiveonelinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(259,1)-(266,75) 25464 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25465 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25468 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25466 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25467 2 0.0 0.0 0.0 0.0
CAF:eta11_r71sS Hledger.Read.JournalReader <no location info> 17968 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25283 0 0.0 0.0 0.0 0.0
includedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(180,1)-(211,59) 25284 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25285 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25288 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25286 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25287 2 0.0 0.0 0.0 0.0
CAF:eta1_r71n3 Hledger.Read.JournalReader <no location info> 17737 0 0.0 0.0 0.0 0.0
accountdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(233,1)-(239,51) 25381 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25382 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25385 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25383 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25384 2 0.0 0.0 0.0 0.0
CAF:eta2_r5Lso Hledger.Read.Common <no location info> 18515 0 0.0 0.0 0.0 0.0
multilinecommentp Hledger.Read.Common Hledger/Read/Common.hs:(603,1)-(609,40) 35592 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 35593 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 35596 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 35594 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 35595 2 0.0 0.0 0.0 0.0
CAF:eta2_r71oW Hledger.Read.JournalReader <no location info> 17808 0 0.0 0.0 0.0 0.0
aliasdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(321,1)-(325,23) 25319 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25320 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25323 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25321 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25322 2 0.0 0.0 0.0 0.0
CAF:eta3_r71pd Hledger.Read.JournalReader <no location info> 17818 0 0.0 0.0 0.0 0.0
tagdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(357,1)-(362,11) 26230 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 26231 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 26232 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 26233 1 0.0 0.0 0.0 0.0
CAF:eta4_r5Lxa Hledger.Read.Common <no location info> 18780 0 0.0 0.0 0.0 0.0
datetagp Hledger.Read.Common Hledger/Read/Common.hs:(797,1)-(818,39) 28801 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 28802 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 28803 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 28804 1 0.0 0.0 0.0 0.0
CAF:eta8_r71st Hledger.Read.JournalReader <no location info> 17952 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26143 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 26144 0 0.0 0.0 0.0 0.0
commoditydirectivemultilinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(272,1)-(281,46) 26145 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 26146 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 26149 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 26147 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 26148 2 0.0 0.0 0.0 0.0
CAF:execOpt Hledger.Utils.Regex Hledger/Utils/Regex.hs:81:1-7 16742 0 0.0 0.0 0.0 0.0
execOpt Hledger.Utils.Regex Hledger/Utils/Regex.hs:81:1-24 81004 1 0.0 0.0 0.0 0.0
CAF:expandAccountName Hledger.Data.AccountName Hledger/Data/AccountName.hs:65:1-17 22258 0 0.0 0.0 0.0 0.0
expandAccountName Hledger.Data.AccountName Hledger/Data/AccountName.hs:65:1-88 78554 1 0.0 0.0 0.0 0.0
CAF:expandArgsAt4 System.Console.CmdArgs.Explicit.ExpandArgsAt <no location info> 12687 0 0.0 0.0 0.0 0.0
CAF:f2_r71tl Hledger.Read.JournalReader <no location info> 17983 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26331 0 0.0 0.0 0.0 0.0
commodityconversiondirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(408,1)-(417,11) 26332 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26333 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 26334 1 0.0 0.0 0.0 0.0
CAF:f3_r71tq Hledger.Read.JournalReader <no location info> 17988 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26308 0 0.0 0.0 0.0 0.0
defaultcommoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(380,1)-(385,50) 26309 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26310 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 26311 1 0.0 0.0 0.0 0.0
CAF:f4_r5Lz2 Hledger.Read.Common <no location info> 18828 0 0.0 0.0 0.0 0.0
postingdatesp Hledger.Read.Common Hledger/Read/Common.hs:(772,1)-(778,35) 28826 0 0.0 0.0 0.0 0.0
postingdatesp.nonp Hledger.Read.Common Hledger/Read/Common.hs:(775,7)-(776,42) 28827 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 28828 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 28829 1 0.0 0.0 0.0 0.0
CAF:f4_r71tS Hledger.Read.JournalReader <no location info> 18008 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25239 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 25240 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 25241 1 0.0 0.0 0.0 0.0
CAF:f5_r71u0 Hledger.Read.JournalReader <no location info> 18016 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26538 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26539 0 0.0 0.0 0.0 0.0
periodictransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(430,1)-(435,50) 26540 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26541 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 26542 1 0.0 0.0 0.0 0.0
CAF:f6_r71u9 Hledger.Read.JournalReader <no location info> 18021 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26503 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26504 0 0.0 0.0 0.0 0.0
modifiertransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(422,1)-(427,49) 26505 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26506 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 26507 1 0.0 0.0 0.0 0.0
CAF:f7_r71ur Hledger.Read.JournalReader <no location info> 18028 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 27662 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 27663 0 0.0 0.0 0.0 0.0
transactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(439,1)-(453,107) 27664 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 27665 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 27666 1 0.0 0.0 0.0 0.0
CAF:f8_r71uK Hledger.Read.JournalReader <no location info> 18034 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 25230 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 25231 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 25232 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 25233 1 0.0 0.0 0.0 0.0
CAF:f_r42Zt Hledger.Query <no location info> 19062 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24519 0 0.0 0.0 0.0 0.0
fromparse Hledger.Utils.Parse Hledger/Utils/Parse.hs:62:1-32 24520 1 0.0 0.0 0.0 0.0
CAF:f_r56c5 Hledger.Reports.ReportOptions <no location info> 17340 0 0.0 0.0 0.0 0.0
intervalFromRawOpts Hledger.Reports.ReportOptions Hledger/Reports/ReportOptions.hs:(269,1)-(280,27) 24489 0 0.0 0.0 0.0 0.0
lastDef Safe Safe.hs:135:1-37 24490 1 0.0 0.0 0.0 0.0
CAF:f_r71qa Hledger.Read.JournalReader <no location info> 17888 0 0.0 0.0 0.0 0.0
postingsp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:553:1-60 27861 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 27862 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 27863 1 0.0 0.0 0.0 0.0
CAF:flat_ Hledger.Reports.ReportOptions Hledger/Reports/ReportOptions.hs:334:1-5 17435 0 0.0 0.0 0.0 0.0
flat_ Hledger.Reports.ReportOptions Hledger/Reports/ReportOptions.hs:334:1-37 78357 1 0.0 0.0 0.0 0.0
CAF:followingcommentp1 Hledger.Read.Common <no location info> 18500 0 0.0 0.0 0.0 0.0
followingcommentp Hledger.Read.Common Hledger/Read/Common.hs:(618,1)-(622,57) 25936 1 0.0 0.0 0.0 0.0
CAF:formatString2 Hledger.Utils.String <no location info> 16694 0 0.0 0.0 0.0 0.0
CAF:formatString5 Hledger.Utils.String <no location info> 16693 0 0.0 0.0 0.0 0.0
CAF:fromSystemString Hledger.Utils.UTF8IOCompat Hledger/Utils/UTF8IOCompat.hs:99:1-16 16613 0 0.0 0.0 0.0 0.0
fromSystemString Hledger.Utils.UTF8IOCompat Hledger/Utils/UTF8IOCompat.hs:99:1-21 24449 1 0.0 0.0 0.0 0.0
CAF:g_r5LsP Hledger.Read.Common <no location info> 18570 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25762 0 0.0 0.0 0.0 0.0
numberp.numeric Hledger.Read.Common Hledger/Read/Common.hs:576:5-36 25763 0 0.0 0.0 0.0 0.0
headDef Safe Safe.hs:134:1-37 25764 1 0.0 0.0 0.0 0.0
CAF:getClockTime1 System.Time <no location info> 13596 0 0.0 0.0 0.0 0.0
getClockTime System.Time System/Time.hsc:(248,1)-(253,69) 25206 1 0.0 0.0 0.0 0.0
CAF:getCurrentDay1 Hledger.Data.Dates <no location info> 21503 0 0.0 0.0 0.0 0.0
getCurrentDay Hledger.Data.Dates Hledger/Data/Dates.hs:(115,1)-(117,46) 24063 1 0.0 0.0 0.0 0.0
CAF:getCurrentYear1 Hledger.Data.Dates <no location info> 21507 0 0.0 0.0 0.0 0.0
getCurrentYear Hledger.Data.Dates Hledger/Data/Dates.hs:(127,1)-(129,10) 25211 1 0.0 0.0 0.0 0.0
CAF:getDefaultCommodityAndStyle1 Hledger.Read.Common <no location info> 18666 0 0.0 0.0 0.0 0.0
getDefaultCommodityAndStyle Hledger.Read.Common Hledger/Read/Common.hs:147:1-63 63958 1 0.0 0.0 0.0 0.0
CAF:getDefaultCommodityAndStyle2 Hledger.Read.Common <no location info> 18665 0 0.0 0.0 0.0 0.0
getDefaultCommodityAndStyle Hledger.Read.Common Hledger/Read/Common.hs:147:1-63 63961 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:105:5-20 63962 1 0.0 0.0 0.0 0.0
CAF:getDefaultCommodityAndStyle3 Hledger.Read.Common <no location info> 18664 0 0.0 0.0 0.0 0.0
getDefaultCommodityAndStyle Hledger.Read.Common Hledger/Read/Common.hs:147:1-63 63964 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:105:5-20 63965 0 0.0 0.0 0.0 0.0
return Text.Megaparsec Text/Megaparsec.hs:352:3-15 63966 1 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 63967 1 0.0 0.0 0.0 0.0
CAF:getParentAccount1 Hledger.Read.Common <no location info> 18654 0 0.0 0.0 0.0 0.0
getParentAccount Hledger.Read.Common Hledger/Read/Common.hs:163:1-81 27959 1 0.0 0.0 0.0 0.0
CAF:getParentAccount2 Hledger.Read.Common <no location info> 18653 0 0.0 0.0 0.0 0.0
getParentAccount Hledger.Read.Common Hledger/Read/Common.hs:163:1-81 27962 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:105:5-20 27963 1 0.0 0.0 0.0 0.0
CAF:getParentAccount3 Hledger.Read.Common <no location info> 18652 0 0.0 0.0 0.0 0.0
getParentAccount Hledger.Read.Common Hledger/Read/Common.hs:163:1-81 27965 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:105:5-20 27966 0 0.0 0.0 0.0 0.0
return Text.Megaparsec Text/Megaparsec.hs:352:3-15 27967 1 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 27968 1 0.0 0.0 0.0 0.0
CAF:getState2 Text.Parsec.Prim <no location info> 13236 0 0.0 0.0 0.0 0.0
getState Text.Parsec.Prim Text/Parsec/Prim.hs:745:1-43 79511 0 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 79512 1 0.0 0.0 0.0 0.0
CAF:getState4 Text.Parsec.Prim <no location info> 13235 0 0.0 0.0 0.0 0.0
getState Text.Parsec.Prim Text/Parsec/Prim.hs:745:1-43 79514 0 0.0 0.0 0.0 0.0
getParserState Text.Parsec.Prim Text/Parsec/Prim.hs:725:1-37 79515 1 0.0 0.0 0.0 0.0
updateParserState Text.Parsec.Prim Text/Parsec/Prim.hs:(735,1)-(738,34) 79516 1 0.0 0.0 0.0 0.0
CAF:getYear1 Hledger.Read.Common <no location info> 18722 0 0.0 0.0 0.0 0.0
getYear Hledger.Read.Common Hledger/Read/Common.hs:141:1-36 27550 1 0.0 0.0 0.0 0.0
CAF:getYear2 Hledger.Read.Common <no location info> 18721 0 0.0 0.0 0.0 0.0
getYear Hledger.Read.Common Hledger/Read/Common.hs:141:1-36 27553 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:105:5-20 27554 1 0.0 0.0 0.0 0.0
CAF:getYear3 Hledger.Read.Common <no location info> 18720 0 0.0 0.0 0.0 0.0
getYear Hledger.Read.Common Hledger/Read/Common.hs:141:1-36 27556 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:105:5-20 27557 0 0.0 0.0 0.0 0.0
return Text.Megaparsec Text/Megaparsec.hs:352:3-15 27558 1 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 27559 1 0.0 0.0 0.0 0.0
CAF:go4_r5Lzx Hledger.Read.Common <no location info> 18863 0 0.0 0.0 0.0 0.0
nontagp Hledger.Read.Common Hledger/Read/Common.hs:(730,1)-(733,56) 28630 0 0.0 0.0 0.0 0.0
CAF:go5_r5Lzz Hledger.Read.Common <no location info> 18864 0 0.0 0.0 0.0 0.0
nontagp Hledger.Read.Common Hledger/Read/Common.hs:(730,1)-(733,56) 28674 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 28675 1 0.0 0.0 0.0 0.0
CAF:hSupportsANSI2 System.Console.ANSI.Unix <no location info> 12282 0 0.0 0.0 0.0 0.0
CAF:hSupportsANSI4 System.Console.ANSI.Unix <no location info> 12283 0 0.0 0.0 0.0 0.0
CAF:hasAmount Hledger.Data.Posting Hledger/Data/Posting.hs:130:1-9 20745 0 0.0 0.0 0.0 0.0
hasAmount Hledger.Data.Posting Hledger/Data/Posting.hs:130:1-42 74251 1 0.0 0.0 0.0 0.0
CAF:hasDetailedVersion_r2m6u Hledger.Cli.Main Hledger/Cli/Main.hs:141:5-22 23951 0 0.0 0.0 0.0 0.0
main Hledger.Cli.Main Hledger/Cli/Main.hs:(98,1)-(196,19) 25117 0 0.0 0.0 0.0 0.0
main.hasDetailedVersion Hledger.Cli.Main Hledger/Cli/Main.hs:141:5-48 25118 1 0.0 0.0 0.0 0.0
CAF:hasVersion_r2m6x Hledger.Cli.Main Hledger/Cli/Main.hs:140:5-14 23953 0 0.0 0.0 0.0 0.0
main Hledger.Cli.Main Hledger/Cli/Main.hs:(98,1)-(196,19) 25113 0 0.0 0.0 0.0 0.0
main.hasVersion Hledger.Cli.Main Hledger/Cli/Main.hs:140:5-47 25114 1 0.0 0.0 0.0 0.0
CAF:hashPrime Data.HashTable.ST.Cuckoo src/Data/HashTable/ST/Cuckoo.hs:736:1-9 15381 0 0.0 0.0 0.0 0.0
hashPrime Data.HashTable.ST.Cuckoo src/Data/HashTable/ST/Cuckoo.hs:(736,1)-(739,36) 77367 1 0.0 0.0 0.0 0.0
hashPrime.hashPrime64 Data.HashTable.ST.Cuckoo src/Data/HashTable/ST/Cuckoo.hs:739:5-36 77368 1 0.0 0.0 0.0 0.0
CAF:headMay Safe Safe.hs:130:1-7 13693 0 0.0 0.0 0.0 0.0
headMay Safe Safe.hs:130:1-27 24005 1 0.0 0.0 0.0 0.0
CAF:helpmode Hledger.Cli.Commands.Help Hledger/Cli/Commands/Help.hs:35:1-8 22807 0 0.0 0.0 0.0 0.0
helpmode Hledger.Cli.Commands.Help Hledger/Cli/Commands/Help.hs:(35,1)-(50,20) 24143 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24144 1 0.0 0.0 0.0 0.0
CAF:helpmode11 Hledger.Cli.Commands.Help <no location info> 22780 0 0.0 0.0 0.0 0.0
CAF:helpmode_aliases Hledger.Cli.Commands.Help Hledger/Cli/Commands/Help.hs:50:9-15 22779 0 0.0 0.0 0.0 0.0
helpmode Hledger.Cli.Commands.Help Hledger/Cli/Commands/Help.hs:(35,1)-(50,20) 24145 0 0.0 0.0 0.0 0.0
helpmode.aliases Hledger.Cli.Commands.Help Hledger/Cli/Commands/Help.hs:50:9-20 24146 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons1 Hledger.Cli.CliOptions <no location info> 23663 0 0.0 0.0 0.0 0.0
hledgerAddons Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(632,1)-(639,12) 24016 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons11 Hledger.Cli.CliOptions <no location info> 23651 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24265 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24266 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 24267 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons13 Hledger.Cli.CliOptions <no location info> 23650 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24287 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24288 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 24289 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons15 Hledger.Cli.CliOptions <no location info> 23615 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24390 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24391 0 0.0 0.0 0.0 0.0
eof Text.Megaparsec Text/Megaparsec.hs:873:3-26 24392 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons17 Hledger.Cli.CliOptions <no location info> 23649 0 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 24290 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 24291 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons18 Hledger.Cli.CliOptions <no location info> 23648 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24387 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24388 0 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 24389 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons19 Hledger.Cli.CliOptions <no location info> 23647 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24293 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24294 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons20 Hledger.Cli.CliOptions <no location info> 23646 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24295 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24296 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 24297 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons22 Hledger.Cli.CliOptions <no location info> 23645 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24325 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24326 0 0.0 0.0 0.0 0.0
choice' Hledger.Utils.Parse Hledger/Utils/Parse.hs:34:1-26 24328 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons23 Hledger.Cli.CliOptions <no location info> 23644 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24329 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24330 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24348 10 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24349 10 0.0 0.0 0.0 0.0
mptext Text.Megaparsec.Compat Text/Megaparsec/Compat.hs:47:1-15 24346 0 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 24347 10 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24350 10 0.0 0.0 0.0 0.0
CAF:hledgerAddons33 Hledger.Cli.CliOptions <no location info> 23636 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons35 Hledger.Cli.CliOptions <no location info> 23635 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons37 Hledger.Cli.CliOptions <no location info> 23634 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons39 Hledger.Cli.CliOptions <no location info> 23633 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons4 Hledger.Cli.CliOptions <no location info> 23661 0 0.0 0.0 0.0 0.0
stripPrognamePrefix Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:641:1-48 24403 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons41 Hledger.Cli.CliOptions <no location info> 23632 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons43 Hledger.Cli.CliOptions <no location info> 23631 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons45 Hledger.Cli.CliOptions <no location info> 23630 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons47 Hledger.Cli.CliOptions <no location info> 23629 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons49 Hledger.Cli.CliOptions <no location info> 23628 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons5 Hledger.Cli.CliOptions <no location info> 23656 0 0.0 0.0 0.0 0.0
hledgerExecutablesInPath Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:671:1-78 24018 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons51 Hledger.Cli.CliOptions <no location info> 23627 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons54 Hledger.Cli.CliOptions <no location info> 23616 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24342 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24343 0 0.0 0.0 0.0 0.0
mptext Text.Megaparsec.Compat Text/Megaparsec/Compat.hs:47:1-15 24344 1 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:875:3-29 24345 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons55 Hledger.Cli.CliOptions <no location info> 23621 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24298 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24299 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:875:3-29 24300 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons57 Hledger.Cli.CliOptions <no location info> 23620 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24322 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24323 0 0.0 0.0 0.0 0.0
chunkEmpty Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:228:3-27 24324 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons58 Hledger.Cli.CliOptions <no location info> 23617 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24304 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24305 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24307 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24308 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24309 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons59 Hledger.Cli.CliOptions <no location info> 23567 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons6 Hledger.Cli.CliOptions <no location info> 23654 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24203 0 0.0 0.0 0.0 0.0
parsewith Hledger.Utils.Parse Hledger/Utils/Parse.hs:45:1-28 24204 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons64 Hledger.Cli.CliOptions <no location info> 23623 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24268 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24269 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 24270 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 24277 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 24278 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons65 Hledger.Cli.CliOptions <no location info> 23622 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24274 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24275 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 24276 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons69 Hledger.Cli.CliOptions <no location info> 23624 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24254 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24255 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 24256 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons7 Hledger.Cli.CliOptions <no location info> 23653 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24211 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24212 1 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 24213 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons74 Hledger.Cli.CliOptions <no location info> 23626 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24216 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24217 0 0.0 0.0 0.0 0.0
mptext Text.Megaparsec.Compat Text/Megaparsec/Compat.hs:47:1-15 24218 1 0.0 0.0 0.0 0.0
chunkEmpty Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:228:3-27 24249 1 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 24222 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24228 1 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:875:3-29 24219 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons75 Hledger.Cli.CliOptions <no location info> 23625 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24223 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24224 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24227 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24225 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24226 2 0.0 0.0 0.0 0.0
CAF:hledgerAddons77 Hledger.Cli.CliOptions <no location info> 23569 0 0.0 0.0 0.0 0.0
likelyExecutablesInPath Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(654,1)-(657,31) 24020 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons78 Hledger.Cli.CliOptions <no location info> 23566 0 0.0 0.0 0.0 0.0
likelyExecutablesInPath Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(654,1)-(657,31) 24029 0 0.0 0.0 0.0 0.0
splitOneOf Data.List.Split.Internals src/Data/List/Split/Internals.hs:400:1-39 24030 0 0.0 0.0 0.0 0.0
dropDelims Data.List.Split.Internals src/Data/List/Split/Internals.hs:295:1-39 24032 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons87 Hledger.Cli.CliOptions <no location info> 23563 0 0.0 0.0 0.0 0.0
CAF:hledgerAddons9 Hledger.Cli.CliOptions <no location info> 23652 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24251 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24252 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 24253 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons_len Hledger.Cli.CliOptions <no location info> 23619 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24301 0 0.0 0.0 0.0 0.0
isHledgerExeName.hledgerexenamep Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(678,7)-(683,11) 24302 0 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 24303 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24310 1 0.0 0.0 0.0 0.0
CAF:hledgerAddons_x Hledger.Cli.CliOptions <no location info> 23564 0 0.0 0.0 0.0 0.0
CAF:ignoredpricecommoditydirectivep_r71q1 Hledger.Read.JournalReader <no location info> 17881 0 0.0 0.0 0.0 0.0
ignoredpricecommoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(400,1)-(405,11) 26345 1 0.0 0.0 0.0 0.0
CAF:importmode Hledger.Cli.Commands.Import Hledger/Cli/Commands/Import.hs:21:1-10 22772 0 0.0 0.0 0.0 0.0
importmode Hledger.Cli.Commands.Import Hledger/Cli/Commands/Import.hs:(21,1)-(37,36) 24147 1 0.0 0.0 0.0 0.0
hledgerCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(264,1)-(277,9) 24148 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24150 1 0.0 0.0 0.0 0.0
parseHelpTemplate Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(248,1)-(256,60) 24149 1 0.0 0.0 0.0 0.0
parseHelpTemplate.names Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:253:9-23 24151 1 0.0 0.0 0.0 0.0
CAF:incomestatement18 Hledger.Cli.Commands.Incomestatement <no location info> 22754 0 0.0 0.0 0.0 0.0
CAF:incomestatement20 Hledger.Cli.Commands.Incomestatement <no location info> 22753 0 0.0 0.0 0.0 0.0
CAF:incomestatementSpec Hledger.Cli.Commands.Incomestatement Hledger/Cli/Commands/Incomestatement.hs:22:1-19 22761 0 0.0 0.0 0.0 0.0
incomestatementSpec Hledger.Cli.Commands.Incomestatement Hledger/Cli/Commands/Incomestatement.hs:(22,1)-(36,1) 24153 1 0.0 0.0 0.0 0.0
CAF:incomestatementmode Hledger.Cli.Commands.Incomestatement Hledger/Cli/Commands/Incomestatement.hs:39:1-19 22762 0 0.0 0.0 0.0 0.0
incomestatementmode Hledger.Cli.Commands.Incomestatement Hledger/Cli/Commands/Incomestatement.hs:39:1-68 24152 1 0.0 0.0 0.0 0.0
compoundBalanceCommandMode Hledger.Cli.CompoundBalanceCommand Hledger/Cli/CompoundBalanceCommand.hs:(48,1)-(82,33) 24154 1 0.0 0.0 0.0 0.0
defCommandMode Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(207,1)-(219,3) 24155 1 0.0 0.0 0.0 0.0
CAF:initialPos1 Text.Megaparsec.Pos <no location info> 15463 0 0.0 0.0 0.0 0.0
pos1 Text.Megaparsec.Pos Text/Megaparsec/Pos.hs:80:1-14 24242 1 0.0 0.0 0.0 0.0
CAF:inputflags56 Hledger.Cli.CliOptions <no location info> 23561 0 0.0 0.0 0.0 0.0
CAF:intervalFromRawOpts_r4ZRn Hledger.Reports.ReportOptions Hledger/Reports/ReportOptions.hs:269:1-19 17341 0 0.0 0.0 0.0 0.0
intervalFromRawOpts Hledger.Reports.ReportOptions Hledger/Reports/ReportOptions.hs:(269,1)-(280,27) 24487 1 0.0 0.0 0.0 0.0
CAF:isFlag_r2m6i Hledger.Cli.Main Hledger/Cli/Main.hs:111:5-10 23947 0 0.0 0.0 0.0 0.0
main Hledger.Cli.Main Hledger/Cli/Main.hs:(98,1)-(196,19) 24009 0 0.0 0.0 0.0 0.0
main.isFlag Hledger.Cli.Main Hledger/Cli/Main.hs:111:5-45 24010 1 0.0 0.0 0.0 0.0
CAF:isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:676:1-16 23655 0 0.0 0.0 0.0 0.0
isHledgerExeName Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(676,1)-(683,11) 24198 1 0.0 0.0 0.0 0.0
CAF:isMovableNoArgFlag2 Hledger.Cli.Main <no location info> 23943 0 0.0 0.0 0.0 0.0
CAF:isReallyZeroAmount1 Hledger.Data.Amount <no location info> 21972 0 0.0 0.0 0.0 0.0
isReallyZeroAmount Hledger.Data.Amount Hledger/Data/Amount.hs:220:1-48 74864 0 0.0 0.0 0.0 0.0
fromInteger Data.Decimal Data/Decimal.hs:214:5-46 74865 1 0.0 0.0 0.0 0.0
CAF:isRight Hledger.Utils Hledger/Utils.hs:128:1-7 16816 0 0.0 0.0 0.0 0.0
isRight Hledger.Utils Hledger/Utils.hs:128:1-22 24200 1 0.0 0.0 0.0 0.0
CAF:isZeroAmount1 Hledger.Data.Amount <no location info> 21935 0 0.0 0.0 0.0 0.0
isZeroAmount Hledger.Data.Amount Hledger/Data/Amount.hs:(215,1)-(216,102) 75286 0 0.0 0.0 0.0 0.0
showAmountWithoutPriceOrCommodity Hledger.Data.Amount Hledger/Data/Amount.hs:251:1-81 75287 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 75288 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 75289 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 75290 1 0.0 0.0 0.0 0.0
CAF:isZeroMixedAmount1 Hledger.Data.Amount <no location info> 22005 0 0.0 0.0 0.0 0.0
isZeroMixedAmount Hledger.Data.Amount Hledger/Data/Amount.hs:502:1-91 74772 1 0.0 0.0 0.0 0.0
CAF:journalAmounts Hledger.Data.Journal Hledger/Data/Journal.hs:837:1-14 21279 0 0.0 0.0 0.0 0.0
journalAmounts Hledger.Data.Journal Hledger/Data/Journal.hs:837:1-66 74325 1 0.0 0.0 0.0 0.0
CAF:journalBalanceTransactions10 Hledger.Data.Journal <no location info> 21252 0 0.0 0.0 0.0 0.0
CAF:journalBalanceTransactions11 Hledger.Data.Journal <no location info> 21251 0 0.0 0.0 0.0 0.0
CAF:journalBalanceTransactions13 Hledger.Data.Journal <no location info> 21296 0 0.0 0.0 0.0 0.0
reader Control.Monad.Reader.Class Control/Monad/Reader/Class.hs:109:5-27 74478 1 0.0 0.0 0.0 0.0
CAF:journalBalanceTransactions14 Hledger.Data.Journal <no location info> 21207 0 0.0 0.0 0.0 0.0
CAF:journalBalanceTransactions16 Hledger.Data.Journal <no location info> 21208 0 0.0 0.0 0.0 0.0
CAF:journalBalanceTransactions7 Hledger.Data.Journal <no location info> 21280 0 0.0 0.0 0.0 0.0
liftModifier Hledger.Data.Journal Hledger/Data/Journal.hs:710:1-42 75376 0 0.0 0.0 0.0 0.0
ask Control.Monad.Reader.Class Control/Monad/Reader/Class.hs:107:5-21 75377 1 0.0 0.0 0.0 0.0
CAF:journalEnvVar Hledger.Read Hledger/Read.hs:70:1-13 18891 0 0.0 0.0 0.0 0.0
journalEnvVar Hledger.Read Hledger/Read.hs:70:1-39 25131 1 0.0 0.0 0.0 0.0
CAF:journalEnvVar2 Hledger.Read Hledger/Read.hs:71:1-14 18892 0 0.0 0.0 0.0 0.0
journalEnvVar2 Hledger.Read Hledger/Read.hs:71:1-34 25133 1 0.0 0.0 0.0 0.0
CAF:journalPostings Hledger.Data.Journal Hledger/Data/Journal.hs:239:1-15 21216 0 0.0 0.0 0.0 0.0
journalPostings Hledger.Data.Journal Hledger/Data/Journal.hs:239:1-45 74155 1 0.0 0.0 0.0 0.0
CAF:journalReload3 Hledger.Cli.Utils <no location info> 23500 0 0.0 0.0 0.0 0.0
CAF:journalp1 Hledger.Read.JournalReader <no location info> 18037 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 25219 1 0.0 0.0 0.0 0.0
CAF:journalp3 Hledger.Read.JournalReader <no location info> 18010 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 35680 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:105:5-20 35681 1 0.0 0.0 0.0 0.0
CAF:journalp4 Hledger.Read.JournalReader <no location info> 18012 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 35625 0 0.0 0.0 0.0 0.0
eof Text.Megaparsec Text/Megaparsec.hs:1136:3-39 35626 1 0.0 0.0 0.0 0.0
CAF:journalp5 Hledger.Read.JournalReader <no location info> 18011 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 35631 0 0.0 0.0 0.0 0.0
eof Text.Megaparsec Text/Megaparsec.hs:1136:3-39 35632 0 0.0 0.0 0.0 0.0
eof Text.Megaparsec Text/Megaparsec.hs:873:3-26 35633 1 0.0 0.0 0.0 0.0
CAF:journalp7 Hledger.Read.JournalReader <no location info> 18036 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 25225 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 25226 1 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 25227 1 0.0 0.0 0.0 0.0
CAF:journalp_f Hledger.Read.JournalReader <no location info> 18009 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 35683 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:105:5-20 35684 0 0.0 0.0 0.0 0.0
return Text.Megaparsec Text/Megaparsec.hs:352:3-15 35685 1 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 35686 1 0.0 0.0 0.0 0.0
CAF:k7_r5Lz5 Hledger.Read.Common <no location info> 18831 0 0.0 0.0 0.0 0.0
postingdatesp Hledger.Read.Common Hledger/Read/Common.hs:(772,1)-(778,35) 28823 0 0.0 0.0 0.0 0.0
postingdatesp.nonp Hledger.Read.Common Hledger/Read/Common.hs:(775,7)-(776,42) 28824 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 28825 1 0.0 0.0 0.0 0.0
CAF:keywordp_r6Kxh Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:298:1-8 17745 0 0.0 0.0 0.0 0.0
keywordp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:298:1-40 25348 1 0.0 0.0 0.0 0.0
CAF:keywordsp_r71nq Hledger.Read.JournalReader <no location info> 17747 0 0.0 0.0 0.0 0.0
keywordsp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:305:1-72 25337 1 0.0 0.0 0.0 0.0
CAF:lastMay Safe Safe.hs:131:1-7 13695 0 0.0 0.0 0.0 0.0
lastMay Safe Safe.hs:131:1-27 24492 1 0.0 0.0 0.0 0.0
CAF:ledgerFromJournal1 Hledger.Data.Ledger <no location info> 21076 0 0.0 0.0 0.0 0.0
ledgerFromJournal Hledger.Data.Ledger Hledger/Data/Ledger.hs:(45,1)-(51,41) 78508 0 0.0 0.0 0.0 0.0
ledgerFromJournal.j' Hledger.Data.Ledger Hledger/Data/Ledger.hs:(48,5)-(49,36) 78509 0 0.0 0.0 0.0 0.0
filterQuery Hledger.Query Hledger/Query.hs:428:1-46 78510 1 0.0 0.0 0.0 0.0
CAF:ledgerFromJournal3 Hledger.Data.Ledger <no location info> 21074 0 0.0 0.0 0.0 0.0
ledgerFromJournal Hledger.Data.Ledger Hledger/Data/Ledger.hs:(45,1)-(51,41) 78461 0 0.0 0.0 0.0 0.0
ledgerFromJournal.(...) Hledger.Data.Ledger Hledger/Data/Ledger.hs:47:5-83 78462 0 0.0 0.0 0.0 0.0
filterQuery Hledger.Query Hledger/Query.hs:428:1-46 78463 1 0.0 0.0 0.0 0.0
CAF:ledgerRootAccount Hledger.Data.Ledger Hledger/Data/Ledger.hs:65:1-17 21079 0 0.0 0.0 0.0 0.0
ledgerRootAccount Hledger.Data.Ledger Hledger/Data/Ledger.hs:65:1-48 78384 1 0.0 0.0 0.0 0.0
CAF:ledgerRootAccount_f Hledger.Data.Ledger <no location info> 21078 0 0.0 0.0 0.0 0.0
ledgerRootAccount Hledger.Data.Ledger Hledger/Data/Ledger.hs:65:1-48 78386 0 0.0 0.0 0.0 0.0
headDef Safe Safe.hs:134:1-37 78387 1 0.0 0.0 0.0 0.0
CAF:leftsymbolamountp2 Hledger.Read.Common <no location info> 18696 0 0.0 0.0 0.0 0.0
leftsymbolamountp Hledger.Read.Common Hledger/Read/Common.hs:(415,1)-(425,26) 25541 1 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 25542 1 0.0 0.0 0.0 0.0
CAF:len1_r71p0 Hledger.Read.JournalReader <no location info> 17810 0 0.0 0.0 0.0 0.0
aliasdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(321,1)-(325,23) 25316 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 25317 0 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 25318 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25324 1 0.0 0.0 0.0 0.0
CAF:len2_r5Lxe Hledger.Read.Common <no location info> 18782 0 0.0 0.0 0.0 0.0
datetagp Hledger.Read.Common Hledger/Read/Common.hs:(797,1)-(818,39) 28798 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 28799 0 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 28800 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 28805 1 0.0 0.0 0.0 0.0
CAF:len2_r71ph Hledger.Read.JournalReader <no location info> 17820 0 0.0 0.0 0.0 0.0
tagdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(357,1)-(362,11) 26227 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 26228 0 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 26229 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 26234 1 0.0 0.0 0.0 0.0
CAF:len4_r71sx Hledger.Read.JournalReader <no location info> 17954 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26138 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 26139 0 0.0 0.0 0.0 0.0
commoditydirectivemultilinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(272,1)-(281,46) 26140 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 26141 0 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 26142 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 26150 1 0.0 0.0 0.0 0.0
CAF:len5_r71sH Hledger.Read.JournalReader <no location info> 17961 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25457 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25458 0 0.0 0.0 0.0 0.0
commoditydirectiveonelinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(259,1)-(266,75) 25459 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 25460 0 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 25461 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25469 1 0.0 0.0 0.0 0.0
CAF:len6_r71sW Hledger.Read.JournalReader <no location info> 17970 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25279 0 0.0 0.0 0.0 0.0
includedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(180,1)-(211,59) 25280 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 25281 0 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 25282 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25289 1 0.0 0.0 0.0 0.0
CAF:len_r5Lss Hledger.Read.Common <no location info> 18517 0 0.0 0.0 0.0 0.0
multilinecommentp Hledger.Read.Common Hledger/Read/Common.hs:(603,1)-(609,40) 35589 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 35590 0 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 35591 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 35597 1 0.0 0.0 0.0 0.0
CAF:len_r71n7 Hledger.Read.JournalReader <no location info> 17739 0 0.0 0.0 0.0 0.0
accountdirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(233,1)-(239,51) 25378 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 25379 0 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 25380 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25386 1 0.0 0.0 0.0 0.0
CAF:lineFormatFromOpts Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:602:1-18 23667 0 0.0 0.0 0.0 0.0
lineFormatFromOpts Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:602:1-87 24071 1 0.0 0.0 0.0 0.0
CAF:linecommentp Hledger.Read.Common Hledger/Read/Common.hs:687:1-12 18491 0 0.0 0.0 0.0 0.0
linecommentp Hledger.Read.Common Hledger/Read/Common.hs:687:1-41 26608 1 0.0 0.0 0.0 0.0
commentStartingWithp Hledger.Read.Common Hledger/Read/Common.hs:(690,1)-(696,19) 26609 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26614 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 26615 1 0.0 0.0 0.0 0.0
CAF:linecommentp1 Hledger.Read.Common <no location info> 18490 0 0.0 0.0 0.0 0.0
CAF:lstrip Hledger.Utils.String Hledger/Utils/String.hs:68:1-6 16712 0 0.0 0.0 0.0 0.0
lstrip Hledger.Utils.String Hledger/Utils/String.hs:68:1-26 83778 1 0.0 0.0 0.0 0.0
CAF:lvl111_r431A Hledger.Query <no location info> 19124 0 0.0 0.0 0.0 0.0
CAF:lvl117_r71oV Hledger.Read.JournalReader <no location info> 17807 0 0.0 0.0 0.0 0.0
CAF:lvl124_r71pc Hledger.Read.JournalReader <no location info> 17817 0 0.0 0.0 0.0 0.0
CAF:lvl126_r4324 Hledger.Query <no location info> 19142 0 0.0 0.0 0.0 0.0
CAF:lvl127_r4325 Hledger.Query <no location info> 19143 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25052 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25053 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25054 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25055 1 0.0 0.0 0.0 0.0
CAF:lvl129_r4327 Hledger.Query <no location info> 19144 0 0.0 0.0 0.0 0.0
CAF:lvl12_r3piY Hledger.Data.Posting <no location info> 20752 0 0.0 0.0 0.0 0.0
accountNameWithoutPostingType Hledger.Data.Posting Hledger/Data/Posting.hs:(244,1)-(247,55) 76809 0 0.0 0.0 0.0 0.0
fromInteger Data.Text.Internal.Fusion.Size Data/Text/Internal/Fusion/Size.hs:(83,5)-(84,42) 76811 0 0.0 0.0 0.0 0.0
CAF:lvl130_r4328 Hledger.Query <no location info> 19145 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25048 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25049 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25050 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25051 1 0.0 0.0 0.0 0.0
CAF:lvl135_r432d Hledger.Query <no location info> 19148 0 0.0 0.0 0.0 0.0
CAF:lvl136_r432e Hledger.Query <no location info> 19149 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25043 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25044 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25047 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25045 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25046 2 0.0 0.0 0.0 0.0
CAF:lvl138_r432g Hledger.Query <no location info> 19150 0 0.0 0.0 0.0 0.0
CAF:lvl139_r432h Hledger.Query <no location info> 19151 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25038 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25039 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25042 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25040 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25041 2 0.0 0.0 0.0 0.0
CAF:lvl141_r432j Hledger.Query <no location info> 19152 0 0.0 0.0 0.0 0.0
CAF:lvl142_r432k Hledger.Query <no location info> 19153 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25034 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25035 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25036 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25037 1 0.0 0.0 0.0 0.0
CAF:lvl144_r432m Hledger.Query <no location info> 19154 0 0.0 0.0 0.0 0.0
CAF:lvl144_r5Lrj Hledger.Read.Common <no location info> 18473 0 0.0 0.0 0.0 0.0
tagvaluep Hledger.Read.Common Hledger/Read/Common.hs:(759,1)-(762,75) 53199 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 53200 1 0.0 0.0 0.0 0.0
CAF:lvl145_r432n Hledger.Query <no location info> 19155 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25029 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25030 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25033 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25031 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25032 2 0.0 0.0 0.0 0.0
CAF:lvl149_r5Lrr Hledger.Read.Common <no location info> 18476 0 0.0 0.0 0.0 0.0
tagvaluep Hledger.Read.Common Hledger/Read/Common.hs:(759,1)-(762,75) 53187 0 0.0 0.0 0.0 0.0
try Text.Megaparsec Text/Megaparsec.hs:868:3-26 53188 1 0.0 0.0 0.0 0.0
CAF:lvl151_r5Lrt Hledger.Read.Common <no location info> 18477 0 0.0 0.0 0.0 0.0
tagvaluep Hledger.Read.Common Hledger/Read/Common.hs:(759,1)-(762,75) 53186 0 0.0 0.0 0.0 0.0
CAF:lvl152_r5Lru Hledger.Read.Common <no location info> 18478 0 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 53184 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 53185 1 0.0 0.0 0.0 0.0
CAF:lvl15_rAXs Hledger.Cli.CliOptions <no location info> 23554 0 0.0 0.0 0.0 0.0
CAF:lvl163_r5LrY Hledger.Read.Common <no location info> 18495 0 0.0 0.0 0.0 0.0
followingcommentp Hledger.Read.Common Hledger/Read/Common.hs:(618,1)-(622,57) 25983 0 0.0 0.0 0.0 0.0
try Text.Megaparsec Text/Megaparsec.hs:1127:3-49 25984 1 0.0 0.0 0.0 0.0
CAF:lvl164_r432G Hledger.Query <no location info> 19164 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25024 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25025 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25028 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25026 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25027 2 0.0 0.0 0.0 0.0
CAF:lvl166_r432I Hledger.Query <no location info> 19165 0 0.0 0.0 0.0 0.0
CAF:lvl167_r432J Hledger.Query <no location info> 19166 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25019 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25020 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25023 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25021 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25022 2 0.0 0.0 0.0 0.0
CAF:lvl169_r432L Hledger.Query <no location info> 19167 0 0.0 0.0 0.0 0.0
CAF:lvl169_r5Lsn Hledger.Read.Common <no location info> 18514 0 0.0 0.0 0.0 0.0
CAF:lvl16_r1JOO Hledger.Utils.Parse <no location info> 16778 0 0.0 0.0 0.0 0.0
restofline Hledger.Utils.Parse Hledger/Utils/Parse.hs:80:1-39 26730 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 26731 1 0.0 0.0 0.0 0.0
CAF:lvl170_r432M Hledger.Query <no location info> 19168 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25014 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25015 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25018 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25016 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25017 2 0.0 0.0 0.0 0.0
CAF:lvl172_r432O Hledger.Query <no location info> 19169 0 0.0 0.0 0.0 0.0
CAF:lvl173_r432P Hledger.Query <no location info> 19170 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25009 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25010 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25013 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25011 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25012 2 0.0 0.0 0.0 0.0
CAF:lvl175_r432R Hledger.Query <no location info> 19171 0 0.0 0.0 0.0 0.0
CAF:lvl176_r432S Hledger.Query <no location info> 19172 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 25004 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25005 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25008 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25006 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25007 2 0.0 0.0 0.0 0.0
CAF:lvl178_r432U Hledger.Query <no location info> 19173 0 0.0 0.0 0.0 0.0
CAF:lvl179_r432V Hledger.Query <no location info> 19174 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 24999 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 25000 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 25003 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 25001 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 25002 2 0.0 0.0 0.0 0.0
CAF:lvl180_r432W Hledger.Query <no location info> 19175 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 24994 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24995 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24998 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24996 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24997 2 0.0 0.0 0.0 0.0
CAF:lvl182_r432Y Hledger.Query <no location info> 19176 0 0.0 0.0 0.0 0.0
CAF:lvl183_r432Z Hledger.Query <no location info> 19177 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 24989 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24990 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24993 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24991 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24992 2 0.0 0.0 0.0 0.0
CAF:lvl184_r4330 Hledger.Query <no location info> 19178 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 24985 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24986 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24987 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24988 1 0.0 0.0 0.0 0.0
CAF:lvl186_r4332 Hledger.Query <no location info> 19179 0 0.0 0.0 0.0 0.0
CAF:lvl187_r4333 Hledger.Query <no location info> 19180 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 24980 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24981 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24984 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24982 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24983 2 0.0 0.0 0.0 0.0
CAF:lvl187_r5Lt3 Hledger.Read.Common <no location info> 18581 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25687 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 25688 1 0.0 0.0 0.0 0.0
CAF:lvl188_r5Lt4 Hledger.Read.Common <no location info> 18582 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25682 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 25683 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 25694 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 25695 1 0.0 0.0 0.0 0.0
CAF:lvl189_r4335 Hledger.Query <no location info> 19181 0 0.0 0.0 0.0 0.0
CAF:lvl18_r4Lkn Text.Regex.TDFA.ReadRegex <no location info> 15836 0 0.0 0.0 0.0 0.0
CAF:lvl190_r4336 Hledger.Query <no location info> 19182 0 0.0 0.0 0.0 0.0
parseQueryTerm Hledger.Query Hledger/Query.hs:(257,1)-(288,61) 24973 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24974 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24977 4 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24975 3 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24976 3 0.0 0.0 0.0 0.0
CAF:lvl190_r5Lt7 Hledger.Read.Common <no location info> 18583 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25714 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 25715 1 0.0 0.0 0.0 0.0
CAF:lvl191_r5Lt8 Hledger.Read.Common <no location info> 18584 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25712 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 25713 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 25716 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 25717 1 0.0 0.0 0.0 0.0
CAF:lvl192_r71ss Hledger.Read.JournalReader <no location info> 17951 0 0.0 0.0 0.0 0.0
CAF:lvl196_r5Ltf Hledger.Read.Common <no location info> 18585 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25726 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 25727 1 0.0 0.0 0.0 0.0
CAF:lvl197_r5Ltg Hledger.Read.Common <no location info> 18586 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25724 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 25725 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 25728 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 25729 1 0.0 0.0 0.0 0.0
CAF:lvl1_r20hw Hledger.Utils.Text <no location info> 16629 0 0.0 0.0 0.0 0.0
textUnbracket Hledger.Utils.Text Hledger/Utils/Text.hs:(188,1)-(190,19) 77581 0 0.0 0.0 0.0 0.0
fromInteger Data.Text.Internal.Fusion.Size Data/Text/Internal/Fusion/Size.hs:(83,5)-(84,42) 77582 0 0.0 0.0 0.0 0.0
CAF:lvl1_rfnM Data.Decimal <no location info> 16596 0 0.0 0.0 0.0 0.0
CAF:lvl200_r71sI Hledger.Read.JournalReader <no location info> 17962 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25481 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25482 0 0.0 0.0 0.0 0.0
commoditydirectiveonelinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(259,1)-(266,75) 25483 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 25484 0 0.0 0.0 0.0 0.0
chunkEmpty Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:228:3-27 25485 1 0.0 0.0 0.0 0.0
CAF:lvl201_r5Ltk Hledger.Read.Common <no location info> 18587 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25675 0 0.0 0.0 0.0 0.0
choice' Hledger.Utils.Parse Hledger/Utils/Parse.hs:34:1-26 25676 0 0.0 0.0 0.0 0.0
CAF:lvl202_r5Ltm Hledger.Read.Common <no location info> 18589 0 0.0 0.0 0.0 0.0
return Text.Megaparsec Text/Megaparsec.hs:352:3-15 25753 1 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 25754 1 0.0 0.0 0.0 0.0
CAF:lvl206_r71sR Hledger.Read.JournalReader <no location info> 17967 0 0.0 0.0 0.0 0.0
CAF:lvl210_r5Ltu Hledger.Read.Common <no location info> 18592 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25775 0 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 25776 1 0.0 0.0 0.0 0.0
CAF:lvl210_r71sX Hledger.Read.JournalReader <no location info> 17971 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26682 0 0.0 0.0 0.0 0.0
includedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(180,1)-(211,59) 26683 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 26684 0 0.0 0.0 0.0 0.0
chunkEmpty Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:228:3-27 26685 1 0.0 0.0 0.0 0.0
CAF:lvl212_r5Ltw Hledger.Read.Common <no location info> 18593 0 0.0 0.0 0.0 0.0
CAF:lvl215_r5Ltz Hledger.Read.Common <no location info> 18595 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 74959 0 0.0 0.0 0.0 0.0
numberp.quantity Hledger.Read.Common Hledger/Read/Common.hs:571:7-46 74960 0 0.0 0.0 0.0 0.0
readsPrec Data.Decimal Data/Decimal.hs:167:5-41 74961 1 0.0 0.0 0.0 0.0
readDecimalP Data.Decimal Data/Decimal.hs:(172,1)-(194,33) 74963 1 0.0 0.0 0.0 0.0
readDecimalP.myOpt Data.Decimal Data/Decimal.hs:194:8-33 74964 1 0.0 0.0 0.0 0.0
CAF:lvl216_r5LtA Hledger.Read.Common <no location info> 18596 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 74957 0 0.0 0.0 0.0 0.0
numberp.quantity Hledger.Read.Common Hledger/Read/Common.hs:571:7-46 74958 0 0.0 0.0 0.0 0.0
CAF:lvl221_r5LtH Hledger.Read.Common <no location info> 18611 0 0.0 0.0 0.0 0.0
accountnamep Hledger.Read.Common Hledger/Read/Common.hs:(328,1)-(340,65) 28101 0 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 28102 1 0.0 0.0 0.0 0.0
CAF:lvl226_r5LtT Hledger.Read.Common <no location info> 18626 0 0.0 0.0 0.0 0.0
codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-106 33398 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 33399 1 0.0 0.0 0.0 0.0
CAF:lvl22_r4Lks Text.Regex.TDFA.ReadRegex <no location info> 15838 0 0.0 0.0 0.0 0.0
CAF:lvl231_r5Lu1 Hledger.Read.Common <no location info> 18628 0 0.0 0.0 0.0 0.0
codep Hledger.Read.Common Hledger/Read/Common.hs:216:1-106 33391 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 33392 1 0.0 0.0 0.0 0.0
CAF:lvl236_r56fu Hledger.Reports.ReportOptions <no location info> 17431 0 0.0 0.0 0.0 0.0
CAF:lvl236_r5Lu8 Hledger.Read.Common <no location info> 18668 0 0.0 0.0 0.0 0.0
nosymbolamountp Hledger.Read.Common Hledger/Read/Common.hs:(439,1)-(449,24) 74422 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 74423 0 0.0 0.0 0.0 0.0
nosymbolamountp.(...) Hledger.Read.Common Hledger/Read/Common.hs:(445,7)-(447,105) 74424 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 74425 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 74426 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 74427 1 0.0 0.0 0.0 0.0
CAF:lvl239_r56fx Hledger.Reports.ReportOptions <no location info> 17432 0 0.0 0.0 0.0 0.0
CAF:lvl23_rUXY Hledger.Cli.Utils <no location info> 23529 0 0.0 0.0 0.0 0.0
withJournalDo Hledger.Cli.Utils Hledger/Cli/Utils.hs:(63,1)-(76,20) 78429 0 0.0 0.0 0.0 0.0
withJournalDo.f Hledger.Cli.Utils Hledger/Cli/Utils.hs:(69,7)-(75,56) 78430 0 0.0 0.0 0.0 0.0
pivotByOpts Hledger.Cli.Utils Hledger/Cli/Utils.hs:(80,1)-(83,18) 78431 0 0.0 0.0 0.0 0.0
maybestringopt Hledger.Data.RawOptions Hledger/Data/RawOptions.hs:48:1-100 78432 1 0.0 0.0 0.0 0.0
CAF:lvl242_r56fA Hledger.Reports.ReportOptions <no location info> 17433 0 0.0 0.0 0.0 0.0
CAF:lvl244_r56fE Hledger.Reports.ReportOptions <no location info> 17437 0 0.0 0.0 0.0 0.0
CAF:lvl246_r56fG Hledger.Reports.ReportOptions <no location info> 17438 0 0.0 0.0 0.0 0.0
CAF:lvl248_r56fI Hledger.Reports.ReportOptions <no location info> 17439 0 0.0 0.0 0.0 0.0
CAF:lvl24_r8CUM Hledger.Reports.BalanceReport <no location info> 17253 0 0.0 0.0 0.0 0.0
balanceReport Hledger.Reports.BalanceReport Hledger/Reports/BalanceReport.hs:(84,1)-(123,93) 83317 0 0.0 0.0 0.0 0.0
balanceReport.total Hledger.Reports.BalanceReport Hledger/Reports/BalanceReport.hs:(119,7)-(123,93) 83318 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 83319 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 83320 0 0.0 0.0 0.0 0.0
fromInteger Data.Decimal Data/Decimal.hs:214:5-46 83379 1 0.0 0.0 0.0 0.0
CAF:lvl24_rUXZ Hledger.Cli.Utils <no location info> 23530 0 0.0 0.0 0.0 0.0
withJournalDo Hledger.Cli.Utils Hledger/Cli/Utils.hs:(63,1)-(76,20) 78436 0 0.0 0.0 0.0 0.0
withJournalDo.f Hledger.Cli.Utils Hledger/Cli/Utils.hs:(69,7)-(75,56) 78437 0 0.0 0.0 0.0 0.0
anonymiseByOpts Hledger.Cli.Utils Hledger/Cli/Utils.hs:(87,1)-(90,17) 78438 0 0.0 0.0 0.0 0.0
maybestringopt Hledger.Data.RawOptions Hledger/Data/RawOptions.hs:48:1-100 78439 1 0.0 0.0 0.0 0.0
CAF:lvl250_r56fK Hledger.Reports.ReportOptions <no location info> 17440 0 0.0 0.0 0.0 0.0
CAF:lvl258_r56fT Hledger.Reports.ReportOptions <no location info> 17444 0 0.0 0.0 0.0 0.0
CAF:lvl25_r8CUN Hledger.Reports.BalanceReport <no location info> 17254 0 0.0 0.0 0.0 0.0
balanceReport Hledger.Reports.BalanceReport Hledger/Reports/BalanceReport.hs:(84,1)-(123,93) 83313 0 0.0 0.0 0.0 0.0
balanceReport.total Hledger.Reports.BalanceReport Hledger/Reports/BalanceReport.hs:(119,7)-(123,93) 83314 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 83315 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 83316 1 0.0 0.0 0.0 0.0
CAF:lvl260_r56fV Hledger.Reports.ReportOptions <no location info> 17445 0 0.0 0.0 0.0 0.0
CAF:lvl262_r56fX Hledger.Reports.ReportOptions <no location info> 17446 0 0.0 0.0 0.0 0.0
CAF:lvl264_r56fZ Hledger.Reports.ReportOptions <no location info> 17447 0 0.0 0.0 0.0 0.0
CAF:lvl266_r56g1 Hledger.Reports.ReportOptions <no location info> 17448 0 0.0 0.0 0.0 0.0
CAF:lvl268_r56g3 Hledger.Reports.ReportOptions <no location info> 17449 0 0.0 0.0 0.0 0.0
CAF:lvl26_r4Lkx Text.Regex.TDFA.ReadRegex <no location info> 15840 0 0.0 0.0 0.0 0.0
CAF:lvl26_r8CUO Hledger.Reports.BalanceReport <no location info> 17255 0 0.0 0.0 0.0 0.0
balanceReport Hledger.Reports.BalanceReport Hledger/Reports/BalanceReport.hs:(84,1)-(123,93) 83309 0 0.0 0.0 0.0 0.0
balanceReport.total Hledger.Reports.BalanceReport Hledger/Reports/BalanceReport.hs:(119,7)-(123,93) 83310 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 83311 1 0.0 0.0 0.0 0.0
CAF:lvl271_r5Lw0 Hledger.Read.Common <no location info> 18733 0 0.0 0.0 0.0 0.0
datep Hledger.Read.Common Hledger/Read/Common.hs:(228,1)-(249,28) 27503 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 27504 1 0.0 0.0 0.0 0.0
CAF:lvl273_r5Lw2 Hledger.Read.Common <no location info> 18734 0 0.0 0.0 0.0 0.0
datep Hledger.Read.Common Hledger/Read/Common.hs:(228,1)-(249,28) 27496 0 0.0 0.0 0.0 0.0
choice' Hledger.Utils.Parse Hledger/Utils/Parse.hs:34:1-26 27497 0 0.0 0.0 0.0 0.0
CAF:lvl274_r56g9 Hledger.Reports.ReportOptions <no location info> 17452 0 0.0 0.0 0.0 0.0
CAF:lvl276_r56gb Hledger.Reports.ReportOptions <no location info> 17453 0 0.0 0.0 0.0 0.0
CAF:lvl276_rkUM Data.HashTable.Internal.Utils <no location info> 15318 0 0.0 0.0 0.0 0.0
primeSizes Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:(114,1)-(234,40) 74117 0 0.0 0.0 0.0 0.0
sSize Data.Vector.Fusion.Bundle.Monadic Data/Vector/Fusion/Bundle/Monadic.hs:124:30-34 74119 1 0.0 0.0 0.0 0.0
upperBound Data.Vector.Fusion.Bundle.Size Data/Vector/Fusion/Bundle/Size.hs:(118,1)-(120,30) 74118 1 0.0 0.0 0.0 0.0
CAF:lvl279_r56gi Hledger.Reports.ReportOptions <no location info> 17455 0 0.0 0.0 0.0 0.0
CAF:lvl280_r5Lwb Hledger.Read.Common <no location info> 18738 0 0.0 0.0 0.0 0.0
datep Hledger.Read.Common Hledger/Read/Common.hs:(228,1)-(249,28) 27607 0 0.0 0.0 0.0 0.0
datep.maybedate Hledger.Read.Common Hledger/Read/Common.hs:245:7-63 27608 0 0.0 0.0 0.0 0.0
CAF:lvl281_r56gk Hledger.Reports.ReportOptions <no location info> 17456 0 0.0 0.0 0.0 0.0
CAF:lvl281_r5Lwc Hledger.Read.Common <no location info> 18739 0 0.0 0.0 0.0 0.0
datep Hledger.Read.Common Hledger/Read/Common.hs:(228,1)-(249,28) 27602 0 0.0 0.0 0.0 0.0
datep.maybedate Hledger.Read.Common Hledger/Read/Common.hs:245:7-63 27603 0 0.0 0.0 0.0 0.0
CAF:lvl281_rkUR Data.HashTable.Internal.Utils <no location info> 15323 0 0.0 0.0 0.0 0.0
nextBestPrime Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:(239,1)-(243,38) 74114 0 0.0 0.0 0.0 0.0
nextBestPrime.idx Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:242:5-36 74115 0 0.0 0.0 0.0 0.0
basicLength Data.Vector Data/Vector.hs:271:3-32 74150 1 0.0 0.0 0.0 0.0
CAF:lvl282_rkUS Data.HashTable.Internal.Utils <no location info> 15324 0 0.0 0.0 0.0 0.0
nextBestPrime Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:(239,1)-(243,38) 74112 0 0.0 0.0 0.0 0.0
nextBestPrime.idx Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:242:5-36 74113 0 0.0 0.0 0.0 0.0
CAF:lvl286_r56gs Hledger.Reports.ReportOptions <no location info> 17459 0 0.0 0.0 0.0 0.0
CAF:lvl288_r56gu Hledger.Reports.ReportOptions <no location info> 17460 0 0.0 0.0 0.0 0.0
CAF:lvl292_r56gy Hledger.Reports.ReportOptions <no location info> 17462 0 0.0 0.0 0.0 0.0
CAF:lvl294_r56gA Hledger.Reports.ReportOptions <no location info> 17463 0 0.0 0.0 0.0 0.0
CAF:lvl296_r56gC Hledger.Reports.ReportOptions <no location info> 17464 0 0.0 0.0 0.0 0.0
CAF:lvl2_r2m6n Hledger.Cli.Main <no location info> 23948 0 0.0 0.0 0.0 0.0
CAF:lvl301_r56gQ Hledger.Reports.ReportOptions <no location info> 17467 0 0.0 0.0 0.0 0.0
rawOptsToReportOpts Hledger.Reports.ReportOptions Hledger/Reports/ReportOptions.hs:(143,1)-(173,5) 24437 0 0.0 0.0 0.0 0.0
maybestringopt Hledger.Data.RawOptions Hledger/Data/RawOptions.hs:48:1-100 24438 1 0.0 0.0 0.0 0.0
CAF:lvl303_r56gS Hledger.Reports.ReportOptions <no location info> 17469 0 0.0 0.0 0.0 0.0
rawOptsToReportOpts Hledger.Reports.ReportOptions Hledger/Reports/ReportOptions.hs:(143,1)-(173,5) 24065 0 0.0 0.0 0.0 0.0
hSupportsANSI System.Console.ANSI.Unix includes/Common-Include.hs:(104,1)-(107,71) 24066 1 0.0 0.0 0.0 0.0
CAF:lvl307_r5Lx0 Hledger.Read.Common <no location info> 18770 0 0.0 0.0 0.0 0.0
partialbalanceassertionp Hledger.Read.Common Hledger/Read/Common.hs:(481,1)-(489,27) 28420 0 0.0 0.0 0.0 0.0
getPosition Text.Megaparsec Text/Megaparsec.hs:1393:1-51 28421 0 0.0 0.0 0.0 0.0
getParserState Text.Megaparsec Text/Megaparsec.hs:879:3-37 28422 1 0.0 0.0 0.0 0.0
CAF:lvl309_r5Lx9 Hledger.Read.Common <no location info> 18779 0 0.0 0.0 0.0 0.0
CAF:lvl30_r2kXk Hledger.Data.Amount <no location info> 21938 0 0.0 0.0 0.0 0.0
showAmountHelper Hledger.Data.Amount Hledger/Data/Amount.hs:(278,1)-(289,25) 75343 0 0.0 0.0 0.0 0.0
showAmountHelper.(...) Hledger.Data.Amount Hledger/Data/Amount.hs:(286,7)-(287,77) 75344 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 75345 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 75346 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 75347 1 0.0 0.0 0.0 0.0
CAF:lvl33_r2kXn Hledger.Data.Amount <no location info> 21939 0 0.0 0.0 0.0 0.0
CAF:lvl35_r1ZHZ Hledger.Cli.Commands.Balance <no location info> 22915 0 0.0 0.0 0.0 0.0
CAF:lvl35_r2kXp Hledger.Data.Amount <no location info> 21940 0 0.0 0.0 0.0 0.0
CAF:lvl362_r5Lzm Hledger.Read.Common <no location info> 18856 0 0.0 0.0 0.0 0.0
nontagp Hledger.Read.Common Hledger/Read/Common.hs:(730,1)-(733,56) 28677 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 28678 1 0.0 0.0 0.0 0.0
CAF:lvl366_r5Lzw Hledger.Read.Common <no location info> 18862 0 0.0 0.0 0.0 0.0
nontagp Hledger.Read.Common Hledger/Read/Common.hs:(730,1)-(733,56) 28633 0 0.0 0.0 0.0 0.0
lookAhead Text.Megaparsec Text/Megaparsec.hs:869:3-32 28634 1 0.0 0.0 0.0 0.0
CAF:lvl369_r5LzC Hledger.Read.Common <no location info> 18871 0 0.0 0.0 0.0 0.0
followingcommentandtagsp Hledger.Read.Common Hledger/Read/Common.hs:(645,1)-(677,39) 28498 0 0.0 0.0 0.0 0.0
getPosition Text.Megaparsec Text/Megaparsec.hs:1393:1-51 28499 0 0.0 0.0 0.0 0.0
getParserState Text.Megaparsec Text/Megaparsec.hs:1142:3-50 28500 1 0.0 0.0 0.0 0.0
CAF:lvl36_r1ZI0 Hledger.Cli.Commands.Balance <no location info> 22916 0 0.0 0.0 0.0 0.0
balanceReportAsText Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:(401,1)-(422,27) 83627 0 0.0 0.0 0.0 0.0
balanceReportAsText.t Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:(407,7)-(422,27) 83628 0 0.0 0.0 0.0 0.0
balanceReportAsText.t.totallines Hledger.Cli.Commands.Balance Hledger/Cli/Commands/Balance.hs:415:19-121 83629 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 83630 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 83631 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 83632 1 0.0 0.0 0.0 0.0
CAF:lvl374_r5LzK Hledger.Read.Common <no location info> 18873 0 0.0 0.0 0.0 0.0
followingcommentandtagsp Hledger.Read.Common Hledger/Read/Common.hs:(645,1)-(677,39) 28541 0 0.0 0.0 0.0 0.0
followingcommentandtagsp.commentp' Hledger.Read.Common Hledger/Read/Common.hs:653:9-65 28542 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 28543 1 0.0 0.0 0.0 0.0
CAF:lvl378_r5LzV Hledger.Read.Common <no location info> 18877 0 0.0 0.0 0.0 0.0
followingcommentandtagsp Hledger.Read.Common Hledger/Read/Common.hs:(645,1)-(677,39) 41150 0 0.0 0.0 0.0 0.0
followingcommentandtagsp.commentp' Hledger.Read.Common Hledger/Read/Common.hs:653:9-65 41151 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 41152 1 0.0 0.0 0.0 0.0
CAF:lvl37_r4LkL Text.Regex.TDFA.ReadRegex <no location info> 15849 0 0.0 0.0 0.0 0.0
p_post_atom Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(56,1)-(60,30) 79633 0 0.0 0.0 0.0 0.0
p_bound Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:62:1-70 79634 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 79635 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 79636 1 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 79637 1 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 79638 1 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 79645 1 0.0 0.0 0.0 0.0
CAF:lvl382_r5LA5 Hledger.Read.Common <no location info> 18884 0 0.0 0.0 0.0 0.0
followingcommentandtagsp Hledger.Read.Common Hledger/Read/Common.hs:(645,1)-(677,39) 28558 0 0.0 0.0 0.0 0.0
try Text.Megaparsec Text/Megaparsec.hs:868:3-26 28559 1 0.0 0.0 0.0 0.0
CAF:lvl3_r1ZHq Hledger.Cli.Commands.Balance <no location info> 22882 0 0.0 0.0 0.0 0.0
CAF:lvl3_raFc Hledger.Utils.Regex <no location info> 16749 0 0.0 0.0 0.0 0.0
CAF:lvl41_r2kXx Hledger.Data.Amount <no location info> 21960 0 0.0 0.0 0.0 0.0
sumSimilarAmountsUsingFirstPrice Hledger.Data.Amount Hledger/Data/Amount.hs:(451,1)-(452,77) 74854 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 74855 0 0.0 0.0 0.0 0.0
fromInteger Data.Decimal Data/Decimal.hs:214:5-46 74856 1 0.0 0.0 0.0 0.0
CAF:lvl424_r2WVg Hledger.Data.Dates <no location info> 21799 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 25224 1 0.0 0.0 0.0 0.0
CAF:lvl425_r2WVh Hledger.Data.Dates <no location info> 21800 0 0.0 0.0 0.0 0.0
return Text.Megaparsec Text/Megaparsec.hs:352:3-15 26006 1 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 26007 1 0.0 0.0 0.0 0.0
CAF:lvl42_r3AMx Hledger.Data.Transaction <no location info> 20222 0 0.0 0.0 0.0 0.0
priceInferrerFor Hledger.Data.Transaction Hledger/Data/Transaction.hs:(486,1)-(512,20) 74819 0 0.0 0.0 0.0 0.0
priceInferrerFor.sumamounts Hledger.Data.Transaction Hledger/Data/Transaction.hs:492:5-54 74820 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 74821 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 74822 0 0.0 0.0 0.0 0.0
fromInteger Data.Decimal Data/Decimal.hs:214:5-46 74857 1 0.0 0.0 0.0 0.0
CAF:lvl42_r71m0 Hledger.Read.JournalReader <no location info> 17687 0 0.0 0.0 0.0 0.0
postingp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(563,1)-(586,4) 27877 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 27878 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 27879 1 0.0 0.0 0.0 0.0
CAF:lvl432_r2WVo Hledger.Data.Dates <no location info> 21805 0 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 25223 1 0.0 0.0 0.0 0.0
CAF:lvl439_r2WVH Hledger.Data.Dates <no location info> 21816 0 0.0 0.0 0.0 0.0
notFollowedBy Text.Megaparsec Text/Megaparsec.hs:870:3-36 28776 1 0.0 0.0 0.0 0.0
CAF:lvl43_r3AMy Hledger.Data.Transaction <no location info> 20223 0 0.0 0.0 0.0 0.0
priceInferrerFor Hledger.Data.Transaction Hledger/Data/Transaction.hs:(486,1)-(512,20) 74815 0 0.0 0.0 0.0 0.0
priceInferrerFor.sumamounts Hledger.Data.Transaction Hledger/Data/Transaction.hs:492:5-54 74816 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 74817 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 74818 1 0.0 0.0 0.0 0.0
CAF:lvl43_r71m6 Hledger.Read.JournalReader <no location info> 17690 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26691 0 0.0 0.0 0.0 0.0
includedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(180,1)-(211,59) 26692 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 26693 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 26694 1 0.0 0.0 0.0 0.0
CAF:lvl442_r2WVL Hledger.Data.Dates <no location info> 21820 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 27798 1 0.0 0.0 0.0 0.0
CAF:lvl444_r2WVN Hledger.Data.Dates <no location info> 21822 0 0.0 0.0 0.0 0.0
updateParserState Text.Megaparsec Text/Megaparsec.hs:880:3-40 28746 1 0.0 0.0 0.0 0.0
CAF:lvl44_r3AMz Hledger.Data.Transaction <no location info> 20224 0 0.0 0.0 0.0 0.0
priceInferrerFor Hledger.Data.Transaction Hledger/Data/Transaction.hs:(486,1)-(512,20) 74807 0 0.0 0.0 0.0 0.0
priceInferrerFor.sumamounts Hledger.Data.Transaction Hledger/Data/Transaction.hs:492:5-54 74808 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 74809 1 0.0 0.0 0.0 0.0
CAF:lvl46_r2kXE Hledger.Data.Amount <no location info> 21985 0 0.0 0.0 0.0 0.0
sumSimilarAmountsUsingFirstPrice Hledger.Data.Amount Hledger/Data/Amount.hs:(451,1)-(452,77) 74840 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 74841 1 0.0 0.0 0.0 0.0
CAF:lvl46_r71ma Hledger.Read.JournalReader <no location info> 17692 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25500 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25501 0 0.0 0.0 0.0 0.0
commoditydirectiveonelinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(259,1)-(266,75) 25502 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 25503 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 25504 1 0.0 0.0 0.0 0.0
CAF:lvl47_r4LkZ Text.Regex.TDFA.ReadRegex <no location info> 15863 0 0.0 0.0 0.0 0.0
p_set_elem_class Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(121,1)-(122,65) 79879 0 0.0 0.0 0.0 0.0
string Text.Parsec.Char Text/Parsec/Char.hs:151:1-51 79880 1 0.0 0.0 0.0 0.0
CAF:lvl48_r3AMG Hledger.Data.Transaction <no location info> 20258 0 0.0 0.0 0.0 0.0
inferBalancingAmount Hledger.Data.Transaction Hledger/Data/Transaction.hs:(415,1)-(435,66) 76967 0 0.0 0.0 0.0 0.0
inferBalancingAmount.bvsum Hledger.Data.Transaction Hledger/Data/Transaction.hs:428:5-49 76968 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 76969 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 76970 0 0.0 0.0 0.0 0.0
fromInteger Data.Decimal Data/Decimal.hs:214:5-46 76994 1 0.0 0.0 0.0 0.0
CAF:lvl49_r3AMH Hledger.Data.Transaction <no location info> 20259 0 0.0 0.0 0.0 0.0
inferBalancingAmount Hledger.Data.Transaction Hledger/Data/Transaction.hs:(415,1)-(435,66) 76963 0 0.0 0.0 0.0 0.0
inferBalancingAmount.bvsum Hledger.Data.Transaction Hledger/Data/Transaction.hs:428:5-49 76964 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 76965 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 76966 1 0.0 0.0 0.0 0.0
CAF:lvl4_r2m6p Hledger.Cli.Main <no location info> 23949 0 0.0 0.0 0.0 0.0
CAF:lvl4_raFd Hledger.Utils.Regex <no location info> 16750 0 0.0 0.0 0.0 0.0
replaceRegex Hledger.Utils.Regex Hledger/Utils/Regex.hs:119:1-97 81759 0 0.0 0.0 0.0 0.0
replaceMatch Hledger.Utils.Regex Hledger/Utils/Regex.hs:(122,1)-(127,89) 81760 0 0.0 0.0 0.0 0.0
replaceMatch.repl Hledger.Utils.Regex Hledger/Utils/Regex.hs:127:5-89 81761 0 0.0 0.0 0.0 0.0
toRegex Hledger.Utils.Regex Hledger/Utils/Regex.hs:72:1-46 81762 0 0.0 0.0 0.0 0.0
memo Data.MemoUgly Data/MemoUgly.hs:24:1-77 81763 0 0.0 0.0 0.0 0.0
memo.\ Data.MemoUgly Data/MemoUgly.hs:24:56-77 81764 1 0.0 0.0 0.0 0.0
memo.f' Data.MemoUgly Data/MemoUgly.hs:24:14-44 81768 0 0.0 0.0 0.0 0.0
memoIO Data.MemoUgly Data/MemoUgly.hs:(11,1)-(18,13) 81769 0 0.0 0.0 0.0 0.0
memoIO.f' Data.MemoUgly Data/MemoUgly.hs:(13,9)-(17,35) 81770 0 0.0 0.0 0.0 0.0
memoIO.f'.r Data.MemoUgly Data/MemoUgly.hs:16:37-43 81771 1 0.0 0.0 0.0 0.0
makeRegexOpts Text.Regex.TDFA.String Text/Regex/TDFA/String.hs:50:3-56 81772 1 0.0 0.0 0.0 0.0
compile Text.Regex.TDFA.String Text/Regex/TDFA/String.hs:(44,1)-(47,67) 81773 1 0.0 0.0 0.0 0.0
parseRegex Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(28,1)-(31,83) 81774 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 81782 21 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81783 86 0.0 0.0 0.0 0.0
putState Text.Parsec.Prim Text/Parsec/Prim.hs:(750,1)-(751,25) 81984 2 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 81988 4 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 81989 4 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 81990 6 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81996 2 0.0 0.0 0.0 0.0
p_set.sets Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:113:23-66 82355 1 0.0 0.0 0.0 0.0
p_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(91,1)-(96,37) 81997 0 0.0 0.0 0.0 0.0
p_char.p_escaped Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:94:3-82 81998 0 0.0 0.0 0.0 0.0
anyChar Text.Parsec.Char Text/Parsec/Char.hs:130:1-42 81999 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82000 0 0.0 0.0 0.0 0.0
p_post_atom Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(56,1)-(60,30) 82002 1 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82003 4 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82004 4 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82005 1 0.0 0.0 0.0 0.0
p_bound Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:62:1-70 82051 1 0.0 0.0 0.0 0.0
between Text.Parsec.Combinator Text/Parsec/Combinator.hs:(74,1)-(75,57) 82057 1 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 82052 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82001 1 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82356 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82357 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82358 0 0.0 0.0 0.0 0.0
p_post_atom Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(56,1)-(60,30) 82360 1 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82361 2 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82362 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82363 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82359 1 0.0 0.0 0.0 0.0
updateParserState Text.Parsec.Prim Text/Parsec/Prim.hs:(735,1)-(738,34) 81991 0 0.0 0.0 0.0 0.0
updateParserState.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(737,5)-(738,34) 81992 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81993 2 0.0 0.0 0.0 0.0
getState Text.Parsec.Prim Text/Parsec/Prim.hs:745:1-43 81994 0 0.0 0.0 0.0 0.0
getParserState Text.Parsec.Prim Text/Parsec/Prim.hs:725:1-37 81995 0 0.0 0.0 0.0 0.0
updateParserState Text.Parsec.Prim Text/Parsec/Prim.hs:(735,1)-(738,34) 81985 2 0.0 0.0 0.0 0.0
updateParserState.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(737,5)-(738,34) 81986 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81987 2 0.0 0.0 0.0 0.0
updateParserState.\.s' Text.Parsec.Prim Text/Parsec/Prim.hs:737:9-16 82014 2 0.0 0.0 0.0 0.0
putState.\ Text.Parsec.Prim Text/Parsec/Prim.hs:750:43-61 82015 2 0.0 0.0 0.0 0.0
setState Text.Parsec.Prim Text/Parsec/Prim.hs:771:1-19 81983 2 0.0 0.0 0.0 0.0
char_index Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(86,1)-(89,33) 81970 0 0.0 0.0 0.0 0.0
getState Text.Parsec.Prim Text/Parsec/Prim.hs:745:1-43 81971 0 0.0 0.0 0.0 0.0
getState Text.Parsec.Prim Text/Parsec/Prim.hs:745:1-43 81972 0 0.0 0.0 0.0 0.0
getParserState Text.Parsec.Prim Text/Parsec/Prim.hs:725:1-37 81973 0 0.0 0.0 0.0 0.0
updateParserState Text.Parsec.Prim Text/Parsec/Prim.hs:(735,1)-(738,34) 81974 0 0.0 0.0 0.0 0.0
updateParserState.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(737,5)-(738,34) 81975 2 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 81977 4 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 81978 4 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 81979 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81980 2 0.0 0.0 0.0 0.0
stateUser Text.Parsec.Prim Text/Parsec/Prim.hs:172:7-15 81981 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81976 2 0.0 0.0 0.0 0.0
updateParserState.\.s' Text.Parsec.Prim Text/Parsec/Prim.hs:737:9-16 81982 2 0.0 0.0 0.0 0.0
p_anchor Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(79,1)-(84,38) 81798 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81842 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81843 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81844 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81845 3 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 81846 3 0.0 0.0 0.0 0.0
p_piece Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:40:1-47 81847 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81848 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81849 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81850 3 0.0 0.0 0.0 0.0
p_atom Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:42:1-56 81851 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81852 3 0.0 0.0 0.0 0.0
p_atom Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:42:1-56 81853 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81854 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81855 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81856 3 0.0 0.0 0.0 0.0
p_group Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(51,1)-(53,62) 81857 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81819 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81820 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81821 3 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 81799 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81800 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81801 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81802 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81803 6 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81804 6 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 81805 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 81808 6 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 81809 4 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81810 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81811 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81812 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81813 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 81814 6 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81822 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81823 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81824 3 0.0 0.0 0.0 0.0
p_piece Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:40:1-47 81815 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81816 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81817 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81818 3 0.0 0.0 0.0 0.0
string Text.Parsec.Char Text/Parsec/Char.hs:151:1-51 81828 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 81829 3 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 81830 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 81831 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81832 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81833 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81834 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81835 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 81836 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81837 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81838 0 0.0 0.0 0.0 0.0
p_piece Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:40:1-47 81839 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81840 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81841 0 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 81825 0 0.0 0.0 0.0 0.0
try.\ Text.Parsec.Prim Text/Parsec/Prim.hs:477:5-34 81826 3 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81827 3 0.0 0.0 0.0 0.0
p_bracket Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:99:1-72 81882 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82102 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82103 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82104 1 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 81883 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81884 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81885 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81886 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81887 4 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81888 4 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 81889 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 81890 4 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 81891 3 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:141:48-66 82099 1 0.0 0.0 0.0 0.0
updatePosChar Text.Parsec.Pos Text/Parsec/Pos.hs:(113,1)-(117,48) 82100 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82101 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81892 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81893 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81894 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81895 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 81896 3 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82105 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82106 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82107 1 0.0 0.0 0.0 0.0
p_group Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(51,1)-(53,62) 81897 0 0.0 0.0 0.0 0.0
p_atom Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:42:1-56 81898 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81899 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81900 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81901 4 0.0 0.0 0.0 0.0
p_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(91,1)-(96,37) 81902 0 0.0 0.0 0.0 0.0
p_char.p_dot Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:92:3-50 81903 0 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82108 0 0.0 0.0 0.0 0.0
p_branch Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:38:1-40 81786 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 81787 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82094 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82095 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82096 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82097 1 0.0 0.0 0.0 0.0
p_piece Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:40:1-47 82098 0 0.0 0.0 0.0 0.0
p_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(91,1)-(96,37) 81904 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81925 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81926 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81927 4 0.0 0.0 0.0 0.0
p_char.p_dot Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:92:3-50 81905 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 81906 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81907 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81908 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81909 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81910 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81911 2 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 81912 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 81913 2 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 81914 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81915 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81916 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81917 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81918 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 81919 2 0.0 0.0 0.0 0.0
p_bracket Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:99:1-72 81920 0 0.0 0.0 0.0 0.0
p_atom Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:42:1-56 81921 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81922 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81923 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81924 2 0.0 0.0 0.0 0.0
p_char.p_escaped Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:94:3-82 81949 0 0.0 0.0 0.0 0.0
anyChar Text.Parsec.Char Text/Parsec/Char.hs:130:1-42 81962 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 81963 0 0.0 0.0 0.0 0.0
p_char.p_escaped.\ Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:94:46-82 81969 1 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:141:48-66 81966 1 0.0 0.0 0.0 0.0
updatePosChar Text.Parsec.Pos Text/Parsec/Pos.hs:(113,1)-(117,48) 81967 1 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 81965 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81968 1 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 81964 1 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 81950 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81951 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81952 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81953 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81954 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81955 2 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 81956 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 81957 2 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:141:48-66 81959 1 0.0 0.0 0.0 0.0
updatePosChar Text.Parsec.Pos Text/Parsec/Pos.hs:(113,1)-(117,48) 81960 1 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 81958 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81961 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82383 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82384 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82385 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82386 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 82387 1 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82388 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82389 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82390 1 0.0 0.0 0.0 0.0
p_char.p_left_brace Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:93:3-97 81928 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 81932 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81933 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81934 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81935 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81936 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81937 2 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 81938 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 81939 2 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 81940 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81941 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81942 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81943 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81944 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 81945 2 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81946 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81947 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81948 2 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 81929 0 0.0 0.0 0.0 0.0
try.\ Text.Parsec.Prim Text/Parsec/Prim.hs:477:5-34 81930 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81931 2 0.0 0.0 0.0 0.0
p_char.p_other_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(95,3)-(96,37) 82391 0 0.0 0.0 0.0 0.0
noneOf Text.Parsec.Char Text/Parsec/Char.hs:40:1-53 82392 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82393 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82394 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82397 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82398 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82399 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82400 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 82401 1 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82402 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82403 0 0.0 0.0 0.0 0.0
p_char.p_dot Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:92:3-50 82406 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82407 0 0.0 0.0 0.0 0.0
p_char.p_left_brace Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:93:3-97 82404 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82405 0 0.0 0.0 0.0 0.0
p_anchor Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(79,1)-(84,38) 82416 0 0.0 0.0 0.0 0.0
p_piece Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:40:1-47 82417 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82418 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82419 0 0.0 0.0 0.0 0.0
p_post_atom Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(56,1)-(60,30) 82420 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82421 0 0.0 0.0 0.0 0.0
p_atom Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:42:1-56 82408 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82409 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82410 0 0.0 0.0 0.0 0.0
p_anchor Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(79,1)-(84,38) 82415 0 0.0 0.0 0.0 0.0
p_bracket Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:99:1-72 82411 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82412 0 0.0 0.0 0.0 0.0
p_group Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(51,1)-(53,62) 82413 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82414 0 0.0 0.0 0.0 0.0
p_char.p_escaped Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:94:3-82 82395 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82396 0 0.0 0.0 0.0 0.0
putState Text.Parsec.Prim Text/Parsec/Prim.hs:(750,1)-(751,25) 82422 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82423 3 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82424 3 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82425 3 0.0 0.0 0.0 0.0
p_branch Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:38:1-40 82426 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82427 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82428 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82429 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82430 0 0.0 0.0 0.0 0.0
manyAccum.\.walk Text.Parsec.Prim Text/Parsec/Prim.hs:(607,9)-(612,41) 82431 0 0.0 0.0 0.0 0.0
manyAccum.\.walk.\ Text.Parsec.Prim Text/Parsec/Prim.hs:612:22-40 82432 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82433 4 0.0 0.0 0.0 0.0
p_regex Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:34:1-48 82434 0 0.0 0.0 0.0 0.0
sepBy1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:(117,1)-(120,25) 82435 0 0.0 0.0 0.0 0.0
p_group Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(51,1)-(53,62) 81858 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 81862 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81863 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81864 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81865 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81866 3 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81867 3 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 81868 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 81869 3 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 81870 2 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81871 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81872 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81873 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81874 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 81875 3 0.0 0.0 0.0 0.0
p_anchor Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(79,1)-(84,38) 81876 0 0.0 0.0 0.0 0.0
p_atom Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:42:1-56 81877 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81878 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81879 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81880 6 0.0 0.0 0.0 0.0
p_bracket Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:99:1-72 81881 0 0.0 0.0 0.0 0.0
lookAhead Text.Parsec.Prim Text/Parsec/Prim.hs:(485,1)-(488,40) 81859 0 0.0 0.0 0.0 0.0
lookAhead.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(486,37)-(488,40) 81860 3 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81861 3 0.0 0.0 0.0 0.0
p_piece Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:40:1-47 81788 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 81789 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 81790 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81791 6 0.0 0.0 0.0 0.0
p_anchor Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(79,1)-(84,38) 81792 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 81793 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 81794 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 81795 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 81796 3 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81797 3 0.0 0.0 0.0 0.0
p_post_atom Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(56,1)-(60,30) 82006 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82030 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82031 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82032 6 0.0 0.0 0.0 0.0
putState Text.Parsec.Prim Text/Parsec/Prim.hs:(750,1)-(751,25) 82033 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82034 0 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82035 0 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82036 0 0.0 0.0 0.0 0.0
p_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(91,1)-(96,37) 82037 0 0.0 0.0 0.0 0.0
p_char.p_escaped Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:94:3-82 82038 0 0.0 0.0 0.0 0.0
anyChar Text.Parsec.Char Text/Parsec/Char.hs:130:1-42 82039 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82040 0 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82365 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82366 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82367 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82007 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82008 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82009 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82010 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82011 5 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82012 5 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82013 0 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 82017 5 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82016 5 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:141:48-66 82368 1 0.0 0.0 0.0 0.0
updatePosChar Text.Parsec.Pos Text/Parsec/Pos.hs:(113,1)-(117,48) 82369 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82370 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82018 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82019 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82020 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82021 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 82022 4 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82041 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82042 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82043 2 0.0 0.0 0.0 0.0
putState Text.Parsec.Prim Text/Parsec/Prim.hs:(750,1)-(751,25) 82044 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82045 0 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82046 0 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82047 0 0.0 0.0 0.0 0.0
p_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(91,1)-(96,37) 82048 0 0.0 0.0 0.0 0.0
p_char.p_escaped Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:94:3-82 82049 0 0.0 0.0 0.0 0.0
anyChar Text.Parsec.Char Text/Parsec/Char.hs:130:1-42 82050 0 0.0 0.0 0.0 0.0
putState Text.Parsec.Prim Text/Parsec/Prim.hs:(750,1)-(751,25) 82023 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82024 0 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82025 0 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82026 0 0.0 0.0 0.0 0.0
p_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(91,1)-(96,37) 82027 0 0.0 0.0 0.0 0.0
p_char.p_escaped Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:94:3-82 82028 0 0.0 0.0 0.0 0.0
anyChar Text.Parsec.Char Text/Parsec/Char.hs:130:1-42 82029 0 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82364 0 0.0 0.0 0.0 0.0
putState Text.Parsec.Prim Text/Parsec/Prim.hs:(750,1)-(751,25) 82371 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82372 0 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82373 0 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82374 1 0.0 0.0 0.0 0.0
p_branch Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:38:1-40 82375 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82376 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82377 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82378 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82379 0 0.0 0.0 0.0 0.0
manyAccum.\.walk Text.Parsec.Prim Text/Parsec/Prim.hs:(607,9)-(612,41) 82380 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82381 1 0.0 0.0 0.0 0.0
manyAccum.\.walk.\ Text.Parsec.Prim Text/Parsec/Prim.hs:612:22-40 82606 0 0.0 0.0 0.0 0.0
p_piece Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:40:1-47 82382 0 0.0 0.0 0.0 0.0
p_bound Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:62:1-70 82053 0 0.0 0.0 0.0 0.0
between Text.Parsec.Combinator Text/Parsec/Combinator.hs:(74,1)-(75,57) 82066 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82067 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82068 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82069 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82070 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82071 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82072 1 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82073 0 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 82075 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82091 1 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82074 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82076 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82077 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82078 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82079 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 82080 1 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82081 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82082 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82083 1 0.0 0.0 0.0 0.0
putState Text.Parsec.Prim Text/Parsec/Prim.hs:(750,1)-(751,25) 82084 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82085 0 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82086 0 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82087 1 0.0 0.0 0.0 0.0
p_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(91,1)-(96,37) 82088 0 0.0 0.0 0.0 0.0
p_char.p_escaped Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:94:3-82 82089 0 0.0 0.0 0.0 0.0
anyChar Text.Parsec.Char Text/Parsec/Char.hs:130:1-42 82090 0 0.0 0.0 0.0 0.0
p_branch Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:38:1-40 82092 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82093 0 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 82054 0 0.0 0.0 0.0 0.0
try.\ Text.Parsec.Prim Text/Parsec/Prim.hs:477:5-34 82055 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82056 1 0.0 0.0 0.0 0.0
putState Text.Parsec.Prim Text/Parsec/Prim.hs:(750,1)-(751,25) 82058 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82059 0 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82060 0 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82061 0 0.0 0.0 0.0 0.0
p_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(91,1)-(96,37) 82062 0 0.0 0.0 0.0 0.0
p_char.p_escaped Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:94:3-82 82063 0 0.0 0.0 0.0 0.0
anyChar Text.Parsec.Char Text/Parsec/Char.hs:130:1-42 82064 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82065 0 0.0 0.0 0.0 0.0
p_regex Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:34:1-48 81784 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82440 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82441 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82442 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82443 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82444 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82445 1 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82446 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82447 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82448 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82449 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82450 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82451 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 82452 1 0.0 0.0 0.0 0.0
sepBy1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:(117,1)-(120,25) 82453 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82454 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82455 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82456 0 0.0 0.0 0.0 0.0
manyAccum.\.\ Text.Parsec.Prim Text/Parsec/Prim.hs:613:51-60 82457 1 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82459 2 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82460 2 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82461 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82462 1 0.0 0.0 0.0 0.0
p_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(91,1)-(96,37) 82463 0 0.0 0.0 0.0 0.0
p_char.p_other_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(95,3)-(96,37) 82464 0 0.0 0.0 0.0 0.0
noneOf Text.Parsec.Char Text/Parsec/Char.hs:40:1-53 82465 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82458 1 0.0 0.0 0.0 0.0
putState Text.Parsec.Prim Text/Parsec/Prim.hs:(750,1)-(751,25) 82466 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82467 1 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82468 1 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82469 1 0.0 0.0 0.0 0.0
p_branch Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:38:1-40 82470 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82471 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82472 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82473 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82474 0 0.0 0.0 0.0 0.0
manyAccum.\.walk Text.Parsec.Prim Text/Parsec/Prim.hs:(607,9)-(612,41) 82475 0 0.0 0.0 0.0 0.0
manyAccum.\.walk.\ Text.Parsec.Prim Text/Parsec/Prim.hs:612:22-40 82476 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82477 2 0.0 0.0 0.0 0.0
sepBy1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:(117,1)-(120,25) 81785 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82436 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82437 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82438 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82439 1 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82109 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82114 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82115 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82116 1 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82117 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82118 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82119 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82120 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82121 3 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82122 3 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82123 0 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 82125 3 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82124 3 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:141:48-66 82340 1 0.0 0.0 0.0 0.0
updatePosChar Text.Parsec.Pos Text/Parsec/Pos.hs:(113,1)-(117,48) 82341 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82342 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82126 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82127 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82128 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82129 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 82130 2 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82131 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82132 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82133 2 0.0 0.0 0.0 0.0
option Text.Parsec.Combinator Text/Parsec/Combinator.hs:51:1-36 82134 0 0.0 0.0 0.0 0.0
p_set_elem_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(139,1)-(144,19) 82343 0 0.0 0.0 0.0 0.0
noneOf Text.Parsec.Char Text/Parsec/Char.hs:40:1-53 82344 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82345 0 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82346 0 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82347 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82348 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82349 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82350 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82351 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 82352 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82353 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82354 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82149 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82229 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82230 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82231 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82232 1 0.0 0.0 0.0 0.0
p_set_elem Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(118,1)-(119,88) 82233 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82234 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82235 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82236 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82237 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82238 1 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82239 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82240 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82241 1 0.0 0.0 0.0 0.0
p_set_elem_class Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(121,1)-(122,65) 82242 0 0.0 0.0 0.0 0.0
option Text.Parsec.Combinator Text/Parsec/Combinator.hs:51:1-36 82110 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82111 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82112 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82113 1 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82135 0 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82136 0 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82137 1 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82138 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82139 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82140 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82141 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82142 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82143 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 82144 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82145 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82146 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82147 1 0.0 0.0 0.0 0.0
p_bracket Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:99:1-72 82148 0 0.0 0.0 0.0 0.0
p_set_elem Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(118,1)-(119,88) 82150 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82151 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82152 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82153 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82154 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82155 1 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82156 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82157 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82158 1 0.0 0.0 0.0 0.0
p_set_elem_class Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(121,1)-(122,65) 82159 0 0.0 0.0 0.0 0.0
p_set_elem_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(139,1)-(144,19) 82288 0 0.0 0.0 0.0 0.0
noneOf Text.Parsec.Char Text/Parsec/Char.hs:40:1-53 82289 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82290 0 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 82292 1 0.0 0.0 0.0 0.0
noneOf.\ Text.Parsec.Char Text/Parsec/Char.hs:40:38-52 82293 1 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82291 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82326 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82327 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82328 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82329 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 82330 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82331 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82332 0 0.0 0.0 0.0 0.0
p_set_elem_coll Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(127,1)-(128,65) 82295 0 0.0 0.0 0.0 0.0
string Text.Parsec.Char Text/Parsec/Char.hs:151:1-51 82296 0 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82297 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82298 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82299 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82300 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82301 0 0.0 0.0 0.0 0.0
manyAccum.\.\ Text.Parsec.Prim Text/Parsec/Prim.hs:613:51-60 82312 1 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82314 2 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82315 2 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82316 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82317 1 0.0 0.0 0.0 0.0
p_set_elem_range Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(130,1)-(137,85) 82318 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82313 1 0.0 0.0 0.0 0.0
p_set_elem Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(118,1)-(119,88) 82302 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82307 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82308 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82309 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82310 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 82311 1 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82303 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82304 0 0.0 0.0 0.0 0.0
p_set_elem_class Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(121,1)-(122,65) 82306 0 0.0 0.0 0.0 0.0
p_set_elem_equiv Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(124,1)-(125,65) 82305 0 0.0 0.0 0.0 0.0
p_set_elem_range Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(130,1)-(137,85) 82294 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82319 0 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82320 0 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82321 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82322 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82333 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82334 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82335 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82336 0 0.0 0.0 0.0 0.0
labels.\.eerr' Text.Parsec.Prim Text/Parsec/Prim.hs:361:9-51 82337 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82338 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82339 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82325 0 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82323 0 0.0 0.0 0.0 0.0
option Text.Parsec.Combinator Text/Parsec/Combinator.hs:51:1-36 82324 0 0.0 0.0 0.0 0.0
p_set_elem_class Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(121,1)-(122,65) 82160 0 0.0 0.0 0.0 0.0
between Text.Parsec.Combinator Text/Parsec/Combinator.hs:(74,1)-(75,57) 82164 0 0.0 0.0 0.0 0.0
string Text.Parsec.Char Text/Parsec/Char.hs:151:1-51 82165 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82166 2 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82243 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82244 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82245 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82246 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82247 0 0.0 0.0 0.0 0.0
p_set_elem Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(118,1)-(119,88) 82248 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82249 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82250 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82251 2 0.0 0.0 0.0 0.0
p_set_elem_equiv Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(124,1)-(125,65) 82252 0 0.0 0.0 0.0 0.0
p_set_elem Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(118,1)-(119,88) 82167 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82168 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82169 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82170 2 0.0 0.0 0.0 0.0
p_set_elem_equiv Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(124,1)-(125,65) 82171 0 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 82161 0 0.0 0.0 0.0 0.0
try.\ Text.Parsec.Prim Text/Parsec/Prim.hs:477:5-34 82162 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82163 2 0.0 0.0 0.0 0.0
p_set_elem_coll Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(127,1)-(128,65) 82185 0 0.0 0.0 0.0 0.0
between Text.Parsec.Combinator Text/Parsec/Combinator.hs:(74,1)-(75,57) 82189 0 0.0 0.0 0.0 0.0
string Text.Parsec.Char Text/Parsec/Char.hs:151:1-51 82190 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82191 2 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82263 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82264 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82265 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82266 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82267 0 0.0 0.0 0.0 0.0
p_set_elem Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(118,1)-(119,88) 82268 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82269 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82270 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82271 2 0.0 0.0 0.0 0.0
p_set_elem_range Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(130,1)-(137,85) 82272 0 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 82273 0 0.0 0.0 0.0 0.0
try.\ Text.Parsec.Prim Text/Parsec/Prim.hs:477:5-34 82274 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82275 1 0.0 0.0 0.0 0.0
p_set_elem Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(118,1)-(119,88) 82193 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82194 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82195 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82196 2 0.0 0.0 0.0 0.0
p_set_elem_range Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(130,1)-(137,85) 82197 0 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 82198 0 0.0 0.0 0.0 0.0
try.\ Text.Parsec.Prim Text/Parsec/Prim.hs:477:5-34 82199 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82200 1 0.0 0.0 0.0 0.0
p_set_elem_equiv Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(124,1)-(125,65) 82192 0 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 82186 0 0.0 0.0 0.0 0.0
try.\ Text.Parsec.Prim Text/Parsec/Prim.hs:477:5-34 82187 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82188 2 0.0 0.0 0.0 0.0
p_set_elem_equiv Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(124,1)-(125,65) 82172 0 0.0 0.0 0.0 0.0
between Text.Parsec.Combinator Text/Parsec/Combinator.hs:(74,1)-(75,57) 82176 0 0.0 0.0 0.0 0.0
string Text.Parsec.Char Text/Parsec/Char.hs:151:1-51 82177 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82178 2 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82253 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82254 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82255 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82256 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82257 0 0.0 0.0 0.0 0.0
p_set_elem Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(118,1)-(119,88) 82258 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82259 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82260 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82261 2 0.0 0.0 0.0 0.0
p_set_elem_coll Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(127,1)-(128,65) 82262 0 0.0 0.0 0.0 0.0
p_set_elem Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(118,1)-(119,88) 82180 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82181 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82182 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82183 2 0.0 0.0 0.0 0.0
p_set_elem_coll Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(127,1)-(128,65) 82184 0 0.0 0.0 0.0 0.0
p_set_elem_class Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(121,1)-(122,65) 82179 0 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 82173 0 0.0 0.0 0.0 0.0
try.\ Text.Parsec.Prim Text/Parsec/Prim.hs:477:5-34 82174 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82175 2 0.0 0.0 0.0 0.0
p_set_elem_range Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(130,1)-(137,85) 82201 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82210 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82211 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82212 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82213 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82214 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82215 1 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82216 0 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:141:48-66 82219 1 0.0 0.0 0.0 0.0
updatePosChar Text.Parsec.Pos Text/Parsec/Pos.hs:(113,1)-(117,48) 82220 1 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 82218 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82221 1 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82217 1 0.0 0.0 0.0 0.0
noneOf Text.Parsec.Char Text/Parsec/Char.hs:40:1-53 82222 0 0.0 0.0 0.0 0.0
noneOf Text.Parsec.Char Text/Parsec/Char.hs:40:1-53 82202 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82203 0 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:142:40-70 82205 3 0.0 0.0 0.0 0.0
noneOf.\ Text.Parsec.Char Text/Parsec/Char.hs:40:38-52 82206 3 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82204 3 0.0 0.0 0.0 0.0
satisfy.\ Text.Parsec.Char Text/Parsec/Char.hs:141:48-66 82207 2 0.0 0.0 0.0 0.0
updatePosChar Text.Parsec.Pos Text/Parsec/Pos.hs:(113,1)-(117,48) 82208 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82209 2 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82223 1 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82224 1 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82225 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82226 1 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82227 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82228 0 0.0 0.0 0.0 0.0
p_set_elem_coll Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(127,1)-(128,65) 82276 0 0.0 0.0 0.0 0.0
string Text.Parsec.Char Text/Parsec/Char.hs:151:1-51 82277 0 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 82278 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82279 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82280 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82281 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82282 0 0.0 0.0 0.0 0.0
p_set_elem Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(118,1)-(119,88) 82283 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82284 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82285 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82286 1 0.0 0.0 0.0 0.0
p_set_elem_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(139,1)-(144,19) 82287 0 0.0 0.0 0.0 0.0
eof Text.Parsec.Combinator Text/Parsec/Combinator.hs:242:1-63 82478 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82479 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82480 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82481 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82482 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82483 1 0.0 0.0 0.0 0.0
anyToken Text.Parsec.Combinator Text/Parsec/Combinator.hs:234:1-66 82493 0 0.0 0.0 0.0 0.0
uncons Text.Parsec.Prim Text/Parsec/Prim.hs:(386,5)-(387,40) 82494 1 0.0 0.0 0.0 0.0
notFollowedBy Text.Parsec.Combinator Text/Parsec/Combinator.hs:(257,1)-(259,27) 82495 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82496 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82497 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82498 1 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82499 0 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82500 0 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82501 1 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82502 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82503 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82504 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82505 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82506 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82507 0 0.0 0.0 0.0 0.0
labels.\.eok' Text.Parsec.Prim Text/Parsec/Prim.hs:(358,9)-(360,49) 82508 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 82509 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82510 1 0.0 0.0 0.0 0.0
p_regex Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:34:1-48 82511 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82512 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82513 0 0.0 0.0 0.0 0.0
putState Text.Parsec.Prim Text/Parsec/Prim.hs:(750,1)-(751,25) 82514 0 0.0 0.0 0.0 0.0
p_branch Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:38:1-40 82515 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82516 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82517 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82518 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82519 0 0.0 0.0 0.0 0.0
manyAccum.\.walk Text.Parsec.Prim Text/Parsec/Prim.hs:(607,9)-(612,41) 82520 0 0.0 0.0 0.0 0.0
manyAccum.\.walk.\ Text.Parsec.Prim Text/Parsec/Prim.hs:612:22-40 82521 0 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 82522 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82523 1 0.0 0.0 0.0 0.0
notFollowedBy Text.Parsec.Combinator Text/Parsec/Combinator.hs:(257,1)-(259,27) 82484 0 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82488 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82489 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82490 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 82491 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82492 1 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 82485 0 0.0 0.0 0.0 0.0
try.\ Text.Parsec.Prim Text/Parsec/Prim.hs:477:5-34 82486 2 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82487 2 0.0 0.0 0.0 0.0
getState Text.Parsec.Prim Text/Parsec/Prim.hs:745:1-43 82524 0 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 82525 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82526 1 0.0 0.0 0.0 0.0
getParserState Text.Parsec.Prim Text/Parsec/Prim.hs:725:1-37 82527 0 0.0 0.0 0.0 0.0
updateParserState Text.Parsec.Prim Text/Parsec/Prim.hs:(735,1)-(738,34) 82528 0 0.0 0.0 0.0 0.0
updateParserState.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(737,5)-(738,34) 82529 1 0.0 0.0 0.0 0.0
updateParserState.\.s' Text.Parsec.Prim Text/Parsec/Prim.hs:737:9-16 82546 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 82530 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82532 2 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82533 2 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82534 2 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 82547 0 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 82548 0 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 82549 0 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 82550 0 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 82551 0 0.0 0.0 0.0 0.0
labels.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(358,5)-(363,39) 82552 0 0.0 0.0 0.0 0.0
labels.\.eok' Text.Parsec.Prim Text/Parsec/Prim.hs:(358,9)-(360,49) 82553 0 0.0 0.0 0.0 0.0
eof Text.Parsec.Combinator Text/Parsec/Combinator.hs:242:1-63 82535 0 0.0 0.0 0.0 0.0
anyToken Text.Parsec.Combinator Text/Parsec/Combinator.hs:234:1-66 82536 0 0.0 0.0 0.0 0.0
notFollowedBy Text.Parsec.Combinator Text/Parsec/Combinator.hs:(257,1)-(259,27) 82537 0 0.0 0.0 0.0 0.0
p_branch Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:38:1-40 82538 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82539 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82540 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82541 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82542 0 0.0 0.0 0.0 0.0
manyAccum.\.walk Text.Parsec.Prim Text/Parsec/Prim.hs:(607,9)-(612,41) 82543 0 0.0 0.0 0.0 0.0
manyAccum.\.walk.\ Text.Parsec.Prim Text/Parsec/Prim.hs:612:22-40 82544 0 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 82531 2 0.0 0.0 0.0 0.0
stateUser Text.Parsec.Prim Text/Parsec/Prim.hs:172:7-15 82545 1 0.0 0.0 0.0 0.0
p_regex Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:34:1-48 82554 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 82555 0 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 82556 0 0.0 0.0 0.0 0.0
putState Text.Parsec.Prim Text/Parsec/Prim.hs:(750,1)-(751,25) 82557 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 82558 0 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 82559 0 0.0 0.0 0.0 0.0
parserReturn.\ Text.Parsec.Prim Text/Parsec/Prim.hs:234:7-30 82560 0 0.0 0.0 0.0 0.0
p_branch Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:38:1-40 82561 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 82562 0 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 82563 0 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 82564 0 0.0 0.0 0.0 0.0
manyAccum.\ Text.Parsec.Prim Text/Parsec/Prim.hs:(607,5)-(613,61) 82565 0 0.0 0.0 0.0 0.0
manyAccum.\.walk Text.Parsec.Prim Text/Parsec/Prim.hs:(607,9)-(612,41) 82566 0 0.0 0.0 0.0 0.0
manyAccum.\.walk.\ Text.Parsec.Prim Text/Parsec/Prim.hs:612:22-40 82567 0 0.0 0.0 0.0 0.0
runParser Text.ParserCombinators.Parsec.Prim Text/ParserCombinators/Parsec/Prim.hs:62:1-23 82568 0 0.0 0.0 0.0 0.0
runParser Text.Parsec.Prim Text/Parsec/Prim.hs:663:1-16 82569 0 0.0 0.0 0.0 0.0
runP Text.Parsec.Prim Text/Parsec/Prim.hs:636:1-48 82570 0 0.0 0.0 0.0 0.0
runPT Text.Parsec.Prim Text/Parsec/Prim.hs:(622,1)-(632,31) 82571 0 0.0 0.0 0.0 0.0
runParsecT Text.Parsec.Prim Text/Parsec/Prim.hs:(137,1)-(141,56) 82572 0 0.0 0.0 0.0 0.0
runParsecT.cok Text.Parsec.Prim Text/Parsec/Prim.hs:138:11-65 82573 1 0.0 0.0 0.0 0.0
runParser Text.ParserCombinators.Parsec.Prim Text/ParserCombinators/Parsec/Prim.hs:62:1-23 81775 0 0.0 0.0 0.0 0.0
runParser Text.Parsec.Prim Text/Parsec/Prim.hs:663:1-16 81776 0 0.0 0.0 0.0 0.0
runP Text.Parsec.Prim Text/Parsec/Prim.hs:636:1-48 81777 1 0.0 0.0 0.0 0.0
runPT Text.Parsec.Prim Text/Parsec/Prim.hs:(622,1)-(632,31) 81778 1 0.0 0.0 0.0 0.0
initialPos Text.Parsec.Pos Text/Parsec/Pos.hs:(54,1)-(55,21) 81806 1 0.0 0.0 0.0 0.0
newPos Text.Parsec.Pos Text/Parsec/Pos.hs:(47,1)-(48,32) 81807 1 0.0 0.0 0.0 0.0
runPT.parserReply Text.Parsec.Prim Text/Parsec/Prim.hs:(629,9)-(632,31) 81779 1 0.0 0.0 0.0 0.0
runParsecT Text.Parsec.Prim Text/Parsec/Prim.hs:(137,1)-(141,56) 81780 1 0.0 0.0 0.0 0.0
unParser Text.Parsec.Prim Text/Parsec/Prim.hs:120:16-23 81781 1 0.0 0.0 0.0 0.0
patternToRegex Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:160:1-96 82575 1 0.0 0.0 0.0 0.0
nfaToDFA Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(53,1)-(157,65) 82579 1 0.0 0.0 0.0 0.0
nfaToDFA.dfa Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:54:3-33 82580 1 0.0 0.0 0.0 0.0
nfaToDFA.indexesToDFA Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:59:3-72 82701 0 0.0 0.0 0.0 0.0
nfaToDFA.indexesToDFA Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:59:54-72 82702 0 0.0 0.0 0.0 0.0
lookupAsc Text.Regex.TDFA.IntArrTrieSet Text/Regex/TDFA/IntArrTrieSet.hs:(23,1)-(25,64) 82703 1 0.0 0.0 0.0 0.0
lookupAsc.\ Text.Regex.TDFA.IntArrTrieSet Text/Regex/TDFA/IntArrTrieSet.hs:(24,13)-(25,63) 82704 2 0.0 0.0 0.0 0.0
nfaToDFA.ifa Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:57:3-54 82737 1 0.0 0.0 0.0 0.0
multiline Text.Regex.TDFA.Common Text/Regex/TDFA/Common.hs:86:5-13 82738 1 0.0 0.0 0.0 0.0
nfaToDFA.indexBounds Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:55:3-28 82757 1 0.0 0.0 0.0 0.0
nfaToDFA.indexesToDFA Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:59:3-72 82581 1 0.0 0.0 0.0 0.0
nfaToDFA.indexesToDFA Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:59:54-72 82582 1 0.0 0.0 0.0 0.0
lookupAsc Text.Regex.TDFA.IntArrTrieSet Text/Regex/TDFA/IntArrTrieSet.hs:(23,1)-(25,64) 82700 1 0.0 0.0 0.0 0.0
nfaToDFA.tagBounds Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:56:3-27 82729 1 0.0 0.0 0.0 0.0
nfaToDFA.trie Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:62:3-71 82583 1 0.0 0.0 0.0 0.0
fromSinglesMerge Text.Regex.TDFA.IntArrTrieSet Text/Regex/TDFA/IntArrTrieSet.hs:(45,1)-(52,33) 82696 1 0.0 0.0 0.0 0.0
fromSinglesMerge.trieSet Text.Regex.TDFA.IntArrTrieSet Text/Regex/TDFA/IntArrTrieSet.hs:46:3-41 82697 1 0.0 0.0 0.0 0.0
fromBounds Text.Regex.TDFA.IntArrTrieSet Text/Regex/TDFA/IntArrTrieSet.hs:(32,1)-(35,86) 82698 1 0.0 0.0 0.0 0.0
fromBounds.build Text.Regex.TDFA.IntArrTrieSet Text/Regex/TDFA/IntArrTrieSet.hs:(33,3)-(35,86) 82699 2 0.0 0.0 0.0 0.0
fromSinglesMerge.keysToValue' Text.Regex.TDFA.IntArrTrieSet Text/Regex/TDFA/IntArrTrieSet.hs:(47,3)-(51,74) 82710 1 0.0 0.0 0.0 0.0
nfaToDFA.indexToDFA Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(85,3)-(111,47) 82711 1 0.0 0.0 0.0 0.0
nfaToDFA.indexToDFA Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:85:52-96 82712 1 0.0 0.0 0.0 0.0
nfaToDFA.indexToDFA.qtToDT Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(89,7)-(111,47) 82768 1 0.0 0.0 0.0 0.0
nfaToDFA.indexToDFA.qtToDT.makeWinner Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(101,11)-(102,69) 82769 1 0.0 0.0 0.0 0.0
nfaToDFA.indexToDFA.(...) Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:87:7-50 82764 1 0.0 0.0 0.0 0.0
nfaToDFA.indexToDFA.qtIn Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:87:7-50 82763 1 0.0 0.0 0.0 0.0
patternToNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(84,1)-(87,45) 82576 1 0.0 0.0 0.0 0.0
debug Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:70:1-13 82577 1 0.0 0.0 0.0 0.0
patternToNFA.(...) Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:85:7-50 82588 1 0.0 0.0 0.0 0.0
patternToQ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(300,1)-(582,28) 82589 1 0.0 0.0 0.0 0.0
patternToQ.(...) Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:301:3-73 82591 1 0.0 0.0 0.0 0.0
patternToQ.monad Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:306:3-52 82619 0 0.0 0.0 0.0 0.0
patternToQ.go Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(420,3)-(582,28) 82620 6 0.0 0.0 0.0 0.0
patternToQ.go.one Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(427,9)-(431,44) 82633 3 0.0 0.0 0.0 0.0
apply Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(213,1)-(214,17) 82671 3 0.0 0.0 0.0 0.0
patternToQ.combineConcat Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(391,3)-(418,36) 82621 0 0.0 0.0 0.0 0.0
patternToQ.combineConcat.combineSeq Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(397,11)-(418,36) 82622 1 0.0 0.0 0.0 0.0
patternToQ.combineConcat.combineSeq.\ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(397,48)-(417,54) 82623 1 0.0 0.0 0.0 0.0
noTag Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(219,1)-(220,15) 82637 10 0.0 0.0 0.0 0.0
tagged Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:79:13-18 82647 4 0.0 0.0 0.0 0.0
canAccept Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:235:1-48 82639 3 0.0 0.0 0.0 0.0
takes Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:75:13-17 82640 3 0.0 0.0 0.0 0.0
toAdvice Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(216,1)-(217,14) 82638 3 0.0 0.0 0.0 0.0
rightAssoc Text.Regex.TDFA.Common Text/Regex/TDFA/Common.hs:93:5-14 82624 2 0.0 0.0 0.0 0.0
takes Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:75:13-17 82642 2 0.0 0.0 0.0 0.0
apply Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(213,1)-(214,17) 82670 1 0.0 0.0 0.0 0.0
listens Control.Monad.Writer.Class Control/Monad/Writer/Class.hs:(89,1)-(91,19) 82631 1 0.0 0.0 0.0 0.0
listen Control.Monad.Writer.Class Control/Monad/Writer/Class.hs:118:5-27 82632 1 0.0 0.0 0.0 0.0
patternToQ.go.one Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(427,9)-(431,44) 82634 0 0.0 0.0 0.0 0.0
patternToQ.combineConcat.combineSeq.\.bothVary Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:398:17-55 82648 1 0.0 0.0 0.0 0.0
varies Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(228,1)-(229,36) 82649 1 0.0 0.0 0.0 0.0
patternToQ.go.accepts Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:491:16-39 82644 1 0.0 0.0 0.0 0.0
canAccept Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:235:1-48 82645 1 0.0 0.0 0.0 0.0
takes Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:75:13-17 82646 1 0.0 0.0 0.0 0.0
patternToQ.go.needsOrbit Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:494:16-53 82635 1 0.0 0.0 0.0 0.0
varies Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(228,1)-(229,36) 82636 1 0.0 0.0 0.0 0.0
patternToQ.go.needsTags Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:497:16-49 82650 1 0.0 0.0 0.0 0.0
seqTake Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:203:1-50 82643 1 0.0 0.0 0.0 0.0
patternToQ.go.one Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(427,9)-(431,44) 82641 0 0.0 0.0 0.0 0.0
patternToQ.aGroups Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:303:3-59 82732 1 0.0 0.0 0.0 0.0
fromRight Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(277,1)-(279,38) 82733 1 0.0 0.0 0.0 0.0
makeGroupArray Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(273,1)-(274,56) 82735 1 0.0 0.0 0.0 0.0
makeGroupArray.filler Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:274:11-56 82736 1 0.0 0.0 0.0 0.0
patternToQ.aTags Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:302:3-51 82718 1 0.0 0.0 0.0 0.0
patternToQ.tag_dlist Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:301:3-73 82721 0 0.0 0.0 0.0 0.0
patternToQ.combineConcat Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(391,3)-(418,36) 82722 0 0.0 0.0 0.0 0.0
patternToQ.combineConcat.combineSeq Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(397,11)-(418,36) 82723 0 0.0 0.0 0.0 0.0
patternToQ.combineConcat.combineSeq.\ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(397,48)-(417,54) 82724 0 0.0 0.0 0.0 0.0
patternToQ.uniq' Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(332,3)-(337,12) 82725 0 0.0 0.0 0.0 0.0
patternToQ.uniq'.op' Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:334:9-27 82726 0 0.0 0.0 0.0 0.0
patternToQ.combineConcat Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(391,3)-(418,36) 82614 1 0.0 0.0 0.0 0.0
rightAssoc Text.Regex.TDFA.Common Text/Regex/TDFA/Common.hs:93:5-14 82615 1 0.0 0.0 0.0 0.0
patternToQ.combineConcat.combineSeq Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(397,11)-(418,36) 82651 0 0.0 0.0 0.0 0.0
patternToQ.combineConcat.combineSeq.\ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(397,48)-(417,54) 82652 0 0.0 0.0 0.0 0.0
patternToQ.uniq' Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(332,3)-(337,12) 82653 0 0.0 0.0 0.0 0.0
patternToQ.uniq'.op' Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:334:9-27 82720 1 0.0 0.0 0.0 0.0
patternToQ.uniq'.s' Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:335:9-19 82717 1 0.0 0.0 0.0 0.0
put Control.Monad.State.Class Control/Monad/State/Class.hs:111:5-21 82655 1 0.0 0.0 0.0 0.0
patternToQ.groups Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:301:3-73 82734 1 0.0 0.0 0.0 0.0
patternToQ.monad Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:306:3-52 82592 1 0.0 0.0 0.0 0.0
patternToQ.go Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(420,3)-(582,28) 82613 1 0.0 0.0 0.0 0.0
patternToQ.combineConcat Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(391,3)-(418,36) 82616 0 0.0 0.0 0.0 0.0
patternToQ.combineConcat.combineSeq Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(397,11)-(418,36) 82617 1 0.0 0.0 0.0 0.0
patternToQ.combineConcat.combineSeq.\ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(397,48)-(417,54) 82618 1 0.0 0.0 0.0 0.0
starTrans Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:140:1-47 82593 0 0.0 0.0 0.0 0.0
dfsPattern Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(146,1)-(156,37) 82594 0 0.0 0.0 0.0 0.0
dfsPattern.dfs Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(148,8)-(156,37) 82595 5 0.0 0.0 0.0 0.0
simplify' Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(326,1)-(343,23) 82598 4 0.0 0.0 0.0 0.0
simplify'.ps' Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:335:7-40 82602 1 0.0 0.0 0.0 0.0
notPEmpty Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(356,1)-(357,23) 82605 2 0.0 0.0 0.0 0.0
flatten Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(347,1)-(353,63) 82603 1 0.0 0.0 0.0 0.0
flatten.\ Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(350,42)-(352,51) 82604 2 0.0 0.0 0.0 0.0
simplify'.ps' Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(327,7)-(329,77) 82599 1 0.0 0.0 0.0 0.0
flatten Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(347,1)-(353,63) 82600 1 0.0 0.0 0.0 0.0
flatten.\ Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(347,38)-(349,47) 82601 1 0.0 0.0 0.0 0.0
notPEmpty Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(356,1)-(357,23) 82612 1 0.0 0.0 0.0 0.0
starTrans' Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(169,1)-(320,14) 82596 4 0.0 0.0 0.0 0.0
starTrans'.pass Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:320:5-14 82597 4 0.0 0.0 0.0 0.0
dfsPattern.unary Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:147:8-28 82607 1 0.0 0.0 0.0 0.0
simplify' Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(326,1)-(343,23) 82611 1 0.0 0.0 0.0 0.0
starTrans' Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(169,1)-(320,14) 82608 1 0.0 0.0 0.0 0.0
canOnlyMatchNull Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(362,1)-(377,13) 82609 1 0.0 0.0 0.0 0.0
reGroup Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(164,1)-(166,13) 82629 1 0.0 0.0 0.0 0.0
starTrans'.asGroup Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:319:5-44 82610 1 0.0 0.0 0.0 0.0
simplify' Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(326,1)-(343,23) 82625 1 0.0 0.0 0.0 0.0
simplify'.ps' Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:335:7-40 82626 1 0.0 0.0 0.0 0.0
notPEmpty Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(356,1)-(357,23) 82630 2 0.0 0.0 0.0 0.0
flatten Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(347,1)-(353,63) 82627 1 0.0 0.0 0.0 0.0
flatten.\ Text.Regex.TDFA.Pattern Text/Regex/TDFA/Pattern.hs:(350,42)-(352,51) 82628 2 0.0 0.0 0.0 0.0
patternToQ.nextTag Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:301:3-73 82716 1 0.0 0.0 0.0 0.0
patternToQ.tag_dlist Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:301:3-73 82719 1 0.0 0.0 0.0 0.0
patternToQ.tnfa Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:301:3-73 82590 1 0.0 0.0 0.0 0.0
patternToQ.uniq' Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(332,3)-(337,12) 82654 0 0.0 0.0 0.0 0.0
patternToNFA.groups Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:85:7-50 82731 1 0.0 0.0 0.0 0.0
patternToNFA.q Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:85:7-50 82587 1 0.0 0.0 0.0 0.0
patternToNFA.tags Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:85:7-50 82715 1 0.0 0.0 0.0 0.0
qToNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(451,1)-(774,35) 82578 1 0.0 0.0 0.0 0.0
qToNFA.(...) Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(456,3)-(457,80) 82585 1 0.0 0.0 0.0 0.0
qToNFA.getTrans Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(461,3)-(468,116) 82586 6 0.0 0.0 0.0 0.0
addTag Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(389,1)-(390,35) 82669 6 0.0 0.0 0.0 0.0
debug Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:70:1-13 82656 6 0.0 0.0 0.0 0.0
addGroupSets Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(400,1)-(402,39) 82660 3 0.0 0.0 0.0 0.0
qToNFA.getTransTagless Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(470,3)-(524,101) 82657 3 0.0 0.0 0.0 0.0
debug Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:70:1-13 82658 3 0.0 0.0 0.0 0.0
unQ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:82:13-15 82659 3 0.0 0.0 0.0 0.0
cannotAccept Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:238:1-52 82661 1 0.0 0.0 0.0 0.0
takes Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:75:13-17 82662 1 0.0 0.0 0.0 0.0
fromQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:337:1-34 82668 1 0.0 0.0 0.0 0.0
newQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(326,1)-(331,13) 82677 1 0.0 0.0 0.0 0.0
debug Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:70:1-13 82679 1 0.0 0.0 0.0 0.0
newQNFA.futureI Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:328:7-26 82678 1 0.0 0.0 0.0 0.0
put Control.Monad.State.Class Control/Monad/State/Class.hs:101:5-18 82680 1 0.0 0.0 0.0 0.0
qToNFA.inStar Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(527,3)-(532,137) 82663 1 0.0 0.0 0.0 0.0
debug Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:70:1-13 82666 1 0.0 0.0 0.0 0.0
notNullable Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:96:1-26 82664 0 0.0 0.0 0.0 0.0
nullQ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:74:13-17 82665 1 0.0 0.0 0.0 0.0
usesQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(104,1)-(106,18) 82667 1 0.0 0.0 0.0 0.0
qToNFA.newTrans Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(731,3)-(738,48) 82672 3 0.0 0.0 0.0 0.0
fromQT Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:340:1-29 82673 2 0.0 0.0 0.0 0.0
newQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(326,1)-(331,13) 82676 1 0.0 0.0 0.0 0.0
debug Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:70:1-13 82682 1 0.0 0.0 0.0 0.0
newQNFA.futureI Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:328:7-26 82681 1 0.0 0.0 0.0 0.0
put Control.Monad.State.Class Control/Monad/State/Class.hs:101:5-18 82683 1 0.0 0.0 0.0 0.0
qToNFA.acceptTrans Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(742,3)-(774,35) 82767 1 0.0 0.0 0.0 0.0
getQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(350,1)-(352,85) 82674 1 0.0 0.0 0.0 0.0
newQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(326,1)-(331,13) 82675 1 0.0 0.0 0.0 0.0
debug Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:70:1-13 82685 1 0.0 0.0 0.0 0.0
newQNFA.futureI Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:328:7-26 82684 1 0.0 0.0 0.0 0.0
newQNFA.qnfa Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:329:7-28 82706 1 0.0 0.0 0.0 0.0
mkQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(114,1)-(115,49) 82707 1 0.0 0.0 0.0 0.0
debug Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:70:1-13 82708 2 0.0 0.0 0.0 0.0
put Control.Monad.State.Class Control/Monad/State/Class.hs:101:5-18 82686 1 0.0 0.0 0.0 0.0
prependTags' Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(296,1)-(303,71) 82766 1 0.0 0.0 0.0 0.0
promoteTasks Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:367:1-72 82765 1 0.0 0.0 0.0 0.0
qToNFA.lastIndex Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(456,3)-(457,80) 82584 1 0.0 0.0 0.0 0.0
qToNFA.startingQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(456,3)-(457,80) 82705 1 0.0 0.0 0.0 0.0
qToNFA.table Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(456,3)-(457,80) 82687 1 0.0 0.0 0.0 0.0
qToNFA.(...) Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(456,3)-(457,80) 82688 0 0.0 0.0 0.0 0.0
getQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(350,1)-(352,85) 82689 0 0.0 0.0 0.0 0.0
newQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(326,1)-(331,13) 82690 0 0.0 0.0 0.0 0.0
qToNFA.getTrans Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(461,3)-(468,116) 82691 0 0.0 0.0 0.0 0.0
qToNFA.getTransTagless Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(470,3)-(524,101) 82694 0 0.0 0.0 0.0 0.0
newQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(326,1)-(331,13) 82695 0 0.0 0.0 0.0 0.0
qToNFA.newTrans Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(731,3)-(738,48) 82692 0 0.0 0.0 0.0 0.0
newQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(326,1)-(331,13) 82693 0 0.0 0.0 0.0 0.0
q_id Text.Regex.TDFA.Common Text/Regex/TDFA/Common.hs:165:19-22 82709 1 0.0 0.0 0.0 0.0
unwrap Text.Regex.TDFA.String Text/Regex/TDFA/String.hs:(37,1)-(38,33) 82574 1 0.0 0.0 0.0 0.0
memo.f' Data.MemoUgly Data/MemoUgly.hs:24:14-44 81765 0 0.0 0.0 0.0 0.0
memoIO Data.MemoUgly Data/MemoUgly.hs:(11,1)-(18,13) 81766 0 0.0 0.0 0.0 0.0
memoIO.f' Data.MemoUgly Data/MemoUgly.hs:(13,9)-(17,35) 81767 1 0.0 0.0 0.0 0.0
CAF:lvl50_r3AMI Hledger.Data.Transaction <no location info> 20260 0 0.0 0.0 0.0 0.0
inferBalancingAmount Hledger.Data.Transaction Hledger/Data/Transaction.hs:(415,1)-(435,66) 76956 0 0.0 0.0 0.0 0.0
inferBalancingAmount.bvsum Hledger.Data.Transaction Hledger/Data/Transaction.hs:428:5-49 76957 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 76958 1 0.0 0.0 0.0 0.0
CAF:lvl51_r3AMJ Hledger.Data.Transaction <no location info> 20261 0 0.0 0.0 0.0 0.0
inferBalancingAmount Hledger.Data.Transaction Hledger/Data/Transaction.hs:(415,1)-(435,66) 75069 0 0.0 0.0 0.0 0.0
inferBalancingAmount.realsum Hledger.Data.Transaction Hledger/Data/Transaction.hs:426:5-53 75070 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 75071 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 75072 0 0.0 0.0 0.0 0.0
fromInteger Data.Decimal Data/Decimal.hs:214:5-46 75096 1 0.0 0.0 0.0 0.0
CAF:lvl51_r42Zy Hledger.Query <no location info> 19065 0 0.0 0.0 0.0 0.0
CAF:lvl51_r4Ll3 Text.Regex.TDFA.ReadRegex <no location info> 15867 0 0.0 0.0 0.0 0.0
p_set_elem_class Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(121,1)-(122,65) 79875 0 0.0 0.0 0.0 0.0
between Text.Parsec.Combinator Text/Parsec/Combinator.hs:(74,1)-(75,57) 79876 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 79877 1 0.0 0.0 0.0 0.0
CAF:lvl52_r3AMK Hledger.Data.Transaction <no location info> 20262 0 0.0 0.0 0.0 0.0
inferBalancingAmount Hledger.Data.Transaction Hledger/Data/Transaction.hs:(415,1)-(435,66) 75065 0 0.0 0.0 0.0 0.0
inferBalancingAmount.realsum Hledger.Data.Transaction Hledger/Data/Transaction.hs:426:5-53 75066 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 75067 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:146:5-67 75068 1 0.0 0.0 0.0 0.0
CAF:lvl52_r42Zz Hledger.Query <no location info> 19066 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24562 0 0.0 0.0 0.0 0.0
words''.prefixedQuotedPattern Hledger.Query Hledger/Query.hs:(190,7)-(198,40) 24563 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24564 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24565 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24566 1 0.0 0.0 0.0 0.0
CAF:lvl53_r3AML Hledger.Data.Transaction <no location info> 20263 0 0.0 0.0 0.0 0.0
inferBalancingAmount Hledger.Data.Transaction Hledger/Data/Transaction.hs:(415,1)-(435,66) 75058 0 0.0 0.0 0.0 0.0
inferBalancingAmount.realsum Hledger.Data.Transaction Hledger/Data/Transaction.hs:426:5-53 75059 0 0.0 0.0 0.0 0.0
fromInteger Hledger.Data.Amount Hledger/Data/Amount.hs:360:5-41 75060 1 0.0 0.0 0.0 0.0
CAF:lvl53_r42ZA Hledger.Query <no location info> 19067 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24555 0 0.0 0.0 0.0 0.0
words''.prefixedQuotedPattern Hledger.Query Hledger/Query.hs:(190,7)-(198,40) 24556 0 0.0 0.0 0.0 0.0
mptext Text.Megaparsec.Compat Text/Megaparsec/Compat.hs:47:1-15 24557 1 0.0 0.0 0.0 0.0
chunkLength Text.Megaparsec.Stream Text/Megaparsec/Stream.hs:227:3-30 24561 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24567 1 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:875:3-29 24558 1 0.0 0.0 0.0 0.0
CAF:lvl53_r4Ll7 Text.Regex.TDFA.ReadRegex <no location info> 15870 0 0.0 0.0 0.0 0.0
p_set_elem_equiv Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(124,1)-(125,65) 79903 0 0.0 0.0 0.0 0.0
string Text.Parsec.Char Text/Parsec/Char.hs:151:1-51 79904 1 0.0 0.0 0.0 0.0
CAF:lvl54_r42ZB Hledger.Query <no location info> 19068 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24553 0 0.0 0.0 0.0 0.0
words''.prefixedQuotedPattern Hledger.Query Hledger/Query.hs:(190,7)-(198,40) 24554 0 0.0 0.0 0.0 0.0
CAF:lvl54_r71mv Hledger.Read.JournalReader <no location info> 17710 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 69814 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 69815 0 0.0 0.0 0.0 0.0
periodictransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(430,1)-(435,50) 69816 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 69817 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 69818 1 0.0 0.0 0.0 0.0
CAF:lvl55_r42ZC Hledger.Query <no location info> 19069 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24574 0 0.0 0.0 0.0 0.0
words''.prefixedQuotedPattern Hledger.Query Hledger/Query.hs:(190,7)-(198,40) 24575 0 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 24576 1 0.0 0.0 0.0 0.0
CAF:lvl567_r43aj Hledger.Query <no location info> 19449 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24955 0 0.0 0.0 0.0 0.0
words''.maybeprefixedquotedphrases Hledger.Query Hledger/Query.hs:188:7-145 24956 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 24957 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 24958 1 0.0 0.0 0.0 0.0
CAF:lvl568_r43ak Hledger.Query <no location info> 19450 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24952 0 0.0 0.0 0.0 0.0
words''.maybeprefixedquotedphrases Hledger.Query Hledger/Query.hs:188:7-145 24953 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 24954 1 0.0 0.0 0.0 0.0
CAF:lvl56_r42ZD Hledger.Query <no location info> 19070 0 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 24549 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 24550 1 0.0 0.0 0.0 0.0
CAF:lvl57_r4Llb Text.Regex.TDFA.ReadRegex <no location info> 15874 0 0.0 0.0 0.0 0.0
p_set_elem_equiv Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(124,1)-(125,65) 79899 0 0.0 0.0 0.0 0.0
between Text.Parsec.Combinator Text/Parsec/Combinator.hs:(74,1)-(75,57) 79900 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 79901 1 0.0 0.0 0.0 0.0
CAF:lvl59_r4Llf Text.Regex.TDFA.ReadRegex <no location info> 15877 0 0.0 0.0 0.0 0.0
p_set_elem_coll Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(127,1)-(128,65) 79928 0 0.0 0.0 0.0 0.0
string Text.Parsec.Char Text/Parsec/Char.hs:151:1-51 79929 1 0.0 0.0 0.0 0.0
CAF:lvl63_r4Llj Text.Regex.TDFA.ReadRegex <no location info> 15881 0 0.0 0.0 0.0 0.0
p_set_elem_coll Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(127,1)-(128,65) 79924 0 0.0 0.0 0.0 0.0
between Text.Parsec.Combinator Text/Parsec/Combinator.hs:(74,1)-(75,57) 79925 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 79926 1 0.0 0.0 0.0 0.0
CAF:lvl67_r42ZY Hledger.Query <no location info> 19079 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24885 0 0.0 0.0 0.0 0.0
words''.singleQuotedPattern Hledger.Query Hledger/Query.hs:200:7-125 24886 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 24887 1 0.0 0.0 0.0 0.0
CAF:lvl67_r4Llt Text.Regex.TDFA.ReadRegex <no location info> 15888 0 0.0 0.0 0.0 0.0
p_set_elem_range Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(130,1)-(137,85) 79946 0 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 79947 1 0.0 0.0 0.0 0.0
CAF:lvl70_r71n2 Hledger.Read.JournalReader <no location info> 17736 0 0.0 0.0 0.0 0.0
CAF:lvl73_r5Lpv Hledger.Read.Common <no location info> 18390 0 0.0 0.0 0.0 0.0
commentStartingWithp Hledger.Read.Common Hledger/Read/Common.hs:(690,1)-(696,19) 27042 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 27043 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 27044 1 0.0 0.0 0.0 0.0
CAF:lvl74_r4LlS Text.Regex.TDFA.ReadRegex <no location info> 15931 0 0.0 0.0 0.0 0.0
p_set Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(102,1)-(114,86) 79846 0 0.0 0.0 0.0 0.0
many1 Text.Parsec.Combinator Text/Parsec/Combinator.hs:94:1-63 79847 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 79848 1 0.0 0.0 0.0 0.0
many Text.Parsec.Prim Text/Parsec/Prim.hs:(588,1)-(590,26) 79988 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 79989 1 0.0 0.0 0.0 0.0
manyAccum Text.Parsec.Prim Text/Parsec/Prim.hs:(605,1)-(613,61) 79991 1 0.0 0.0 0.0 0.0
CAF:lvl74_r5Lpx Hledger.Read.Common <no location info> 18392 0 0.0 0.0 0.0 0.0
followingcommentp Hledger.Read.Common Hledger/Read/Common.hs:(618,1)-(622,57) 25947 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 25948 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 25949 1 0.0 0.0 0.0 0.0
CAF:lvl75_r4LlT Text.Regex.TDFA.ReadRegex <no location info> 15945 0 0.0 0.0 0.0 0.0
p_group Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(51,1)-(53,62) 80268 0 0.0 0.0 0.0 0.0
char Text.Parsec.Char Text/Parsec/Char.hs:125:1-49 80269 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 80270 1 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 80271 1 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 80272 1 0.0 0.0 0.0 0.0
satisfy Text.Parsec.Char Text/Parsec/Char.hs:(140,1)-(142,71) 80273 1 0.0 0.0 0.0 0.0
CAF:lvl75_r5LpA Hledger.Read.Common <no location info> 18395 0 0.0 0.0 0.0 0.0
emptyorcommentlinep Hledger.Read.Common Hledger/Read/Common.hs:(612,1)-(614,11) 26595 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 26596 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 26597 1 0.0 0.0 0.0 0.0
CAF:lvl76_r4LlU Text.Regex.TDFA.ReadRegex <no location info> 15948 0 0.0 0.0 0.0 0.0
parseRegex Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(28,1)-(31,83) 80679 0 0.0 0.0 0.0 0.0
eof Text.Parsec.Combinator Text/Parsec/Combinator.hs:242:1-63 80680 0 0.0 0.0 0.0 0.0
anyToken Text.Parsec.Combinator Text/Parsec/Combinator.hs:234:1-66 80681 1 0.0 0.0 0.0 0.0
CAF:lvl79_r430l Hledger.Query <no location info> 19088 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24909 0 0.0 0.0 0.0 0.0
words''.doubleQuotedPattern Hledger.Query Hledger/Query.hs:202:7-124 24910 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 24911 1 0.0 0.0 0.0 0.0
CAF:lvl80_r56bH Hledger.Reports.ReportOptions <no location info> 17334 0 0.0 0.0 0.0 0.0
CAF:lvl80_r5LpL Hledger.Read.Common <no location info> 18412 0 0.0 0.0 0.0 0.0
leftsymbolamountp Hledger.Read.Common Hledger/Read/Common.hs:(415,1)-(425,26) 28246 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 28247 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 28248 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 28249 1 0.0 0.0 0.0 0.0
CAF:lvl81_r5LpN Hledger.Read.Common <no location info> 18414 0 0.0 0.0 0.0 0.0
rightsymbolamountp Hledger.Read.Common Hledger/Read/Common.hs:(428,1)-(436,27) 25805 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 25806 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 25807 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 25808 1 0.0 0.0 0.0 0.0
CAF:lvl82_r5LpP Hledger.Read.Common <no location info> 18416 0 0.0 0.0 0.0 0.0
priceamountp Hledger.Read.Common Hledger/Read/Common.hs:(465,1)-(478,27) 25880 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 25881 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 25882 1 0.0 0.0 0.0 0.0
CAF:lvl82_r71nv Hledger.Read.JournalReader <no location info> 17750 0 0.0 0.0 0.0 0.0
CAF:lvl83_r5LpR Hledger.Read.Common <no location info> 18418 0 0.0 0.0 0.0 0.0
spaceandamountormissingp Hledger.Read.Common Hledger/Read/Common.hs:(351,1)-(355,34) 28141 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 28142 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 28143 1 0.0 0.0 0.0 0.0
CAF:lvl84_r430y Hledger.Query <no location info> 19094 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24931 0 0.0 0.0 0.0 0.0
words''.pattern Hledger.Query Hledger/Query.hs:204:7-63 24932 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 24933 1 0.0 0.0 0.0 0.0
CAF:lvl84_r4KpQ Hledger.Data.Journal <no location info> 21210 0 0.0 0.0 0.0 0.0
CAF:lvl84_r56bL Hledger.Reports.ReportOptions <no location info> 17335 0 0.0 0.0 0.0 0.0
CAF:lvl84_r5LpT Hledger.Read.Common <no location info> 18420 0 0.0 0.0 0.0 0.0
fixedlotpricep Hledger.Read.Common Hledger/Read/Common.hs:(503,1)-(514,27) 28446 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 28447 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 28448 1 0.0 0.0 0.0 0.0
CAF:lvl85_r430z Hledger.Query <no location info> 19095 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24921 0 0.0 0.0 0.0 0.0
words''.pattern Hledger.Query Hledger/Query.hs:204:7-63 24922 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 24928 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 24923 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 24924 1 0.0 0.0 0.0 0.0
CAF:lvl85_r71nH Hledger.Read.JournalReader <no location info> 17757 0 0.0 0.0 0.0 0.0
CAF:lvl86_r5LpX Hledger.Read.Common <no location info> 18424 0 0.0 0.0 0.0 0.0
partialbalanceassertionp Hledger.Read.Common Hledger/Read/Common.hs:(481,1)-(489,27) 28412 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 28413 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 28414 1 0.0 0.0 0.0 0.0
CAF:lvl87_r5LpZ Hledger.Read.Common <no location info> 18426 0 0.0 0.0 0.0 0.0
followingcommentandtagsp Hledger.Read.Common Hledger/Read/Common.hs:(645,1)-(677,39) 28526 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 28527 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 28528 1 0.0 0.0 0.0 0.0
CAF:lvl88_r56bP Hledger.Reports.ReportOptions <no location info> 17336 0 0.0 0.0 0.0 0.0
CAF:lvl88_r5Lq1 Hledger.Read.Common <no location info> 18428 0 0.0 0.0 0.0 0.0
followingcommentandtagsp Hledger.Read.Common Hledger/Read/Common.hs:(645,1)-(677,39) 28563 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 28564 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 28568 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 28569 1 0.0 0.0 0.0 0.0
CAF:lvl88_r71nP Hledger.Read.JournalReader <no location info> 17763 0 0.0 0.0 0.0 0.0
CAF:lvl8_r42Yh Hledger.Query <no location info> 19016 0 0.0 0.0 0.0 0.0
CAF:lvl91_r71nY Hledger.Read.JournalReader <no location info> 17770 0 0.0 0.0 0.0 0.0
CAF:lvl91_rAZg Hledger.Cli.CliOptions <no location info> 23676 0 0.0 0.0 0.0 0.0
rawOptsToCliOpts Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(397,1)-(421,14) 24443 0 0.0 0.0 0.0 0.0
stringopt Hledger.Data.RawOptions Hledger/Data/RawOptions.hs:51:1-51 24444 0 0.0 0.0 0.0 0.0
maybestringopt Hledger.Data.RawOptions Hledger/Data/RawOptions.hs:48:1-100 24445 1 0.0 0.0 0.0 0.0
CAF:lvl92_r56bT Hledger.Reports.ReportOptions <no location info> 17337 0 0.0 0.0 0.0 0.0
CAF:lvl92_rAZh Hledger.Cli.CliOptions <no location info> 23677 0 0.0 0.0 0.0 0.0
rawOptsToCliOpts Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(397,1)-(421,14) 78168 0 0.0 0.0 0.0 0.0
maybestringopt Hledger.Data.RawOptions Hledger/Data/RawOptions.hs:48:1-100 78169 1 0.0 0.0 0.0 0.0
CAF:lvl93_r71o1 Hledger.Read.JournalReader <no location info> 17772 0 0.0 0.0 0.0 0.0
CAF:lvl93_rAZi Hledger.Cli.CliOptions <no location info> 23678 0 0.0 0.0 0.0 0.0
rawOptsToCliOpts Hledger.Cli.CliOptions Hledger/Cli/CliOptions.hs:(397,1)-(421,14) 78175 0 0.0 0.0 0.0 0.0
maybestringopt Hledger.Data.RawOptions Hledger/Data/RawOptions.hs:48:1-100 78176 1 0.0 0.0 0.0 0.0
CAF:lvl96_r56bX Hledger.Reports.ReportOptions <no location info> 17338 0 0.0 0.0 0.0 0.0
CAF:lvl98_r56bZ Hledger.Reports.ReportOptions <no location info> 17339 0 0.0 0.0 0.0 0.0
CAF:lvl9_r4Lk6 Text.Regex.TDFA.ReadRegex <no location info> 15825 0 0.0 0.0 0.0 0.0
p_set_elem_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(139,1)-(144,19) 80422 0 0.0 0.0 0.0 0.0
return Text.Parsec.Prim Text/Parsec/Prim.hs:201:5-29 80424 1 0.0 0.0 0.0 0.0
parserReturn Text.Parsec.Prim Text/Parsec/Prim.hs:(232,1)-(234,30) 80425 1 0.0 0.0 0.0 0.0
CAF:m10_r71m7 Hledger.Read.JournalReader <no location info> 17691 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26686 0 0.0 0.0 0.0 0.0
includedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(180,1)-(211,59) 26687 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 26688 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 26702 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 26703 1 0.0 0.0 0.0 0.0
CAF:m11_r5LxV Hledger.Read.Common <no location info> 18800 0 0.0 0.0 0.0 0.0
bracketeddatetagsp Hledger.Read.Common Hledger/Read/Common.hs:(853,1)-(881,48) 28818 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 28819 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 28820 1 0.0 0.0 0.0 0.0
CAF:m11_r71mb Hledger.Read.JournalReader <no location info> 17693 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25910 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25911 0 0.0 0.0 0.0 0.0
commoditydirectiveonelinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(259,1)-(266,75) 25912 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 25921 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 25913 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 25914 1 0.0 0.0 0.0 0.0
CAF:m12_r42ZG Hledger.Query <no location info> 19072 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24547 0 0.0 0.0 0.0 0.0
words''.prefixedQuotedPattern Hledger.Query Hledger/Query.hs:(190,7)-(198,40) 24548 0 0.0 0.0 0.0 0.0
CAF:m13_r5LxW Hledger.Read.Common <no location info> 18801 0 0.0 0.0 0.0 0.0
bracketeddatetagsp Hledger.Read.Common Hledger/Read/Common.hs:(853,1)-(881,48) 28815 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 28816 1 0.0 0.0 0.0 0.0
CAF:m13_r71mc Hledger.Read.JournalReader <no location info> 17694 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25494 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25495 0 0.0 0.0 0.0 0.0
commoditydirectiveonelinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(259,1)-(266,75) 25496 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 25497 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 25512 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 25513 1 0.0 0.0 0.0 0.0
CAF:m1_r1JOR Hledger.Utils.Parse <no location info> 16781 0 0.0 0.0 0.0 0.0
restofline Hledger.Utils.Parse Hledger/Utils/Parse.hs:80:1-39 26729 0 0.0 0.0 0.0 0.0
CAF:m1_r4301 Hledger.Query <no location info> 19081 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24874 0 0.0 0.0 0.0 0.0
words''.singleQuotedPattern Hledger.Query Hledger/Query.hs:200:7-125 24875 0 0.0 0.0 0.0 0.0
<* Text.Megaparsec Text/Megaparsec.hs:329:3-50 24876 1 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 24877 1 0.0 0.0 0.0 0.0
CAF:m1_r4LlW Text.Regex.TDFA.ReadRegex <no location info> 15950 0 0.0 0.0 0.0 0.0
parseRegex Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(28,1)-(31,83) 80652 0 0.0 0.0 0.0 0.0
eof Text.Parsec.Combinator Text/Parsec/Combinator.hs:242:1-63 80653 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 80654 1 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 80655 1 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 80656 1 0.0 0.0 0.0 0.0
CAF:m1_r4tCO Text.Regex.TDFA.CorePattern <no location info> 16057 0 0.0 0.0 0.0 0.0
patternToQ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(300,1)-(582,28) 80890 0 0.0 0.0 0.0 0.0
patternToQ.uniq' Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(332,3)-(337,12) 80891 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:110:5-21 80892 1 0.0 0.0 0.0 0.0
CAF:m1_r52ye Text.Regex.TDFA.TNFA <no location info> 16187 0 0.0 0.0 0.0 0.0
newQNFA Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(326,1)-(331,13) 80956 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:100:5-18 80957 1 0.0 0.0 0.0 0.0
CAF:m1_r5lXC Text.Regex.TDFA.TDFA <no location info> 16253 0 0.0 0.0 0.0 0.0
modifyPos Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(397,1)-(400,21) 81407 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:100:5-18 81408 1 0.0 0.0 0.0 0.0
CAF:m1_r71kY Hledger.Read.JournalReader <no location info> 17651 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25528 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25529 0 0.0 0.0 0.0 0.0
commoditydirectiveonelinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(259,1)-(266,75) 25530 0 0.0 0.0 0.0 0.0
amountp Hledger.Read.Common Hledger/Read/Common.hs:375:1-78 25531 1 0.0 0.0 0.0 0.0
CAF:m20_r71ms Hledger.Read.JournalReader <no location info> 17707 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 27633 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 27634 0 0.0 0.0 0.0 0.0
transactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(439,1)-(453,107) 27635 0 0.0 0.0 0.0 0.0
spacenonewline Hledger.Utils.Parse Hledger/Utils/Parse.hs:77:1-43 27636 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 27637 1 0.0 0.0 0.0 0.0
CAF:m21_r5Lz3 Hledger.Read.Common <no location info> 18829 0 0.0 0.0 0.0 0.0
postingdatesp Hledger.Read.Common Hledger/Read/Common.hs:(772,1)-(778,35) 28838 0 0.0 0.0 0.0 0.0
postingdatesp.nonp Hledger.Read.Common Hledger/Read/Common.hs:(775,7)-(776,42) 28839 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 28840 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 28841 1 0.0 0.0 0.0 0.0
CAF:m22_r5Lzn Hledger.Read.Common <no location info> 18857 0 0.0 0.0 0.0 0.0
nontagp Hledger.Read.Common Hledger/Read/Common.hs:(730,1)-(733,56) 28676 0 0.0 0.0 0.0 0.0
CAF:m22_r71mw Hledger.Read.JournalReader <no location info> 17711 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 69803 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 69804 0 0.0 0.0 0.0 0.0
periodictransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(430,1)-(435,50) 69805 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 69811 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 69806 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 69807 1 0.0 0.0 0.0 0.0
CAF:m28_r71tj Hledger.Read.JournalReader <no location info> 17981 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26341 0 0.0 0.0 0.0 0.0
commodityconversiondirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(408,1)-(417,11) 26342 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26343 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 26344 1 0.0 0.0 0.0 0.0
CAF:m29_r71tm Hledger.Read.JournalReader <no location info> 17984 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26328 0 0.0 0.0 0.0 0.0
commodityconversiondirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(408,1)-(417,11) 26329 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26330 1 0.0 0.0 0.0 0.0
CAF:m2_r430o Hledger.Query <no location info> 19090 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24898 0 0.0 0.0 0.0 0.0
words''.doubleQuotedPattern Hledger.Query Hledger/Query.hs:202:7-124 24899 0 0.0 0.0 0.0 0.0
<* Text.Megaparsec Text/Megaparsec.hs:329:3-50 24900 1 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 24901 1 0.0 0.0 0.0 0.0
CAF:m2_r4tEu Text.Regex.TDFA.CorePattern <no location info> 16088 0 0.0 0.0 0.0 0.0
patternToQ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(300,1)-(582,28) 80882 0 0.0 0.0 0.0 0.0
patternToQ.combineConcat Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(391,3)-(418,36) 80883 0 0.0 0.0 0.0 0.0
patternToQ.combineConcat.combineSeq Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(397,11)-(418,36) 80884 0 0.0 0.0 0.0 0.0
patternToQ.combineConcat.combineSeq.\ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(397,48)-(417,54) 80885 0 0.0 0.0 0.0 0.0
patternToQ.uniq' Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(332,3)-(337,12) 80886 1 0.0 0.0 0.0 0.0
CAF:m30_r71to Hledger.Read.JournalReader <no location info> 17986 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26318 0 0.0 0.0 0.0 0.0
defaultcommoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(380,1)-(385,50) 26319 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26320 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 26321 1 0.0 0.0 0.0 0.0
CAF:m31_r71tr Hledger.Read.JournalReader <no location info> 17989 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26305 0 0.0 0.0 0.0 0.0
defaultcommoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(380,1)-(385,50) 26306 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26307 1 0.0 0.0 0.0 0.0
CAF:m36_r71tB Hledger.Read.JournalReader <no location info> 17995 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26133 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 26134 0 0.0 0.0 0.0 0.0
commoditydirectivemultilinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(272,1)-(281,46) 26135 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 26136 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:875:3-29 26137 1 0.0 0.0 0.0 0.0
CAF:m37_r71tC Hledger.Read.JournalReader <no location info> 17996 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26126 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 26127 0 0.0 0.0 0.0 0.0
commoditydirectivemultilinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(272,1)-(281,46) 26128 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 26129 1 0.0 0.0 0.0 0.0
CAF:m38_r71tH Hledger.Read.JournalReader <no location info> 17998 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25452 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25453 0 0.0 0.0 0.0 0.0
commoditydirectiveonelinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(259,1)-(266,75) 25454 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 25455 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:875:3-29 25456 1 0.0 0.0 0.0 0.0
CAF:m39_r71tI Hledger.Read.JournalReader <no location info> 17999 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25446 0 0.0 0.0 0.0 0.0
commoditydirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:252:1-85 25447 0 0.0 0.0 0.0 0.0
commoditydirectiveonelinep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(259,1)-(266,75) 25448 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 25449 1 0.0 0.0 0.0 0.0
CAF:m3_r4tEv Text.Regex.TDFA.CorePattern <no location info> 16089 0 0.0 0.0 0.0 0.0
patternToQ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(300,1)-(582,28) 80907 0 0.0 0.0 0.0 0.0
patternToQ.go Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(420,3)-(582,28) 80908 0 0.0 0.0 0.0 0.0
patternToQ.uniq' Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(332,3)-(337,12) 80909 1 0.0 0.0 0.0 0.0
CAF:m3_r5lXT Text.Regex.TDFA.TDFA <no location info> 16263 0 0.0 0.0 0.0 0.0
assemble Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(345,1)-(357,71) 81597 0 0.0 0.0 0.0 0.0
assemble.oneInstruction Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(346,3)-(357,71) 81598 0 0.0 0.0 0.0 0.0
enterOrbit Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(378,1)-(388,70) 81599 0 0.0 0.0 0.0 0.0
modifyOrbit Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(403,1)-(406,21) 81600 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:100:5-18 81601 1 0.0 0.0 0.0 0.0
CAF:m40_r71tM Hledger.Read.JournalReader <no location info> 18003 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26745 0 0.0 0.0 0.0 0.0
includedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(180,1)-(211,59) 26746 0 0.0 0.0 0.0 0.0
getPosition Text.Megaparsec Text/Megaparsec.hs:1393:1-51 26747 0 0.0 0.0 0.0 0.0
getParserState Text.Megaparsec Text/Megaparsec.hs:1142:3-50 26748 0 0.0 0.0 0.0 0.0
getParserState Text.Megaparsec Text/Megaparsec.hs:879:3-37 26749 1 0.0 0.0 0.0 0.0
CAF:m41_r71tO Hledger.Read.JournalReader <no location info> 18004 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25275 0 0.0 0.0 0.0 0.0
includedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(180,1)-(211,59) 25276 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 25277 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:875:3-29 25278 1 0.0 0.0 0.0 0.0
CAF:m42_r71tP Hledger.Read.JournalReader <no location info> 18005 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25268 0 0.0 0.0 0.0 0.0
includedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(180,1)-(211,59) 25269 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 25270 1 0.0 0.0 0.0 0.0
CAF:m43_r71tQ Hledger.Read.JournalReader <no location info> 18006 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25248 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 25249 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 25250 1 0.0 0.0 0.0 0.0
CAF:m44_r71tR Hledger.Read.JournalReader <no location info> 18007 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 25243 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 25244 1 0.0 0.0 0.0 0.0
CAF:m45_r71tY Hledger.Read.JournalReader <no location info> 18014 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26550 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26551 0 0.0 0.0 0.0 0.0
periodictransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(430,1)-(435,50) 26552 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26553 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 26554 1 0.0 0.0 0.0 0.0
CAF:m46_r71u1 Hledger.Read.JournalReader <no location info> 18017 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26533 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26534 0 0.0 0.0 0.0 0.0
periodictransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(430,1)-(435,50) 26535 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26536 1 0.0 0.0 0.0 0.0
CAF:m47_r71u2 Hledger.Read.JournalReader <no location info> 18018 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26526 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26527 0 0.0 0.0 0.0 0.0
periodictransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(430,1)-(435,50) 26528 1 0.0 0.0 0.0 0.0
CAF:m48_r71u7 Hledger.Read.JournalReader <no location info> 18019 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26516 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26517 0 0.0 0.0 0.0 0.0
modifiertransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(422,1)-(427,49) 26518 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26519 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 26520 1 0.0 0.0 0.0 0.0
CAF:m49_r71ua Hledger.Read.JournalReader <no location info> 18022 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26498 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26499 0 0.0 0.0 0.0 0.0
modifiertransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(422,1)-(427,49) 26500 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26501 1 0.0 0.0 0.0 0.0
CAF:m4_r4tEx Text.Regex.TDFA.CorePattern <no location info> 16090 0 0.0 0.0 0.0 0.0
patternToQ Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(300,1)-(582,28) 80896 0 0.0 0.0 0.0 0.0
patternToQ.go Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(420,3)-(582,28) 80897 0 0.0 0.0 0.0 0.0
patternToQ.go.newUniq Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:460:16-83 80898 0 0.0 0.0 0.0 0.0
patternToQ.uniq' Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:(332,3)-(337,12) 80899 1 0.0 0.0 0.0 0.0
CAF:m4_r5lXV Text.Regex.TDFA.TDFA <no location info> 16264 0 0.0 0.0 0.0 0.0
assemble Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(345,1)-(357,71) 81533 0 0.0 0.0 0.0 0.0
assemble.oneInstruction Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(346,3)-(357,71) 81534 0 0.0 0.0 0.0 0.0
leaveOrbit Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(391,1)-(394,27) 81535 0 0.0 0.0 0.0 0.0
modifyOrbit Text.Regex.TDFA.TDFA Text/Regex/TDFA/TDFA.hs:(403,1)-(406,21) 81536 0 0.0 0.0 0.0 0.0
get Control.Monad.State.Class Control/Monad/State/Class.hs:100:5-18 81537 1 0.0 0.0 0.0 0.0
CAF:m50_r71ub Hledger.Read.JournalReader <no location info> 18023 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26491 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26492 0 0.0 0.0 0.0 0.0
modifiertransactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(422,1)-(427,49) 26493 1 0.0 0.0 0.0 0.0
CAF:m51_r71uc Hledger.Read.JournalReader <no location info> 18024 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 37038 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 37039 0 0.0 0.0 0.0 0.0
transactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(439,1)-(453,107) 37040 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 37041 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 37042 1 0.0 0.0 0.0 0.0
CAF:m52_r71ui Hledger.Read.JournalReader <no location info> 18027 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26418 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26419 0 0.0 0.0 0.0 0.0
transactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(439,1)-(453,107) 26420 0 0.0 0.0 0.0 0.0
getPosition Text.Megaparsec Text/Megaparsec.hs:1393:1-51 26421 0 0.0 0.0 0.0 0.0
getParserState Text.Megaparsec Text/Megaparsec.hs:1142:3-50 26422 0 0.0 0.0 0.0 0.0
getParserState Text.Megaparsec Text/Megaparsec.hs:879:3-37 26423 1 0.0 0.0 0.0 0.0
CAF:m53_r71us Hledger.Read.JournalReader <no location info> 18029 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 27658 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 27659 0 0.0 0.0 0.0 0.0
transactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(439,1)-(453,107) 27660 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 27661 1 0.0 0.0 0.0 0.0
CAF:m54_r71uI Hledger.Read.JournalReader <no location info> 18032 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26406 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26407 0 0.0 0.0 0.0 0.0
transactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(439,1)-(453,107) 26408 0 0.0 0.0 0.0 0.0
getPosition Text.Megaparsec Text/Megaparsec.hs:1393:1-51 26409 1 0.0 0.0 0.0 0.0
getParserState Text.Megaparsec Text/Megaparsec.hs:1142:3-50 26413 1 0.0 0.0 0.0 0.0
CAF:m55_r71uJ Hledger.Read.JournalReader <no location info> 18033 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 26399 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 26400 0 0.0 0.0 0.0 0.0
transactionp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(439,1)-(453,107) 26401 1 0.0 0.0 0.0 0.0
CAF:m5_r5Lxg Hledger.Read.Common <no location info> 18784 0 0.0 0.0 0.0 0.0
datetagp Hledger.Read.Common Hledger/Read/Common.hs:(797,1)-(818,39) 28795 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 28796 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:875:3-29 28797 1 0.0 0.0 0.0 0.0
CAF:m6_r5Lxh Hledger.Read.Common <no location info> 18785 0 0.0 0.0 0.0 0.0
datetagp Hledger.Read.Common Hledger/Read/Common.hs:(797,1)-(818,39) 28789 0 0.0 0.0 0.0 0.0
tokens Text.Megaparsec Text/Megaparsec.hs:1138:3-49 28790 1 0.0 0.0 0.0 0.0
CAF:m8_r71m1 Hledger.Read.JournalReader <no location info> 17688 0 0.0 0.0 0.0 0.0
postingp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(563,1)-(586,4) 27873 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 27874 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 27881 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 27882 1 0.0 0.0 0.0 0.0
CAF:m9_r71m2 Hledger.Read.JournalReader <no location info> 17689 0 0.0 0.0 0.0 0.0
postingp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(563,1)-(586,4) 27944 0 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 27947 1 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 27945 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 27946 1 0.0 0.0 0.0 0.0
CAF:main1 Hledger.Cli.Main <no location info> 23978 0 0.0 0.0 0.0 0.0
main Hledger.Cli.Main Hledger/Cli/Main.hs:(98,1)-(196,19) 23980 1 0.0 0.0 0.0 0.0
CAF:markBoringParentAccounts_r8A23 Hledger.Reports.BalanceReport Hledger/Reports/BalanceReport.hs:129:1-24 17259 0 0.0 0.0 0.0 0.0
markBoringParentAccounts Hledger.Reports.BalanceReport Hledger/Reports/BalanceReport.hs:(129,1)-(132,26) 78371 1 0.0 0.0 0.0 0.0
CAF:marketpricedirectivep1 Hledger.Read.JournalReader <no location info> 17857 0 0.0 0.0 0.0 0.0
marketpricedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(388,1)-(397,40) 26562 1 0.0 0.0 0.0 0.0
CAF:marketpricedirectivep3 Hledger.Read.JournalReader <no location info> 17855 0 0.0 0.0 0.0 0.0
marketpricedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(388,1)-(397,40) 26567 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26568 1 0.0 0.0 0.0 0.0
CAF:marketpricedirectivep4 Hledger.Read.JournalReader <no location info> 17854 0 0.0 0.0 0.0 0.0
marketpricedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(388,1)-(397,40) 26572 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26573 1 0.0 0.0 0.0 0.0
CAF:marketpricedirectivep5 Hledger.Read.JournalReader <no location info> 17853 0 0.0 0.0 0.0 0.0
marketpricedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(388,1)-(397,40) 26577 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:1137:3-51 26578 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 26579 1 0.0 0.0 0.0 0.0
CAF:marketpricedirectivep_f Hledger.Read.JournalReader <no location info> 17852 0 0.0 0.0 0.0 0.0
marketpricedirectivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(388,1)-(397,40) 26569 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 26570 0 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 26571 1 0.0 0.0 0.0 0.0
CAF:maxLoad Data.HashTable.ST.Cuckoo src/Data/HashTable/ST/Cuckoo.hs:774:1-7 15371 0 0.0 0.0 0.0 0.0
maxLoad Data.HashTable.ST.Cuckoo src/Data/HashTable/ST/Cuckoo.hs:774:1-14 74223 1 0.0 0.0 0.0 0.0
CAF:maxprecision Hledger.Data.Amount Hledger/Data/Amount.hs:337:1-12 21976 0 0.0 0.0 0.0 0.0
maxprecision Hledger.Data.Amount Hledger/Data/Amount.hs:337:1-21 75302 1 0.0 0.0 0.0 0.0
CAF:maxprecisionwithpoint Hledger.Data.Amount Hledger/Data/Amount.hs:341:1-21 21975 0 0.0 0.0 0.0 0.0
maxprecisionwithpoint Hledger.Data.Amount Hledger/Data/Amount.hs:341:1-30 75301 1 0.0 0.0 0.0 0.0
CAF:mergeQTrans_r52yc Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:280:3-13 16186 0 0.0 0.0 0.0 0.0
mergeQTWith Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:(245,1)-(280,38) 81503 0 0.0 0.0 0.0 0.0
mergeQTWith.mergeQTrans Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:280:3-38 81504 1 0.0 0.0 0.0 0.0
CAF:missingamt Hledger.Data.Amount Hledger/Data/Amount.hs:159:1-10 21995 0 0.0 0.0 0.0 0.0
missingamt Hledger.Data.Amount Hledger/Data/Amount.hs:159:1-38 74266 1 0.0 0.0 0.0 0.0
CAF:missingamt1 Hledger.Data.Amount <no location info> 21950 0 0.0 0.0 0.0 0.0
missingamt Hledger.Data.Amount Hledger/Data/Amount.hs:159:1-38 74271 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 74272 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 74273 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 74274 1 0.0 0.0 0.0 0.0
CAF:missingamt2 Hledger.Data.Amount <no location info> 21936 0 0.0 0.0 0.0 0.0
CAF:modeModes System.Console.CmdArgs.Explicit.Type System/Console/CmdArgs/Explicit/Type.hs:103:1-9 12606 0 0.0 0.0 0.0 0.0
modeModes System.Console.CmdArgs.Explicit.Type System/Console/CmdArgs/Explicit/Type.hs:103:1-38 24093 1 0.0 0.0 0.0 0.0
CAF:modifiedaccountnamep1 Hledger.Read.Common <no location info> 18656 0 0.0 0.0 0.0 0.0
modifiedaccountnamep Hledger.Read.Common Hledger/Read/Common.hs:(312,1)-(320,5) 27955 1 0.0 0.0 0.0 0.0
CAF:moveFlagsAfterCommand4 Hledger.Cli.Main <no location info> 23946 0 0.0 0.0 0.0 0.0
CAF:multilinecommentp1 Hledger.Read.Common <no location info> 18536 0 0.0 0.0 0.0 0.0
multilinecommentp Hledger.Read.Common Hledger/Read/Common.hs:(603,1)-(609,40) 35575 1 0.0 0.0 0.0 0.0
CAF:multiplierp1 Hledger.Read.Common <no location info> 18560 0 0.0 0.0 0.0 0.0
multiplierp Hledger.Read.Common Hledger/Read/Common.hs:(409,1)-(412,47) 25579 1 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 25580 1 0.0 0.0 0.0 0.0
CAF:multiplierp3 Hledger.Read.Common <no location info> 18559 0 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 25583 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 25584 1 0.0 0.0 0.0 0.0
CAF:multiplierp4 Hledger.Read.Common <no location info> 18555 0 0.0 0.0 0.0 0.0
multiplierp Hledger.Read.Common Hledger/Read/Common.hs:(409,1)-(412,47) 25592 0 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 25593 1 0.0 0.0 0.0 0.0
CAF:multiplierp5 Hledger.Read.Common <no location info> 18558 0 0.0 0.0 0.0 0.0
multiplierp Hledger.Read.Common Hledger/Read/Common.hs:(409,1)-(412,47) 25585 0 0.0 0.0 0.0 0.0
CAF:multiplierp6 Hledger.Read.Common <no location info> 18557 0 0.0 0.0 0.0 0.0
multiplierp Hledger.Read.Common Hledger/Read/Common.hs:(409,1)-(412,47) 25588 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 25589 1 0.0 0.0 0.0 0.0
CAF:multiplierp8 Hledger.Read.Common <no location info> 18556 0 0.0 0.0 0.0 0.0
CAF:n15_r71t9 Hledger.Read.JournalReader <no location info> 17978 0 0.0 0.0 0.0 0.0
directivep Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(160,1)-(177,19) 26364 0 0.0 0.0 0.0 0.0
mzero Text.Megaparsec Text/Megaparsec.hs:420:3-15 26365 1 0.0 0.0 0.0 0.0
CAF:n16_r71tT Hledger.Read.JournalReader <no location info> 18013 0 0.0 0.0 0.0 0.0
journalp Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(133,1)-(136,5) 35599 0 0.0 0.0 0.0 0.0
addJournalItemP Hledger.Read.JournalReader Hledger/Read/JournalReader.hs:(141,1)-(152,36) 35600 0 0.0 0.0 0.0 0.0
mzero Text.Megaparsec Text/Megaparsec.hs:420:3-15 35601 1 0.0 0.0 0.0 0.0
CAF:name_r56go Hledger.Reports.ReportOptions <no location info> 17457 0 0.0 0.0 0.0 0.0
CAF:newBitStream1 Data.HashTable.Internal.CheapPseudoRandomBitStream <no location info> 15363 0 0.0 0.0 0.0 0.0
newBitStream Data.HashTable.Internal.CheapPseudoRandomBitStream src/Data/HashTable/Internal/CheapPseudoRandomBitStream.hs:(86,1)-(90,42) 74233 1 0.0 0.0 0.0 0.0
CAF:newMQ_r23MG Text.Regex.TDFA.NewDFA.Engine_NC <no location info> 16299 0 0.0 0.0 0.0 0.0
newMQ Text.Regex.TDFA.NewDFA.Engine_NC Text/Regex/TDFA/NewDFA/Engine_NC.hs:(185,1)-(188,27) 82759 1 0.0 0.0 0.0 0.0
CAF:newMQ_r3EdL Text.Regex.TDFA.NewDFA.Engine <no location info> 16391 0 0.0 0.0 0.0 0.0
newMQ Text.Regex.TDFA.NewDFA.Engine Text/Regex/TDFA/NewDFA/Engine.hs:(420,1)-(423,27) 81080 1 0.0 0.0 0.0 0.0
CAF:noWin Text.Regex.TDFA.Common Text/Regex/TDFA/Common.hs:69:1-5 16413 0 0.0 0.0 0.0 0.0
noWin Text.Regex.TDFA.Common Text/Regex/TDFA/Common.hs:69:1-12 81093 1 0.0 0.0 0.0 0.0
CAF:nonsimplecommoditychars Hledger.Data.Commodity Hledger/Data/Commodity.hs:27:1-23 21856 0 0.0 0.0 0.0 0.0
nonsimplecommoditychars Hledger.Data.Commodity Hledger/Data/Commodity.hs:27:1-62 25630 1 0.0 0.0 0.0 0.0
CAF:nonspace1 Hledger.Utils.Parse <no location info> 16775 0 0.0 0.0 0.0 0.0
nonspace Hledger.Utils.Parse Hledger/Utils/Parse.hs:74:1-34 27981 1 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 27982 1 0.0 0.0 0.0 0.0
CAF:nontagp Hledger.Read.Common Hledger/Read/Common.hs:730:1-7 18866 0 0.0 0.0 0.0 0.0
nontagp Hledger.Read.Common Hledger/Read/Common.hs:(730,1)-(733,56) 28626 1 0.0 0.0 0.0 0.0
CAF:nontagp_go Hledger.Read.Common <no location info> 18865 0 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 28627 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 28628 1 0.0 0.0 0.0 0.0
CAF:normaliseMixedAmount Hledger.Data.Amount Hledger/Data/Amount.hs:392:1-20 21998 0 0.0 0.0 0.0 0.0
normaliseMixedAmount Hledger.Data.Amount Hledger/Data/Amount.hs:392:1-44 74811 1 0.0 0.0 0.0 0.0
CAF:normaliseMixedAmount1 Hledger.Data.Amount <no location info> 21996 0 0.0 0.0 0.0 0.0
missingmixedamt Hledger.Data.Amount Hledger/Data/Amount.hs:373:1-36 74261 1 0.0 0.0 0.0 0.0
CAF:normaliseMixedAmountSquashPricesForDisplay Hledger.Data.Amount Hledger/Data/Amount.hs:434:1-42 22000 0 0.0 0.0 0.0 0.0
normaliseMixedAmountSquashPricesForDisplay Hledger.Data.Amount Hledger/Data/Amount.hs:434:1-65 74775 1 0.0 0.0 0.0 0.0
CAF:nosymbolamountp2 Hledger.Read.Common <no location info> 18698 0 0.0 0.0 0.0 0.0
nosymbolamountp Hledger.Read.Common Hledger/Read/Common.hs:(439,1)-(449,24) 40637 1 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:1126:3-53 40638 1 0.0 0.0 0.0 0.0
CAF:notNull_r4jYU Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:139:1-7 16078 0 0.0 0.0 0.0 0.0
notNull Text.Regex.TDFA.CorePattern Text/Regex/TDFA/CorePattern.hs:139:1-12 80936 1 0.0 0.0 0.0 0.0
CAF:notNullable_r4Uji Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:96:1-11 16184 0 0.0 0.0 0.0 0.0
notNullable Text.Regex.TDFA.TNFA Text/Regex/TDFA/TNFA.hs:96:1-26 80930 1 0.0 0.0 0.0 0.0
CAF:nullacct Hledger.Data.Account Hledger/Data/Account.hs:47:1-8 22300 0 0.0 0.0 0.0 0.0
nullacct Hledger.Data.Account Hledger/Data/Account.hs:(47,1)-(55,3) 78409 1 0.0 0.0 0.0 0.0
CAF:nullamt Hledger.Data.Amount Hledger/Data/Amount.hs:155:1-7 21984 0 0.0 0.0 0.0 0.0
nullamt Hledger.Data.Amount Hledger/Data/Amount.hs:155:1-16 74823 1 0.0 0.0 0.0 0.0
CAF:nulljournal Hledger.Data.Journal Hledger/Data/Journal.hs:179:1-11 21299 0 0.0 0.0 0.0 0.0
nulljournal Hledger.Data.Journal Hledger/Data/Journal.hs:(179,1)-(196,3) 26029 1 0.0 0.0 0.0 0.0
CAF:nullledger Hledger.Data.Ledger Hledger/Data/Ledger.hs:35:1-10 21073 0 0.0 0.0 0.0 0.0
nullledger Hledger.Data.Ledger Hledger/Data/Ledger.hs:(35,1)-(38,3) 78393 1 0.0 0.0 0.0 0.0
CAF:nullmixedamt1 Hledger.Data.Amount <no location info> 21973 0 0.0 0.0 0.0 0.0
nullmixedamt Hledger.Data.Amount Hledger/Data/Amount.hs:369:1-23 78870 1 0.0 0.0 0.0 0.0
CAF:nullposting Hledger.Data.Posting Hledger/Data/Posting.hs:80:1-11 20750 0 0.0 0.0 0.0 0.0
nullposting Hledger.Data.Posting Hledger/Data/Posting.hs:(80,1)-(92,17) 74259 1 0.0 0.0 0.0 0.0
CAF:numElemsInCacheLine Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:52:1-19 15315 0 0.0 0.0 0.0 0.0
numElemsInCacheLine Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:(52,1)-(54,62) 74220 1 0.0 0.0 0.0 0.0
numElemsInCacheLine.z Data.HashTable.Internal.Utils src/Data/HashTable/Internal/Utils.hs:54:5-62 74221 1 0.0 0.0 0.0 0.0
CAF:numberp1 Hledger.Read.Common <no location info> 18601 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25660 1 0.0 0.0 0.0 0.0
label Text.Megaparsec Text/Megaparsec.hs:867:3-28 25661 1 0.0 0.0 0.0 0.0
CAF:numberp12 Hledger.Read.Common <no location info> 18600 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25664 0 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 25665 1 0.0 0.0 0.0 0.0
CAF:numberp14 Hledger.Read.Common <no location info> 18568 0 0.0 0.0 0.0 0.0
signp Hledger.Read.Common Hledger/Read/Common.hs:(403,1)-(406,38) 25548 1 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 25549 1 0.0 0.0 0.0 0.0
CAF:numberp16 Hledger.Read.Common <no location info> 18567 0 0.0 0.0 0.0 0.0
CAF:numberp18 Hledger.Read.Common <no location info> 18566 0 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 25552 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 25553 1 0.0 0.0 0.0 0.0
CAF:numberp19 Hledger.Read.Common <no location info> 18562 0 0.0 0.0 0.0 0.0
signp Hledger.Read.Common Hledger/Read/Common.hs:(403,1)-(406,38) 25562 0 0.0 0.0 0.0 0.0
pure Text.Megaparsec Text/Megaparsec.hs:326:3-18 25563 1 0.0 0.0 0.0 0.0
CAF:numberp20 Hledger.Read.Common <no location info> 18565 0 0.0 0.0 0.0 0.0
signp Hledger.Read.Common Hledger/Read/Common.hs:(403,1)-(406,38) 25555 0 0.0 0.0 0.0 0.0
CAF:numberp21 Hledger.Read.Common <no location info> 18564 0 0.0 0.0 0.0 0.0
signp Hledger.Read.Common Hledger/Read/Common.hs:(403,1)-(406,38) 25558 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 25559 1 0.0 0.0 0.0 0.0
CAF:numberp23 Hledger.Read.Common <no location info> 18563 0 0.0 0.0 0.0 0.0
CAF:numeric_r5LsQ Hledger.Read.Common Hledger/Read/Common.hs:576:5-11 18571 0 0.0 0.0 0.0 0.0
numberp Hledger.Read.Common Hledger/Read/Common.hs:(529,1)-(576,36) 25759 0 0.0 0.0 0.0 0.0
numberp.numeric Hledger.Read.Common Hledger/Read/Common.hs:576:5-36 25760 1 0.0 0.0 0.0 0.0
CAF:outputFileFlag4 Hledger.Cli.CliOptions <no location info> 23560 0 0.0 0.0 0.0 0.0
CAF:outputFileFromOpts2 Hledger.Cli.CliOptions <no location info> 23578 0 0.0 0.0 0.0 0.0
CAF:outputFormatFlag6 Hledger.Cli.CliOptions <no location info> 23559 0 0.0 0.0 0.0 0.0
CAF:p1_r42ZZ Hledger.Query <no location info> 19080 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24880 0 0.0 0.0 0.0 0.0
words''.singleQuotedPattern Hledger.Query Hledger/Query.hs:200:7-125 24881 0 0.0 0.0 0.0 0.0
*> Text.Megaparsec Text/Megaparsec.hs:328:3-32 24882 1 0.0 0.0 0.0 0.0
CAF:p1_r4LlV Text.Regex.TDFA.ReadRegex <no location info> 15949 0 0.0 0.0 0.0 0.0
parseRegex Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(28,1)-(31,83) 80663 0 0.0 0.0 0.0 0.0
eof Text.Parsec.Combinator Text/Parsec/Combinator.hs:242:1-63 80664 0 0.0 0.0 0.0 0.0
notFollowedBy Text.Parsec.Combinator Text/Parsec/Combinator.hs:(257,1)-(259,27) 80665 1 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 80666 2 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 80671 1 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 80672 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 80676 1 0.0 0.0 0.0 0.0
CAF:p1_r5Lzo Hledger.Read.Common <no location info> 18858 0 0.0 0.0 0.0 0.0
nontagp Hledger.Read.Common Hledger/Read/Common.hs:(730,1)-(733,56) 28666 0 0.0 0.0 0.0 0.0
eof Text.Megaparsec Text/Megaparsec.hs:873:3-26 28667 1 0.0 0.0 0.0 0.0
CAF:p2_r4Lme Text.Regex.TDFA.ReadRegex <no location info> 15966 0 0.0 0.0 0.0 0.0
p_group Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(51,1)-(53,62) 79750 0 0.0 0.0 0.0 0.0
between Text.Parsec.Combinator Text/Parsec/Combinator.hs:(74,1)-(75,57) 79751 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 79752 2 0.0 0.0 0.0 0.0
CAF:p2_r5Lzq Hledger.Read.Common <no location info> 18859 0 0.0 0.0 0.0 0.0
nontagp Hledger.Read.Common Hledger/Read/Common.hs:(730,1)-(733,56) 28639 0 0.0 0.0 0.0 0.0
CAF:p3_r5Lzs Hledger.Read.Common <no location info> 18860 0 0.0 0.0 0.0 0.0
nontagp Hledger.Read.Common Hledger/Read/Common.hs:(730,1)-(733,56) 28637 0 0.0 0.0 0.0 0.0
try Text.Megaparsec Text/Megaparsec.hs:868:3-26 28638 1 0.0 0.0 0.0 0.0
CAF:p4_r5Lzt Hledger.Read.Common <no location info> 18861 0 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 28635 1 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 28636 1 0.0 0.0 0.0 0.0
CAF:p5_r430m Hledger.Query <no location info> 19089 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24904 0 0.0 0.0 0.0 0.0
words''.doubleQuotedPattern Hledger.Query Hledger/Query.hs:202:7-124 24905 0 0.0 0.0 0.0 0.0
*> Text.Megaparsec Text/Megaparsec.hs:328:3-32 24906 1 0.0 0.0 0.0 0.0
CAF:p_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:91:1-6 15910 0 0.0 0.0 0.0 0.0
p_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(91,1)-(96,37) 79367 1 0.0 0.0 0.0 0.0
<|> Text.Parsec.Prim Text/Parsec/Prim.hs:348:1-23 79368 1 0.0 0.0 0.0 0.0
mplus Text.Parsec.Prim Text/Parsec/Prim.hs:289:5-34 79369 1 0.0 0.0 0.0 0.0
CAF:p_r4LjQ Text.Regex.TDFA.ReadRegex <no location info> 15812 0 0.0 0.0 0.0 0.0
parseRegex Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(28,1)-(31,83) 80716 0 0.0 0.0 0.0 0.0
getState Text.Parsec.Prim Text/Parsec/Prim.hs:745:1-43 80717 1 0.0 0.0 0.0 0.0
CAF:p_r5Lzg Hledger.Read.Common <no location info> 18855 0 0.0 0.0 0.0 0.0
nontagp Hledger.Read.Common Hledger/Read/Common.hs:(730,1)-(733,56) 28679 0 0.0 0.0 0.0 0.0
token Text.Megaparsec Text/Megaparsec.hs:874:3-28 28680 1 0.0 0.0 0.0 0.0
CAF:p_set_elem_char_r4LlF Text.Regex.TDFA.ReadRegex <no location info> 15918 0 0.0 0.0 0.0 0.0
p_set_elem_char Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(139,1)-(144,19) 80073 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 80074 1 0.0 0.0 0.0 0.0
CAF:p_set_elem_class_r4Ll6 Text.Regex.TDFA.ReadRegex <no location info> 15869 0 0.0 0.0 0.0 0.0
p_set_elem_class Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(121,1)-(122,65) 79866 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 79867 1 0.0 0.0 0.0 0.0
CAF:p_set_elem_coll_r4Llm Text.Regex.TDFA.ReadRegex <no location info> 15883 0 0.0 0.0 0.0 0.0
p_set_elem_coll Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(127,1)-(128,65) 79915 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 79916 1 0.0 0.0 0.0 0.0
CAF:p_set_elem_equiv_r4Lle Text.Regex.TDFA.ReadRegex <no location info> 15876 0 0.0 0.0 0.0 0.0
p_set_elem_equiv Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(124,1)-(125,65) 79890 1 0.0 0.0 0.0 0.0
>>= Text.Parsec.Prim Text/Parsec/Prim.hs:202:5-29 79891 1 0.0 0.0 0.0 0.0
CAF:p_set_elem_r4LlK Text.Regex.TDFA.ReadRegex <no location info> 15923 0 0.0 0.0 0.0 0.0
p_set_elem Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(118,1)-(119,88) 79850 1 0.0 0.0 0.0 0.0
<?> Text.Parsec.Prim Text/Parsec/Prim.hs:333:1-23 79851 1 0.0 0.0 0.0 0.0
label Text.Parsec.Prim Text/Parsec/Prim.hs:(352,1)-(353,18) 79852 1 0.0 0.0 0.0 0.0
labels Text.Parsec.Prim Text/Parsec/Prim.hs:(356,1)-(370,48) 79853 1 0.0 0.0 0.0 0.0
CAF:p_set_elem_range_r4Llu Text.Regex.TDFA.ReadRegex <no location info> 15889 0 0.0 0.0 0.0 0.0
p_set_elem_range Text.Regex.TDFA.ReadRegex Text/Regex/TDFA/ReadRegex.hs:(130,1)-(137,85) 79940 1 0.0 0.0 0.0 0.0
try Text.Parsec.Prim Text/Parsec/Prim.hs:(475,1)-(477,34) 79941 1 0.0 0.0 0.0 0.0
CAF:parseQuery1 Hledger.Query <no location info> 19618 0 0.0 0.0 0.0 0.0
parseQuery Hledger.Query Hledger/Query.hs:(160,1)-(167,84) 24515 0 0.0 0.0 0.0 0.0
parseQuery.terms Hledger.Query Hledger/Query.hs:162:5-30 24516 0 0.0 0.0 0.0 0.0
words'' Hledger.Query Hledger/Query.hs:(185,1)-(204,63) 24517 1 0.0 0.0 0.0 0.0
parsewith Hledger.Utils.Parse Hledger/Utils/Parse.hs:45:1-28 24522 1 0.0 0.0 0.0 0.0
words''.maybeprefixedquotedphrases Hledger.Query Hledger/Query.hs:188:7-145 24529 1 0.0 0.0 0.0 0.0
<*> Text.Megaparsec Text/Megaparsec.hs:327:3-16 24535 2 0.0 0.0 0.0 0.0
<|> Text.Megaparsec Text/Megaparsec.hs:347:3-16 24530 2 0.0 0.0 0.0 0.0
mplus Text.Megaparsec Text/Megaparsec.hs:421:3-15 24531 2 0.0 0.0 0.0 0.0
*> Text.Megaparsec Text/Megaparsec.hs:328:3-32 24949 1 0.0 0.0 0.0 0.0
choice' Hledger.Utils.Parse Hledger/Utils/Parse.hs:34:1-26 24537 0 0.0 0.0 0.0 0.0
words''.prefixedQuotedPattern Hledger.Query Hledger/Query.hs:(190,7)-(198,40) 24543 1 0.0 0.0 0.0 0.0
>>= Text.Megaparsec Text/Megaparsec.hs:353:3-16 24544 1 0.0 0.0 0.0 0.0
CAF:parseQuery17 Hledger.Query <no location info> 19434 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24845 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24846 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24847 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24852 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24853 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24854 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24855 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24856 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24859 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24860 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24857 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24858 1 0.0 0.0 0.0 0.0
CAF:parseQuery18 Hledger.Query <no location info> 19402 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24600 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24601 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24602 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24603 1 0.0 0.0 0.0 0.0
CAF:parseQuery19 Hledger.Query <no location info> 19138 0 0.0 0.0 0.0 0.0
CAF:parseQuery21 Hledger.Query <no location info> 19433 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24848 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24849 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24850 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24851 1 0.0 0.0 0.0 0.0
CAF:parseQuery22 Hledger.Query <no location info> 19388 0 0.0 0.0 0.0 0.0
CAF:parseQuery24 Hledger.Query <no location info> 19432 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24828 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24829 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24830 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24836 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24837 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24838 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24839 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24840 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24843 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24844 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24841 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24842 1 0.0 0.0 0.0 0.0
CAF:parseQuery25 Hledger.Query <no location info> 19431 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24831 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24832 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24835 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24833 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24834 2 0.0 0.0 0.0 0.0
CAF:parseQuery26 Hledger.Query <no location info> 19389 0 0.0 0.0 0.0 0.0
CAF:parseQuery28 Hledger.Query <no location info> 19430 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24811 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24812 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24813 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24819 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24820 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24821 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24822 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24823 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24826 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24827 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24824 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24825 1 0.0 0.0 0.0 0.0
CAF:parseQuery29 Hledger.Query <no location info> 19429 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24814 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24815 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24818 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24816 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24817 2 0.0 0.0 0.0 0.0
CAF:parseQuery30 Hledger.Query <no location info> 19390 0 0.0 0.0 0.0 0.0
CAF:parseQuery32 Hledger.Query <no location info> 19428 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24795 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24796 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24797 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24802 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24803 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24804 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24805 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24806 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24809 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24810 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24807 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24808 1 0.0 0.0 0.0 0.0
CAF:parseQuery33 Hledger.Query <no location info> 19427 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24798 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24799 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24800 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24801 1 0.0 0.0 0.0 0.0
CAF:parseQuery34 Hledger.Query <no location info> 19391 0 0.0 0.0 0.0 0.0
CAF:parseQuery36 Hledger.Query <no location info> 19426 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24779 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24780 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24781 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24786 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24787 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24788 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24789 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24790 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24793 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24794 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24791 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24792 1 0.0 0.0 0.0 0.0
CAF:parseQuery37 Hledger.Query <no location info> 19425 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24782 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24783 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24784 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24785 1 0.0 0.0 0.0 0.0
CAF:parseQuery38 Hledger.Query <no location info> 19392 0 0.0 0.0 0.0 0.0
CAF:parseQuery40 Hledger.Query <no location info> 19424 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24762 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24763 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24764 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24770 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24771 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24772 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24773 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24774 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24777 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24778 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24775 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24776 1 0.0 0.0 0.0 0.0
CAF:parseQuery41 Hledger.Query <no location info> 19423 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24765 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24766 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24769 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24767 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24768 2 0.0 0.0 0.0 0.0
CAF:parseQuery42 Hledger.Query <no location info> 19393 0 0.0 0.0 0.0 0.0
CAF:parseQuery44 Hledger.Query <no location info> 19422 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24745 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24746 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24747 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24753 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24754 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24755 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24756 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24757 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24760 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24761 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24758 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24759 1 0.0 0.0 0.0 0.0
CAF:parseQuery45 Hledger.Query <no location info> 19421 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24748 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24749 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24752 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24750 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24751 2 0.0 0.0 0.0 0.0
CAF:parseQuery46 Hledger.Query <no location info> 19394 0 0.0 0.0 0.0 0.0
CAF:parseQuery48 Hledger.Query <no location info> 19420 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24729 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24730 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24731 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24736 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24737 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24738 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24739 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24740 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24743 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24744 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24741 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24742 1 0.0 0.0 0.0 0.0
CAF:parseQuery49 Hledger.Query <no location info> 19419 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24732 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24733 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24734 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24735 1 0.0 0.0 0.0 0.0
CAF:parseQuery50 Hledger.Query <no location info> 19395 0 0.0 0.0 0.0 0.0
CAF:parseQuery52 Hledger.Query <no location info> 19418 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24713 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24714 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24715 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24720 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24721 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24722 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24723 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24724 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24727 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24728 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24725 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24726 1 0.0 0.0 0.0 0.0
CAF:parseQuery53 Hledger.Query <no location info> 19417 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24716 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24717 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24718 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24719 1 0.0 0.0 0.0 0.0
CAF:parseQuery54 Hledger.Query <no location info> 19396 0 0.0 0.0 0.0 0.0
CAF:parseQuery56 Hledger.Query <no location info> 19416 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24697 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24698 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24699 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24704 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24705 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24706 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24707 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24708 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24711 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24712 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24709 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24710 1 0.0 0.0 0.0 0.0
CAF:parseQuery57 Hledger.Query <no location info> 19415 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24700 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24701 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24702 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24703 1 0.0 0.0 0.0 0.0
CAF:parseQuery58 Hledger.Query <no location info> 19118 0 0.0 0.0 0.0 0.0
CAF:parseQuery60 Hledger.Query <no location info> 19414 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24680 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24681 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24682 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24688 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24689 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24690 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24691 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24692 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24695 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24696 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24693 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24694 1 0.0 0.0 0.0 0.0
CAF:parseQuery61 Hledger.Query <no location info> 19413 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24683 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24684 0 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24687 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24685 2 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24686 2 0.0 0.0 0.0 0.0
CAF:parseQuery62 Hledger.Query <no location info> 19121 0 0.0 0.0 0.0 0.0
CAF:parseQuery64 Hledger.Query <no location info> 19412 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24664 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24665 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24666 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24671 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24672 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24673 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24674 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24675 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24678 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24679 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24676 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24677 1 0.0 0.0 0.0 0.0
CAF:parseQuery65 Hledger.Query <no location info> 19411 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24667 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24668 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24669 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24670 1 0.0 0.0 0.0 0.0
CAF:parseQuery66 Hledger.Query <no location info> 19397 0 0.0 0.0 0.0 0.0
CAF:parseQuery68 Hledger.Query <no location info> 19410 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24648 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24649 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24650 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24655 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24656 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24657 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24658 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24659 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24662 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24663 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24660 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24661 1 0.0 0.0 0.0 0.0
CAF:parseQuery69 Hledger.Query <no location info> 19409 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24651 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24652 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24653 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24654 1 0.0 0.0 0.0 0.0
CAF:parseQuery70 Hledger.Query <no location info> 19398 0 0.0 0.0 0.0 0.0
CAF:parseQuery72 Hledger.Query <no location info> 19408 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24632 0 0.0 0.0 0.0 0.0
mappend Data.Text Data/Text.hs:347:5-18 24633 0 0.0 0.0 0.0 0.0
<> Data.Text Data/Text.hs:341:5-17 24634 0 0.0 0.0 0.0 0.0
append Data.Text Data/Text.hs:(456,1)-(468,18) 24639 1 0.0 0.0 0.0 0.0
append.len Data.Text Data/Text.hs:462:7-21 24640 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24641 1 0.0 0.0 0.0 0.0
run Data.Text.Array Data/Text/Array.hs:178:1-34 24642 1 0.0 0.0 0.0 0.0
append.x Data.Text Data/Text.hs:(464,7)-(468,18) 24643 0 0.0 0.0 0.0 0.0
aBA Data.Text.Array Data/Text/Array.hs:84:7-9 24646 2 0.0 0.0 0.0 0.0
maBA Data.Text.Array Data/Text/Array.hs:92:7-10 24647 2 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24644 1 0.0 0.0 0.0 0.0
shiftR Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:63:5-51 24645 1 0.0 0.0 0.0 0.0
CAF:parseQuery73 Hledger.Query <no location info> 19407 0 0.0 0.0 0.0 0.0
prefixes Hledger.Query Hledger/Query.hs:(222,1)-(239,5) 24635 0 0.0 0.0 0.0 0.0
fromString Data.Text Data/Text.hs:354:5-21 24636 0 0.0 0.0 0.0 0.0
shiftL Data.Text.Internal.Unsafe.Shift Data/Text/Internal/Unsafe/Shift.hs:60:5-50 24637 1 0.0 0.
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment