hledger-1.32.3/Hledger/0000755000000000000000000000000014555053231012755 5ustar0000000000000000hledger-1.32.3/Hledger/Cli/0000755000000000000000000000000014555425351013472 5ustar0000000000000000hledger-1.32.3/Hledger/Cli/Commands/0000755000000000000000000000000014555433334015233 5ustar0000000000000000hledger-1.32.3/app/0000755000000000000000000000000014555053231012163 5ustar0000000000000000hledger-1.32.3/bench/0000755000000000000000000000000014434445206012465 5ustar0000000000000000hledger-1.32.3/embeddedfiles/0000755000000000000000000000000014555053231014157 5ustar0000000000000000hledger-1.32.3/shell-completion/0000755000000000000000000000000014513751565014672 5ustar0000000000000000hledger-1.32.3/test/0000755000000000000000000000000014555433443012371 5ustar0000000000000000hledger-1.32.3/Hledger/Cli.hs0000644000000000000000000003443614555053231014032 0ustar0000000000000000{-# LANGUAGE LambdaCase #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} {-# HLINT ignore "Unused LANGUAGE pragma" #-} {-| This is the root module of the @hledger@ package, providing hledger's command-line interface. The main function, commands, command-line options, and utilities useful to other hledger command-line programs are exported. It also re-exports hledger-lib:Hledger and cmdargs:System.Concole.CmdArgs.Explicit See also: - hledger-lib:Hledger - [The README files](https://github.com/search?q=repo%3Asimonmichael%2Fhledger+path%3A**%2FREADME*&type=code&ref=advsearch) - [The high-level developer docs](https://hledger.org/dev.html) == About hledger - a fast, reliable, user-friendly plain text accounting tool. Copyright (c) 2007-2023 Simon Michael and contributors Released under GPL version 3 or later. hledger is a Haskell rewrite of John Wiegley's "ledger". It generates financial reports from a plain text general journal. You can use the command line: > $ hledger or ghci: > $ make ghci > ghci> Right j <- runExceptT $ readJournalFile definputopts "examples/sample.journal" -- or: j <- defaultJournal > ghci> :t j > j :: Journal > ghci> stats defcliopts j > Main file : examples/sample.journal > Included files : > Transactions span : 2008-01-01 to 2009-01-01 (366 days) > Last transaction : 2008-12-31 (733772 days from now) > Transactions : 5 (0.0 per day) > Transactions last 30 days: 0 (0.0 per day) > Transactions last 7 days : 0 (0.0 per day) > Payees/descriptions : 5 > Accounts : 8 (depth 3) > Commodities : 1 ($) > Market prices : 0 () > > Run time (throughput) : 1695276900.00s (0 txns/s) > ghci> balance defcliopts j > $1 assets:bank:saving > $-2 assets:cash > $1 expenses:food > $1 expenses:supplies > $-1 income:gifts > $-1 income:salary > $1 liabilities:debts > -------------------- > 0 > ghci> etc. -} module Hledger.Cli ( prognameandversion, versionString, main, mainmode, argsToCliOpts, -- * Re-exports module Hledger.Cli.CliOptions, module Hledger.Cli.Commands, module Hledger.Cli.DocFiles, module Hledger.Cli.Utils, module Hledger.Cli.Version, module Hledger, -- ** System.Console.CmdArgs.Explicit module System.Console.CmdArgs.Explicit, ) where import Control.Monad (when) import Data.List import Safe import qualified System.Console.CmdArgs.Explicit as C import System.Environment import System.Exit import System.FilePath import System.Process import Text.Printf import Data.Time.Clock.POSIX (getPOSIXTime) import GitHash (tGitInfoCwdTry) import System.Console.CmdArgs.Explicit hiding (Name) -- don't clash with hledger-ui import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Commands import Hledger.Cli.DocFiles import Hledger.Cli.Utils import Hledger.Cli.Version -- | The program name and version string for this build of the hledger tool, -- including any git info available at build time. prognameandversion :: String prognameandversion = versionString progname packageversion -- | A helper to generate the best version string we can from the given -- program name and package version strings, current os and architecture, -- and any git info available at build time (commit hash, commit date, branch -- name, patchlevel since latest release tag for that program's package). -- Typically called for programs "hledger", "hledger-ui", or "hledger-web". -- -- The git info changes whenever any file in the repository changes. -- Keeping this template haskell call here and not down in Hledger.Cli.Version -- helps reduce the number of modules recompiled. versionString :: ProgramName -> PackageVersion -> String versionString = versionStringWith $$tGitInfoCwdTry -- | The overall cmdargs mode describing hledger's command-line options and subcommands. mainmode addons = defMode { modeNames = [progname ++ " [CMD]"] ,modeArgs = ([], Just $ argsFlag "[ARGS]") ,modeHelp = unlines ["hledger's main command line interface. Runs builtin commands and other hledger executables. Type \"hledger\" to list available commands."] ,modeGroupModes = Group { -- subcommands in the unnamed group, shown first: groupUnnamed = [ ] -- subcommands in named groups: ,groupNamed = [ ] -- subcommands handled but not shown in the help: ,groupHidden = map fst builtinCommands ++ map addonCommandMode addons } ,modeGroupFlags = Group { -- flags in named groups: groupNamed = [ ( "General input flags", inputflags) ,("\nGeneral reporting flags", reportflags) ,("\nGeneral help flags", helpflags) ] -- flags in the unnamed group, shown last: ,groupUnnamed = [] -- flags handled but not shown in the help: ,groupHidden = [detailedversionflag] -- ++ inputflags -- included here so they'll not raise a confusing error if present with no COMMAND } ,modeHelpSuffix = "Examples:" : map (progname ++) [ " list commands" ," CMD [--] [OPTS] [ARGS] run a command (use -- with addon commands)" ,"-CMD [OPTS] [ARGS] or run addon commands directly" ," -h show general usage" ," CMD -h show command usage" ," help [MANUAL] show any of the hledger manuals in various formats" ] } -- | Let's go! main :: IO () main = do starttime <- getPOSIXTime -- try to encourage user's $PAGER to properly display ANSI when useColorOnStdout setupPager -- Choose and run the appropriate internal or external command based -- on the raw command-line arguments, cmdarg's interpretation of -- same, and hledger-* executables in the user's PATH. A somewhat -- complex mishmash of cmdargs and custom processing, hence all the -- debugging support and tests. See also Hledger.Cli.CliOptions and -- command-line.test. -- some preliminary (imperfect) argument parsing to supplement cmdargs args <- getArgs >>= expandArgsAt let args' = moveFlagsAfterCommand $ replaceNumericFlags args isFlag = ("-" `isPrefixOf`) isNonEmptyNonFlag s = not (isFlag s) && not (null s) rawcmd = headDef "" $ takeWhile isNonEmptyNonFlag args' isNullCommand = null rawcmd (argsbeforecmd, argsaftercmd') = break (==rawcmd) args argsaftercmd = drop 1 argsaftercmd' dbgIO :: Show a => String -> a -> IO () dbgIO = ptraceAtIO 8 dbgIO "running" prognameandversion dbgIO "raw args" args dbgIO "raw args rearranged for cmdargs" args' dbgIO "raw command is probably" rawcmd dbgIO "raw args before command" argsbeforecmd dbgIO "raw args after command" argsaftercmd -- Search PATH for add-ons, excluding any that match built-in command names addons' <- hledgerAddons let addons = filter (not . (`elem` builtinCommandNames) . dropExtension) addons' -- parse arguments with cmdargs opts' <- argsToCliOpts args addons let opts = opts'{progstarttime_=starttime} -- select an action and run it. let cmd = command_ opts -- the full matched internal or external command name, if any isInternalCommand = cmd `elem` builtinCommandNames -- not (null cmd) && not (cmd `elem` addons) isExternalCommand = not (null cmd) && cmd `elem` addons -- probably isBadCommand = not (null rawcmd) && null cmd hasVersion = ("--version" `elem`) printUsage = pager $ showModeUsage $ mainmode addons badCommandError = error' ("command "++rawcmd++" is not recognized, run with no command to see a list") >> exitFailure -- PARTIAL: hasHelpFlag args1 = any (`elem` args1) ["-h","--help"] hasManFlag args1 = (`elem` args1) "--man" hasInfoFlag args1 = (`elem` args1) "--info" f `orShowHelp` mode1 | hasHelpFlag args = pager $ showModeUsage mode1 | hasInfoFlag args = runInfoForTopic "hledger" (headMay $ modeNames mode1) | hasManFlag args = runManForTopic "hledger" (headMay $ modeNames mode1) | otherwise = f -- where -- lastdocflag dbgIO "processed opts" opts dbgIO "command matched" cmd dbgIO "isNullCommand" isNullCommand dbgIO "isInternalCommand" isInternalCommand dbgIO "isExternalCommand" isExternalCommand dbgIO "isBadCommand" isBadCommand dbgIO "period from opts" (period_ . _rsReportOpts $ reportspec_ opts) dbgIO "interval from opts" (interval_ . _rsReportOpts $ reportspec_ opts) dbgIO "query from opts & args" (_rsQuery $ reportspec_ opts) let journallesserror = error $ cmd++" tried to read the journal but is not supposed to" runHledgerCommand -- high priority flags and situations. -h, then --help, then --info are highest priority. | isNullCommand && hasHelpFlag args = dbgIO "" "-h/--help with no command, showing general help" >> printUsage | isNullCommand && hasInfoFlag args = dbgIO "" "--info with no command, showing general info manual" >> runInfoForTopic "hledger" Nothing | isNullCommand && hasManFlag args = dbgIO "" "--man with no command, showing general man page" >> runManForTopic "hledger" Nothing | not (isExternalCommand || hasHelpFlag args || hasInfoFlag args || hasManFlag args) && (hasVersion args) -- || (hasVersion argsaftercmd && isInternalCommand)) = putStrLn prognameandversion -- \| (null externalcmd) && boolopt "binary-filename" rawopts = putStrLn $ binaryfilename progname -- \| "--browse-args" `elem` args = System.Console.CmdArgs.Helper.execute "cmdargs-browser" mainmode' args >>= (putStr . show) | isNullCommand = dbgIO "" "no command, showing commands list" >> printCommandsList prognameandversion addons | isBadCommand = badCommandError -- builtin commands | Just (cmdmode, cmdaction) <- findBuiltinCommand cmd = (case True of -- these commands should not require or read the journal _ | cmd `elem` ["demo","help","test"] -> cmdaction opts journallesserror -- these commands should create the journal if missing _ | cmd `elem` ["add","import"] -> do ensureJournalFileExists . head =<< journalFilePathFromOpts opts withJournalDo opts (cmdaction opts) -- other commands read the journal and should fail if it's missing _ -> withJournalDo opts (cmdaction opts) ) `orShowHelp` cmdmode -- addon commands | isExternalCommand = do let externalargs = argsbeforecmd ++ filter (/="--") argsaftercmd let shellcmd = printf "%s-%s %s" progname cmd (unwords' externalargs) :: String dbgIO "external command selected" cmd dbgIO "external command arguments" (map quoteIfNeeded externalargs) dbgIO "running shell command" shellcmd system shellcmd >>= exitWith -- deprecated commands -- cmd == "convert" = error' (modeHelp oldconvertmode) >> exitFailure -- shouldn't reach here | otherwise = usageError ("could not understand the arguments "++show args) >> exitFailure runHledgerCommand -- | Parse hledger CLI options from these command line arguments and -- add-on command names, or raise any error. argsToCliOpts :: [String] -> [String] -> IO CliOpts argsToCliOpts args addons = do let args' = moveFlagsAfterCommand $ replaceNumericFlags args cmdargsopts = either usageError id $ C.process (mainmode addons) args' rawOptsToCliOpts cmdargsopts -- | A hacky workaround for cmdargs not accepting flags before the -- subcommand name: try to detect and move such flags after the -- command. This allows the user to put them in either position. -- The order of options is not preserved, but that should be ok. -- -- Since we're not parsing flags as precisely as cmdargs here, this is -- imperfect. We make a decent effort to: -- - move all no-argument help/input/report flags -- - move all required-argument help/input/report flags along with their values, space-separated or not -- - ensure --debug has an argument (because.. "or this all goes to hell") -- - not confuse things further or cause misleading errors. moveFlagsAfterCommand :: [String] -> [String] moveFlagsAfterCommand args = moveArgs $ ensureDebugHasArg args where moveArgs args1 = insertFlagsAfterCommand $ moveArgs' (args1, []) where -- -f FILE ..., --alias ALIAS ... moveArgs' ((f:v:a:as), flags) | isMovableReqArgFlag f, isValue v = moveArgs' (a:as, flags ++ [f,v]) -- -fFILE ..., --alias=ALIAS ... moveArgs' ((fv:a:as), flags) | isMovableArgFlagAndValue fv = moveArgs' (a:as, flags ++ [fv]) -- -f(missing arg) moveArgs' ((f:a:as), flags) | isMovableReqArgFlag f, not (isValue a) = moveArgs' (a:as, flags ++ [f]) -- -h ..., --version ... moveArgs' ((f:a:as), flags) | isMovableNoArgFlag f = moveArgs' (a:as, flags ++ [f]) -- anything else moveArgs' (as, flags) = (as, flags) insertFlagsAfterCommand ([], flags) = flags insertFlagsAfterCommand (command1:args2, flags) = [command1] ++ flags ++ args2 isMovableNoArgFlag a = "-" `isPrefixOf` a && dropWhile (=='-') a `elem` optargflagstomove ++ noargflagstomove isMovableReqArgFlag a = "-" `isPrefixOf` a && dropWhile (=='-') a `elem` reqargflagstomove isMovableArgFlagAndValue ('-':'-':a:as) = case break (== '=') (a:as) of (f:fs,_:_) -> (f:fs) `elem` optargflagstomove ++ reqargflagstomove _ -> False isMovableArgFlagAndValue ('-':shortflag:_:_) = [shortflag] `elem` reqargflagstomove isMovableArgFlagAndValue _ = False isValue "-" = True isValue ('-':_) = False isValue _ = True flagstomove = inputflags ++ reportflags ++ helpflags noargflagstomove = concatMap flagNames $ filter ((==FlagNone).flagInfo) flagstomove reqargflagstomove = -- filter (/= "debug") $ concatMap flagNames $ filter ((==FlagReq ).flagInfo) flagstomove optargflagstomove = concatMap flagNames $ filter (isFlagOpt .flagInfo) flagstomove where isFlagOpt = \case FlagOpt _ -> True FlagOptRare _ -> True _ -> False -- unit tests (tests_Hledger_Cli) are defined in Hledger.Cli.Commands hledger-1.32.3/Hledger/Cli/CliOptions.hs0000644000000000000000000010712614555425351016120 0ustar0000000000000000{-| Common cmdargs modes and flags, a command-line options type, and related utilities used by hledger commands. -} {-# LANGUAGE CPP #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PackageImports #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Hledger.Cli.CliOptions ( -- * cmdargs flags & modes helpflags, detailedversionflag, flattreeflags, hiddenflags, inputflags, reportflags, -- outputflags, outputFormatFlag, outputFileFlag, generalflagsgroup1, generalflagsgroup2, generalflagsgroup3, defMode, defCommandMode, addonCommandMode, hledgerCommandMode, argsFlag, showModeUsage, withAliases, likelyExecutablesInPath, hledgerExecutablesInPath, ensureDebugHasArg, -- * CLI options CliOpts(..), HasCliOpts(..), defcliopts, getHledgerCliOpts, getHledgerCliOpts', rawOptsToCliOpts, outputFormats, defaultOutputFormat, CommandDoc, -- possibly these should move into argsToCliOpts -- * CLI option accessors -- | These do the extra processing required for some options. journalFilePathFromOpts, rulesFilePathFromOpts, outputFileFromOpts, outputFormatFromOpts, defaultWidth, -- widthFromOpts, replaceNumericFlags, -- | For register: registerWidthsFromOpts, -- * Other utils hledgerAddons, topicForMode, -- -- * Convenience re-exports -- module Data.String.Here, -- module System.Console.CmdArgs.Explicit, ) where import qualified Control.Exception as C import Control.Monad (when) import Data.Char import Data.Default import Data.Either (fromRight, isRight) import Data.List.Extra (groupSortOn, intercalate, isInfixOf, nubSort) import Data.List.Split (splitOn) import Data.Maybe --import Data.String.Here -- import Data.Text (Text) import qualified Data.Text as T import Data.Void (Void) import Safe import String.ANSI import System.Console.CmdArgs hiding (Default,def) import System.Console.CmdArgs.Explicit import System.Console.CmdArgs.Text #ifndef mingw32_HOST_OS import System.Console.Terminfo #endif import System.Directory import System.Environment import System.Exit (exitSuccess) import System.FilePath import System.Info (os) import Text.Megaparsec import Text.Megaparsec.Char import Hledger import Hledger.Cli.DocFiles import Hledger.Cli.Version import Data.Time.Clock.POSIX (POSIXTime) import Data.List (isPrefixOf, isSuffixOf) -- common cmdargs flags -- keep synced with flag docs in doc/common.m4 -- | Common help flags: --help, --debug, --version... helpflags :: [Flag RawOpts] helpflags = [ -- XXX why are these duplicated in defCommandMode below ? flagNone ["help","h"] (setboolopt "help") "show general help (or after CMD, command help)" ,flagNone ["man"] (setboolopt "man") "show user manual with man" ,flagNone ["info"] (setboolopt "info") "show info manual with info" -- ,flagNone ["browse-args"] (setboolopt "browse-args") "use a web UI to select options and build up a command line" ,flagReq ["debug"] (\s opts -> Right $ setopt "debug" s opts) "[N]" "show debug output (levels 1-9, default: 1)" ,flagNone ["version"] (setboolopt "version") "show version information" ] -- | A hidden flag just for the hledger executable. detailedversionflag :: Flag RawOpts detailedversionflag = flagNone ["version+"] (setboolopt "version+") "show version information with extra detail" -- | Common input-related flags: --file, --rules-file, --alias... inputflags :: [Flag RawOpts] inputflags = [ flagReq ["file","f"] (\s opts -> Right $ setopt "file" s opts) "FILE" "use a different input file. For stdin, use - (default: $LEDGER_FILE or $HOME/.hledger.journal)" ,flagReq ["rules-file"] (\s opts -> Right $ setopt "rules-file" s opts) "RFILE" "CSV conversion rules file (default: FILE.rules)" ,flagReq ["alias"] (\s opts -> Right $ setopt "alias" s opts) "OLD=NEW" "rename accounts named OLD to NEW" ,flagReq ["pivot"] (\s opts -> Right $ setopt "pivot" s opts) "TAGNAME" "use some other field/tag for account names" ,flagNone ["ignore-assertions","I"] (setboolopt "ignore-assertions") "ignore any balance assertions" ,flagNone ["strict","s"] (setboolopt "strict") "do extra error checking (check that all posted accounts are declared)" ] -- | Common report-related flags: --period, --cost, etc. reportflags :: [Flag RawOpts] reportflags = [ -- report period & interval flagReq ["begin","b"] (\s opts -> Right $ setopt "begin" s opts) "DATE" "include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval)" ,flagReq ["end","e"] (\s opts -> Right $ setopt "end" s opts) "DATE" "include postings/txns before this date (will be adjusted to following subperiod end when using a report interval)" ,flagNone ["daily","D"] (setboolopt "daily") "multiperiod/multicolumn report by day" ,flagNone ["weekly","W"] (setboolopt "weekly") "multiperiod/multicolumn report by week" ,flagNone ["monthly","M"] (setboolopt "monthly") "multiperiod/multicolumn report by month" ,flagNone ["quarterly","Q"] (setboolopt "quarterly") "multiperiod/multicolumn report by quarter" ,flagNone ["yearly","Y"] (setboolopt "yearly") "multiperiod/multicolumn report by year" ,flagReq ["period","p"] (\s opts -> Right $ setopt "period" s opts) "PERIODEXP" "set start date, end date, and/or report interval all at once" ,flagNone ["date2"] (setboolopt "date2") "match the secondary date instead. See command help for other effects. (--effective, --aux-date also accepted)" -- see also hiddenflags ,flagReq ["today"] (\s opts -> Right $ setopt "today" s opts) "DATE" "override today's date (affects relative smart dates, for tests/examples)" -- status/realness/depth/zero filters ,flagNone ["unmarked","U"] (setboolopt "unmarked") "include only unmarked postings/txns (can combine with -P or -C)" ,flagNone ["pending","P"] (setboolopt "pending") "include only pending postings/txns" ,flagNone ["cleared","C"] (setboolopt "cleared") "include only cleared postings/txns" ,flagNone ["real","R"] (setboolopt "real") "include only non-virtual postings" ,flagReq ["depth"] (\s opts -> Right $ setopt "depth" s opts) "NUM" "(or -NUM): hide accounts/postings deeper than this" ,flagNone ["empty","E"] (setboolopt "empty") "show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web)" -- valuation, including https://hledger.org/dev/hledger.html#valuation-type : ,flagNone ["B","cost"] (setboolopt "B") "show amounts converted to their cost/selling amount, using the transaction price." ,flagNone ["V","market"] (setboolopt "V") (unwords ["show amounts converted to period-end market value in their default valuation commodity." ,"Equivalent to --value=end." ]) ,flagReq ["X","exchange"] (\s opts -> Right $ setopt "X" s opts) "COMM" (unwords ["show amounts converted to current (single period reports)" ,"or period-end (multiperiod reports) market value in the specified commodity." ,"Equivalent to --value=end,COMM." ]) ,flagReq ["value"] (\s opts -> Right $ setopt "value" s opts) "TYPE[,COMM]" (unlines ["show amounts converted with valuation TYPE, and optionally to specified commodity COMM. TYPE can be:" ,"'then': convert to contemporaneous market value, in default valuation commodity or COMM (print & register commands only)" ,"'end': convert to period-end market value, in default valuation commodity or COMM" ,"'now': convert to current market value, in default valuation commodity or COMM" ,"YYYY-MM-DD: convert to market value on the given date, in default valuation commodity or COMM" ]) ,flagNone ["infer-equity"] (setboolopt "infer-equity") "infer conversion equity postings from costs" ,flagNone ["infer-costs"] (setboolopt "infer-costs") "infer costs from conversion equity postings" -- history of this flag so far, lest we be confused: -- originally --infer-value -- 2021-02 --infer-market-price added, --infer-value deprecated -- 2021-09 -- --infer-value hidden -- --infer-market-price renamed to --infer-market-prices, old spelling still works -- ReportOptions{infer_value_} renamed to infer_prices_, BalancingOpts{infer_prices_} renamed to infer_transaction_prices_ -- some related prices command changes -- --costs deprecated and hidden, uses --infer-market-prices instead -- --inverted-costs renamed to --infer-reverse-prices ,flagNone ["infer-market-prices"] (setboolopt "infer-market-prices") "use costs as additional market prices, as if they were P directives" -- generating transactions/postings ,flagOpt "" ["forecast"] (\s opts -> Right $ setopt "forecast" s opts) "PERIOD" (unwords [ "Generate transactions from periodic rules," , "between the latest recorded txn and 6 months from today," , "or during the specified PERIOD (= is required)." , "Auto posting rules will be applied to these transactions as well." , "Also, in hledger-ui make future-dated transactions visible." ]) ,flagNone ["auto"] (setboolopt "auto") "Generate extra postings by applying auto posting rules to all txns (not just forecast txns)." ,flagNone ["verbose-tags"] (setboolopt "verbose-tags") "Add visible tags indicating transactions or postings which have been generated/modified." -- general output-related ,flagReq ["commodity-style", "c"] (\s opts -> Right $ setopt "commodity-style" s opts) "COMM" "Override the commodity style in the output for the specified commodity. For example 'EUR1.000,00'." -- This has special support in hledger-lib:colorOption, keep synced ,flagReq ["color","colour"] (\s opts -> Right $ setopt "color" s opts) "WHEN" (unlines ["Should color-supporting commands use ANSI color codes in text output." ,"'auto' (default): whenever stdout seems to be a color-supporting terminal." ,"'always' or 'yes': always, useful eg when piping output into 'less -R'." ,"'never' or 'no': never." ,"A NO_COLOR environment variable overrides this." ]) ,flagOpt "yes" ["pretty"] (\s opts -> Right $ setopt "pretty" s opts) "WHEN" (unwords ["Show prettier output, e.g. using unicode box-drawing characters." ,"Accepts 'yes' (the default) or 'no'." ,"If you provide an argument you must use '=', e.g. '--pretty=yes'." ]) ] -- | Flags for selecting flat/tree mode, used for reports organised by account. -- With a True argument, shows some extra help about inclusive/exclusive amounts. flattreeflags :: Bool -> [Flag RawOpts] flattreeflags showamounthelp = [ flagNone ["flat","l"] (setboolopt "flat") ("show accounts as a flat list (default)" ++ if showamounthelp then ". Amounts exclude subaccount amounts, except where the account is depth-clipped." else "") ,flagNone ["tree","t"] (setboolopt "tree") ("show accounts as a tree" ++ if showamounthelp then ". Amounts include subaccount amounts." else "") ] -- | Common flags that are accepted but not shown in --help, -- such as --effective, --aux-date. hiddenflags :: [Flag RawOpts] hiddenflags = [ flagNone ["effective","aux-date"] (setboolopt "date2") "Ledger-compatible aliases for --date2" ,flagNone ["infer-value"] (setboolopt "infer-market-prices") "legacy flag that was renamed" ,flagNone ["pretty-tables"] (setopt "pretty" "always") "legacy flag that was renamed" ,flagNone ["anon"] (setboolopt "anon") "deprecated, renamed to --obfuscate" -- #2133, handled by anonymiseByOpts ,flagNone ["obfuscate"] (setboolopt "obfuscate") "slightly obfuscate hledger's output. Warning, does not give privacy. Formerly --anon." -- #2133, handled by maybeObfuscate ] -- | Common output-related flags: --output-file, --output-format... -- outputflags = [outputFormatFlag, outputFileFlag] outputFormatFlag :: [String] -> Flag RawOpts outputFormatFlag fmts = flagReq ["output-format","O"] (\s opts -> Right $ setopt "output-format" s opts) "FMT" ("select the output format. Supported formats:\n" ++ intercalate ", " fmts ++ ".") -- This has special support in hledger-lib:outputFileOption, keep synced outputFileFlag :: Flag RawOpts outputFileFlag = flagReq ["output-file","o"] (\s opts -> Right $ setopt "output-file" s opts) "FILE" "write output to FILE. A file extension matching one of the above formats selects that format." argsFlag :: FlagHelp -> Arg RawOpts argsFlag = flagArg (\s opts -> Right $ setopt "args" s opts) generalflagstitle :: String generalflagstitle = "\nGeneral flags" generalflagsgroup1, generalflagsgroup2, generalflagsgroup3 :: (String, [Flag RawOpts]) generalflagsgroup1 = (generalflagstitle, inputflags ++ reportflags ++ helpflags) generalflagsgroup2 = (generalflagstitle, inputflags ++ helpflags) generalflagsgroup3 = (generalflagstitle, helpflags) -- cmdargs mode constructors -- | An empty cmdargs mode to use as a template. -- Modes describe the top-level command, ie the program, or a subcommand, -- telling cmdargs how to parse a command line and how to -- generate the command's usage text. defMode :: Mode RawOpts defMode = Mode { modeNames = [] -- program/command name(s) ,modeHelp = "" -- short help for this command ,modeHelpSuffix = [] -- text displayed after the usage ,modeGroupFlags = Group { -- description of flags accepted by the command groupNamed = [] -- named groups of flags ,groupUnnamed = [] -- ungrouped flags ,groupHidden = [] -- flags not displayed in the usage } ,modeArgs = ([], Nothing) -- description of arguments accepted by the command ,modeValue = def -- value returned when this mode is used to parse a command line ,modeCheck = Right -- whether the mode's value is correct ,modeReform = const Nothing -- function to convert the value back to a command line arguments ,modeExpandAt = True -- expand @ arguments for program ? ,modeGroupModes = toGroup [] -- sub-modes } -- | A cmdargs mode suitable for a hledger built-in command -- with the given names (primary name + optional aliases). -- The usage message shows [QUERY] as argument. defCommandMode :: [Name] -> Mode RawOpts defCommandMode names = defMode { modeNames=names ,modeGroupFlags = Group { groupNamed = [] ,groupUnnamed = [ flagNone ["help"] (setboolopt "help") "Show command-line help" -- ,flagNone ["help"] (setboolopt "help") "Show long help." ,flagNone ["man"] (setboolopt "man") "Show user manual with man" ,flagNone ["info"] (setboolopt "info") "Show info manual with info" ] ,groupHidden = [] -- flags not displayed in the usage } ,modeArgs = ([], Just $ argsFlag "[QUERY]") ,modeValue=setopt "command" (headDef "" names) def } -- | A cmdargs mode representing the hledger add-on command with the -- given name, providing hledger's common input/reporting/help flags. -- Just used when invoking addons. addonCommandMode :: Name -> Mode RawOpts addonCommandMode nam = (defCommandMode [nam]) { modeHelp = "" -- XXX not needed ? -- fromMaybe "" $ lookup (stripAddonExtension name) [ -- ("addon" , "dummy add-on command for testing") -- ,("addon2" , "dummy add-on command for testing") -- ,("addon3" , "dummy add-on command for testing") -- ,("addon4" , "dummy add-on command for testing") -- ,("addon5" , "dummy add-on command for testing") -- ,("addon6" , "dummy add-on command for testing") -- ,("addon7" , "dummy add-on command for testing") -- ,("addon8" , "dummy add-on command for testing") -- ,("addon9" , "dummy add-on command for testing") -- ] ,modeGroupFlags = Group { groupUnnamed = [] ,groupHidden = hiddenflags ,groupNamed = [generalflagsgroup1] } } -- | A command's documentation. Used both as part of CLI help, and as -- part of the hledger manual. See parseCommandDoc. type CommandDoc = String -- | Build a cmdarg mode for a hledger command, -- from a help template and flag/argument specifications. -- Reduces boilerplate a little, though the complicated cmdargs -- flag and argument specs are still required. hledgerCommandMode :: CommandDoc -> [Flag RawOpts] -> [(String, [Flag RawOpts])] -> [Flag RawOpts] -> ([Arg RawOpts], Maybe (Arg RawOpts)) -> Mode RawOpts hledgerCommandMode doc unnamedflaggroup namedflaggroups hiddenflaggroup argsdescr = case parseCommandDoc doc of Nothing -> error' $ "Could not parse command doc:\n"++doc++"\n" -- PARTIAL: Just (names, shorthelp, longhelplines) -> (defCommandMode names) { modeHelp = shorthelp ,modeHelpSuffix = longhelplines ,modeGroupFlags = Group { groupUnnamed = unnamedflaggroup ,groupNamed = namedflaggroups ,groupHidden = hiddenflaggroup } ,modeArgs = argsdescr } -- | Parse a command's help text file (Somecommand.txt). -- This is generated from the command's doc source file (Somecommand.md) -- by Shake cmdhelp, and it should be formatted as follows: -- -- - First line: main command name -- -- - Third line: command aliases, comma-and-space separated, in parentheses (optional) -- -- - Fifth or third line to the line containing just _FLAGS (or end of file): short command help -- -- - Any lines after _FLAGS: long command help -- -- The CLI --help displays the short help, the flags help generated by cmdargs, -- then the long help (which some day we might make optional again). -- The manual displays the short help, then the long help (but not the flags list). -- parseCommandDoc :: CommandDoc -> Maybe ([Name], String, [String]) parseCommandDoc t = case lines t of [] -> Nothing (l1:_:l3:ls) -> Just (cmdname:cmdaliases, shorthelp, longhelplines) where cmdname = strip l1 (cmdaliases, rest) = if "(" `isPrefixOf` l3 && ")" `isSuffixOf` l3 then (words $ filter (/=',') $ drop 1 $ init l3, ls) else ([], l3:ls) (shorthelpls, longhelpls) = break (== "_FLAGS") $ dropWhile (=="") rest shorthelp = unlines $ reverse $ dropWhile null $ reverse shorthelpls longhelplines = dropWhile null $ drop 1 longhelpls _ -> Nothing -- error' "misformatted command help text file" -- | Get a mode's usage message as a nicely wrapped string. showModeUsage :: Mode a -> String showModeUsage = highlightHelp . (showText defaultWrap :: [Text] -> String) . (helpText [] HelpFormatDefault :: Mode a -> [Text]) -- | Add some ANSI decoration to cmdargs' help output. highlightHelp | not useColorOnStdout = id | otherwise = unlines . zipWith (curry f) [1..] . lines where f (n,s) | n==1 = bold s | s `elem` [ "General input flags:" ,"General reporting flags:" ,"General help flags:" ,"Flags:" ,"General flags:" ,"Examples:" ] = bold s | otherwise = s -- | Get the most appropriate documentation topic for a mode. -- Currently, that is either the hledger, hledger-ui or hledger-web -- manual. topicForMode :: Mode a -> Topic topicForMode m | n == "hledger-ui" = "ui" | n == "hledger-web" = "web" | otherwise = "cli" where n = headDef "" $ modeNames m -- | Add command aliases to the command's help string. withAliases :: String -> [String] -> String s `withAliases` [] = s s `withAliases` as = s ++ " (" ++ intercalate ", " as ++ ")" -- s `withAliases` (a:[]) = s ++ " (alias: " ++ a ++ ")" -- s `withAliases` as = s ++ " (aliases: " ++ intercalate ", " as ++ ")" -- help_postscript = [ -- -- "DATES can be Y/M/D or smart dates like \"last month\"." -- -- ,"PATTERNS are regular" -- -- ,"expressions which filter by account name. Prefix a pattern with desc: to" -- -- ,"filter by transaction description instead, prefix with not: to negate it." -- -- ,"When using both, not: comes last." -- ] -- CliOpts -- | Command line options, used in the @hledger@ package and above. -- This is the \"opts\" used throughout hledger CLI code. -- representing the options and arguments that were provided at -- startup on the command-line. data CliOpts = CliOpts { rawopts_ :: RawOpts ,command_ :: String ,file_ :: [FilePath] ,inputopts_ :: InputOpts ,reportspec_ :: ReportSpec ,output_file_ :: Maybe FilePath ,output_format_ :: Maybe String ,debug_ :: Int -- ^ debug level, set by @--debug[=N]@. See also 'Hledger.Utils.debugLevel'. ,no_new_accounts_ :: Bool -- add ,width_ :: Maybe String -- ^ the --width value provided, if any ,available_width_ :: Int -- ^ estimated usable screen width, based on -- 1. the COLUMNS env var, if set -- 2. the width reported by the terminal, if supported -- 3. the default (80) ,progstarttime_ :: POSIXTime } deriving (Show) instance Default CliOpts where def = defcliopts defcliopts :: CliOpts defcliopts = CliOpts { rawopts_ = def , command_ = "" , file_ = [] , inputopts_ = definputopts , reportspec_ = def , output_file_ = Nothing , output_format_ = Nothing , debug_ = 0 , no_new_accounts_ = False , width_ = Nothing , available_width_ = defaultWidth , progstarttime_ = 0 } -- | Default width for hledger console output, when not otherwise specified. defaultWidth :: Int defaultWidth = 80 -- | Replace any numeric flags (eg -2) with their long form (--depth 2), -- as I'm guessing cmdargs doesn't support this directly. replaceNumericFlags :: [String] -> [String] replaceNumericFlags = map replace where replace ('-':ds) | not (null ds) && all isDigit ds = "--depth="++ds replace s = s -- | Parse raw option string values to the desired final data types. -- Any relative smart dates will be converted to fixed dates based on -- today's date. Parsing failures will raise an error. -- Also records the terminal width, if supported. rawOptsToCliOpts :: RawOpts -> IO CliOpts rawOptsToCliOpts rawopts = do currentDay <- getCurrentDay let day = case maybestringopt "today" rawopts of Nothing -> currentDay Just d -> fromRight (error' $ "Unable to parse date \"" ++ d ++ "\"") $ -- PARTIAL: fromEFDay <$> fixSmartDateStrEither' currentDay (T.pack d) let iopts = rawOptsToInputOpts day rawopts rspec <- either error' pure $ rawOptsToReportSpec day rawopts -- PARTIAL: mcolumns <- readMay <$> getEnvSafe "COLUMNS" mtermwidth <- #ifdef mingw32_HOST_OS return Nothing #else (`getCapability` termColumns) <$> setupTermFromEnv -- XXX Throws a SetupTermError if the terminfo database could not be read, should catch #endif let availablewidth = head $ catMaybes [mcolumns, mtermwidth, Just defaultWidth] return defcliopts { rawopts_ = rawopts ,command_ = stringopt "command" rawopts ,file_ = listofstringopt "file" rawopts ,inputopts_ = iopts ,reportspec_ = rspec ,output_file_ = maybestringopt "output-file" rawopts ,output_format_ = maybestringopt "output-format" rawopts ,debug_ = posintopt "debug" rawopts ,no_new_accounts_ = boolopt "no-new-accounts" rawopts -- add ,width_ = maybestringopt "width" rawopts ,available_width_ = availablewidth } -- | A helper for addon commands: this parses options and arguments from -- the current command line using the given hledger-style cmdargs mode, -- and returns a CliOpts. Or, with --help or -h present, it prints -- long or short help, and exits the program. -- When --debug is present, also prints some debug output. -- Note this is not used by the main hledger executable. -- -- The help texts are generated from the mode. -- Long help includes the full usage description generated by cmdargs -- (including all supported options), framed by whatever pre- and postamble -- text the mode specifies. It's intended that this forms a complete -- help document or manual. -- -- Short help is a truncated version of the above: the preamble and -- the first part of the usage, up to the first line containing "flags:" -- (normally this marks the start of the common hledger flags); -- plus a mention of --help and the (presumed supported) common -- hledger options not displayed. -- -- Tips: -- Empty lines in the pre/postamble are removed by cmdargs; -- add a space character to preserve them. -- getHledgerCliOpts' :: Mode RawOpts -> [String] -> IO CliOpts getHledgerCliOpts' mode' args0 = do let rawopts = either usageError id $ process mode' args0 opts <- rawOptsToCliOpts rawopts debugArgs args0 opts when (boolopt "help" $ rawopts_ opts) $ putStr shorthelp >> exitSuccess -- when (boolopt "help" $ rawopts_ opts) $ putStr longhelp >> exitSuccess return opts where longhelp = showModeUsage mode' shorthelp = unlines $ (reverse $ dropWhile null $ reverse $ takeWhile (not . ("flags:" `isInfixOf`)) $ lines longhelp) ++ ["" ," See also hledger -h for general hledger options." ] -- | Print debug info about arguments and options if --debug is present. -- XXX use standard dbg helpers debugArgs :: [String] -> CliOpts -> IO () debugArgs args1 opts = when ("--debug" `elem` args1) $ do progname' <- getProgName putStrLn $ "running: " ++ progname' putStrLn $ "raw args: " ++ show args1 putStrLn $ "processed opts:\n" ++ show opts putStrLn $ "search query: " ++ show (_rsQuery $ reportspec_ opts) getHledgerCliOpts :: Mode RawOpts -> IO CliOpts getHledgerCliOpts mode' = do args' <- getArgs >>= expandArgsAt getHledgerCliOpts' mode' args' -- CliOpts accessors -- | Get the (tilde-expanded, absolute) journal file path from -- 1. options, 2. an environment variable, or 3. the default. -- Actually, returns one or more file paths. There will be more -- than one if multiple -f options were provided. -- File paths can have a READER: prefix naming a reader/data format. journalFilePathFromOpts :: CliOpts -> IO [String] journalFilePathFromOpts opts = do f <- defaultJournalPath d <- getCurrentDirectory case file_ opts of [] -> return [f] fs -> mapM (expandPathPreservingPrefix d) fs expandPathPreservingPrefix :: FilePath -> PrefixedFilePath -> IO PrefixedFilePath expandPathPreservingPrefix d prefixedf = do let (p,f) = splitReaderPrefix prefixedf f' <- expandPath d f return $ case p of Just p' -> p' ++ ":" ++ f' Nothing -> f' -- | Get the expanded, absolute output file path specified by an -- -o/--output-file options, or nothing, meaning stdout. outputFileFromOpts :: CliOpts -> IO (Maybe FilePath) outputFileFromOpts opts = do d <- getCurrentDirectory case output_file_ opts of Nothing -> return Nothing Just f -> Just <$> expandPath d f defaultOutputFormat :: String defaultOutputFormat = "txt" -- | All the output formats known by any command, for outputFormatFromOpts. -- To automatically infer it from -o/--output-file, it needs to be listed here. outputFormats :: [String] outputFormats = [defaultOutputFormat, "beancount", "csv", "json", "html", "sql", "tsv"] -- | Get the output format from the --output-format option, -- otherwise from a recognised file extension in the --output-file option, -- otherwise the default (txt). outputFormatFromOpts :: CliOpts -> String outputFormatFromOpts opts = case output_format_ opts of Just f -> f Nothing -> case filePathExtension <$> output_file_ opts of Just ext | ext `elem` outputFormats -> ext _ -> defaultOutputFormat -- -- | Get the file name without its last extension, from a file path. -- filePathBaseFileName :: FilePath -> String -- filePathBaseFileName = fst . splitExtension . snd . splitFileName -- | Get the last file extension, without the dot, from a file path. -- May return the null string. filePathExtension :: FilePath -> String filePathExtension = dropWhile (=='.') . snd . splitExtension . snd . splitFileName -- | Get the (tilde-expanded) rules file path from options, if any. rulesFilePathFromOpts :: CliOpts -> IO (Maybe FilePath) rulesFilePathFromOpts opts = do d <- getCurrentDirectory maybe (return Nothing) (fmap Just . expandPath d) $ mrules_file_ $ inputopts_ opts -- -- | Get the width in characters to use for console output. -- -- This comes from the --width option, or the COLUMNS environment -- -- variable, or (on posix platforms) the current terminal width, or 80. -- -- Will raise a parse error for a malformed --width argument. -- widthFromOpts :: CliOpts -> Int -- widthFromOpts CliOpts{width_=Nothing, available_width_=w} = w -- widthFromOpts CliOpts{width_=Just s} = -- case runParser (read `fmap` some digitChar <* eof :: ParsecT Void String Identity Int) "(unknown)" s of -- Left e -> usageError $ "could not parse width option: "++errorBundlePretty e -- Right w -> w -- for register: -- | Get the width in characters to use for the register command's console output, -- and also the description column width if specified (following the main width, comma-separated). -- The widths will be as follows: -- @ -- no --width flag - overall width is the available width (COLUMNS, or posix terminal width, or 80); description width is unspecified (auto) -- --width W - overall width is W, description width is auto -- --width W,D - overall width is W, description width is D -- @ -- Will raise a parse error for a malformed --width argument. registerWidthsFromOpts :: CliOpts -> (Int, Maybe Int) registerWidthsFromOpts CliOpts{width_=Nothing, available_width_=w} = (w, Nothing) registerWidthsFromOpts CliOpts{width_=Just s} = case runParser registerwidthp "(unknown)" s of Left e -> usageError $ "could not parse width option: "++errorBundlePretty e Right ws -> ws where registerwidthp :: (Stream s, Char ~ Token s) => ParsecT Void s m (Int, Maybe Int) registerwidthp = do totalwidth <- read `fmap` some digitChar descwidth <- optional (char ',' >> read `fmap` some digitChar) eof return (totalwidth, descwidth) -- Other utils -- | Get the sorted unique canonical names of hledger addon commands -- found in the current user's PATH. These are used in command line -- parsing and to display the commands list. -- -- Canonical addon names are the filenames of hledger-* executables in -- PATH, without the "hledger-" prefix, and without the file extension -- except when it's needed for disambiguation (see below). -- -- When there are exactly two versions of an executable (same base -- name, different extensions) that look like a source and compiled -- pair (one has .exe, .com, or no extension), the source version will -- be excluded (even if it happens to be newer). When there are three -- or more versions (or two versions that don't look like a -- source/compiled pair), they are all included, with file extensions -- intact. -- hledgerAddons :: IO [String] hledgerAddons = do -- past bug generator as1 <- hledgerExecutablesInPath -- ["hledger-check","hledger-check-dates","hledger-check-dates.hs","hledger-check.hs","hledger-check.py"] let as2 = map stripPrognamePrefix as1 -- ["check","check-dates","check-dates.hs","check.hs","check.py"] let as3 = groupSortOn takeBaseName as2 -- [["check","check.hs","check.py"],["check-dates","check-dates.hs"]] let as4 = concatMap dropRedundantSourceVersion as3 -- ["check","check.hs","check.py","check-dates"] return as4 stripPrognamePrefix = drop (length progname + 1) dropRedundantSourceVersion [f,g] | map toLower (takeExtension f) `elem` compiledExts = [f] | map toLower (takeExtension g) `elem` compiledExts = [g] dropRedundantSourceVersion fs = fs compiledExts = ["",".com",".exe"] -- | Get the sorted unique filenames of all hledger-* executables in -- the current user's PATH. These are files in any of the PATH directories, -- named hledger-*, with either no extension (and no periods in the name) -- or one of the addonExtensions. -- We do not currently filter out non-file objects or files without execute permission. hledgerExecutablesInPath :: IO [String] hledgerExecutablesInPath = filter isHledgerExeName <$> likelyExecutablesInPath -- None of https://hackage.haskell.org/package/directory-1.3.8.1/docs/System-Directory.html#g:5 -- do quite what we need (find all the executables in PATH with a filename prefix). -- | Get all sorted unique filenames in the current user's PATH. -- We do not currently filter out non-file objects or files without execute permission. likelyExecutablesInPath :: IO [String] likelyExecutablesInPath = do pathdirs <- splitOn pathsep `fmap` getEnvSafe "PATH" pathfiles <- concat `fmap` mapM getDirectoryContentsSafe pathdirs return $ nubSort pathfiles where pathsep = if os == "mingw32" then ";" else ":" -- -- Exclude directories and files without execute permission: -- this would do a stat for each hledger-* file found, which is probably ok. -- But it needs file paths, not just file names. -- -- exes' <- filterM doesFileExist exe' -- exes'' <- filterM isExecutable exes' -- return exes'' -- where isExecutable f = getPermissions f >>= (return . executable) isHledgerExeName :: String -> Bool isHledgerExeName = isRight . parsewith hledgerexenamep . T.pack where hledgerexenamep = do _ <- string $ T.pack progname _ <- char '-' _ <- some $ noneOf ['.'] optional (string "." >> choice' (map (string . T.pack) addonExtensions)) eof -- stripAddonExtension :: String -> String -- stripAddonExtension = regexReplace re "" where re = "\\.(" ++ intercalate "|" addonExtensions ++ ")$" addonExtensions :: [String] addonExtensions = ["bat" ,"com" ,"exe" ,"hs" ,"js" ,"lhs" ,"lua" ,"php" ,"pl" ,"py" ,"rb" ,"rkt" ,"sh" -- ,"" ] getEnvSafe :: String -> IO String getEnvSafe v = getEnv v `C.catch` (\(_::C.IOException) -> return "") -- XXX should catch only isDoesNotExistError e getDirectoryContentsSafe :: FilePath -> IO [String] getDirectoryContentsSafe d = (filter (not . (`elem` [".",".."])) `fmap` getDirectoryContents d) `C.catch` (\(_::C.IOException) -> return []) -- not used: -- -- | Print debug info about arguments and options if --debug is present. -- debugArgs :: [String] -> CliOpts -> IO () -- debugArgs args opts = -- when ("--debug" `elem` args) $ do -- progname <- getProgName -- putStrLn $ "running: " ++ progname -- putStrLn $ "raw args: " ++ show args -- putStrLn $ "processed opts:\n" ++ show opts -- d <- getCurrentDay -- putStrLn $ "search query: " ++ (show $ queryFromOpts d $ reportopts_ opts) -- ** Lenses makeHledgerClassyLenses ''CliOpts instance HasInputOpts CliOpts where inputOpts = inputopts instance HasBalancingOpts CliOpts where balancingOpts = inputOpts.balancingOpts instance HasReportSpec CliOpts where reportSpec = reportspec instance HasReportOptsNoUpdate CliOpts where reportOptsNoUpdate = reportSpec.reportOptsNoUpdate instance HasReportOpts CliOpts where reportOpts = reportSpec.reportOpts -- | Convert an argument-less --debug flag to --debug=1 in the given arguments list. -- Used by hledger/ui/web to make their command line parsing easier somehow. ensureDebugHasArg as = case break (=="--debug") as of (bs,"--debug":c:cs) | null c || not (all isDigit c) -> bs++"--debug=1":c:cs (bs,["--debug"]) -> bs++["--debug=1"] _ -> as hledger-1.32.3/Hledger/Cli/Commands.hs0000644000000000000000000006513114555053231015567 0ustar0000000000000000{-| hledger's built-in commands, and helpers for printing the commands list. New built-in commands should be added in four places below: the export list, the import list, builtinCommands, commandsList. -} -- Note: commands list rendering is intensely sensitive to change, -- very easy to break in ways that tests currently do not catch. {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands ( testcmd ,builtinCommands ,builtinCommandNames ,findBuiltinCommand ,knownAddonCommands ,knownCommands ,printCommandsList ,tests_Hledger_Cli ,module Hledger.Cli.Commands.Accounts ,module Hledger.Cli.Commands.Activity ,module Hledger.Cli.Commands.Add ,module Hledger.Cli.Commands.Aregister ,module Hledger.Cli.Commands.Balance ,module Hledger.Cli.Commands.Balancesheet ,module Hledger.Cli.Commands.Balancesheetequity ,module Hledger.Cli.Commands.Cashflow ,module Hledger.Cli.Commands.Close ,module Hledger.Cli.Commands.Codes ,module Hledger.Cli.Commands.Commodities ,module Hledger.Cli.Commands.Demo ,module Hledger.Cli.Commands.Descriptions ,module Hledger.Cli.Commands.Diff ,module Hledger.Cli.Commands.Help ,module Hledger.Cli.Commands.Import ,module Hledger.Cli.Commands.Incomestatement ,module Hledger.Cli.Commands.Notes ,module Hledger.Cli.Commands.Payees ,module Hledger.Cli.Commands.Prices ,module Hledger.Cli.Commands.Print ,module Hledger.Cli.Commands.Register ,module Hledger.Cli.Commands.Rewrite ,module Hledger.Cli.Commands.Stats ,module Hledger.Cli.Commands.Tags ) where import Data.Char (isAlphaNum, isSpace) import Data.List import Data.List.Extra (nubSort) import Data.Text (Text) import qualified Data.Text as T import Data.Time.Calendar import String.ANSI import System.Environment (withArgs) import System.Console.CmdArgs.Explicit as C import Test.Tasty (defaultMain) import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Version import Hledger.Cli.Commands.Accounts import Hledger.Cli.Commands.Activity import Hledger.Cli.Commands.Add import Hledger.Cli.Commands.Aregister import Hledger.Cli.Commands.Balance import Hledger.Cli.Commands.Balancesheet import Hledger.Cli.Commands.Balancesheetequity import Hledger.Cli.Commands.Cashflow import Hledger.Cli.Commands.Check import Hledger.Cli.Commands.Close import Hledger.Cli.Commands.Codes import Hledger.Cli.Commands.Commodities import Hledger.Cli.Commands.Demo import Hledger.Cli.Commands.Descriptions import Hledger.Cli.Commands.Diff import Hledger.Cli.Commands.Files import Hledger.Cli.Commands.Help import Hledger.Cli.Commands.Import import Hledger.Cli.Commands.Incomestatement import Hledger.Cli.Commands.Notes import Hledger.Cli.Commands.Payees import Hledger.Cli.Commands.Prices import Hledger.Cli.Commands.Print import Hledger.Cli.Commands.Register import Hledger.Cli.Commands.Rewrite import Hledger.Cli.Commands.Roi import Hledger.Cli.Commands.Stats import Hledger.Cli.Commands.Tags import Hledger.Cli.Utils (tests_Cli_Utils) -- | The cmdargs subcommand mode (for command-line parsing) -- and IO action (for doing the command's work) for each builtin command. -- Command actions take parsed CLI options and a (lazy) finalised journal. builtinCommands :: [(Mode RawOpts, CliOpts -> Journal -> IO ())] builtinCommands = [ (accountsmode , accounts) ,(activitymode , activity) ,(addmode , add) ,(aregistermode , aregister) ,(balancemode , balance) ,(balancesheetequitymode , balancesheetequity) ,(balancesheetmode , balancesheet) ,(cashflowmode , cashflow) ,(checkmode , check) ,(closemode , close) ,(codesmode , codes) ,(commoditiesmode , commodities) ,(demomode , demo) ,(descriptionsmode , descriptions) ,(diffmode , diff) ,(filesmode , files) ,(helpmode , help') ,(importmode , importcmd) ,(incomestatementmode , incomestatement) ,(notesmode , notes) ,(payeesmode , payees) ,(pricesmode , prices) ,(printmode , print') ,(registermode , register) ,(rewritemode , rewrite) ,(roimode , roi) ,(statsmode , stats) ,(tagsmode , tags) ,(testmode , testcmd) ] -- figlet -f FONTNAME hledger, then escape backslashes _banner_slant = drop 1 ["" -----------------------------------------80------------------------------------- ," __ __ __ " ," / /_ / /__ ____/ /___ ____ _____" ," / __ \\/ / _ \\/ __ / __ `/ _ \\/ ___/" ," / / / / / __/ /_/ / /_/ / __/ / " ,"/_/ /_/_/\\___/\\__,_/\\__, /\\___/_/ " ," /____/ " ] _banner_smslant = drop 1 ["" ," __ __ __ " ," / / / /__ ___/ /__ ____ ____" ," / _ \\/ / -_) _ / _ `/ -_) __/" ,"/_//_/_/\\__/\\_,_/\\_, /\\__/_/ " ," /___/ " ] _banner_speed = drop 1 ["" ,"______ ______ _________ " ,"___ /____ /__________ /______ _____________" ,"__ __ \\_ /_ _ \\ __ /__ __ `/ _ \\_ ___/" ,"_ / / / / / __/ /_/ / _ /_/ // __/ / " ,"/_/ /_//_/ \\___/\\__,_/ _\\__, / \\___//_/ " ," /____/ " ] -- | Choose and apply an accent color for hledger output, if possible -- picking one that will contrast with the current terminal background colour. accent :: String -> String accent | not useColorOnStdout = id | terminalIsLight == Just False = brightWhite | terminalIsLight == Just True = brightBlack | otherwise = id -- | The commands list, showing command names, standard aliases, -- and short descriptions. This is modified at runtime, as follows: -- -- progversion is the program name and version. -- -- Lines beginning with a space represent builtin commands, with format: -- COMMAND (ALIASES) DESCRIPTION -- These should be kept synced with builtinCommands above, and -- their docs (Commands/\*.md). -- -- Lines beginning with + represent known addon commands. These lines -- will be suppressed if hledger-CMD is not found in $PATH at runtime. -- -- OTHER is replaced with additional command lines (without descriptions) -- for any unknown addon commands found in $PATH at runtime. -- -- TODO: generate more of this automatically. -- commandsList :: String -> [String] -> [String] commandsList progversion othercmds = map (bold'.accent) _banner_smslant ++ [ -- Keep the following synced with: -- commands.m4 -- hledger.m4.md -> Commands -- commandsFromCommandsList. Only commands should begin with space or plus. "-------------------------------------------------------------------------------" ,progversion ,"Usage: hledger CMD [OPTS] [-- ADDONCMDOPTS]" ,"Commands (builtins + addons):" ,"" ,bold' "ENTERING DATA (add or edit transactions, updating the journal file)" ," add add transactions using terminal prompts" ,"+edit edit a subset of transactions" ,"+iadd add transactions using a TUI" ," import add new transactions from other files, eg CSV files" ,"" -----------------------------------------80------------------------------------- ,bold' "GENERATING DATA (generate entries to be added to the journal file)" ,"+autosync download/deduplicate/convert OFX data" ," close generate balance-zeroing/restoring transactions" ,"+interest generate interest transactions" ,"+lots sell generate a lot-selling transaction" ," rewrite generate auto postings, like print --auto" ,"+stockquotes download market prices from AlphaVantage" ,"" -----------------------------------------80------------------------------------- ,bold' "MANAGING DATA (error checking, version control..)" ," check check for various kinds of error in the data" ,"+check-fancyassertions check more powerful balance assertions" ,"+check-tagfiles check file paths in tag values exist" ," diff compare account transactions in two journal files" ,"+git simple version management with git" ,"+pijul simple version management with pijul" ,"" -----------------------------------------80------------------------------------- ,bold' "FINANCIAL REPORTS (standard financial statements)" ," aregister (areg) show transactions in a particular account" ," balancesheet (bs) show assets, liabilities and net worth" ," balancesheetequity (bse) show assets, liabilities and equity" ," cashflow (cf) show changes in liquid assets" ," incomestatement (is) show revenues and expenses" ,"" -----------------------------------------80------------------------------------- ,bold' "VERSATILE REPORTS (more complex/versatile reporting commands)" ," activity show a simple bar chart of posting counts per period" ," balance (bal) show balance changes, end balances, budgets, gains.." ,"+bar show a balance report as a simple bar chart" ,"+lots show a commodity's lots" ,"+plot create charts from balance reports, in terminal or GUI" ," print show transactions or export journal data" ," register (reg) show postings in one or more accounts & running total" ," roi show return on investments" ,"" -----------------------------------------80------------------------------------- ,bold' "BASIC REPORTS (lists and stats)" ," accounts show account names" ," codes show transaction codes" ," commodities show commodity/currency symbols" ," descriptions show full transaction descriptions (payee and note)" ," files show data files in use" ," notes show note part of transaction descriptions" ," payees show payee names" ," prices show historical market prices" ," stats show journal statistics" ," tags show tag names" ,"" -----------------------------------------80------------------------------------- ,bold' "UIS (other user interfaces)" ,"+ui run terminal UI" ,"+web run web UI" ,"" -----------------------------------------80------------------------------------- ,bold' "HELP (show help and docs)" ," hledger show this commands list" ," hledger -h show hledger's command-line help" ," hledger CMD -h show CMD's command-line help and manual" ," hledger help [-i|-m|-p] [TOPIC] show hledger's manual with info, man, or pager" ," hledger demo [DEMO] [-- ASCOPTS] show brief demos on various topics" ," hledger test [-- TASTYOPTS] run self tests" ," https://hledger.org html manuals, tutorials, support.." ,"" -----------------------------------------80------------------------------------- ,bold' "OTHER (more hledger-* addon commands found in PATH)" ] ++ map (' ':) (lines $ multicol 79 othercmds) ++ [""] -- | Extract just the command names from the default commands list above, -- (the first word of lines between "Usage:" and "HELP" beginning with a space or plus sign), -- in the order they occur. With a true first argument, extracts only the addon command names. -- Needs to be kept synced with commandsList. commandsListExtractCommands :: Bool -> [String] -> [String] commandsListExtractCommands addonsonly l = [ w | c:ws@(d:_) <- takeWhile (not . isInfixOf "HELP") $ dropWhile (not . isInfixOf "Usage:") l , c `elem` '+':[' '|not addonsonly] , isAlphaNum d , not $ "://" `isInfixOf` ws , let w:_ = words ws ] -- | Canonical names of all commands which have a slot in the commands list, in alphabetical order. -- These include the builtin commands and the known addon commands. knownCommands :: [String] knownCommands = nubSort . commandsListExtractCommands False $ commandsList progname [] -- | Canonical names of the known addon commands which have a slot in the commands list, -- in alphabetical order. knownAddonCommands :: [String] knownAddonCommands = nubSort . commandsListExtractCommands True $ commandsList progname [] -- | All names and aliases of the builtin commands. builtinCommandNames :: [String] builtinCommandNames = concatMap (modeNames . fst) builtinCommands -- | Look up a builtin command's mode and action by exact command name or alias. findBuiltinCommand :: String -> Maybe (Mode RawOpts, CliOpts -> Journal -> IO ()) findBuiltinCommand cmdname = find (elem cmdname . modeNames . fst) builtinCommands -- | Print the commands list, with a pager if appropriate, customising the -- commandsList template above with the given version string and the installed addons. -- Uninstalled known addons will be removed from the list, -- installed known addons will have the + prefix removed, -- and installed unknown addons will be added under Misc. printCommandsList :: String -> [String] -> IO () printCommandsList progversion installedaddons = seq (length $ dbg8 "uninstalledknownaddons" uninstalledknownaddons) $ -- for debug output seq (length $ dbg8 "installedknownaddons" installedknownaddons) $ seq (length $ dbg8 "installedunknownaddons" installedunknownaddons) $ pager $ unlines $ map unplus $ filter (not.isuninstalledaddon) $ commandsList progversion installedunknownaddons where knownaddons = knownAddonCommands uninstalledknownaddons = knownaddons \\ installedaddons installedknownaddons = knownaddons `intersect` installedaddons installedunknownaddons = installedaddons \\ knownaddons unplus ('+':cs) = ' ':cs unplus s = s isuninstalledaddon = \case ('+':l) | cmd `notElem` installedaddons -> dbg9With (const $ "hiding uninstalled addon: "<>cmd) $ True where cmd = takeWhile (not . isSpace) l _ -> False -- The test command is defined here for easy access to other modules' tests. testmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Test.txt") [] [generalflagsgroup3] [] ([], Just $ argsFlag "[-- TASTYOPTS]") -- | The test command, which runs the hledger and hledger-lib -- packages' unit tests. This command also accepts tasty test runner -- options, written after a -- (double hyphen). -- -- Unlike most hledger commands, this one does not read the user's journal. -- A 'Journal' argument remains in the type signature, but it should -- not be used (and would raise an error). -- testcmd :: CliOpts -> Journal -> IO () testcmd opts _undefined = do withArgs (listofstringopt "args" $ rawopts_ opts) $ Test.Tasty.defaultMain $ testGroup "hledger" [ tests_Hledger ,tests_Hledger_Cli ] -- All unit tests for Hledger.Cli, defined here rather than -- Hledger.Cli so testcmd can use them. tests_Hledger_Cli = testGroup "Hledger.Cli" [ tests_Cli_Utils ,tests_Commands ] tests_Commands = testGroup "Commands" [ tests_Balance ,tests_Register ,tests_Aregister -- some more tests easiest to define here: ,testGroup "apply account directive" [ testCase "works" $ do let ignoresourcepos j = j{jtxns=map (\t -> t{tsourcepos=nullsourcepos}) (jtxns j)} sameParse str1 str2 = do j1 <- ignoresourcepos <$> readJournal' str1 -- PARTIAL: j2 <- ignoresourcepos <$> readJournal' str2 -- PARTIAL: j1 @?= j2{jlastreadtime=jlastreadtime j1, jfiles=jfiles j1} --, jparsestate=jparsestate j1} sameParse ("2008/12/07 One\n alpha $-1\n beta $1\n" <> "apply account outer\n2008/12/07 Two\n aigh $-2\n bee $2\n" <> "apply account inner\n2008/12/07 Three\n gamma $-3\n delta $3\n" <> "end apply account\n2008/12/07 Four\n why $-4\n zed $4\n" <> "end apply account\n2008/12/07 Five\n foo $-5\n bar $5\n" ) ("2008/12/07 One\n alpha $-1\n beta $1\n" <> "2008/12/07 Two\n outer:aigh $-2\n outer:bee $2\n" <> "2008/12/07 Three\n outer:inner:gamma $-3\n outer:inner:delta $3\n" <> "2008/12/07 Four\n outer:why $-4\n outer:zed $4\n" <> "2008/12/07 Five\n foo $-5\n bar $5\n" ) ,testCase "preserves \"virtual\" posting type" $ do j <- readJournal' "apply account test\n2008/12/07 One\n (from) $-1\n (to) $1\n" -- PARTIAL: let p = head $ tpostings $ head $ jtxns j paccount p @?= "test:from" ptype p @?= VirtualPosting ] ,testCase "alias directive" $ do j <- readJournal' "!alias expenses = equity:draw:personal\n1/1\n (expenses:food) 1\n" -- PARTIAL: let p = head $ tpostings $ head $ jtxns j paccount p @?= "equity:draw:personal:food" ,testCase "Y default year directive" $ do j <- readJournal' defaultyear_journal_txt -- PARTIAL: tdate (head $ jtxns j) @?= fromGregorian 2009 1 1 ,testCase "ledgerAccountNames" $ (ledgerAccountNames ledger7) @?= ["assets","assets:cash","assets:checking","assets:saving","equity","equity:opening balances", "expenses","expenses:food","expenses:food:dining","expenses:phone","expenses:vacation", "liabilities","liabilities:credit cards","liabilities:credit cards:discover"] -- ,testCase "journalCanonicaliseAmounts" ~: -- "use the greatest precision" ~: -- (map asprecision $ journalAmountAndPriceCommodities $ journalCanonicaliseAmounts $ journalWithAmounts ["1","2.00"]) @?= [2,2] -- don't know what this should do -- ,testCase "elideAccountName" ~: do -- (elideAccountName 50 "aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa" -- @?= "aa:aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa") -- (elideAccountName 20 "aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa" -- @?= "aa:aa:aaaaaaaaaaaaaa") ,testCase "show dollars" $ showAmount (usd 1) @?= "$1.00" ,testCase "show hours" $ showAmount (hrs 1) @?= "1.00h" ] -- test data -- date1 = fromGregorian 2008 11 26 -- t1 = LocalTime date1 midday {- samplejournal = readJournal' sample_journal_str sample_journal_str = unlines ["; A sample journal file." ,";" ,"; Sets up this account tree:" ,"; assets" ,"; bank" ,"; checking" ,"; saving" ,"; cash" ,"; expenses" ,"; food" ,"; supplies" ,"; income" ,"; gifts" ,"; salary" ,"; liabilities" ,"; debts" ,"" ,"2008/01/01 income" ," assets:bank:checking $1" ," income:salary" ,"" ,"2008/06/01 gift" ," assets:bank:checking $1" ," income:gifts" ,"" ,"2008/06/02 save" ," assets:bank:saving $1" ," assets:bank:checking" ,"" ,"2008/06/03 * eat & shop" ," expenses:food $1" ," expenses:supplies $1" ," assets:cash" ,"" ,"2008/12/31 * pay off" ," liabilities:debts $1" ," assets:bank:checking" ,"" ,"" ,";final comment" ] -} defaultyear_journal_txt :: Text defaultyear_journal_txt = T.unlines ["Y2009" ,"" ,"01/01 A" ," a $1" ," b" ] -- write_sample_journal = writeFile "sample.journal" sample_journal_str -- entry2_str = unlines -- ["2007/01/27 * joes diner" -- ," expenses:food:dining $10.00" -- ," expenses:gifts $10.00" -- ," assets:checking $-20.00" -- ,"" -- ] -- entry3_str = unlines -- ["2007/01/01 * opening balance" -- ," assets:cash $4.82" -- ," equity:opening balances" -- ,"" -- ,"2007/01/01 * opening balance" -- ," assets:cash $4.82" -- ," equity:opening balances" -- ,"" -- ,"2007/01/28 coopportunity" -- ," expenses:food:groceries $47.18" -- ," assets:checking" -- ,"" -- ] -- periodic_entry1_str = unlines -- ["~ monthly from 2007/2/2" -- ," assets:saving $200.00" -- ," assets:checking" -- ,"" -- ] -- periodic_entry2_str = unlines -- ["~ monthly from 2007/2/2" -- ," assets:saving $200.00 ;auto savings" -- ," assets:checking" -- ,"" -- ] -- periodic_entry3_str = unlines -- ["~ monthly from 2007/01/01" -- ," assets:cash $4.82" -- ," equity:opening balances" -- ,"" -- ,"~ monthly from 2007/01/01" -- ," assets:cash $4.82" -- ," equity:opening balances" -- ,"" -- ] -- journal1_str = unlines -- ["" -- ,"2007/01/27 * joes diner" -- ," expenses:food:dining $10.00" -- ," expenses:gifts $10.00" -- ," assets:checking $-20.00" -- ,"" -- ,"" -- ,"2007/01/28 coopportunity" -- ," expenses:food:groceries $47.18" -- ," assets:checking $-47.18" -- ,"" -- ,"" -- ] -- journal2_str = unlines -- [";comment" -- ,"2007/01/27 * joes diner" -- ," expenses:food:dining $10.00" -- ," assets:checking $-47.18" -- ,"" -- ] -- journal3_str = unlines -- ["2007/01/27 * joes diner" -- ," expenses:food:dining $10.00" -- ,";intra-entry comment" -- ," assets:checking $-47.18" -- ,"" -- ] -- journal4_str = unlines -- ["include \"somefile\"" -- ,"2007/01/27 * joes diner" -- ," expenses:food:dining $10.00" -- ," assets:checking $-47.18" -- ,"" -- ] -- journal5_str = "" -- journal6_str = unlines -- ["~ monthly from 2007/1/21" -- ," expenses:entertainment $16.23 ;netflix" -- ," assets:checking" -- ,"" -- ,"; 2007/01/01 * opening balance" -- ,"; assets:saving $200.04" -- ,"; equity:opening balances " -- ,"" -- ] -- journal7_str = unlines -- ["2007/01/01 * opening balance" -- ," assets:cash $4.82" -- ," equity:opening balances " -- ,"" -- ,"2007/01/01 * opening balance" -- ," income:interest $-4.82" -- ," equity:opening balances " -- ,"" -- ,"2007/01/02 * ayres suites" -- ," expenses:vacation $179.92" -- ," assets:checking " -- ,"" -- ,"2007/01/02 * auto transfer to savings" -- ," assets:saving $200.00" -- ," assets:checking " -- ,"" -- ,"2007/01/03 * poquito mas" -- ," expenses:food:dining $4.82" -- ," assets:cash " -- ,"" -- ,"2007/01/03 * verizon" -- ," expenses:phone $95.11" -- ," assets:checking " -- ,"" -- ,"2007/01/03 * discover" -- ," liabilities:credit cards:discover $80.00" -- ," assets:checking " -- ,"" -- ,"2007/01/04 * blue cross" -- ," expenses:health:insurance $90.00" -- ," assets:checking " -- ,"" -- ,"2007/01/05 * village market liquor" -- ," expenses:food:dining $6.48" -- ," assets:checking " -- ,"" -- ] journal7 :: Journal journal7 = nulljournal {jtxns = [ txnTieKnot Transaction { tindex=0, tsourcepos=nullsourcepos, tdate=fromGregorian 2007 01 01, tdate2=Nothing, tstatus=Unmarked, tcode="*", tdescription="opening balance", tcomment="", ttags=[], tpostings= ["assets:cash" `post` usd 4.82 ,"equity:opening balances" `post` usd (-4.82) ], tprecedingcomment="" } , txnTieKnot Transaction { tindex=0, tsourcepos=nullsourcepos, tdate=fromGregorian 2007 02 01, tdate2=Nothing, tstatus=Unmarked, tcode="*", tdescription="ayres suites", tcomment="", ttags=[], tpostings= ["expenses:vacation" `post` usd 179.92 ,"assets:checking" `post` usd (-179.92) ], tprecedingcomment="" } , txnTieKnot Transaction { tindex=0, tsourcepos=nullsourcepos, tdate=fromGregorian 2007 01 02, tdate2=Nothing, tstatus=Unmarked, tcode="*", tdescription="auto transfer to savings", tcomment="", ttags=[], tpostings= ["assets:saving" `post` usd 200 ,"assets:checking" `post` usd (-200) ], tprecedingcomment="" } , txnTieKnot Transaction { tindex=0, tsourcepos=nullsourcepos, tdate=fromGregorian 2007 01 03, tdate2=Nothing, tstatus=Unmarked, tcode="*", tdescription="poquito mas", tcomment="", ttags=[], tpostings= ["expenses:food:dining" `post` usd 4.82 ,"assets:cash" `post` usd (-4.82) ], tprecedingcomment="" } , txnTieKnot Transaction { tindex=0, tsourcepos=nullsourcepos, tdate=fromGregorian 2007 01 03, tdate2=Nothing, tstatus=Unmarked, tcode="*", tdescription="verizon", tcomment="", ttags=[], tpostings= ["expenses:phone" `post` usd 95.11 ,"assets:checking" `post` usd (-95.11) ], tprecedingcomment="" } , txnTieKnot Transaction { tindex=0, tsourcepos=nullsourcepos, tdate=fromGregorian 2007 01 03, tdate2=Nothing, tstatus=Unmarked, tcode="*", tdescription="discover", tcomment="", ttags=[], tpostings= ["liabilities:credit cards:discover" `post` usd 80 ,"assets:checking" `post` usd (-80) ], tprecedingcomment="" } ] } ledger7 :: Ledger ledger7 = ledgerFromJournal Any journal7 hledger-1.32.3/Hledger/Cli/Commands/Accounts.hs0000644000000000000000000001471614555053231017351 0ustar0000000000000000{-| The @accounts@ command lists account names: - in flat mode (default), it lists the full names of accounts posted to by matched postings, clipped to the specified depth, possibly with leading components dropped. - in tree mode, it shows the indented short names of accounts posted to by matched postings, and their parents, to the specified depth. -} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Accounts ( accountsmode ,accounts ) where import Data.List import qualified Data.Text as T import qualified Data.Text.IO as T import System.Console.CmdArgs.Explicit as C import Hledger import Hledger.Cli.CliOptions import Control.Monad (forM_) import Data.Maybe (fromMaybe) import Safe (headDef) -- | Command line options for this command. accountsmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Accounts.txt") ( [flagNone ["used","u"] (setboolopt "used") "show only accounts used by transactions" ,flagNone ["declared","d"] (setboolopt "declared") "show only accounts declared by account directive" -- no s to avoid line wrap ,flagNone ["unused"] (setboolopt "unused") "show only accounts declared but not used" ,flagNone ["undeclared"] (setboolopt "undeclared") "show only accounts used but not declared" ,flagNone ["types"] (setboolopt "types") "also show account types when known" ,flagNone ["positions"] (setboolopt "positions") "also show where accounts were declared" ,flagNone ["directives"] (setboolopt "directives") "show as account directives, for use in journals" ,flagNone ["find"] (setboolopt "find") "find the first account matched by the first argument (a case-insensitive infix regexp or account name)" ] ++ flattreeflags False ++ [flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "flat mode: omit N leading account name parts"] ) [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- | The accounts command. accounts :: CliOpts -> Journal -> IO () accounts CliOpts{rawopts_=rawopts, reportspec_=ReportSpec{_rsQuery=query,_rsReportOpts=ropts}} j = do -- 1. identify the accounts we'll show let tree = tree_ ropts used = boolopt "used" rawopts decl = boolopt "declared" rawopts unused = boolopt "unused" rawopts undecl = boolopt "undeclared" rawopts find_ = boolopt "find" rawopts types = boolopt "types" rawopts positions = boolopt "positions" rawopts directives = boolopt "directives" rawopts -- a depth limit will clip and exclude account names later, but we don't want to exclude accounts at this stage nodepthq = dbg4 "nodepthq" $ filterQuery (not . queryIsDepth) query -- just the acct: part of the query will be reapplied later, after clipping acctq = dbg4 "acctq" $ filterQuery queryIsAcct query dep = dbg4 "depth" $ queryDepth $ filterQuery queryIsDepth query matcheddeclaredaccts = dbg5 "matcheddeclaredaccts" $ nub $ filter (matchesAccountExtra (journalAccountType j) (journalInheritedAccountTags j) nodepthq) $ map fst $ jdeclaredaccounts j matchedusedaccts = dbg5 "matchedusedaccts" $ nub $ map paccount $ journalPostings $ filterJournalPostings nodepthq j matchedunusedaccts = dbg5 "matchedunusedaccts" $ nub $ matcheddeclaredaccts \\ matchedusedaccts matchedundeclaredaccts = dbg5 "matchedundeclaredaccts" $ nub $ matchedusedaccts \\ matcheddeclaredaccts -- keep synced with aregister matchedacct = dbg5 "matchedacct" $ fromMaybe (error' $ show apat ++ " did not match any account.") -- PARTIAL: . firstMatch $ journalAccountNamesDeclaredOrImplied j where firstMatch = case toRegexCI $ T.pack apat of Right re -> find (regexMatchText re) Left _ -> const Nothing apat = headDef (error' "With --find, please provide an account name or\naccount pattern (case-insensitive, infix, regexp) as first command argument.") $ listofstringopt "args" rawopts accts = dbg5 "accts to show" $ if | not decl && used -> matchedusedaccts | decl && not used -> matcheddeclaredaccts | unused -> matchedunusedaccts | undecl -> matchedundeclaredaccts | find_ -> [matchedacct] | otherwise -> matcheddeclaredaccts ++ matchedusedaccts -- 2. sort them by declaration order (then undeclared accounts alphabetically) -- within each group of siblings sortedaccts = sortAccountNamesByDeclaration j tree accts -- 3. if there's a depth limit, depth-clip and remove any no longer useful items clippedaccts = dbg4 "clippedaccts" $ filter (matchesAccount acctq) $ -- clipping can leave accounts that no longer match the query, remove such nub $ -- clipping can leave duplicates (adjacent, hopefully) filter (not . T.null) $ -- depth:0 can leave nulls map (clipAccountName dep) $ -- clip at depth if specified sortedaccts -- 4. print what remains as a list or tree, maybe applying --drop in the former case. -- Add various bits of info if enabled. let showKeyword = if directives then "account " else "" -- some contortions here to show types nicely aligned showName a = case accountlistmode_ ropts of ALTree -> indent <> accountLeafName droppedName ALFlat -> droppedName where indent = T.replicate (2 * (max 0 (accountNameLevel a - drop_ ropts) - 1)) " " droppedName = accountNameDrop (drop_ ropts) a showType a | types = pad a <> " ; type: " <> maybe "" (T.pack . show) (journalAccountType j a) | otherwise = "" showAcctDeclOrder a | positions = (if types then "," else pad a <> " ;") <> case lookup a $ jdeclaredaccounts j of Just adi -> " declared at " <> (T.pack $ sourcePosPretty $ adisourcepos adi) <> -- TODO: hide the column number ", overall declaration order " <> (T.pack $ show $ adideclarationorder adi) Nothing -> " undeclared" | otherwise = "" pad a = T.replicate (maxwidth - T.length (showName a)) " " maxwidth = maximum $ map (T.length . showName) clippedaccts forM_ clippedaccts $ \a -> T.putStrLn $ showKeyword <> showName a <> showType a <> showAcctDeclOrder a hledger-1.32.3/Hledger/Cli/Commands/Activity.hs0000644000000000000000000000276114555053231017363 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} {-| Print a bar chart of posting activity per day, or other report interval. -} module Hledger.Cli.Commands.Activity where import Data.List (sortOn) import Text.Printf (printf) import Lens.Micro ((^.), set) import Hledger import Hledger.Cli.CliOptions activitymode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Activity.txt") [] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") barchar :: Char barchar = '*' -- | Print a bar chart of number of postings per report interval. activity :: CliOpts -> Journal -> IO () activity CliOpts{reportspec_=rspec} j = putStr $ showHistogram rspec j showHistogram :: ReportSpec -> Journal -> String showHistogram rspec@ReportSpec{_rsQuery=q} j = concatMap (printDayWith countBar) spanps where spans = filter (DateSpan Nothing Nothing /=) . snd . reportSpan j $ case rspec ^. interval of NoInterval -> set interval (Days 1) rspec _ -> rspec spanps = [(s, filter (isPostingInDateSpan s) ps) | s <- spans] -- same as Register -- should count transactions, not postings ? -- ps = sortBy (comparing postingDate) $ filterempties $ filter matchapats $ filterdepth $ journalPostings j ps = sortOn postingDate $ filter (q `matchesPosting`) $ journalPostings j printDayWith f (DateSpan (Just b) _, ps) = printf "%s %s\n" (show $ fromEFDay b) (f ps) printDayWith _ _ = error "Expected start date for DateSpan" -- PARTIAL: countBar ps = replicate (length ps) barchar hledger-1.32.3/Hledger/Cli/Commands/Add.hs0000644000000000000000000005543114555423340016263 0ustar0000000000000000{-| A history-aware add command to help with data entry. |-} {-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-unused-do-bind #-} {-# LANGUAGE ScopedTypeVariables, RecordWildCards, TypeOperators, FlexibleContexts, OverloadedStrings, PackageImports, LambdaCase #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Add ( addmode ,add ,appendToJournalFileOrStdout ,journalAddTransaction ) where import Control.Exception as E import Control.Monad (when) import Control.Monad.Trans.Class import Control.Monad.State.Strict (evalState, evalStateT) import Control.Monad.Trans (liftIO) import Data.Char (toUpper, toLower) import Data.Either (isRight) import Data.Functor.Identity (Identity(..)) import Data.List (isPrefixOf, nub) import Data.Maybe (fromJust, fromMaybe, isJust) import Data.Text (Text) import qualified Data.Text as T import qualified Data.Text.IO as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.IO as TL import Data.Time.Calendar (Day) import Data.Time.Format (formatTime, defaultTimeLocale) import Lens.Micro ((^.)) import Safe (headDef, headMay, atMay) import System.Console.CmdArgs.Explicit (flagNone) import System.Console.Haskeline (runInputT, defaultSettings, setComplete) import System.Console.Haskeline.Completion (CompletionFunc, completeWord, isFinished, noCompletion, simpleCompletion) import System.Console.Wizard (Wizard, defaultTo, line, output, retryMsg, linePrewritten, nonEmpty, parser, run) import System.Console.Wizard.Haskeline import System.IO ( stderr, hPutStr, hPutStrLn ) import Text.Megaparsec import Text.Megaparsec.Char import Text.Printf import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Commands.Register (postingsReportAsText) import Hledger.Cli.Utils (journalSimilarTransaction) addmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Add.txt") [flagNone ["no-new-accounts"] (setboolopt "no-new-accounts") "don't allow creating new accounts"] [generalflagsgroup2] [] ([], Just $ argsFlag "[DATE [DESCRIPTION [ACCOUNT1 [AMOUNT1 [ACCOUNT2 [ETC...]]]]]]") -- | State used while entering transactions. data EntryState = EntryState { esOpts :: CliOpts -- ^ command line options ,esArgs :: [String] -- ^ command line arguments remaining to be used as defaults ,esToday :: Day -- ^ today's date ,esDefDate :: Day -- ^ the default date for next transaction ,esJournal :: Journal -- ^ the journal we are adding to ,esSimilarTransaction :: Maybe Transaction -- ^ the most similar historical txn ,esPostings :: [Posting] -- ^ postings entered so far in the current txn } deriving (Show) defEntryState = EntryState { esOpts = defcliopts ,esArgs = [] ,esToday = nulldate ,esDefDate = nulldate ,esJournal = nulljournal ,esSimilarTransaction = Nothing ,esPostings = [] } data RestartTransactionException = RestartTransactionException deriving (Show) instance Exception RestartTransactionException -- data ShowHelpException = ShowHelpException deriving (Show) -- instance Exception ShowHelpException -- | Read multiple transactions from the console, prompting for each -- field, and append them to the journal file. If the journal came -- from stdin, this command has no effect. add :: CliOpts -> Journal -> IO () add opts j | journalFilePath j == "-" = return () | otherwise = do hPutStrLn stderr $ "Adding transactions to journal file " <> journalFilePath j showHelp let today = opts^.rsDay es = defEntryState{esOpts=opts ,esArgs=listofstringopt "args" $ rawopts_ opts ,esToday=today ,esDefDate=today ,esJournal=j } getAndAddTransactions es `E.catch` (\(_::UnexpectedEOF) -> putStr "") showHelp = hPutStr stderr $ unlines [ "Any command line arguments will be used as defaults." ,"Use tab key to complete, readline keys to edit, enter to accept defaults." ,"An optional (CODE) may follow transaction dates." ,"An optional ; COMMENT may follow descriptions or amounts." ,"If you make a mistake, enter < at any prompt to go one step backward." ,"To end a transaction, enter . when prompted." ,"To quit, enter . at a date prompt or press control-d or control-c." ] -- | Loop reading transactions from the console, prompting, validating -- and appending each one to the journal file, until end of input or -- ctrl-c (then raise an EOF exception). If provided, command-line -- arguments are used as defaults; otherwise defaults come from the -- most similar recent transaction in the journal. getAndAddTransactions :: EntryState -> IO () getAndAddTransactions es@EntryState{..} = (do let defaultPrevInput = PrevInput{prevDateAndCode=Nothing, prevDescAndCmnt=Nothing, prevAccount=[], prevAmountAndCmnt=[]} mt <- runInputT (setComplete noCompletion defaultSettings) (System.Console.Wizard.run $ haskeline $ confirmedTransactionWizard defaultPrevInput es []) case mt of Nothing -> error "Could not interpret the input, restarting" -- caught below causing a restart, I believe -- PARTIAL: Just t -> do j <- if debug_ esOpts > 0 then do hPutStrLn stderr "Skipping journal add due to debug mode." return esJournal else do j' <- journalAddTransaction esJournal esOpts t hPutStrLn stderr "Saved." return j' hPutStrLn stderr "Starting the next transaction (. or ctrl-D/ctrl-C to quit)" getAndAddTransactions es{esJournal=j, esDefDate=tdate t} ) `E.catch` (\(_::RestartTransactionException) -> hPutStrLn stderr "Restarting this transaction." >> getAndAddTransactions es) data TxnParams = TxnParams { txnDate :: Day , txnCode :: Text , txnDesc :: Text , txnCmnt :: Text } deriving (Show) data PrevInput = PrevInput { prevDateAndCode :: Maybe String , prevDescAndCmnt :: Maybe String , prevAccount :: [String] , prevAmountAndCmnt :: [String] } deriving (Show) data AddingStage = EnterDateAndCode | EnterDescAndComment (Day, Text) | EnterAccount TxnParams | EnterAmountAndComment TxnParams String | EndStage Transaction | EnterNewPosting TxnParams (Maybe Posting) confirmedTransactionWizard :: PrevInput -> EntryState -> [AddingStage] -> Wizard Haskeline Transaction confirmedTransactionWizard prevInput es [] = confirmedTransactionWizard prevInput es [EnterDateAndCode] confirmedTransactionWizard prevInput es@EntryState{..} stack@(currentStage : _) = case currentStage of EnterDateAndCode -> dateAndCodeWizard prevInput es >>= \case Just (efd, code) -> do let date = fromEFDay efd es' = es{ esArgs = drop 1 esArgs , esDefDate = date } dateAndCodeString = formatTime defaultTimeLocale yyyymmddFormat date ++ T.unpack (if T.null code then "" else " (" <> code <> ")") yyyymmddFormat = "%Y-%m-%d" confirmedTransactionWizard prevInput{prevDateAndCode=Just dateAndCodeString} es' (EnterDescAndComment (date, code) : stack) Nothing -> confirmedTransactionWizard prevInput es stack EnterDescAndComment (date, code) -> descriptionAndCommentWizard prevInput es >>= \case Just (desc, comment) -> do let mbaset = journalSimilarTransaction esOpts esJournal desc es' = es { esArgs = drop 1 esArgs , esPostings = [] , esSimilarTransaction = mbaset } descAndCommentString = T.unpack $ desc <> (if T.null comment then "" else " ; " <> comment) prevInput' = prevInput{prevDescAndCmnt=Just descAndCommentString} when (isJust mbaset) . liftIO $ do hPutStrLn stderr "Using this similar transaction for defaults:" T.hPutStr stderr $ showTransaction (fromJust mbaset) confirmedTransactionWizard prevInput' es' ((EnterNewPosting TxnParams{txnDate=date, txnCode=code, txnDesc=desc, txnCmnt=comment} Nothing) : stack) Nothing -> confirmedTransactionWizard prevInput es (drop 1 stack) EnterNewPosting txnParams@TxnParams{..} p -> case (esPostings, p) of ([], Nothing) -> confirmedTransactionWizard prevInput es (EnterAccount txnParams : stack) (_, Just _) -> confirmedTransactionWizard prevInput es (EnterAccount txnParams : stack) (_, Nothing) -> do let t = nulltransaction{tdate=txnDate ,tstatus=Unmarked ,tcode=txnCode ,tdescription=txnDesc ,tcomment=txnCmnt ,tpostings=esPostings } case balanceTransaction defbalancingopts t of -- imprecise balancing (?) Right t' -> confirmedTransactionWizard prevInput es (EndStage t' : stack) Left err -> do liftIO (hPutStrLn stderr $ "\n" ++ (capitalize err) ++ "please re-enter.") let notFirstEnterPost stage = case stage of EnterNewPosting _ Nothing -> False _ -> True confirmedTransactionWizard prevInput es{esPostings=[]} (dropWhile notFirstEnterPost stack) EnterAccount txnParams -> accountWizard prevInput es >>= \case Just account | account `elem` [".", ""] -> case (esPostings, postingsBalanced esPostings) of ([],_) -> liftIO (hPutStrLn stderr "Please enter some postings first.") >> confirmedTransactionWizard prevInput es stack (_,False) -> liftIO (hPutStrLn stderr "Please enter more postings to balance the transaction.") >> confirmedTransactionWizard prevInput es stack (_,True) -> confirmedTransactionWizard prevInput es (EnterNewPosting txnParams Nothing : stack) | otherwise -> do let prevAccount' = replaceNthOrAppend (length esPostings) account (prevAccount prevInput) confirmedTransactionWizard prevInput{prevAccount=prevAccount'} es{esArgs=drop 1 esArgs} (EnterAmountAndComment txnParams account : stack) Nothing -> do let notPrevAmountAndNotEnterDesc stage = case stage of EnterAmountAndComment _ _ -> False EnterDescAndComment _ -> False _ -> True confirmedTransactionWizard prevInput es{esPostings=init esPostings} (dropWhile notPrevAmountAndNotEnterDesc stack) EnterAmountAndComment txnParams account -> amountAndCommentWizard prevInput es >>= \case Just (amt, comment) -> do let p = nullposting{paccount=T.pack $ stripbrackets account ,pamount=mixedAmount amt ,pcomment=comment ,ptype=accountNamePostingType $ T.pack account } amountAndCommentString = showAmount amt ++ T.unpack (if T.null comment then "" else " ;" <> comment) prevAmountAndCmnt' = replaceNthOrAppend (length esPostings) amountAndCommentString (prevAmountAndCmnt prevInput) es' = es{esPostings=esPostings++[p], esArgs=drop 2 esArgs} confirmedTransactionWizard prevInput{prevAmountAndCmnt=prevAmountAndCmnt'} es' (EnterNewPosting txnParams (Just posting) : stack) Nothing -> confirmedTransactionWizard prevInput es (drop 1 stack) EndStage t -> do output . T.unpack $ showTransaction t y <- let def = "y" in retryMsg "Please enter y or n." $ parser ((fmap (\c -> if c == '<' then Nothing else Just c)) . headMay . map toLower . strip) $ defaultTo' def $ nonEmpty $ line $ green $ printf "Save this transaction to the journal ?%s: " (showDefault def) case y of Just 'y' -> return t Just _ -> throw RestartTransactionException Nothing -> confirmedTransactionWizard prevInput es (drop 2 stack) where replaceNthOrAppend n newElem xs = take n xs ++ [newElem] ++ drop (n + 1) xs dateAndCodeWizard PrevInput{..} EntryState{..} = do let def = headDef (T.unpack $ showDate esDefDate) esArgs retryMsg "A valid hledger smart date is required. Eg: 2022-08-30, 8/30, 30, yesterday." $ parser (parseSmartDateAndCode esToday) $ withCompletion (dateCompleter def) $ defaultTo' def $ nonEmpty $ maybeExit $ -- maybeShowHelp $ linePrewritten (green $ printf "Date%s: " (showDefault def)) (fromMaybe "" prevDateAndCode) "" where parseSmartDateAndCode refdate s = if s == "<" then return Nothing else either (const Nothing) (\(d,c) -> return $ Just (fixSmartDate refdate d, c)) edc where edc = runParser (dateandcodep <* eof) "" $ T.pack $ lowercase s dateandcodep :: SimpleTextParser (SmartDate, Text) dateandcodep = do d <- smartdate c <- optional codep skipNonNewlineSpaces eof return (d, fromMaybe "" c) -- defday = fixSmartDate today $ fromparse $ (parse smartdate "" . lowercase) defdate -- datestr = showDate $ fixSmartDate defday smtdate descriptionAndCommentWizard PrevInput{..} EntryState{..} = do let def = headDef "" esArgs s <- withCompletion (descriptionCompleter esJournal def) $ defaultTo' def $ nonEmpty $ linePrewritten (green $ printf "Description%s: " (showDefault def)) (fromMaybe "" prevDescAndCmnt) "" if s == "<" then return Nothing else do let (desc,comment) = (T.pack $ strip a, T.pack $ strip $ dropWhile (==';') b) where (a,b) = break (==';') s return $ Just (desc, comment) postingsBalanced :: [Posting] -> Bool postingsBalanced ps = isRight $ balanceTransaction defbalancingopts nulltransaction{tpostings=ps} accountWizard PrevInput{..} EntryState{..} = do let pnum = length esPostings + 1 historicalp = fmap ((!! (pnum - 1)) . (++ (repeat nullposting)) . tpostings) esSimilarTransaction historicalacct = case historicalp of Just p -> showAccountName Nothing (ptype p) (paccount p) Nothing -> "" def = headDef (T.unpack historicalacct) esArgs endmsg | canfinish && null def = " (or . or enter to finish this transaction)" | canfinish = " (or . to finish this transaction)" | otherwise = "" retryMsg "A valid hledger account name is required. Eg: assets:cash, expenses:food:eating out." $ parser (parseAccountOrDotOrNull def canfinish) $ withCompletion (accountCompleter esJournal def) $ defaultTo' def $ -- nonEmpty $ linePrewritten (green $ printf "Account %d%s%s: " pnum (endmsg::String) (showDefault def)) (fromMaybe "" $ prevAccount `atMay` length esPostings) "" where canfinish = not (null esPostings) && postingsBalanced esPostings parseAccountOrDotOrNull :: String -> Bool -> String -> Maybe (Maybe String) parseAccountOrDotOrNull _ _ "<" = dbg' $ Just Nothing parseAccountOrDotOrNull _ _ "." = dbg' $ Just $ Just "." -- . always signals end of txn parseAccountOrDotOrNull "" True "" = dbg' $ Just $ Just "" -- when there's no default and txn is balanced, "" also signals end of txn parseAccountOrDotOrNull def@(_:_) _ "" = dbg' $ Just $ Just def -- when there's a default, "" means use that parseAccountOrDotOrNull _ _ s = dbg' $ fmap (Just . T.unpack) $ either (const Nothing) validateAccount $ flip evalState esJournal $ runParserT (accountnamep <* eof) "" (T.pack s) -- otherwise, try to parse the input as an accountname where validateAccount :: Text -> Maybe Text validateAccount t | no_new_accounts_ esOpts && notElem t (journalAccountNamesDeclaredOrImplied esJournal) = Nothing | otherwise = Just t dbg' = id -- strace amountAndCommentWizard PrevInput{..} EntryState{..} = do let pnum = length esPostings + 1 (mhistoricalp,followedhistoricalsofar) = case esSimilarTransaction of Nothing -> (Nothing,False) Just Transaction{tpostings=ps} -> ( if length ps >= pnum then Just (ps !! (pnum-1)) else Nothing , all sameamount $ zip esPostings ps ) where sameamount (p1,p2) = mixedAmountUnstyled (pamount p1) == mixedAmountUnstyled (pamount p2) def | (d:_) <- esArgs = d | Just hp <- mhistoricalp, followedhistoricalsofar = showamt $ pamount hp | pnum > 1 && not (mixedAmountLooksZero balancingamt) = showamt balancingamtfirstcommodity | otherwise = "" retryMsg "A valid hledger amount is required. Eg: 1, $2, 3 EUR, \"4 red apples\"." $ parser parseAmountAndComment $ withCompletion (amountCompleter def) $ defaultTo' def $ nonEmpty $ linePrewritten (green $ printf "Amount %d%s: " pnum (showDefault def)) (fromMaybe "" $ prevAmountAndCmnt `atMay` length esPostings) "" where parseAmountAndComment s = if s == "<" then return Nothing else either (const Nothing) (return . Just) $ runParser (evalStateT (amountandcommentp <* eof) nodefcommodityj) "" (T.pack s) nodefcommodityj = esJournal{jparsedefaultcommodity=Nothing} amountandcommentp :: JournalParser Identity (Amount, Text) amountandcommentp = do a <- amountp lift skipNonNewlineSpaces c <- T.pack <$> fromMaybe "" `fmap` optional (char ';' >> many anySingle) -- eof return (a,c) balancingamt = maNegate . sumPostings $ filter isReal esPostings balancingamtfirstcommodity = mixed . take 1 $ amounts balancingamt showamt = wbUnpack . showMixedAmountB noColour . mixedAmountSetPrecision -- what should this be ? -- 1 maxprecision (show all decimal places or none) ? -- 2 maxprecisionwithpoint (show all decimal places or .0 - avoids some but not all confusion with thousands separators) ? -- 3 canonical precision for this commodity in the journal ? -- 4 maximum precision entered so far in this transaction ? -- 5 3 or 4, whichever would show the most decimal places ? -- I think 1 or 4, whichever would show the most decimal places NaturalPrecision -- -- let -- (amt,comment) = (strip a, strip $ dropWhile (==';') b) where (a,b) = break (==';') amtcmt -- a = fromparse $ runParser (amountp <|> return missingamt) (jparsestate esJournal) "" amt -- awithoutjps = fromparse $ runParser (amountp <|> return missingamt) mempty "" amt -- defamtaccepted = Just (showAmount a) == mdefamt -- es2 = if defamtaccepted then es1 else es1{esHistoricalPostings=Nothing} -- mdefaultcommodityapplied = if acommodity a == acommodity awithoutjps then Nothing else Just $ acommodity a -- when (isJust mdefaultcommodityapplied) $ -- liftIO $ hPutStrLn stderr $ printf "using default commodity (%s)" (fromJust mdefaultcommodityapplied) maybeExit = parser (\s -> if s=="." then throw UnexpectedEOF else Just s) -- maybeShowHelp :: Wizard Haskeline String -> Wizard Haskeline String -- maybeShowHelp wizard = maybe (liftIO showHelp >> wizard) return $ -- parser (\s -> if s=="?" then Nothing else Just s) wizard -- Completion helpers dateCompleter :: String -> CompletionFunc IO dateCompleter = completer ["today","tomorrow","yesterday"] -- Offer payees declared, payees used, or full descriptions used. descriptionCompleter :: Journal -> String -> CompletionFunc IO descriptionCompleter j = completer (map T.unpack $ nub $ journalPayeesDeclaredOrUsed j ++ journalDescriptions j) accountCompleter :: Journal -> String -> CompletionFunc IO accountCompleter j = completer (map T.unpack $ journalAccountNamesDeclaredOrImplied j) amountCompleter :: String -> CompletionFunc IO amountCompleter = completer [] -- | Generate a haskeline completion function from the given -- completions and default, that case insensitively completes with -- prefix matches, or infix matches above a minimum length, or -- completes the null string with the default. completer :: [String] -> String -> CompletionFunc IO completer completions def = completeWord Nothing "" completionsFor where simpleCompletion' s = (simpleCompletion s){isFinished=False} completionsFor "" = return [simpleCompletion' def] completionsFor i = return (map simpleCompletion' ciprefixmatches) where ciprefixmatches = [c | c <- completions, i `isPrefixOf` c] -- mixed-case completions require haskeline > 0.7.1.2 -- ciprefixmatches = [c | c <- completions, lowercase i `isPrefixOf` lowercase c] -------------------------------------------------------------------------------- -- utilities defaultTo' = flip defaultTo withCompletion f = withSettings (setComplete f defaultSettings) green s = "\ESC[1;32m\STX"++s++"\ESC[0m\STX" showDefault "" = "" showDefault s = " [" ++ s ++ "]" -- | Append this transaction to the journal's file and transaction list. journalAddTransaction :: Journal -> CliOpts -> Transaction -> IO Journal journalAddTransaction j@Journal{jtxns=ts} opts t = do let f = journalFilePath j appendToJournalFileOrStdout f $ showTransaction t -- unelided shows all amounts explicitly, in case there's a price, cf #283 when (debug_ opts > 0) $ do putStrLn $ printf "\nAdded transaction to %s:" f TL.putStrLn =<< registerFromString (showTransaction t) return j{jtxns=ts++[t]} -- | Append a string, typically one or more transactions, to a journal -- file, or if the file is "-", dump it to stdout. Tries to avoid -- excess whitespace. -- -- XXX This writes unix line endings (\n), some at least, -- even if the file uses dos line endings (\r\n), which could leave -- mixed line endings in the file. See also writeFileWithBackupIfChanged. -- appendToJournalFileOrStdout :: FilePath -> Text -> IO () appendToJournalFileOrStdout f s | f == "-" = T.putStr s' | otherwise = appendFile f $ T.unpack s' where s' = "\n" <> ensureOneNewlineTerminated s -- | Replace a string's 0 or more terminating newlines with exactly one. ensureOneNewlineTerminated :: Text -> Text ensureOneNewlineTerminated = (<>"\n") . T.dropWhileEnd (=='\n') -- | Convert a string of journal data into a register report. registerFromString :: T.Text -> IO TL.Text registerFromString s = do j <- readJournal' s return . postingsReportAsText opts $ postingsReport rspec j where ropts = defreportopts{empty_=True} rspec = defreportspec{_rsReportOpts=ropts} opts = defcliopts{reportspec_=rspec} capitalize :: String -> String capitalize "" = "" capitalize (c:cs) = toUpper c : cs hledger-1.32.3/Hledger/Cli/Commands/Aregister.hs0000644000000000000000000003005214555423340017510 0ustar0000000000000000{-| The @aregister@ command lists a single account's transactions, like the account register in hledger-ui and hledger-web, and unlike the register command which lists postings across multiple accounts. -} {-# LANGUAGE CPP #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Aregister ( aregistermode ,aregister -- ,showPostingWithBalanceForVty ,tests_Aregister ) where import Data.Default (def) import Data.List (find) import Data.Maybe (fromMaybe) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Builder as TB import Lucid as L hiding (value_) import System.Console.CmdArgs.Explicit (flagNone, flagReq) import Hledger import Hledger.Read.CsvUtils (CSV, CsvRecord, printCSV, printTSV) import Hledger.Cli.CliOptions import Hledger.Cli.Utils import Text.Tabular.AsciiWide hiding (render) aregistermode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Aregister.txt") ([ flagNone ["txn-dates"] (setboolopt "txn-dates") "filter strictly by transaction date, not posting date. Warning: this can show a wrong running balance." ,flagNone ["no-elide"] (setboolopt "no-elide") "don't show only 2 commodities per amount" -- flagNone ["cumulative"] (setboolopt "cumulative") -- "show running total from report start date (default)" -- ,flagNone ["historical","H"] (setboolopt "historical") -- "show historical running total/balance (includes postings before report start date)\n " -- ,flagNone ["average","A"] (setboolopt "average") -- "show running average of posting amounts instead of total (implies --empty)" -- ,flagNone ["related","r"] (setboolopt "related") "show postings' siblings instead" -- ,flagNone ["invert"] (setboolopt "invert") "display all amounts with reversed sign" ,flagReq ["width","w"] (\s opts -> Right $ setopt "width" s opts) "N" ("set output width (default: " ++ #ifdef mingw32_HOST_OS show defaultWidth #else "terminal width" #endif ++ " or $COLUMNS). -wN,M sets description width as well." ) ,flagNone ["align-all"] (setboolopt "align-all") "guarantee alignment across all lines (slower)" ,outputFormatFlag ["txt","html","csv","tsv","json"] ,outputFileFlag ]) [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "ACCTPAT [QUERY]") -- based on Hledger.UI.RegisterScreen: -- | Print an account register report for a specified account. aregister :: CliOpts -> Journal -> IO () aregister opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do -- the first argument specifies the account, any remaining arguments are a filter query let help = "aregister needs an ACCTPAT argument to select an account" (apat,querystr) <- case listofstringopt "args" rawopts of [] -> error' $ help <> ".\nPlease provide an account name or a (case-insensitive, infix, regexp) pattern." (a:as) -> return (a, map T.pack as) let -- keep synced with accounts --find acct = fromMaybe (error' $ help <> ",\nbut " ++ show apat++" did not match any account.") -- PARTIAL: . firstMatch $ journalAccountNamesDeclaredOrImplied j firstMatch = case toRegexCI $ T.pack apat of Right re -> find (regexMatchText re) Left _ -> const Nothing -- gather report options inclusive = True -- tree_ ropts thisacctq = Acct $ (if inclusive then accountNameToAccountRegex else accountNameToAccountOnlyRegex) acct ropts' = (_rsReportOpts rspec) { -- ignore any depth limit, as in postingsReport; allows register's total to match balance reports (cf #1468) depth_=Nothing -- always show historical balance , balanceaccum_= Historical , querystring_ = querystr } wd = whichDate ropts' -- and regenerate the ReportSpec, making sure to use the above rspec' <- either fail return $ updateReportSpec ropts' rspec let -- run the report -- TODO: need to also pass the queries so we can choose which date to render - move them into the report ? items = accountTransactionsReport rspec' j thisacctq items' = styleAmounts (journalCommodityStyles j) $ (if empty_ ropts' then id else filter (not . mixedAmountLooksZero . fifth6)) $ reverse items -- select renderer render | fmt=="txt" = accountTransactionsReportAsText opts (_rsQuery rspec') thisacctq | fmt=="html" = accountTransactionsReportAsHTML opts (_rsQuery rspec') thisacctq | fmt=="csv" = printCSV . accountTransactionsReportAsCsv wd (_rsQuery rspec') thisacctq | fmt=="tsv" = printTSV . accountTransactionsReportAsCsv wd (_rsQuery rspec') thisacctq | fmt=="json" = toJsonText | otherwise = error' $ unsupportedOutputFormatError fmt -- PARTIAL: where fmt = outputFormatFromOpts opts writeOutputLazyText opts $ render items' accountTransactionsReportAsCsv :: WhichDate -> Query -> Query -> AccountTransactionsReport -> CSV accountTransactionsReportAsCsv wd reportq thisacctq is = ["txnidx","date","code","description","otheraccounts","change","balance"] : map (accountTransactionsReportItemAsCsvRecord wd reportq thisacctq) is accountTransactionsReportItemAsCsvRecord :: WhichDate -> Query -> Query -> AccountTransactionsReportItem -> CsvRecord accountTransactionsReportItemAsCsvRecord wd reportq thisacctq (t@Transaction{tindex,tcode,tdescription}, _, _issplit, otheracctsstr, change, balance) = [idx,date,tcode,tdescription,otheracctsstr,amt,bal] where idx = T.pack $ show tindex date = showDate $ transactionRegisterDate wd reportq thisacctq t amt = wbToText $ showMixedAmountB csvDisplay change bal = wbToText $ showMixedAmountB csvDisplay balance -- | Render a register report as a HTML snippet. accountTransactionsReportAsHTML :: CliOpts -> Query -> Query -> AccountTransactionsReport -> TL.Text accountTransactionsReportAsHTML copts reportq thisacctq items = L.renderText $ L.table_ (do L.thead_ (L.tr_ (do L.th_ "date" L.th_ "description" L.th_ "otheraccounts" L.th_ "change" L.th_ "balance")) L.tbody_ (mconcat (map (htmlRow copts reportq thisacctq) items))) -- | Render one account register report line item as a HTML table row snippet. htmlRow :: CliOpts -> Query -> Query -> AccountTransactionsReportItem -> L.Html () htmlRow CliOpts{reportspec_=ReportSpec{_rsReportOpts=ropts}} reportq thisacctq (t@Transaction{tdescription}, _, _issplit, otheracctsstr, amt, bal) = L.tr_ (do (L.td_ . toHtml . show . transactionRegisterDate (whichDate ropts) reportq thisacctq) t (L.td_ . toHtml) tdescription (L.td_ . toHtml) otheracctsstr -- piggy back on the oneLine display style for now. (L.td_ . toHtml . wbUnpack . showMixedAmountB oneLine) amt (L.td_ . toHtml . wbUnpack . showMixedAmountB oneLine) bal) -- | Render a register report as plain text suitable for console output. accountTransactionsReportAsText :: CliOpts -> Query -> Query -> AccountTransactionsReport -> TL.Text accountTransactionsReportAsText copts reportq thisacctq items = TB.toLazyText $ title <> TB.singleton '\n' <> postingsOrTransactionsReportAsText alignAll copts itemAsText itemamt itembal items where alignAll = boolopt "align-all" $ rawopts_ copts itemAsText = accountTransactionsReportItemAsText copts reportq thisacctq itemamt (_,_,_,_,a,_) = a itembal (_,_,_,_,_,a) = a -- show a title indicating which account was picked, which can be confusing otherwise title = maybe mempty (\s -> foldMap TB.fromText ["Transactions in ", s, " and subaccounts", qmsg, ":"]) macct where -- XXX temporary hack ? recover the account name from the query macct = case filterQuery queryIsAcct thisacctq of Acct r -> Just . T.drop 1 . T.dropEnd 5 $ reString r -- Acct "^JS:expenses(:|$)" _ -> Nothing -- shouldn't happen -- show a hint in the title when results are restricted by an extra query (other than depth or date or date2) qmsg = if hasextraquery then " (matching query)" else "" where hasextraquery = length (querystring_ $ _rsReportOpts $ reportspec_ copts) > 1 && not (queryIsNull $ filterQuery (not.(\q->queryIsDepth q || queryIsDateOrDate2 q)) reportq) -- | Render one account register report line item as plain text. Layout is like so: -- @ -- <---------------- width (specified, terminal width, or 80) --------------------> -- date (10) description other accounts change (12) balance (12) -- DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA -- @ -- If description's width is specified, account will use the remaining space. -- Otherwise, description and account divide up the space equally. -- -- Returns a string which can be multi-line, eg if the running balance -- has multiple commodities. -- accountTransactionsReportItemAsText :: CliOpts -> Query -> Query -> Int -> Int -> (AccountTransactionsReportItem, [WideBuilder], [WideBuilder]) -> TB.Builder accountTransactionsReportItemAsText copts@CliOpts{reportspec_=ReportSpec{_rsReportOpts=ropts}} reportq thisacctq preferredamtwidth preferredbalwidth ((t@Transaction{tdescription}, _, _issplit, otheracctsstr, _, _), amt, bal) = -- Transaction -- the transaction, unmodified -- Transaction -- the transaction, as seen from the current account -- Bool -- is this a split (more than one posting to other accounts) ? -- String -- a display string describing the other account(s), if any -- MixedAmount -- the amount posted to the current account(s) (or total amount posted) -- MixedAmount -- the register's running total or the current account(s)'s historical balance, after this transaction table <> TB.singleton '\n' where table = renderRowB def{tableBorders=False, borderSpaces=False} . Group NoLine $ map Header [ textCell TopLeft $ fitText (Just datewidth) (Just datewidth) True True date , spacerCell , textCell TopLeft $ fitText (Just descwidth) (Just descwidth) True True tdescription , spacerCell2 , textCell TopLeft $ fitText (Just acctwidth) (Just acctwidth) True True accts , spacerCell2 , Cell TopRight $ map (pad amtwidth) amt , spacerCell2 , Cell BottomRight $ map (pad balwidth) bal ] spacerCell = Cell BottomLeft [WideBuilder (TB.singleton ' ') 1] spacerCell2 = Cell BottomLeft [WideBuilder (TB.fromString " ") 2] pad fullwidth amt1 = WideBuilder (TB.fromText $ T.replicate w " ") w <> amt1 where w = fullwidth - wbWidth amt1 -- calculate widths (totalwidth,mdescwidth) = registerWidthsFromOpts copts (datewidth, date) = (10, showDate $ transactionRegisterDate wd reportq thisacctq t) where wd = whichDate ropts (amtwidth, balwidth) | shortfall <= 0 = (preferredamtwidth, preferredbalwidth) | otherwise = (adjustedamtwidth, adjustedbalwidth) where mincolwidth = 2 -- columns always show at least an ellipsis maxamtswidth = max 0 (totalwidth - (datewidth + 1 + mincolwidth + 2 + mincolwidth + 2 + 2)) shortfall = (preferredamtwidth + preferredbalwidth) - maxamtswidth amtwidthproportion = fromIntegral preferredamtwidth / fromIntegral (preferredamtwidth + preferredbalwidth) adjustedamtwidth = round $ amtwidthproportion * fromIntegral maxamtswidth adjustedbalwidth = maxamtswidth - adjustedamtwidth remaining = totalwidth - (datewidth + 1 + 2 + amtwidth + 2 + balwidth) (descwidth, acctwidth) = (w, remaining - 2 - w) where w = fromMaybe ((remaining - 2) `div` 2) mdescwidth -- gather content accts = -- T.unpack $ elideAccountName acctwidth $ T.pack otheracctsstr -- tests tests_Aregister = testGroup "Aregister" [ ] hledger-1.32.3/Hledger/Cli/Commands/Balance.hs0000644000000000000000000010554614555423340017123 0ustar0000000000000000{-| A ledger-compatible @balance@ command, with additional support for multi-column reports. Here is a description/specification for the balance command. See also "Hledger.Reports" -> \"Balance reports\". /Basic balance report/ With no report interval (@--monthly@ etc.), hledger's balance command emulates ledger's, showing accounts indented according to hierarchy, along with their total amount posted (including subaccounts). Here's an example. With @examples/sample.journal@, which defines the following account tree: @ assets bank checking saving cash expenses food supplies income gifts salary liabilities debts @ the basic @balance@ command gives this output: @ $ hledger -f sample.journal balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 @ Subaccounts are displayed indented below their parent. Only the account leaf name (the final part) is shown. (With @--flat@, account names are shown in full and unindented.) Each account's \"balance\" is the sum of postings in that account and any subaccounts during the report period. When the report period includes all transactions, this is equivalent to the account's current balance. The overall total of the highest-level displayed accounts is shown below the line. (The @--no-total/-N@ flag prevents this.) /Eliding and omitting/ Accounts which have a zero balance, and no non-zero subaccount balances, are normally omitted from the report. (The @--empty/-E@ flag forces such accounts to be displayed.) Eg, above @checking@ is omitted because it has a zero balance and no subaccounts. Accounts which have a single subaccount also being displayed, with the same balance, are normally elided into the subaccount's line. (The @--no-elide@ flag prevents this.) Eg, above @bank@ is elided to @bank:saving@ because it has only a single displayed subaccount (@saving@) and their balance is the same ($1). Similarly, @liabilities@ is elided to @liabilities:debts@. /Date limiting/ The default report period is that of the whole journal, including all known transactions. The @--begin\/-b@, @--end\/-e@, @--period\/-p@ options or @date:@/@date2:@ patterns can be used to report only on transactions before and/or after specified dates. /Depth limiting/ The @--depth@ option can be used to limit the depth of the balance report. Eg, to see just the top level accounts (still including their subaccount balances): @ $ hledger -f sample.journal balance --depth 1 $-1 assets $2 expenses $-2 income $1 liabilities -------------------- 0 @ /Account limiting/ With one or more account pattern arguments, the report is restricted to accounts whose name matches one of the patterns, plus their parents and subaccounts. Eg, adding the pattern @o@ to the first example gives: @ $ hledger -f sample.journal balance o $1 expenses:food $-2 income $-1 gifts $-1 salary -------------------- $-1 @ * The @o@ pattern matched @food@ and @income@, so they are shown. * @food@'s parent (@expenses@) is shown even though the pattern didn't match it, to clarify the hierarchy. The usual eliding rules cause it to be elided here. * @income@'s subaccounts are also shown. /Multi-column balance report/ hledger's balance command will show multiple columns when a reporting interval is specified (eg with @--monthly@), one column for each sub-period. There are three accumulation strategies for multi-column balance report, indicated by the heading: * A \"period balance\" (or \"flow\") report (with @--change@, the default) shows the change of account balance in each period, which is equivalent to the sum of postings in each period. Here, checking's balance increased by 10 in Feb: > Change of balance (flow): > > Jan Feb Mar > assets:checking 20 10 -5 * A \"cumulative balance\" report (with @--cumulative@) shows the accumulated ending balance across periods, starting from zero at the report's start date. Here, 30 is the sum of checking postings during Jan and Feb: > Ending balance (cumulative): > > Jan Feb Mar > assets:checking 20 30 25 * A \"historical balance\" report (with @--historical/-H@) also shows ending balances, but it includes the starting balance from any postings before the report start date. Here, 130 is the balance from all checking postings at the end of Feb, including pre-Jan postings which created a starting balance of 100: > Ending balance (historical): > > Jan Feb Mar > assets:checking 120 130 125 /Eliding and omitting, 2/ Here's a (imperfect?) specification for the eliding/omitting behaviour: * Each account is normally displayed on its own line. * An account less deep than the report's max depth, with just one interesting subaccount, and the same balance as the subaccount, is non-interesting, and prefixed to the subaccount's line, unless @--no-elide@ is in effect. * An account with a zero inclusive balance and less than two interesting subaccounts is not displayed at all, unless @--empty@ is in effect. * Multi-column balance reports show full account names with no eliding (like @--flat@). Accounts (and periods) are omitted as described below. /Which accounts to show in balance reports/ By default: * single-column: accounts with non-zero balance in report period. (With @--flat@: accounts with non-zero balance and postings.) * change: accounts with postings and non-zero period balance in any period * cumulative: accounts with non-zero cumulative balance in any period * historical: accounts with non-zero historical balance in any period With @-E/--empty@: * single-column: accounts with postings in report period * change: accounts with postings in report period * cumulative: accounts with postings in report period * historical: accounts with non-zero starting balance + accounts with postings in report period /Which periods (columns) to show in balance reports/ An empty period/column is one where no report account has any postings. A zero period/column is one where no report account has a non-zero period balance. Currently, by default: * single-column: N/A * change: all periods within the overall report period, except for leading and trailing empty periods * cumulative: all periods within the overall report period, except for leading and trailing empty periods * historical: all periods within the overall report period, except for leading and trailing empty periods With @-E/--empty@: * single-column: N/A * change: all periods within the overall report period * cumulative: all periods within the overall report period * historical: all periods within the overall report period /What to show in empty cells/ An empty periodic balance report cell is one which has no corresponding postings. An empty cumulative/historical balance report cell is one which has no corresponding or prior postings, ie the account doesn't exist yet. Currently, empty cells show 0. -} {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Balance ( balancemode ,balance ,balanceReportAsText ,balanceReportAsCsv ,balanceReportItemAsText ,multiBalanceRowAsCsvText ,multiBalanceRowAsTableText ,multiBalanceReportAsText ,multiBalanceReportAsCsv ,multiBalanceReportAsHtml ,multiBalanceReportHtmlRows ,multiBalanceReportHtmlFootRow ,balanceReportAsTable ,balanceReportTableAsText ,tests_Balance ) where import Data.Default (def) import Data.List (transpose, transpose) import qualified Data.Set as S import Data.Maybe (fromMaybe) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Builder as TB import Data.Time (addDays, fromGregorian) import System.Console.CmdArgs.Explicit as C import Lucid as L hiding (value_) import Safe (headMay, maximumMay) import Text.Tabular.AsciiWide (Align(..), Cell(..), Table(..), TableOpts(..), cellWidth, concatTables, renderColumns, renderRowB, textCell) import qualified Text.Tabular.AsciiWide as Tab import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Utils import Hledger.Read.CsvUtils (CSV, printCSV, printTSV) -- | Command line options for this command. balancemode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Balance.txt") ( -- https://hledger.org/dev/hledger.html#calculation-type : [flagNone ["sum"] (setboolopt "sum") "show sum of posting amounts (default)" -- XXX --budget[=DESCPAT], --forecast[=PERIODEXP], could be more consistent ,flagOpt "" ["budget"] (\s opts -> Right $ setopt "budget" s opts) "DESCPAT" (unlines [ "show sum of posting amounts together with budget goals defined by periodic" , "transactions. With a DESCPAT argument (must be separated by = not space)," , "use only periodic transactions with matching description" , "(case insensitive substring match)." ]) ,flagNone ["valuechange"] (setboolopt "valuechange") "show total change of value of period-end historical balances (caused by deposits, withdrawals, market price fluctuations)" ,flagNone ["gain"] (setboolopt "gain") "show unrealised capital gain/loss (historical balance value minus cost basis)" ,flagNone ["count"] (setboolopt "count") "show the count of postings" -- https://hledger.org/dev/hledger.html#accumulation-type : ,flagNone ["change"] (setboolopt "change") "accumulate amounts from column start to column end (in multicolumn reports, default)" ,flagNone ["cumulative"] (setboolopt "cumulative") "accumulate amounts from report start (specified by e.g. -b/--begin) to column end" ,flagNone ["historical","H"] (setboolopt "historical") "accumulate amounts from journal start to column end (includes postings before report start date)\n " ] -- other options specific to this command: ++ flattreeflags True ++ [flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "omit N leading account name parts (in flat mode)" ,flagNone ["declared"] (setboolopt "declared") "include non-parent declared accounts (best used with -E)" ,flagNone ["average","A"] (setboolopt "average") "show a row average column (in multicolumn reports)" ,flagNone ["related","r"] (setboolopt "related") "show postings' siblings instead" ,flagNone ["row-total","T"] (setboolopt "row-total") "show a row total column (in multicolumn reports)" ,flagNone ["summary-only"] (setboolopt "summary-only") "display only row summaries (e.g. row total, average) (in multicolumn reports)" ,flagNone ["no-total","N"] (setboolopt "no-total") "omit the final total row" ,flagNone ["no-elide"] (setboolopt "no-elide") "don't squash boring parent accounts (in tree mode)" ,flagReq ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format (in simple reports)" ,flagNone ["sort-amount","S"] (setboolopt "sort-amount") "sort by amount instead of account code/name (in flat mode). With multiple columns, sorts by the row total, or by row average if that is displayed." ,flagNone ["percent", "%"] (setboolopt "percent") "express values in percentage of each column's total" ,flagNone ["invert"] (setboolopt "invert") "display all amounts with reversed sign" ,flagNone ["transpose"] (setboolopt "transpose") "transpose rows and columns" ,flagReq ["layout"] (\s opts -> Right $ setopt "layout" s opts) "ARG" (unlines ["how to lay out multi-commodity amounts and the overall table:" ,"'wide[,WIDTH]': commodities on one line" ,"'tall' : commodities on separate lines" ,"'bare' : commodity symbols in one column" ,"'tidy' : every attribute in its own column" ]) -- output: ,outputFormatFlag ["txt","html","csv","tsv","json"] ,outputFileFlag ] ) [generalflagsgroup1] (hiddenflags ++ [ flagNone ["commodity-column"] (setboolopt "commodity-column") "show commodity symbols in a separate column, amounts as bare numbers, one row per commodity" ]) ([], Just $ argsFlag "[QUERY]") -- | The balance command, prints a balance report. balance :: CliOpts -> Journal -> IO () balance opts@CliOpts{reportspec_=rspec} j = case balancecalc_ of CalcBudget -> do -- single or multi period budget report let rspan = fst $ reportSpan j rspec budgetreport = styleAmounts styles $ budgetReport rspec (balancingopts_ $ inputopts_ opts) rspan j render = case fmt of "txt" -> budgetReportAsText ropts "json" -> (<>"\n") . toJsonText "csv" -> printCSV . budgetReportAsCsv ropts "tsv" -> printTSV . budgetReportAsCsv ropts _ -> error' $ unsupportedOutputFormatError fmt writeOutputLazyText opts $ render budgetreport _ | multiperiod -> do -- multi period balance report let report = styleAmounts styles $ multiBalanceReport rspec j render = case fmt of "txt" -> multiBalanceReportAsText ropts "csv" -> printCSV . multiBalanceReportAsCsv ropts "tsv" -> printTSV . multiBalanceReportAsCsv ropts "html" -> (<>"\n") . L.renderText . multiBalanceReportAsHtml ropts "json" -> (<>"\n") . toJsonText _ -> const $ error' $ unsupportedOutputFormatError fmt -- PARTIAL: writeOutputLazyText opts $ render report _ -> do -- single period simple balance report let report = styleAmounts styles $ balanceReport rspec j -- simple Ledger-style balance report render = case fmt of "txt" -> \ropts1 -> TB.toLazyText . balanceReportAsText ropts1 "csv" -> \ropts1 -> printCSV . balanceReportAsCsv ropts1 "tsv" -> \ropts1 -> printTSV . balanceReportAsCsv ropts1 -- "html" -> \ropts -> (<>"\n") . L.renderText . multiBalanceReportAsHtml ropts . balanceReportAsMultiBalanceReport ropts "json" -> const $ (<>"\n") . toJsonText _ -> error' $ unsupportedOutputFormatError fmt -- PARTIAL: writeOutputLazyText opts $ render ropts report where styles = journalCommodityStylesWith HardRounding j ropts@ReportOpts{..} = _rsReportOpts rspec -- Tidy csv/tsv should be consistent between single period and multiperiod reports. multiperiod = interval_ /= NoInterval || (layout_ == LayoutTidy && delimited) delimited = fmt == "csv" || fmt == "tsv" fmt = outputFormatFromOpts opts -- XXX this allows rough HTML rendering of a flat BalanceReport, but it can't handle tree mode etc. -- -- | Convert a BalanceReport to a MultiBalanceReport. -- balanceReportAsMultiBalanceReport :: ReportOpts -> BalanceReport -> MultiBalanceReport -- balanceReportAsMultiBalanceReport _ropts (britems, brtotal) = -- let -- mbrrows = -- [PeriodicReportRow{ -- prrName = flatDisplayName brfullname -- , prrAmounts = [bramt] -- , prrTotal = bramt -- , prrAverage = bramt -- } -- | (brfullname, _, _, bramt) <- britems -- ] -- in -- PeriodicReport{ -- prDates = [nulldatespan] -- , prRows = mbrrows -- , prTotals = PeriodicReportRow{ -- prrName=() -- ,prrAmounts=[brtotal] -- ,prrTotal=brtotal -- ,prrAverage=brtotal -- } -- } -- XXX should all the per-report, per-format rendering code live in the command module, -- like the below, or in the report module, like budgetReportAsText/budgetReportAsCsv ? -- rendering single-column balance reports -- | Render a single-column balance report as CSV. balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV balanceReportAsCsv opts (items, total) = headers : concatMap (\(a, _, _, b) -> rows a b) items ++ if no_total_ opts then [] else rows "total" total where headers = "account" : case layout_ opts of LayoutBare -> ["commodity", "balance"] _ -> ["balance"] rows :: AccountName -> MixedAmount -> [[T.Text]] rows name ma = case layout_ opts of LayoutBare -> map (\a -> [showName name, acommodity a, renderAmount $ mixedAmount a]) . amounts $ mixedAmountStripPrices ma _ -> [[showName name, renderAmount ma]] showName = accountNameDrop (drop_ opts) renderAmount amt = wbToText $ showMixedAmountB bopts amt where bopts = csvDisplay{displayCommodity=showcomm, displayCommodityOrder = commorder} (showcomm, commorder) | layout_ opts == LayoutBare = (False, Just $ S.toList $ maCommodities amt) | otherwise = (True, Nothing) -- | Render a single-column balance report as plain text. balanceReportAsText :: ReportOpts -> BalanceReport -> TB.Builder balanceReportAsText opts ((items, total)) = case layout_ opts of LayoutBare | iscustom -> error' "Custom format not supported with commodity columns" -- PARTIAL: LayoutBare -> balanceReportAsText' opts ((items, total)) _ -> unlinesB ls <> unlinesB (if no_total_ opts then [] else [overline, totalLines]) where (ls, sizes) = unzip $ map (balanceReportItemAsText opts) items -- abuse renderBalanceReportItem to render the total with similar format (totalLines, _) = renderBalanceReportItem opts ("",0,total) -- with a custom format, extend the line to the full report width; -- otherwise show the usual 20-char line for compatibility iscustom = case format_ opts of OneLine ((FormatField _ _ _ TotalField):_) -> False TopAligned ((FormatField _ _ _ TotalField):_) -> False BottomAligned ((FormatField _ _ _ TotalField):_) -> False _ -> True overlinewidth = if iscustom then sum (map maximum' $ transpose sizes) else 20 overline = TB.fromText $ T.replicate overlinewidth "-" -- | Render a single-column balance report as plain text in commodity-column mode balanceReportAsText' :: ReportOpts -> BalanceReport -> TB.Builder balanceReportAsText' opts ((items, total)) = unlinesB . fmap (renderColumns def{tableBorders=False} sizes . Tab.Group Tab.NoLine . fmap Tab.Header) $ ls ++ concat [[[overline], totalline] | not (no_total_ opts)] where render (_, acctname, dep, amt) = [ Cell TopRight damts , Cell TopLeft (fmap wbFromText cs) , Cell TopLeft (replicate (length damts - 1) mempty ++ [wbFromText dispname]) ] where dopts = oneLine{displayCommodity=layout_ opts /= LayoutBare, displayCommodityOrder=Just cs, displayColour=color_ opts} cs = if mixedAmountLooksZero amt then [""] else S.toList $ maCommodities amt dispname = T.replicate ((dep - 1) * 2) " " <> acctname damts = showMixedAmountLinesB dopts amt ls = fmap render items totalline = render ("", "", 0, total) sizes = fromMaybe 0 . maximumMay . map cellWidth <$> transpose ([totalline | not (no_total_ opts)] ++ ls) overline = Cell TopLeft . pure . wbFromText . flip T.replicate "-" . fromMaybe 0 $ headMay sizes {- :r This implementation turned out to be a bit convoluted but implements the following algorithm for formatting: - If there is a single amount, print it with the account name directly: - Otherwise, only print the account name on the last line. a USD 1 ; Account 'a' has a single amount EUR -1 b USD -1 ; Account 'b' has two amounts. The account name is printed on the last line. -} -- | Render one balance report line item as plain text suitable for console output (or -- whatever string format is specified). Note, prices will not be rendered, and -- differently-priced quantities of the same commodity will appear merged. -- The output will be one or more lines depending on the format and number of commodities. balanceReportItemAsText :: ReportOpts -> BalanceReportItem -> (TB.Builder, [Int]) balanceReportItemAsText opts (_, accountName, dep, amt) = renderBalanceReportItem opts (accountName, dep, amt) -- | Render a balance report item using the given StringFormat, generating one or more lines of text. renderBalanceReportItem :: ReportOpts -> (AccountName, Int, MixedAmount) -> (TB.Builder, [Int]) renderBalanceReportItem opts (acctname, dep, total) = case format_ opts of OneLine comps -> renderRow' $ render True True comps TopAligned comps -> renderRow' $ render True False comps BottomAligned comps -> renderRow' $ render False False comps where renderRow' is = ( renderRowB def{tableBorders=False, borderSpaces=False} . Tab.Group Tab.NoLine $ map Tab.Header is , map cellWidth is ) render topaligned oneline = map (renderComponent topaligned oneline opts (acctname, dep, total)) -- | Render one StringFormat component for a balance report item. renderComponent :: Bool -> Bool -> ReportOpts -> (AccountName, Int, MixedAmount) -> StringFormatComponent -> Cell renderComponent _ _ _ _ (FormatLiteral s) = textCell TopLeft s renderComponent topaligned oneline opts (acctname, dep, total) (FormatField ljust mmin mmax field) = case field of DepthSpacerField -> Cell align [WideBuilder (TB.fromText $ T.replicate d " ") d] where d = maybe id min mmax $ dep * fromMaybe 1 mmin AccountField -> textCell align $ formatText ljust mmin mmax acctname TotalField -> Cell align . pure $ showMixedAmountB dopts total _ -> Cell align [mempty] where align | topaligned && ljust = TopLeft | topaligned = TopRight | ljust = BottomLeft | otherwise = BottomRight dopts = noCost{displayCommodity = layout_ opts /= LayoutBare ,displayOneLine = oneline ,displayMinWidth = mmin ,displayMaxWidth = mmax ,displayColour = color_ opts } -- rendering multi-column balance reports -- | Render a multi-column balance report as CSV. -- The CSV will always include the initial headings row, -- and will include the final totals row unless --no-total is set. multiBalanceReportAsCsv :: ReportOpts -> MultiBalanceReport -> CSV multiBalanceReportAsCsv opts@ReportOpts{..} report = maybeTranspose allRows where allRows = case layout_ of LayoutTidy -> rows -- tidy csv should not include totals or averages _ -> rows ++ totals (rows, totals) = multiBalanceReportAsCsv' opts report maybeTranspose = if transpose_ then transpose else id multiBalanceReportAsCsv' :: ReportOpts -> MultiBalanceReport -> (CSV, CSV) multiBalanceReportAsCsv' opts@ReportOpts{..} (PeriodicReport colspans items tr) = (headers : concatMap fullRowAsTexts items, totalrows) where headers = "account" : case layout_ of LayoutTidy -> ["period", "start_date", "end_date", "commodity", "value"] LayoutBare -> "commodity" : dateHeaders _ -> dateHeaders dateHeaders = map showDateSpan colspans ++ ["total" | row_total_] ++ ["average" | average_] fullRowAsTexts row = map (showName row :) $ multiBalanceRowAsCsvText opts colspans row showName = accountNameDrop drop_ . prrFullName totalrows | no_total_ = mempty | otherwise = map ("total" :) $ multiBalanceRowAsCsvText opts colspans tr -- | Render a multi-column balance report as HTML. multiBalanceReportAsHtml :: ReportOpts -> MultiBalanceReport -> Html () multiBalanceReportAsHtml ropts mbr = let (headingsrow,bodyrows,mtotalsrows) = multiBalanceReportHtmlRows ropts mbr in table_ $ mconcat $ [headingsrow] ++ bodyrows ++ mtotalsrows -- | Render the HTML table rows for a MultiBalanceReport. -- Returns the heading row, 0 or more body rows, and the totals row if enabled. multiBalanceReportHtmlRows :: ReportOpts -> MultiBalanceReport -> (Html (), [Html ()], [Html ()]) multiBalanceReportHtmlRows ropts mbr = let -- TODO: should the commodity_column be displayed as a subaccount in this case as well? (headingsrow:bodyrows, mtotalsrows) | transpose_ ropts = error' "Sorry, --transpose with HTML output is not yet supported" -- PARTIAL: | otherwise = multiBalanceReportAsCsv' ropts mbr in (multiBalanceReportHtmlHeadRow ropts headingsrow ,map (multiBalanceReportHtmlBodyRow ropts) bodyrows ,multiBalanceReportHtmlFootRow ropts <$> mtotalsrows -- TODO pad totals row with zeros when there are ) -- | Render one MultiBalanceReport heading row as a HTML table row. multiBalanceReportHtmlHeadRow :: ReportOpts -> [T.Text] -> Html () multiBalanceReportHtmlHeadRow _ [] = mempty -- shouldn't happen multiBalanceReportHtmlHeadRow ropts (acct:cells) = let defstyle = style_ "" (amts,tot,avg) | row_total_ ropts && average_ ropts = (ini2, sndlst2, lst2) | row_total_ ropts = (ini1, lst1, []) | average_ ropts = (ini1, [], lst1) | otherwise = (cells, [], []) where n = length cells (ini1,lst1) = splitAt (n-1) cells (ini2, rest) = splitAt (n-2) cells (sndlst2,lst2) = splitAt 1 rest in tr_ $ mconcat $ td_ [class_ "account"] (toHtml acct) : [td_ [class_ "", defstyle] (toHtml a) | a <- amts] ++ [td_ [class_ "rowtotal", defstyle] (toHtml a) | a <- tot] ++ [td_ [class_ "rowaverage", defstyle] (toHtml a) | a <- avg] -- | Render one MultiBalanceReport data row as a HTML table row. multiBalanceReportHtmlBodyRow :: ReportOpts -> [T.Text] -> Html () multiBalanceReportHtmlBodyRow _ [] = mempty -- shouldn't happen multiBalanceReportHtmlBodyRow ropts (label:cells) = let defstyle = style_ "text-align:right" (amts,tot,avg) | row_total_ ropts && average_ ropts = (ini2, sndlst2, lst2) | row_total_ ropts = (ini1, lst1, []) | average_ ropts = (ini1, [], lst1) | otherwise = (cells, [], []) where n = length cells (ini1,lst1) = splitAt (n-1) cells (ini2, rest) = splitAt (n-2) cells (sndlst2,lst2) = splitAt 1 rest in tr_ $ mconcat $ td_ [class_ "account", style_ "text-align:left"] (toHtml label) : [td_ [class_ "amount", defstyle] (toHtml a) | a <- amts] ++ [td_ [class_ "amount rowtotal", defstyle] (toHtml a) | a <- tot] ++ [td_ [class_ "amount rowaverage", defstyle] (toHtml a) | a <- avg] -- | Render one MultiBalanceReport totals row as a HTML table row. multiBalanceReportHtmlFootRow :: ReportOpts -> [T.Text] -> Html () multiBalanceReportHtmlFootRow _ropts [] = mempty -- TODO pad totals row with zeros when subreport is empty -- multiBalanceReportHtmlFootRow ropts $ -- "" -- : repeat nullmixedamt zeros -- ++ (if row_total_ ropts then [nullmixedamt] else []) -- ++ (if average_ ropts then [nullmixedamt] else []) multiBalanceReportHtmlFootRow ropts (acct:cells) = let defstyle = style_ "text-align:right" (amts,tot,avg) | row_total_ ropts && average_ ropts = (ini2, sndlst2, lst2) | row_total_ ropts = (ini1, lst1, []) | average_ ropts = (ini1, [], lst1) | otherwise = (cells, [], []) where n = length cells (ini1,lst1) = splitAt (n-1) cells (ini2, rest) = splitAt (n-2) cells (sndlst2,lst2) = splitAt 1 rest in tr_ $ mconcat $ th_ [style_ "text-align:left"] (toHtml acct) : [th_ [class_ "amount coltotal", defstyle] (toHtml a) | a <- amts] ++ [th_ [class_ "amount coltotal", defstyle] (toHtml a) | a <- tot] ++ [th_ [class_ "amount colaverage", defstyle] (toHtml a) | a <- avg] --thRow :: [String] -> Html () --thRow = tr_ . mconcat . map (th_ . toHtml) -- | Render a multi-column balance report as plain text suitable for console output. multiBalanceReportAsText :: ReportOpts -> MultiBalanceReport -> TL.Text multiBalanceReportAsText ropts@ReportOpts{..} r = TB.toLazyText $ TB.fromText title <> TB.fromText "\n\n" <> balanceReportTableAsText ropts (balanceReportAsTable ropts r) where title = mtitle <> " in " <> showDateSpan (periodicReportSpan r) <> valuationdesc <> ":" mtitle = case (balancecalc_, balanceaccum_) of (CalcValueChange, PerPeriod ) -> "Period-end value changes" (CalcValueChange, Cumulative ) -> "Cumulative period-end value changes" (CalcGain, PerPeriod ) -> "Incremental gain" (CalcGain, Cumulative ) -> "Cumulative gain" (CalcGain, Historical ) -> "Historical gain" (_, PerPeriod ) -> "Balance changes" (_, Cumulative ) -> "Ending balances (cumulative)" (_, Historical) -> "Ending balances (historical)" valuationdesc = (case conversionop_ of Just ToCost -> ", converted to cost" _ -> "") <> (case value_ of Just (AtThen _mc) -> ", valued at posting date" Just (AtEnd _mc) | changingValuation -> "" Just (AtEnd _mc) -> ", valued at period ends" Just (AtNow _mc) -> ", current value" Just (AtDate d _mc) -> ", valued at " <> showDate d Nothing -> "") changingValuation = case (balancecalc_, balanceaccum_) of (CalcValueChange, PerPeriod) -> True (CalcValueChange, Cumulative) -> True _ -> False -- | Build a 'Table' from a multi-column balance report. balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table T.Text T.Text WideBuilder balanceReportAsTable opts@ReportOpts{summary_only_, average_, row_total_, balanceaccum_} (PeriodicReport spans items tr) = maybetranspose $ addtotalrow $ Table (Tab.Group Tab.NoLine $ map Tab.Header (concat accts)) (Tab.Group Tab.NoLine $ map Tab.Header colheadings) (concat rows) where totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical] colheadings = ["Commodity" | layout_ opts == LayoutBare] ++ (if not summary_only_ then map (reportPeriodName balanceaccum_ spans) spans else []) ++ [" Total" | totalscolumn] ++ ["Average" | average_] fullRowAsTexts row = let rs = multiBalanceRowAsTableText opts row in (replicate (length rs) (renderacct row), rs) (accts, rows) = unzip $ fmap fullRowAsTexts items renderacct row = T.replicate ((prrDepth row - 1) * 2) " " <> prrDisplayName row addtotalrow | no_total_ opts = id | otherwise = let totalrows = multiBalanceRowAsTableText opts tr rh = Tab.Group Tab.NoLine . replicate (length totalrows) $ Tab.Header "" ch = Tab.Header [] -- ignored in (flip (concatTables Tab.SingleLine) $ Table rh ch totalrows) maybetranspose | transpose_ opts = \(Table rh ch vals) -> Table ch rh (transpose vals) | otherwise = id multiBalanceRowAsWbs :: AmountDisplayOpts -> ReportOpts -> [DateSpan] -> PeriodicReportRow a MixedAmount -> [[WideBuilder]] multiBalanceRowAsWbs bopts ReportOpts{..} colspans (PeriodicReportRow _ as rowtot rowavg) = case layout_ of LayoutWide width -> [fmap (showMixedAmountB bopts{displayMaxWidth=width}) allamts] LayoutTall -> paddedTranspose mempty . fmap (showMixedAmountLinesB bopts{displayMaxWidth=Nothing}) $ allamts LayoutBare -> zipWith (:) (fmap wbFromText cs) -- add symbols . transpose -- each row becomes a list of Text quantities . fmap (showMixedAmountLinesB bopts{displayCommodity=False, displayCommodityOrder=Just cs, displayMinWidth=Nothing}) $ allamts LayoutTidy -> concat . zipWith (map . addDateColumns) colspans . fmap ( zipWith (\c a -> [wbFromText c, a]) cs . showMixedAmountLinesB bopts{displayCommodity=False, displayCommodityOrder=Just cs, displayMinWidth=Nothing}) $ as -- Do not include totals column or average for tidy output, as this -- complicates the data representation and can be easily calculated where totalscolumn = row_total_ && balanceaccum_ `notElem` [Cumulative, Historical] cs = if all mixedAmountLooksZero allamts then [""] else S.toList $ foldMap maCommodities allamts allamts = (if not summary_only_ then as else []) ++ [rowtot | totalscolumn && not (null as)] ++ [rowavg | average_ && not (null as)] addDateColumns spn@(DateSpan s e) = (wbFromText (showDateSpan spn) :) . (wbFromText (maybe "" showEFDate s) :) . (wbFromText (maybe "" (showEFDate . modifyEFDay (addDays (-1))) e) :) paddedTranspose :: a -> [[a]] -> [[a]] paddedTranspose _ [] = [[]] paddedTranspose n as1 = take (maximum . map length $ as1) . trans $ as1 where trans ([] : xss) = (n : map h xss) : trans ([n] : map t xss) trans ((x : xs) : xss) = (x : map h xss) : trans (m xs : map t xss) trans [] = [] h (x:_) = x h [] = n t (_:xs) = xs t [] = [n] m (x:xs) = x:xs m [] = [n] multiBalanceRowAsCsvText :: ReportOpts -> [DateSpan] -> PeriodicReportRow a MixedAmount -> [[T.Text]] multiBalanceRowAsCsvText opts colspans = fmap (fmap wbToText) . multiBalanceRowAsWbs csvDisplay opts colspans multiBalanceRowAsTableText :: ReportOpts -> PeriodicReportRow a MixedAmount -> [[WideBuilder]] multiBalanceRowAsTableText opts = multiBalanceRowAsWbs oneLine{displayColour=color_ opts} opts [] tests_Balance = testGroup "Balance" [ testGroup "balanceReportAsText" [ testCase "unicode in balance layout" $ do j <- readJournal' "2009/01/01 * медвежья шкура\n расходы:покупки 100\n актив:наличные\n" let rspec = defreportspec{_rsReportOpts=defreportopts{no_total_=True}} TB.toLazyText (balanceReportAsText (_rsReportOpts rspec) (balanceReport rspec{_rsDay=fromGregorian 2008 11 26} j)) @?= TL.unlines [" -100 актив:наличные" ," 100 расходы:покупки" ] ] ] hledger-1.32.3/Hledger/Cli/Commands/Balancesheet.hs0000644000000000000000000000245114513751565020152 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} {-| The @balancesheet@ command prints a simple balance sheet. -} module Hledger.Cli.Commands.Balancesheet ( balancesheetmode ,balancesheet ) where import System.Console.CmdArgs.Explicit import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.CompoundBalanceCommand balancesheetSpec = CompoundBalanceCommandSpec { cbcdoc = $(embedFileRelative "Hledger/Cli/Commands/Balancesheet.txt"), cbctitle = "Balance Sheet", cbcqueries = [ CBCSubreportSpec{ cbcsubreporttitle="Assets" ,cbcsubreportquery=Type [Asset] ,cbcsubreportoptions=(\ropts -> ropts{normalbalance_=Just NormallyPositive}) ,cbcsubreporttransform=id ,cbcsubreportincreasestotal=True } ,CBCSubreportSpec{ cbcsubreporttitle="Liabilities" ,cbcsubreportquery=Type [Liability] ,cbcsubreportoptions=(\ropts -> ropts{normalbalance_=Just NormallyNegative}) ,cbcsubreporttransform=fmap maNegate ,cbcsubreportincreasestotal=False } ], cbcaccum = Historical } balancesheetmode :: Mode RawOpts balancesheetmode = compoundBalanceCommandMode balancesheetSpec balancesheet :: CliOpts -> Journal -> IO () balancesheet = compoundBalanceCommand balancesheetSpec hledger-1.32.3/Hledger/Cli/Commands/Balancesheetequity.hs0000644000000000000000000000325014513751565021411 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} {-| The @balancesheetequity@ command prints a simple balance sheet. -} module Hledger.Cli.Commands.Balancesheetequity ( balancesheetequitymode ,balancesheetequity ) where import System.Console.CmdArgs.Explicit import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.CompoundBalanceCommand balancesheetequitySpec = CompoundBalanceCommandSpec { cbcdoc = $(embedFileRelative "Hledger/Cli/Commands/Balancesheetequity.txt"), cbctitle = "Balance Sheet With Equity", cbcqueries = [ CBCSubreportSpec{ cbcsubreporttitle="Assets" ,cbcsubreportquery=Type [Asset] ,cbcsubreportoptions=(\ropts -> ropts{normalbalance_=Just NormallyPositive}) ,cbcsubreporttransform=id ,cbcsubreportincreasestotal=True } ,CBCSubreportSpec{ cbcsubreporttitle="Liabilities" ,cbcsubreportquery=Type [Liability] ,cbcsubreportoptions=(\ropts -> ropts{normalbalance_=Just NormallyNegative}) ,cbcsubreporttransform=fmap maNegate ,cbcsubreportincreasestotal=False } ,CBCSubreportSpec{ cbcsubreporttitle="Equity" ,cbcsubreportquery=Type [Equity] ,cbcsubreportoptions=(\ropts -> ropts{normalbalance_=Just NormallyNegative}) ,cbcsubreporttransform=fmap maNegate ,cbcsubreportincreasestotal=False } ], cbcaccum = Historical } balancesheetequitymode :: Mode RawOpts balancesheetequitymode = compoundBalanceCommandMode balancesheetequitySpec balancesheetequity :: CliOpts -> Journal -> IO () balancesheetequity = compoundBalanceCommand balancesheetequitySpec hledger-1.32.3/Hledger/Cli/Commands/Cashflow.hs0000644000000000000000000000227114513751565017342 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} {-| The @cashflow@ command prints a simplified cashflow statement. It just shows the change in all "cash" accounts for the period (without the traditional segmentation into operating, investing, and financing cash flows.) -} module Hledger.Cli.Commands.Cashflow ( cashflowmode ,cashflow ) where import System.Console.CmdArgs.Explicit import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.CompoundBalanceCommand cashflowSpec = CompoundBalanceCommandSpec { cbcdoc = $(embedFileRelative "Hledger/Cli/Commands/Cashflow.txt"), cbctitle = "Cashflow Statement", cbcqueries = [ CBCSubreportSpec{ cbcsubreporttitle="Cash flows" ,cbcsubreportquery=Type [Cash] ,cbcsubreportoptions=(\ropts -> ropts{normalbalance_= Just NormallyPositive}) ,cbcsubreporttransform=id ,cbcsubreportincreasestotal=True } ], cbcaccum = PerPeriod } cashflowmode :: Mode RawOpts cashflowmode = compoundBalanceCommandMode cashflowSpec cashflow :: CliOpts -> Journal -> IO () cashflow = compoundBalanceCommand cashflowSpec hledger-1.32.3/Hledger/Cli/Commands/Check.hs0000644000000000000000000000764614555053231016613 0ustar0000000000000000{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Check ( checkmode ,check ) where import Data.Char (toLower) import Data.Either (partitionEithers) import Data.List (isPrefixOf, find) import Control.Monad (forM_) import System.Console.CmdArgs.Explicit import Hledger import Hledger.Cli.CliOptions checkmode :: Mode RawOpts checkmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Check.txt") [] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[CHECKS]") check :: CliOpts -> Journal -> IO () check copts@CliOpts{rawopts_} j = do let args = listofstringopt "args" rawopts_ -- reset the report spec that was generated by argsToCliOpts, -- since we are not using arguments as a query in the usual way copts' = cliOptsUpdateReportSpecWith (\ropts -> ropts{querystring_=[]}) copts case partitionEithers (map parseCheckArgument args) of (unknowns@(_:_), _) -> error' $ "These checks are unknown: "++unwords unknowns ([], checks) -> forM_ checks $ runCheck copts' j -- | Regenerate this CliOpts' report specification, after updating its -- underlying report options with the given update function. -- This can raise an error if there is a problem eg due to missing or -- unparseable options data. See also updateReportSpecFromOpts. cliOptsUpdateReportSpecWith :: (ReportOpts -> ReportOpts) -> CliOpts -> CliOpts cliOptsUpdateReportSpecWith roptsupdate copts@CliOpts{reportspec_} = case updateReportSpecWith roptsupdate reportspec_ of Left e -> error' e -- PARTIAL: Right rs -> copts{reportspec_=rs} -- | A type of error check that we can perform on the data. -- Some of these imply other checks that are done first, -- eg currently Parseable and Autobalanced are always done, -- and Assertions are always done unless -I is in effect. data Check = -- done always Parseable | Autobalanced -- done always unless -I is used | Assertions -- done when -s is used, or on demand by check | Accounts | Commodities | Balanced -- done on demand by check | Ordereddates | Payees | Recentassertions | Tags | Uniqueleafnames deriving (Read,Show,Eq,Enum,Bounded) -- | Parse the name (or a name prefix) of an error check, or return the name unparsed. -- Check names are conventionally all lower case, but this parses case insensitively. parseCheck :: String -> Either String Check parseCheck s = maybe (Left s) (Right . read) $ -- PARTIAL: read should not fail here find (s' `isPrefixOf`) $ checknames where s' = capitalise $ map toLower s checknames = map show [minBound..maxBound::Check] -- | Parse a check argument: a string which is the lower-case name of an error check, -- or a prefix thereof, followed by zero or more space-separated arguments for that check. parseCheckArgument :: String -> Either String (Check,[String]) parseCheckArgument s = dbg3 "check argument" $ ((,checkargs)) <$> parseCheck checkname where (checkname:checkargs) = words' s -- XXX do all of these print on stderr ? -- | Run the named error check, possibly with some arguments, -- on this journal with these options. runCheck :: CliOpts -> Journal -> (Check,[String]) -> IO () runCheck CliOpts{reportspec_=ReportSpec{_rsReportOpts=ropts}} j (chck,_) = do d <- getCurrentDay let results = case chck of Accounts -> journalCheckAccounts j Commodities -> journalCheckCommodities j Ordereddates -> journalCheckOrdereddates (whichDate ropts) j Payees -> journalCheckPayees j Recentassertions -> journalCheckRecentAssertions d j Tags -> journalCheckTags j Uniqueleafnames -> journalCheckUniqueleafnames j -- the other checks have been done earlier during withJournalDo _ -> Right () case results of Right () -> return () Left err -> error' err hledger-1.32.3/Hledger/Cli/Commands/Close.hs0000644000000000000000000002036114555425567016647 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE MultiWayIf #-} module Hledger.Cli.Commands.Close ( closemode ,close ) where import Control.Monad (when) import Data.Function (on) import Data.List (groupBy) import Data.Maybe (fromMaybe) import qualified Data.Text as T import qualified Data.Text.IO as T import Data.Time.Calendar (addDays) import Lens.Micro ((^.)) import System.Console.CmdArgs.Explicit as C import Hledger import Hledger.Cli.CliOptions defretaindesc = "retain earnings" defclosedesc = "closing balances" defopendesc = "opening balances" defretainacct = "equity:retained earnings" defcloseacct = "equity:opening/closing balances" closemode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Close.txt") [flagNone ["close"] (setboolopt "close") "show a closing transaction (default)" ,flagNone ["open"] (setboolopt "open") "show an opening transaction" ,flagNone ["migrate"] (setboolopt "migrate") "show both closing and opening transactions" ,flagNone ["retain"] (setboolopt "retain") "show a retain earnings transaction (for RX accounts)" ,flagNone ["explicit","x"] (setboolopt "explicit") "show all amounts explicitly" ,flagNone ["show-costs"] (setboolopt "show-costs") "show amounts with different costs separately" ,flagNone ["interleaved"] (setboolopt "interleaved") "show source and destination postings together" ,flagReq ["close-desc"] (\s opts -> Right $ setopt "close-desc" s opts) "DESC" "set closing transaction's description" ,flagReq ["close-acct"] (\s opts -> Right $ setopt "close-acct" s opts) "ACCT" "set closing transaction's destination account" ,flagReq ["open-desc"] (\s opts -> Right $ setopt "open-desc" s opts) "DESC" "set opening transaction's description" ,flagReq ["open-acct"] (\s opts -> Right $ setopt "open-acct" s opts) "ACCT" "set opening transaction's source account" ] [generalflagsgroup1] (hiddenflags ++ -- keep supporting old flag names for compatibility [flagNone ["closing"] (setboolopt "close") "old spelling of --close" ,flagNone ["opening"] (setboolopt "open") "old spelling of --open" ,flagReq ["close-to"] (\s opts -> Right $ setopt "close-acct" s opts) "ACCT" "old spelling of --close-acct" ,flagReq ["open-from"] (\s opts -> Right $ setopt "open-acct" s opts) "ACCT" "old spelling of --open-acct" ] ) ([], Just $ argsFlag "[--close | --open | --migrate | --retain] [ACCTQUERY]") -- Debugger, beware: close is incredibly devious; simple rules combine to make a horrid maze. -- Tests are in hledger/test/close.test. -- This code is also used by the close command. close copts@CliOpts{rawopts_=rawopts, reportspec_=rspec0} j = do let (close_, open_, defclosedesc_, defopendesc_, defcloseacct_, defacctsq_) = if | boolopt "retain" rawopts -> (True, False, defretaindesc, undefined, defretainacct, Type [Revenue, Expense]) | boolopt "migrate" rawopts -> (True, True, defclosedesc, defopendesc, defcloseacct, Type [Asset, Liability, Equity]) | boolopt "open" rawopts -> (False, True, undefined, defopendesc, defcloseacct, Type [Asset, Liability, Equity]) | otherwise -> (True, False, defclosedesc, undefined, defcloseacct, Type [Asset, Liability, Equity]) -- descriptions to use for the closing/opening transactions closedesc = T.pack $ fromMaybe defclosedesc_ $ maybestringopt "close-desc" rawopts opendesc = T.pack $ fromMaybe defopendesc_ $ maybestringopt "open-desc" rawopts -- equity/balancing accounts to use closeacct = T.pack $ fromMaybe defcloseacct_ $ maybestringopt "close-acct" rawopts openacct = maybe closeacct T.pack $ maybestringopt "open-acct" rawopts ropts = (_rsReportOpts rspec0){balanceaccum_=Historical, accountlistmode_=ALFlat} rspec1 = setDefaultConversionOp NoConversionOp rspec0{_rsReportOpts=ropts} -- Dates of the closing and opening transactions. -- "The default closing date is yesterday, or the journal's end date, whichever is later. -- You can change this by specifying a [report end date](#report-start--end-date) with `-e`. -- The last day of the report period will be the closing date, eg `-e 2024` means "close on 2023-12-31". -- The opening date is always the day after the closing date." argsq = _rsQuery rspec1 yesterday = addDays (-1) $ _rsDay rspec1 yesterdayorjournalend = case journalLastDay False j of Just journalend -> max yesterday journalend Nothing -> yesterday mreportlastday = addDays (-1) <$> queryEndDate False argsq closedate = fromMaybe yesterdayorjournalend mreportlastday opendate = addDays 1 closedate -- should we show the amount(s) on the equity posting(s) ? explicit = boolopt "explicit" rawopts || copts ^. infer_costs -- the balances to close argsacctq = filterQuery (\q -> queryIsAcct q || queryIsType q) argsq q2 = if queryIsNull argsacctq then And [argsq, defacctsq_] else argsq rspec2 = rspec1{_rsQuery=q2} (acctbals',_) = balanceReport rspec2 j acctbals = map (\(a,_,_,b) -> (a, if show_costs_ ropts then b else mixedAmountStripPrices b)) acctbals' totalamt = maSum $ map snd acctbals -- since balance assertion amounts are required to be exact, the -- amounts in opening/closing transactions should be too (#941, #1137) precise = amountSetFullPrecision -- interleave equity postings next to the corresponding closing posting, or put them all at the end ? interleaved = boolopt "interleaved" rawopts -- the closing transaction closetxn = nulltransaction{tdate=closedate, tdescription=closedesc, tpostings=closeps} closeps = concat [ posting{paccount = a ,pamount = mixedAmount . precise $ negate b -- after each commodity's last posting, assert 0 balance (#1035) -- balance assertion amounts are unpriced (#824) ,pbalanceassertion = if islast then Just nullassertion{baamount=precise b{aquantity=0, aprice=Nothing}} else Nothing } -- maybe an interleaved posting transferring this balance to equity : [posting{paccount=closeacct, pamount=mixedAmount $ precise b} | interleaved] | -- get the balances for each commodity and transaction price (a,mb) <- acctbals , let bs0 = amounts mb -- mark the last balance in each commodity with True , let bs2 = concat [reverse $ zip (reverse bs1) (True : repeat False) | bs1 <- groupBy ((==) `on` acommodity) bs0] , (b, islast) <- bs2 ] -- or a final multicommodity posting transferring all balances to equity -- (print will show this as multiple single-commodity postings) ++ [posting{paccount=closeacct, pamount=if explicit then mixedAmountSetFullPrecision totalamt else missingmixedamt} | not interleaved] -- the opening transaction opentxn = nulltransaction{tdate=opendate, tdescription=opendesc, tpostings=openps} openps = concat [ posting{paccount = a ,pamount = mixedAmount $ precise b ,pbalanceassertion = case mcommoditysum of Just s -> Just nullassertion{baamount=precise s{aprice=Nothing}} Nothing -> Nothing } : [posting{paccount=openacct, pamount=mixedAmount . precise $ negate b} | interleaved] | (a,mb) <- acctbals , let bs0 = amounts mb -- mark the last balance in each commodity with the unpriced sum in that commodity (for a balance assertion) , let bs2 = concat [reverse $ zip (reverse bs1) (Just commoditysum : repeat Nothing) | bs1 <- groupBy ((==) `on` acommodity) bs0 , let commoditysum = (sum bs1)] , (b, mcommoditysum) <- bs2 ] ++ [posting{paccount=openacct, pamount=if explicit then mixedAmountSetFullPrecision (maNegate totalamt) else missingmixedamt} | not interleaved] -- print them when close_ . T.putStr $ showTransaction closetxn when open_ . T.putStr $ showTransaction opentxn hledger-1.32.3/Hledger/Cli/Commands/Codes.hs0000644000000000000000000000162414513751565016632 0ustar0000000000000000{-| The @codes@ command lists the codes seen in transactions, in the order parsed. -} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Codes ( codesmode ,codes ) where import qualified Data.Text as T import qualified Data.Text.IO as T import Hledger import Hledger.Cli.CliOptions -- | Command line options for this command. codesmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Codes.txt") [] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- | The codes command. codes :: CliOpts -> Journal -> IO () codes CliOpts{reportspec_=rspec} j = do let ts = entriesReport rspec j codes' = (if empty_ (_rsReportOpts rspec) then id else filter (not . T.null)) $ map tcode ts mapM_ T.putStrLn codes' hledger-1.32.3/Hledger/Cli/Commands/Commodities.hs0000644000000000000000000000131214513751565020043 0ustar0000000000000000{-| The @commodities@ command lists commodity/currency symbols. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Commodities ( commoditiesmode ,commodities ) where import qualified Data.Set as S import qualified Data.Text.IO as T import Hledger import Hledger.Cli.CliOptions -- | Command line options for this command. commoditiesmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Commodities.txt") [] [generalflagsgroup2] [] ([], Nothing) commodities :: CliOpts -> Journal -> IO () commodities _copts = -- TODO support --declared/--used like accounts, payees mapM_ T.putStrLn . S.filter (/= "AUTO") . journalCommodities hledger-1.32.3/Hledger/Cli/Commands/Demo.hs0000644000000000000000000001452614555053231016455 0ustar0000000000000000{-| The @demo@ command lists and plays small hledger demos in the terminal, using asciinema. -} {- PROJECTS improve cast output install command line editing glitches shrink / compress ? help screen corrupted by pager demo update (or drop till stable) add print balance document cast production tips always clear screen after running pager/curses apps ? record with tall window to avoid showing pager in playback ? improve functionality show "done" in final red line ? mirror common asciinema flags like -s, -i and/or set speed/max idle with optional arguments support other asciinema operations (cat) show hledger.org player urls windows/PowerSession support attract/continuous play mode more casts clarify goals/target user(s)/scenarios identify and prioritise some casts needed -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Demo ( demomode ,demo ) where import Hledger import Hledger.Cli.CliOptions import System.Exit (exitFailure) import Text.Printf import Control.Concurrent (threadDelay) import System.Process (callProcess) import System.IO.Error (catchIOError) import Safe (readMay, atMay, headMay) import Data.List (isPrefixOf, find, findIndex, isInfixOf, dropWhileEnd) import Control.Applicative ((<|>)) import Data.ByteString as B (ByteString) import Data.Maybe import qualified Data.ByteString.Char8 as B import System.IO.Temp (withSystemTempFile) import System.IO (hClose) import System.Console.CmdArgs.Explicit (flagReq) demos :: [Demo] demos = map readDemo [ -- XXX these are confusing, redo -- (embedFileRelative "embeddedfiles/help.cast"), -- https://asciinema.org/a/568112 Getting help -- (embedFileRelative "embeddedfiles/demo.cast"), -- https://asciinema.org/a/567944 Watching the built-in demos $(embedFileRelative "embeddedfiles/add.cast"), -- https://asciinema.org/a/567935 The easiest way to start a journal (add) $(embedFileRelative "embeddedfiles/print.cast"), -- https://asciinema.org/a/567936 Show full transactions (print) $(embedFileRelative "embeddedfiles/balance.cast"), -- https://asciinema.org/a/567937 Show account balances and changes (balance) $(embedFileRelative "embeddedfiles/install.cast") -- https://asciinema.org/a/567934 Installing hledger from source with hledger-install ] -- | An embedded asciinema cast, with some of the metadata separated out. -- The original file name is not preserved. data Demo = Demo { dtitle :: String, -- asciinema title field _dcontent :: ByteString -- asciinema v2 content } -- | Command line options for this command. demomode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Demo.txt") [ flagReq ["speed","s"] (\s opts -> Right $ setopt "speed" s opts) "SPEED" ("playback speed (1 is original speed, .5 is half, 2 is double, etc (default: 2))") ] [generalflagsgroup3] [] ([], Just $ argsFlag optsstr) optsstr = "[NUM|PREFIX|SUBSTR] [-- ASCIINEMAOPTS]" usagestr = "Usage: hledger demo " <> optsstr -- | The demo command. demo :: CliOpts -> Journal -> IO () demo CliOpts{rawopts_=rawopts, reportspec_=ReportSpec{_rsQuery=_query}} _j = do -- demos <- getCurrentDirectory >>= readDemos case listofstringopt "args" rawopts of [] -> putStrLn usagestr >> printDemos (a:as) -> case findDemo demos a of Nothing -> do putStrLn $ "No demo \"" <> a <> "\" was found." putStrLn usagestr printDemos exitFailure Just (Demo t c) -> do let -- try to preserve the original pauses a bit while also moving things along defidlelimit = 10 defspeed = 2 speed = case maybestringopt "speed" rawopts of Nothing -> defspeed Just s -> fromMaybe err $ readMay s where err = error' $ "could not parse --speed " <> s <> ", numeric argument expected" idx = maybe 0 (1+) $ findIndex (\(Demo t2 _) -> t2 == t) demos -- should succeed mw <- getTerminalWidth let line = red' $ replicate w '.' where w = fromMaybe (length t) mw printf "playing: %d) %s\nspace to pause, . to step, ctrl-c to quit\n" idx (bold' t) putStrLn line putStrLn "" threadDelay 1000000 runAsciinemaPlay speed defidlelimit c as putStrLn "" putStrLn line readDemo :: ByteString -> Demo readDemo content = Demo title content where title = maybe "" (readTitle . B.unpack) $ headMay $ B.lines content where readTitle s | "\"title\":" `isPrefixOf` s = takeWhile (/='"') $ drop 1 $ lstrip $ drop 8 s | null s = "" | otherwise = readTitle $ tail s findDemo :: [Demo] -> String -> Maybe Demo findDemo ds s = (readMay s >>= atMay ds . subtract 1) -- try to find by number <|> find ((sl `isPrefixOf`).lowercase.dtitle) ds -- or by title prefix (ignoring case) <|> find ((sl `isInfixOf`) .lowercase.dtitle) ds -- or by title substring (ignoring case) where sl = lowercase s printDemos :: IO () printDemos = putStrLn $ unlines $ "Demos:" : -- "" : [show i <> ") " <> bold' t | (i, Demo t _) <- zip [(1::Int)..] demos] -- | Run asciinema play with the given speed and idle limit, passing the given content to its stdin. runAsciinemaPlay :: Float -> Float -> ByteString -> [String] -> IO () runAsciinemaPlay speed idlelimit content args = -- XXX try piping to stdin also withSystemTempFile "hledger-cast" $ \f h -> do -- don't add an extra newline here, it breaks asciinema 2.3.0 (#2094). -- XXX we could try harder and strip excess newlines/carriage returns+linefeeds here B.hPutStr h content >> hClose h callProcess "asciinema" (dbg8With (("asciinema: "++).unwords) $ concat [ ["play"] ,["-s"<> showwithouttrailingzero speed] ,if idlelimit == 0 then [] else ["-i"<>showwithouttrailingzero idlelimit] ,[f] ,args ]) `catchIOError` \err -> do putStrLn $ "\n" <> show err putStrLn "Error: running asciinema failed. Trying 'asciinema --version':" callProcess "asciinema" ["--version"] `catchIOError` \_ -> putStrLn "This also failed. Check that asciinema is installed in your PATH." exitFailure where showwithouttrailingzero = dropWhileEnd (=='.') . dropWhileEnd (=='0') . show hledger-1.32.3/Hledger/Cli/Commands/Descriptions.hs0000644000000000000000000000157714513751565020252 0ustar0000000000000000{-| The @descriptions@ command lists all unique descriptions seen in transactions, sorted alphabetically. -} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Descriptions ( descriptionsmode ,descriptions ) where import Data.List.Extra (nubSort) import qualified Data.Text.IO as T import Hledger import Hledger.Cli.CliOptions -- | Command line options for this command. descriptionsmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Descriptions.txt") [] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- | The descriptions command. descriptions :: CliOpts -> Journal -> IO () descriptions CliOpts{reportspec_=rspec} j = do let ts = entriesReport rspec j descs = nubSort $ map tdescription ts mapM_ T.putStrLn descs hledger-1.32.3/Hledger/Cli/Commands/Diff.hs0000644000000000000000000000745614513751565016456 0ustar0000000000000000{-| The @diff@ command compares two diff. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Diff ( diffmode ,diff ) where import Data.List.Extra ((\\), groupSortOn, nubBy, sortBy) import Data.Function (on) import Data.Ord (comparing) import Data.Maybe (fromJust) import Data.Time (diffDays) import Data.Either (partitionEithers) import qualified Data.Text.IO as T import Lens.Micro (set) import System.Exit (exitFailure) import Hledger import Hledger.Cli.CliOptions -- | Command line options for this command. diffmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Diff.txt") [] [generalflagsgroup2] [] ([], Just $ argsFlag "-f FILE1 -f FILE2 FULLACCOUNTTNAME") data PostingWithPath = PostingWithPath { ppposting :: Posting, pptxnidx :: Int, pppidx :: Int } deriving (Show) instance Eq PostingWithPath where a == b = pptxnidx a == pptxnidx b && pppidx a == pppidx b pptxn :: PostingWithPath -> Transaction pptxn = fromJust . ptransaction . ppposting ppamountqty :: PostingWithPath -> Quantity ppamountqty = aquantity . head . amounts . pamount . ppposting allPostingsWithPath :: Journal -> [PostingWithPath] allPostingsWithPath j = do (txnidx, txn) <- zip [0..] $ jtxns j (pidx, p) <- zip [0..] $ tpostings txn return PostingWithPath { ppposting = p, pptxnidx = txnidx, pppidx = pidx } combine :: ([a], [b]) -> [Either a b] combine (ls, rs) = map Left ls ++ map Right rs combinedBinBy :: Ord b => (a -> b) -> ([a], [a]) -> [([a], [a])] combinedBinBy f = map partitionEithers . groupSortOn (either f f) . combine greedyMaxMatching :: (Eq a, Eq b) => [(a,b)] -> [(a,b)] greedyMaxMatching = greedyMaxMatching' [] greedyMaxMatching' :: (Eq a, Eq b) => [Either a b] -> [(a,b)] -> [(a,b)] greedyMaxMatching' alreadyUsed ((l,r):rest) | Left l `elem` alreadyUsed || Right r `elem` alreadyUsed = greedyMaxMatching' alreadyUsed rest | otherwise = (l,r) : greedyMaxMatching' (Left l : Right r : alreadyUsed) rest greedyMaxMatching' _ [] = [] dateCloseness :: (PostingWithPath, PostingWithPath) -> Integer dateCloseness = negate . uncurry (diffDays `on` tdate.pptxn) type Matching = [(PostingWithPath, PostingWithPath)] matching :: [PostingWithPath] -> [PostingWithPath] -> Matching matching ppl ppr = do (left, right) <- combinedBinBy ppamountqty (ppl, ppr) -- TODO: probably not a correct choice of bins greedyMaxMatching $ sortBy (comparing dateCloseness) [ (l,r) | l <- left, r <- right ] matchingPostings :: AccountName -> Journal -> [PostingWithPath] matchingPostings acct j = filter ((== acct) . paccount . ppposting) $ allPostingsWithPath j pickSide :: Side -> (a,a) -> a pickSide L (l,_) = l pickSide R (_,r) = r unmatchedtxns :: Side -> [PostingWithPath] -> Matching -> [Transaction] unmatchedtxns s pp m = map pptxn $ nubBy ((==) `on` pptxnidx) $ pp \\ map (pickSide s) m -- | The diff command. diff :: CliOpts -> Journal -> IO () diff CliOpts{file_=[f1, f2], reportspec_=ReportSpec{_rsQuery=Acct acctRe}} _ = do j1 <- orDieTrying $ readJournalFile (set ignore_assertions True definputopts) f1 j2 <- orDieTrying $ readJournalFile (set ignore_assertions True definputopts) f2 let acct = reString acctRe let pp1 = matchingPostings acct j1 let pp2 = matchingPostings acct j2 let m = matching pp1 pp2 let unmatchedtxn1 = unmatchedtxns L pp1 m let unmatchedtxn2 = unmatchedtxns R pp2 m putStrLn "These transactions are in the first file only:\n" mapM_ (T.putStr . showTransaction) unmatchedtxn1 putStrLn "These transactions are in the second file only:\n" mapM_ (T.putStr . showTransaction) unmatchedtxn2 diff _ _ = do putStrLn "Please specify two input files. Usage: hledger diff -f FILE1 -f FILE2 FULLACCOUNTNAME" exitFailure hledger-1.32.3/Hledger/Cli/Commands/Help.hs0000644000000000000000000000403214513751565016461 0ustar0000000000000000{-| The help command. |-} --TODO rename manuals --TODO substring matching {-# LANGUAGE PackageImports #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Help ( helpmode ,help' ) where import Data.Maybe import System.Console.CmdArgs.Explicit import System.Environment import System.IO import Hledger.Utils (embedFileRelative) import Hledger.Data.RawOptions import Hledger.Data.Types import Hledger.Cli.CliOptions import Hledger.Cli.DocFiles import Safe (headMay) --import Hledger.Utils.Debug helpmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Help.txt") [flagNone ["i"] (setboolopt "info") "show the manual with info" ,flagNone ["m"] (setboolopt "man") "show the manual with man" ,flagNone ["p"] (setboolopt "pager") "show the manual with $PAGER or less" ,flagNone ["help","h"] (setboolopt "help") "show this help" ] [] [] ([], Just $ argsFlag "[TOPIC]") -- | Display the hledger manual in various formats. -- You can select a docs viewer with one of the `--info`, `--man`, `--pager` flags. -- Otherwise it will use the first available of: info, man, $PAGER, less, stdout -- (and always stdout if output is non-interactive). help' :: CliOpts -> Journal -> IO () help' opts _ = do exes <- likelyExecutablesInPath pagerprog <- fromMaybe "less" <$> lookupEnv "PAGER" interactive <- hIsTerminalDevice stdout let args = take 1 $ listofstringopt "args" $ rawopts_ opts mtopic = headMay args [info, man, pager, cat] = [runInfoForTopic, runManForTopic, runPagerForTopic, printHelpForTopic] viewer | boolopt "info" $ rawopts_ opts = info | boolopt "man" $ rawopts_ opts = man | boolopt "pager" $ rawopts_ opts = pager | not interactive = cat | "info" `elem` exes = info | "man" `elem` exes = man | pagerprog `elem` exes = pager | "less" `elem` exes = pager | otherwise = cat viewer "hledger" mtopic hledger-1.32.3/Hledger/Cli/Commands/Files.hs0000644000000000000000000000141614513751565016636 0ustar0000000000000000{-| The @files@ command lists included files. -} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Files ( filesmode ,files ) where import qualified Data.Text as T import Safe (headMay) import Hledger import Hledger.Cli.CliOptions -- | Command line options for this command. filesmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Files.txt") [] [generalflagsgroup2] [] ([], Just $ argsFlag "[REGEX]") -- | The files command. files :: CliOpts -> Journal -> IO () files CliOpts{rawopts_=rawopts} j = do let args = listofstringopt "args" rawopts regex <- mapM (either fail pure . toRegex . T.pack) $ headMay args let fs = maybe id (filter . regexMatch) regex $ map fst $ jfiles j mapM_ putStrLn fs hledger-1.32.3/Hledger/Cli/Commands/Import.hs0000644000000000000000000001046414555425351017046 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE NamedFieldPuns #-} module Hledger.Cli.Commands.Import ( importmode ,importcmd ) where import Control.Monad import Data.List import qualified Data.Text.IO as T import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Commands.Add (journalAddTransaction) -- import Hledger.Cli.Commands.Print (print') import System.Console.CmdArgs.Explicit import Text.Printf importmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Import.txt") [flagNone ["catchup"] (setboolopt "catchup") "just mark all transactions as already imported" ,flagNone ["dry-run"] (setboolopt "dry-run") "just show the transactions to be imported" ] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "FILE [...]") importcmd opts@CliOpts{rawopts_=rawopts,inputopts_=iopts} j = do -- XXX could be helpful to show the last-seen date, and number of old transactions, too let inputfiles = listofstringopt "args" rawopts inputstr = intercalate ", " $ map quoteIfNeeded inputfiles catchup = boolopt "catchup" rawopts dryrun = boolopt "dry-run" rawopts combinedStyles = let maybeInputStyles = commodity_styles_ . balancingopts_ $ iopts inferredStyles = journalCommodityStyles j in case maybeInputStyles of Nothing -> Just inferredStyles Just inputStyles -> Just $ inputStyles <> inferredStyles iopts' = iopts{ new_=True, -- read only new transactions since last time new_save_=False, -- defer saving .latest files until the end strict_=False, -- defer strict checks until the end balancingopts_=defbalancingopts{commodity_styles_= combinedStyles} -- use amount styles from both when balancing txns } case inputfiles of [] -> error' "please provide one or more input files as arguments" -- PARTIAL: fs -> do enewjandlatestdatesforfiles <- runExceptT $ readJournalFilesAndLatestDates iopts' fs case enewjandlatestdatesforfiles of Left err -> error' err Right (newj, latestdatesforfiles) -> case sortOn tdate $ jtxns newj of -- with --dry-run the output should be valid journal format, so messages have ; prepended [] -> do -- in this case, we vary the output depending on --dry-run, which is a bit awkward let semicolon = if dryrun then "; " else "" :: String printf "%sno new transactions found in %s\n\n" semicolon inputstr newts | catchup -> if dryrun then printf "--catchup would skip %d transactions (dry run)\n\n" (length newts) else do printf "marked %s as caught up, skipping %d transactions\n\n" inputstr (length newts) saveLatestDatesForFiles latestdatesforfiles newts -> do if dryrun then do -- show txns to be imported printf "; would import %d new transactions from %s:\n\n" (length newts) inputstr mapM_ (T.putStr . showTransaction) newts -- then check the whole journal with them added, if in strict mode when (strict_ iopts) $ strictChecks else do -- first check the whole journal with them added, if in strict mode when (strict_ iopts) $ strictChecks -- then append the transactions to the main journal file. -- XXX This writes unix line endings (\n), some at least, -- even if the file uses dos line endings (\r\n), which could leave -- mixed line endings in the file. See also writeFileWithBackupIfChanged. foldM_ (`journalAddTransaction` opts) j newts -- gets forced somehow.. (how ?) printf "imported %d new transactions from %s to %s\n" (length newts) inputstr (journalFilePath j) -- and if we got this far, update each file's .latest file saveLatestDatesForFiles latestdatesforfiles where -- add the new transactions to the journal in memory and check the whole thing strictChecks = either fail pure $ journalStrictChecks j' where j' = foldl' (flip addTransaction) j newts hledger-1.32.3/Hledger/Cli/Commands/Incomestatement.hs0000644000000000000000000000347214513751565020737 0ustar0000000000000000{-# LANGUAGE QuasiQuotes, TemplateHaskell, OverloadedStrings #-} {-| The @incomestatement@ command prints a simple income statement (profit & loss report). -} module Hledger.Cli.Commands.Incomestatement ( incomestatementmode ,incomestatement ) where import System.Console.CmdArgs.Explicit import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.CompoundBalanceCommand incomestatementSpec = CompoundBalanceCommandSpec { cbcdoc = $(embedFileRelative "Hledger/Cli/Commands/Incomestatement.txt"), cbctitle = "Income Statement", cbcqueries = [ CBCSubreportSpec{ cbcsubreporttitle="Revenues" ,cbcsubreportquery=Type [Revenue] ,cbcsubreportoptions=(\ropts -> ropts{normalbalance_=Just NormallyNegative}) ,cbcsubreporttransform=fmap maNegate ,cbcsubreportincreasestotal=True } ,CBCSubreportSpec{ cbcsubreporttitle="Expenses" ,cbcsubreportquery=Type [Expense] ,cbcsubreportoptions=(\ropts -> ropts{normalbalance_=Just NormallyPositive}) ,cbcsubreporttransform=id ,cbcsubreportincreasestotal=False } ], cbcaccum = PerPeriod } incomestatementmode :: Mode RawOpts incomestatementmode = compoundBalanceCommandMode incomestatementSpec incomestatement :: CliOpts -> Journal -> IO () incomestatement = compoundBalanceCommand incomestatementSpec {- Summary of code flow, 2021-11: incomestatement compoundBalanceCommand compoundBalanceReport compoundBalanceReportWith colps = getPostingsByColumn startps = startingPostings generateSubreport startbals = startingBalances (startps restricted to this subreport) generateMultiBalanceReport startbals (colps restricted to this subreport) matrix = calculateReportMatrix startbals colps displaynames = displayedAccounts buildReportRows displaynames matrix -} hledger-1.32.3/Hledger/Cli/Commands/Notes.hs0000644000000000000000000000155714513751565016672 0ustar0000000000000000{-| The @notes@ command lists all unique notes (description part after a |) seen in transactions, sorted alphabetically. -} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE CPP #-} module Hledger.Cli.Commands.Notes ( notesmode ,notes ) where import Data.List.Extra (nubSort) import qualified Data.Text.IO as T import Hledger import Hledger.Cli.CliOptions -- | Command line options for this command. notesmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Notes.txt") [] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- | The notes command. notes :: CliOpts -> Journal -> IO () notes CliOpts{reportspec_=rspec} j = do let ts = entriesReport rspec j notes' = nubSort $ map transactionNote ts mapM_ T.putStrLn notes' hledger-1.32.3/Hledger/Cli/Commands/Payees.hs0000644000000000000000000000315714513751565017026 0ustar0000000000000000{-| The @payees@ command lists all unique payees (description part before a |) seen in transactions, sorted alphabetically. -} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Payees ( payeesmode ,payees ) where import qualified Data.Set as S import qualified Data.Text.IO as T import System.Console.CmdArgs.Explicit as C import Hledger import Hledger.Cli.CliOptions -- | Command line options for this command. payeesmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Payees.txt") [flagNone ["declared"] (setboolopt "declared") "show payees declared with payee directives" ,flagNone ["used"] (setboolopt "used") "show payees referenced by transactions" ] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- | The payees command. payees :: CliOpts -> Journal -> IO () payees CliOpts{rawopts_=rawopts, reportspec_=ReportSpec{_rsQuery=query}} j = do let decl = boolopt "declared" rawopts used = boolopt "used" rawopts -- XXX matchesPayee is currently an alias for matchesDescription, not sure if it matters matcheddeclaredpayees = S.fromList . filter (matchesPayeeWIP query) $ journalPayeesDeclared j matchedusedpayees = S.fromList . map transactionPayee $ filter (matchesTransaction query) $ jtxns j payees' = if | decl && not used -> matcheddeclaredpayees | not decl && used -> matchedusedpayees | otherwise -> matcheddeclaredpayees <> matchedusedpayees mapM_ T.putStrLn payees' hledger-1.32.3/Hledger/Cli/Commands/Prices.hs0000644000000000000000000000754514555423340017023 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE NamedFieldPuns #-} module Hledger.Cli.Commands.Prices ( pricesmode ,prices ) where import Data.List import qualified Data.Text as T import qualified Data.Text.IO as T import Hledger import Hledger.Cli.CliOptions import System.Console.CmdArgs.Explicit import Data.Maybe (mapMaybe) import Data.Function ((&)) pricesmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Prices.txt") [flagNone ["show-reverse"] (setboolopt "show-reverse") "also show the prices inferred by reversing known prices" ] [generalflagsgroup1] (hiddenflags ++ [flagNone ["costs"] (setboolopt "infer-market-prices") "deprecated, use --infer-market-prices instead" ,flagNone ["inverted-costs"] (setboolopt "show-reverse") "deprecated, use --show-reverse instead" ,flagNone ["infer-reverse-prices"] (setboolopt "show-reverse") "deprecated, use --show-reverse instead" ]) ([], Just $ argsFlag "[QUERY]") instance HasAmounts PriceDirective where styleAmounts styles pd = pd{pdamount=styleAmounts styles $ pdamount pd} -- List market prices. prices opts j = do let styles = journalCommodityStyles j q = _rsQuery $ reportspec_ opts -- XXX duplicates logic in Hledger.Data.Valuation.makePriceGraph, keep synced declaredprices = -- dbg0 "declaredprices" $ jpricedirectives j pricesfromcosts = -- dbg0 "pricesfromcosts" $ concatMap postingPriceDirectivesFromCost $ journalPostings j forwardprices = -- dbg0 "forwardprices" $ if boolopt "infer-market-prices" (rawopts_ opts) then declaredprices `mergePriceDirectives` pricesfromcosts else declaredprices reverseprices = -- dbg0 "reverseprices" $ mapMaybe reversePriceDirective forwardprices allprices = -- dbg0 "allprices" $ if boolopt "show-reverse" (rawopts_ opts) then forwardprices `mergePriceDirectives` reverseprices else forwardprices filteredprices = -- dbg0 "filtered unsorted" $ filter (matchesPriceDirective q) allprices mapM_ (T.putStrLn . showPriceDirective . styleAmounts styles) $ sortOn pddate filteredprices -- XXX performance -- | Append any new price directives (with different from commodity, -- to commodity, or date) from the second list to the first. -- (Does not remove redundant prices from the first; just avoids adding more.) mergePriceDirectives :: [PriceDirective] -> [PriceDirective] -> [PriceDirective] mergePriceDirectives pds1 pds2 = pds1 ++ [ pd | pd <- pds2 , pdid pd `notElem` pds1ids ] where pds1ids = map pdid pds1 pdid PriceDirective{pddate,pdcommodity,pdamount} = (pddate, pdcommodity, acommodity pdamount) showPriceDirective :: PriceDirective -> T.Text showPriceDirective mp = T.unwords [ "P", T.pack . show $ pddate mp, quoteCommoditySymbolIfNeeded $ pdcommodity mp, wbToText . showAmountB noColour{displayZeroCommodity=True} $ pdamount mp ] -- | Convert a market price directive to a corresponding one in the -- opposite direction, if possible. (A price directive with a zero -- price can't be reversed.) -- -- The price's display precision will be set to show all significant -- decimal digits (or if they appear infinite, a smaller default precision (8). -- This is visible eg in the prices command's output. -- reversePriceDirective :: PriceDirective -> Maybe PriceDirective reversePriceDirective pd@PriceDirective{pdcommodity=c, pdamount=a} | amountIsZero a = Nothing | otherwise = Just pd{pdcommodity=acommodity a, pdamount=a'} where lbl = lbl_ "reversePriceDirective" a' = amountSetFullPrecisionOr (Just defaultMaxPrecision) $ invertAmount a{acommodity=c} & dbg9With (lbl "calculated reverse price".showAmount) -- & dbg9With (lbl "precision of reverse price".show.amountDisplayPrecision) hledger-1.32.3/Hledger/Cli/Commands/Print.hs0000644000000000000000000002361514555433334016672 0ustar0000000000000000{-| A ledger-compatible @print@ command. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Print ( printmode ,print' -- ,entriesReportAsText ,transactionWithMostlyOriginalPostings ) where import Data.List (intersperse, intercalate) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Builder as TB import Lens.Micro ((^.), _Just, has) import System.Console.CmdArgs.Explicit import Hledger import Hledger.Read.CsvUtils (CSV, printCSV, printTSV) import Hledger.Cli.CliOptions import Hledger.Cli.Utils import System.Exit (exitFailure) import Safe (lastMay, minimumDef) import Data.Function ((&)) import Data.List.Extra (nubSort) printmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Print.txt") ([flagNone ["explicit","x"] (setboolopt "explicit") "show all amounts explicitly" ,flagNone ["show-costs"] (setboolopt "show-costs") "show transaction prices even with conversion postings" ,flagReq ["round"] (\s opts -> Right $ setopt "round" s opts) "TYPE" $ intercalate "\n" ["how much rounding or padding should be done when displaying amounts ?" ,"none - show original decimal digits," ," as in journal" ,"soft - just add or remove decimal zeros" ," to match precision (default)" ,"hard - round posting amounts to precision" ," (can unbalance transactions)" ,"all - also round cost amounts to precision" ," (can unbalance transactions)" ] ,flagNone ["new"] (setboolopt "new") "show only newer-dated transactions added in each file since last run" ,let arg = "DESC" in flagReq ["match","m"] (\s opts -> Right $ setopt "match" s opts) arg ("fuzzy search for one recent transaction with description closest to "++arg) ,outputFormatFlag ["txt","beancount","csv","tsv","json","sql"] ,outputFileFlag ]) [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- | Get the --round option's value, if any. Can fail with a parse error. roundFromRawOpts :: RawOpts -> Maybe Rounding roundFromRawOpts = lastMay . collectopts roundfromrawopt where roundfromrawopt (n,v) | n=="round", v=="none" = Just NoRounding | n=="round", v=="soft" = Just SoftRounding | n=="round", v=="hard" = Just HardRounding | n=="round", v=="all" = Just AllRounding | n=="round" = error' $ "--round's value should be none, soft, hard or all; got: "++v | otherwise = Nothing -- | Print journal transactions in standard format. print' :: CliOpts -> Journal -> IO () print' opts j = do -- The print command should show all amounts with their original decimal places, -- but as part of journal reading the posting amounts have already been normalised -- according to commodity display styles, and currently it's not easy to avoid -- that. For now we try to reverse it by increasing all amounts' decimal places -- sufficiently to show the amount exactly. The displayed amounts may have minor -- differences from the originals, such as trailing zeroes added. let -- lbl = lbl_ "print'" j' = j -- & dbg9With (lbl "amounts before setting full precision".showJournalAmountsDebug) & journalMapPostingAmounts mixedAmountSetFullPrecision -- & dbg9With (lbl "amounts after setting full precision: ".showJournalAmountsDebug) case maybestringopt "match" $ rawopts_ opts of Nothing -> printEntries opts j' Just desc -> -- match mode, prints one recent transaction most similar to given description -- XXX should match similarly to register --match case journalSimilarTransaction opts j' (dbg1 "finding best match for description" $ T.pack desc) of Just t -> printEntries opts j'{jtxns=[t]} Nothing -> putStrLn "no matches found." >> exitFailure printEntries :: CliOpts -> Journal -> IO () printEntries opts@CliOpts{rawopts_=rawopts, reportspec_=rspec} j = writeOutputLazyText opts $ render $ entriesReport rspec j where -- print does user-specified rounding or (by default) no rounding, in all output formats styles = case roundFromRawOpts rawopts of Nothing -> styles0 Just NoRounding -> styles0 Just r -> amountStylesSetRounding r styles0 where styles0 = journalCommodityStyles j fmt = outputFormatFromOpts opts render | fmt=="txt" = entriesReportAsText . styleAmounts styles . map maybeoriginalamounts | fmt=="beancount" = entriesReportAsBeancount . styleAmounts styles . map maybeoriginalamounts | fmt=="csv" = printCSV . entriesReportAsCsv . styleAmounts styles | fmt=="tsv" = printTSV . entriesReportAsCsv . styleAmounts styles | fmt=="json" = toJsonText . styleAmounts styles | fmt=="sql" = entriesReportAsSql . styleAmounts styles | otherwise = error' $ unsupportedOutputFormatError fmt -- PARTIAL: where maybeoriginalamounts -- Use the fully inferred and amount-styled/rounded transaction in the following situations: -- with -x/--explicit: | boolopt "explicit" (rawopts_ opts) = id -- with --show-costs: | opts ^. infer_costs = id -- with -B/-V/-X/--value ("because of #551, and because of print -V valuing only one posting when there's an implicit txn price.") | has (value . _Just) opts = id -- Otherwise, keep the transaction's amounts close to how they were written in the journal. | otherwise = transactionWithMostlyOriginalPostings -- | Replace this transaction's postings with the original postings if any, but keep the -- current possibly rewritten account names, and the inferred values of any auto postings. -- This is mainly for showing transactions with the amounts in their original journal format. transactionWithMostlyOriginalPostings :: Transaction -> Transaction transactionWithMostlyOriginalPostings = transactionMapPostings postingMostlyOriginal where postingMostlyOriginal p = orig { paccount = paccount p , pamount = pamount $ if isGenerated then p else orig } where orig = originalPosting p isGenerated = "_generated-posting" `elem` map fst (ptags p) entriesReportAsText :: EntriesReport -> TL.Text entriesReportAsText = entriesReportAsTextHelper showTransaction entriesReportAsTextHelper :: (Transaction -> T.Text) -> EntriesReport -> TL.Text entriesReportAsTextHelper showtxn = TB.toLazyText . foldMap (TB.fromText . showtxn) -- In addition to rendering the transactions in (best effort) Beancount format, -- this generates an account open directive for each account name used -- (using the earliest transaction date). entriesReportAsBeancount :: EntriesReport -> TL.Text entriesReportAsBeancount ts = -- PERF: gathers and converts all account names, then repeats that work when showing each transaction opendirectives <> "\n" <> entriesReportAsTextHelper showTransactionBeancount ts where opendirectives | null ts = "" | otherwise = TL.fromStrict $ T.unlines [ firstdate <> " open " <> accountNameToBeancount a | a <- nubSort $ concatMap (map paccount.tpostings) ts ] where firstdate = showDate $ minimumDef err $ map tdate ts where err = error' "entriesReportAsBeancount: should not happen" entriesReportAsSql :: EntriesReport -> TL.Text entriesReportAsSql txns = TB.toLazyText $ mconcat [ TB.fromText "create table if not exists postings(id serial,txnidx int,date1 date,date2 date,status text,code text,description text,comment text,account text,amount numeric,commodity text,credit numeric,debit numeric,posting_status text,posting_comment text);\n" , TB.fromText "insert into postings(txnidx,date1,date2,status,code,description,comment,account,amount,commodity,credit,debit,posting_status,posting_comment) values\n" , mconcat . intersperse (TB.fromText ",") $ map values csv , TB.fromText ";\n" ] where values vs = TB.fromText "(" <> mconcat (intersperse (TB.fromText ",") $ map toSql vs) <> TB.fromText ")\n" toSql "" = TB.fromText "NULL" toSql s = TB.fromText "'" <> TB.fromText (T.replace "'" "''" s) <> TB.fromText "'" csv = concatMap (transactionToCSV . transactionMapPostingAmounts (mapMixedAmount setDecimalPoint)) txns where setDecimalPoint a = a{astyle=(astyle a){asdecimalmark=Just '.'}} entriesReportAsCsv :: EntriesReport -> CSV entriesReportAsCsv txns = ["txnidx","date","date2","status","code","description","comment","account","amount","commodity","credit","debit","posting-status","posting-comment"] : concatMap transactionToCSV txns -- | Generate one CSV record per posting, duplicating the common transaction fields. -- The txnidx field (transaction index) allows postings to be grouped back into transactions. transactionToCSV :: Transaction -> CSV transactionToCSV t = map (\p -> T.pack (show idx):d:d2:status:code:description:comment:p) (concatMap postingToCSV $ tpostings t) where idx = tindex t description = tdescription t d = showDate (tdate t) d2 = maybe "" showDate $ tdate2 t status = T.pack . show $ tstatus t code = tcode t comment = T.strip $ tcomment t postingToCSV :: Posting -> CSV postingToCSV p = map (\(a@(Amount {aquantity=q,acommodity=c})) -> -- commodity goes into separate column, so we suppress it, along with digit group -- separators and prices let a_ = amountStripCost a{acommodity=""} in let showamt = wbToText . showAmountB csvDisplay in let amt = showamt a_ in let credit = if q < 0 then showamt $ negate a_ else "" in let debit = if q >= 0 then showamt a_ else "" in [account, amt, c, credit, debit, status, comment]) . amounts $ pamount p where status = T.pack . show $ pstatus p account = showAccountName Nothing (ptype p) (paccount p) comment = T.strip $ pcomment p hledger-1.32.3/Hledger/Cli/Commands/Register.hs0000644000000000000000000002637014555423340017357 0ustar0000000000000000{-| A ledger-compatible @register@ command. -} {-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Register ( registermode ,register ,postingsReportAsText ,postingsReportItemAsText -- ,showPostingWithBalanceForVty ,tests_Register ) where import Data.Default (def) import Data.Maybe (fromMaybe, isJust) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.IO as TL import qualified Data.Text.Lazy.Builder as TB import System.Console.CmdArgs.Explicit (flagNone, flagReq) import Hledger hiding (per) import Hledger.Read.CsvUtils (CSV, CsvRecord, printCSV, printTSV) import Hledger.Cli.CliOptions import Hledger.Cli.Utils import Text.Tabular.AsciiWide hiding (render) import Data.List (sortBy) import Data.Char (toUpper) import Data.List.Extra (intersect) import System.Exit (exitFailure) registermode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Register.txt") ([flagNone ["cumulative"] (setboolopt "cumulative") "show running total from report start date (default)" ,flagNone ["historical","H"] (setboolopt "historical") "show historical running total/balance (includes postings before report start date)\n " ,flagNone ["average","A"] (setboolopt "average") "show running average of posting amounts instead of total (implies --empty)" ,let arg = "DESC" in flagReq ["match","m"] (\s opts -> Right $ setopt "match" s opts) arg ("fuzzy search for one recent posting with description closest to "++arg) ,flagNone ["related","r"] (setboolopt "related") "show postings' siblings instead" ,flagNone ["invert"] (setboolopt "invert") "display all amounts with reversed sign" ,flagReq ["width","w"] (\s opts -> Right $ setopt "width" s opts) "N" ("set output width (default: " ++ #ifdef mingw32_HOST_OS show defaultWidth #else "terminal width" #endif ++ " or $COLUMNS). -wN,M sets description width as well." ) ,flagNone ["align-all"] (setboolopt "align-all") "guarantee alignment across all lines (slower)" ,outputFormatFlag ["txt","csv","tsv","json"] ,outputFileFlag ]) [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- | Print a (posting) register report. register :: CliOpts -> Journal -> IO () register opts@CliOpts{rawopts_=rawopts, reportspec_=rspec} j -- match mode, print one recent posting most similar to given description, if any -- XXX should match similarly to print --match | Just desc <- maybestringopt "match" rawopts = do let ps = [p | (_,_,_,p,_) <- rpt] case similarPosting ps desc of Nothing -> putStrLn "no matches found." >> exitFailure Just p -> TL.putStr $ postingsReportAsText opts [pri] where pri = (Just (postingDate p) ,Nothing ,tdescription <$> ptransaction p ,styleAmounts styles p ,styleAmounts styles nullmixedamt) -- normal register report, list postings | otherwise = writeOutputLazyText opts $ render $ styleAmounts styles rpt where styles = journalCommodityStylesWith HardRounding j rpt = postingsReport rspec j render | fmt=="txt" = postingsReportAsText opts | fmt=="csv" = printCSV . postingsReportAsCsv | fmt=="tsv" = printTSV . postingsReportAsCsv | fmt=="json" = toJsonText | otherwise = error' $ unsupportedOutputFormatError fmt -- PARTIAL: where fmt = outputFormatFromOpts opts postingsReportAsCsv :: PostingsReport -> CSV postingsReportAsCsv is = ["txnidx","date","code","description","account","amount","total"] : map postingsReportItemAsCsvRecord is postingsReportItemAsCsvRecord :: PostingsReportItem -> CsvRecord postingsReportItemAsCsvRecord (_, _, _, p, b) = [idx,date,code,desc,acct,amt,bal] where idx = T.pack . show . maybe 0 tindex $ ptransaction p date = showDate $ postingDate p -- XXX csv should show date2 with --date2 code = maybe "" tcode $ ptransaction p desc = maybe "" tdescription $ ptransaction p acct = bracket $ paccount p where bracket = case ptype p of BalancedVirtualPosting -> wrap "[" "]" VirtualPosting -> wrap "(" ")" _ -> id -- Since postingsReport strips prices from all Amounts when not used, we can display prices. amt = wbToText . showMixedAmountB csvDisplay $ pamount p bal = wbToText $ showMixedAmountB csvDisplay b -- | Render a register report as plain text suitable for console output. postingsReportAsText :: CliOpts -> PostingsReport -> TL.Text postingsReportAsText opts = TB.toLazyText . postingsOrTransactionsReportAsText alignAll opts (postingsReportItemAsText opts) itemamt itembal where alignAll = boolopt "align-all" $ rawopts_ opts itemamt (_,_,_,Posting{pamount=a},_) = a itembal (_,_,_,_,a) = a -- | Render one register report line item as plain text. Layout is like so: -- @ -- <---------------- width (specified, terminal width, or 80) --------------------> -- date (10) description account amount (12) balance (12) -- DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA -- @ -- If description's width is specified, account will use the remaining space. -- Otherwise, description and account divide up the space equally. -- -- With a report interval, the layout is like so: -- @ -- <---------------- width (specified, terminal width, or 80) --------------------> -- date (21) account amount (12) balance (12) -- DDDDDDDDDDDDDDDDDDDDD aaaaaaaaaaaaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA -- @ -- -- date and description are shown for the first posting of a transaction only. -- -- Returns a string which can be multi-line, eg if the running balance -- has multiple commodities. Does not yet support formatting control -- like balance reports. -- -- Also returns the natural width (without padding) of the amount and balance -- fields. postingsReportItemAsText :: CliOpts -> Int -> Int -> (PostingsReportItem, [WideBuilder], [WideBuilder]) -> TB.Builder postingsReportItemAsText opts preferredamtwidth preferredbalwidth ((mdate, mperiod, mdesc, p, _), amt, bal) = table <> TB.singleton '\n' where table = renderRowB def{tableBorders=False, borderSpaces=False} . Group NoLine $ map Header [ textCell TopLeft $ fitText (Just datewidth) (Just datewidth) True True date , spacerCell , textCell TopLeft $ fitText (Just descwidth) (Just descwidth) True True desc , spacerCell2 , textCell TopLeft $ fitText (Just acctwidth) (Just acctwidth) True True acct , spacerCell2 , Cell TopRight $ map (pad amtwidth) amt , spacerCell2 , Cell BottomRight $ map (pad balwidth) bal ] spacerCell = Cell BottomLeft [WideBuilder (TB.singleton ' ') 1] spacerCell2 = Cell BottomLeft [WideBuilder (TB.fromString " ") 2] pad fullwidth amt' = WideBuilder (TB.fromText $ T.replicate w " ") w <> amt' where w = fullwidth - wbWidth amt' -- calculate widths (totalwidth,mdescwidth) = registerWidthsFromOpts opts datewidth = maybe 10 periodTextWidth mperiod date = case mperiod of Just per -> if isJust mdate then showPeriod per else "" Nothing -> maybe "" showDate mdate (amtwidth, balwidth) | shortfall <= 0 = (preferredamtwidth, preferredbalwidth) | otherwise = (adjustedamtwidth, adjustedbalwidth) where mincolwidth = 2 -- columns always show at least an ellipsis maxamtswidth = max 0 (totalwidth - (datewidth + 1 + mincolwidth + 2 + mincolwidth + 2 + 2)) shortfall = (preferredamtwidth + preferredbalwidth) - maxamtswidth amtwidthproportion = fromIntegral preferredamtwidth / fromIntegral (preferredamtwidth + preferredbalwidth) adjustedamtwidth = round $ amtwidthproportion * fromIntegral maxamtswidth adjustedbalwidth = maxamtswidth - adjustedamtwidth remaining = totalwidth - (datewidth + 1 + 2 + amtwidth + 2 + balwidth) (descwidth, acctwidth) | isJust mperiod = (0, remaining - 2) | otherwise = (w, remaining - 2 - w) where w = fromMaybe ((remaining - 2) `div` 2) mdescwidth -- gather content desc = fromMaybe "" mdesc acct = parenthesise . elideAccountName awidth $ paccount p where (parenthesise, awidth) = case ptype p of BalancedVirtualPosting -> (wrap "[" "]", acctwidth-2) VirtualPosting -> (wrap "(" ")", acctwidth-2) _ -> (id,acctwidth) -- for register --match: -- Identify the closest recent match for this description in the given date-sorted postings. similarPosting :: [Posting] -> String -> Maybe Posting similarPosting ps desc = let matches = sortBy compareRelevanceAndRecency $ filter ((> threshold).fst) [(maybe 0 (\t -> compareDescriptions desc (T.unpack $ tdescription t)) (ptransaction p), p) | p <- ps] where compareRelevanceAndRecency (n1,p1) (n2,p2) = compare (n2,postingDate p2) (n1,postingDate p1) threshold = 0 in case matches of [] -> Nothing m:_ -> Just $ snd m -- -- Identify the closest recent match for this description in past transactions. -- similarTransaction :: Journal -> Query -> String -> Maybe Transaction -- similarTransaction j q desc = -- case historymatches = transactionsSimilarTo j q desc of -- ((,t):_) = Just t -- [] = Nothing compareDescriptions :: String -> String -> Double compareDescriptions s t = compareStrings s' t' where s' = simplify s t' = simplify t simplify = filter (not . (`elem` ("0123456789"::String))) -- | Return a similarity measure, from 0 to 1, for two strings. -- This is Simon White's letter pairs algorithm from -- http://www.catalysoft.com/articles/StrikeAMatch.html -- with a modification for short strings. compareStrings :: String -> String -> Double compareStrings "" "" = 1 compareStrings [_] "" = 0 compareStrings "" [_] = 0 compareStrings [a] [b] = if toUpper a == toUpper b then 1 else 0 compareStrings s1 s2 = 2.0 * fromIntegral i / fromIntegral u where i = length $ intersect pairs1 pairs2 u = length pairs1 + length pairs2 pairs1 = wordLetterPairs $ uppercase s1 pairs2 = wordLetterPairs $ uppercase s2 wordLetterPairs = concatMap letterPairs . words letterPairs (a:b:rest) = [a,b] : letterPairs (b:rest) letterPairs _ = [] -- tests tests_Register = testGroup "Register" [ testGroup "postingsReportAsText" [ testCase "unicode in register layout" $ do j <- readJournal' "2009/01/01 * медвежья шкура\n расходы:покупки 100\n актив:наличные\n" let rspec = defreportspec (TL.unpack . postingsReportAsText defcliopts $ postingsReport rspec j) @?= unlines ["2009-01-01 медвежья шкура расходы:покупки 100 100" ," актив:наличные -100 0"] ] ] hledger-1.32.3/Hledger/Cli/Commands/Rewrite.hs0000644000000000000000000001413114555053231017202 0ustar0000000000000000{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE ViewPatterns #-} module Hledger.Cli.Commands.Rewrite ( rewritemode ,rewrite ) where import Data.Functor.Identity import Data.List (sortOn, foldl') import Data.Text (Text) import qualified Data.Text as T import qualified Data.Text.IO as T import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Commands.Print import System.Console.CmdArgs.Explicit import Text.Printf import Text.Megaparsec hiding (pos1) import qualified Data.Algorithm.Diff as D rewritemode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Rewrite.txt") [flagReq ["add-posting"] (\s opts -> Right $ setopt "add-posting" s opts) "'ACCT AMTEXPR'" "add a posting to ACCT, which may be parenthesised. AMTEXPR is either a literal amount, or *N which means the transaction's first matched amount multiplied by N (a decimal number). Two spaces separate ACCT and AMTEXPR." ,flagNone ["diff"] (setboolopt "diff") "generate diff suitable as an input for patch tool" ] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY] --add-posting \"ACCT AMTEXPR\" ...") -- TODO regex matching and interpolating matched name in replacement -- TODO interpolating match groups in replacement -- TODO allow using this on unbalanced entries, eg to rewrite while editing rewrite opts@CliOpts{rawopts_=rawopts,reportspec_=rspec} j@Journal{jtxns=ts} = do -- rewrite matched transactions let today = _rsDay rspec verbosetags = boolopt "verbose-tags" rawopts modifiers = transactionModifierFromOpts opts : jtxnmodifiers j let j' = j{jtxns=either error' id $ modifyTransactions (journalAccountType j) (journalInheritedAccountTags j) mempty today verbosetags modifiers ts} -- PARTIAL: -- run the print command, showing all transactions, or show diffs printOrDiff rawopts opts{reportspec_=rspec{_rsQuery=Any}} j j' -- | Build a 'TransactionModifier' from any query arguments and --add-posting flags -- provided on the command line, or throw a parse error. transactionModifierFromOpts :: CliOpts -> TransactionModifier transactionModifierFromOpts CliOpts{rawopts_=rawopts} = TransactionModifier{tmquerytxt=q, tmpostingrules=ps} where q = T.pack . unwords . map quoteIfNeeded $ listofstringopt "args" rawopts ps = map (parseposting . T.pack) $ listofstringopt "add-posting" rawopts parseposting t = either (error' . errorBundlePretty) id ep -- PARTIAL: where ep = runIdentity (runJournalParser (tmpostingrulep Nothing <* eof) t') t' = " " <> t <> "\n" -- inject space and newline for proper parsing printOrDiff :: RawOpts -> (CliOpts -> Journal -> Journal -> IO ()) printOrDiff opts | boolopt "diff" opts = const diffOutput | otherwise = flip (const print') diffOutput :: Journal -> Journal -> IO () diffOutput j j' = do let changed = [(transactionWithMostlyOriginalPostings t, transactionWithMostlyOriginalPostings t') | (t, t') <- zip (jtxns j) (jtxns j'), t /= t'] T.putStr $ renderPatch $ map (uncurry $ diffTxn j) changed type Chunk = (SourcePos, [DiffLine Text]) -- XXX doctests, update needed: -- >>> putStr $ renderPatch [(GenericSourcePos "a" 1 1, [D.First "x", D.Second "y"])] -- --- a -- +++ a -- @@ -1,1 +1,1 @@ -- -x -- +y -- >>> putStr $ renderPatch [(GenericSourcePos "a" 1 1, [D.Both "x" "x", D.Second "y"]), (GenericSourcePos "a" 5 1, [D.Second "z"])] -- --- a -- +++ a -- @@ -1,1 +1,2 @@ -- x -- +y -- @@ -5,0 +6,1 @@ -- +z -- >>> putStr $ renderPatch [(GenericSourcePos "a" 1 1, [D.Both "x" "x", D.Second "y"]), (GenericSourcePos "b" 5 1, [D.Second "z"])] -- --- a -- +++ a -- @@ -1,1 +1,2 @@ -- x -- +y -- --- b -- +++ b -- @@ -5,0 +5,1 @@ -- +z -- | Render list of changed lines as a unified diff renderPatch :: [Chunk] -> Text renderPatch = go Nothing . sortOn fst where go _ [] = "" go Nothing cs@((SourcePos fp _ _, _):_) = fileHeader fp <> go (Just (fp, 0)) cs go (Just (fp, _)) cs@((SourcePos fp' _ _, _):_) | fp /= fp' = go Nothing cs go (Just (fp, offs)) ((SourcePos _ lineno _, diffs):cs) = chunkHeader <> chnk <> go (Just (fp, offs + adds - dels)) cs where chunkHeader = T.pack $ printf "@@ -%d,%d +%d,%d @@\n" (unPos lineno) dels (unPos lineno+offs) adds (dels, adds) = foldl' countDiff (0, 0) diffs chnk = foldMap renderLine diffs fileHeader fp = "--- " <> T.pack fp <> "\n+++ " <> T.pack fp <> "\n" countDiff (dels, adds) = \case Del _ -> (dels + 1, adds) Add _ -> (dels , adds + 1) Ctx _ -> (dels + 1, adds + 1) renderLine = \case Del s -> "-" <> s <> "\n" Add s -> "+" <> s <> "\n" Ctx s -> " " <> s <> "\n" diffTxn :: Journal -> Transaction -> Transaction -> Chunk diffTxn j t t' = case tsourcepos t of (pos1@(SourcePos fp line col), pos2) | pos1 == pos2 -> (SourcePos fp (line <> mkPos 1) col, diffs) where -- TODO: use range and produce two chunks: one removes part of -- original file, other adds transaction to new file with -- suffix .ledger (generated). I.e. move transaction from one file to another. diffs :: [DiffLine Text] diffs = concatMap (traverse showPostingLines . mapDiff) $ D.getDiff (tpostings t) (tpostings t') (pos1@(SourcePos fp line _), SourcePos _ line' _) -> (pos1, diffs) where -- We do diff for original lines vs generated ones. Often leads -- to big diff because of re-format effect. diffs :: [DiffLine Text] diffs = map mapDiff $ D.getDiff source changed' source | Just contents <- lookup fp $ jfiles j = drop (unPos line-1) . take (unPos line' - 1) $ T.lines contents | otherwise = [] changed = T.lines $ showTransaction t' changed' | null changed = changed | T.null $ last changed = init changed | otherwise = changed data DiffLine a = Del a | Add a | Ctx a deriving (Show, Functor, Foldable, Traversable) mapDiff :: D.Diff a -> DiffLine a mapDiff = \case D.First x -> Del x D.Second x -> Add x D.Both x _ -> Ctx x hledger-1.32.3/Hledger/Cli/Commands/Roi.hs0000644000000000000000000004027314555433271016326 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ParallelListComp #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ViewPatterns #-} {-| The @roi@ command prints internal rate of return and time-weighted rate of return for and investment. -} module Hledger.Cli.Commands.Roi ( roimode , roi ) where import Control.Monad import System.Exit import Data.Time.Calendar import Text.Printf import Data.Bifunctor (second) import Data.Either (fromLeft, fromRight, isLeft) import Data.Function (on) import Data.List import Numeric.RootFinding import Data.Decimal import qualified Data.Text as T import qualified Data.Text.Lazy.IO as TL import System.Console.CmdArgs.Explicit as CmdArgs import Text.Tabular.AsciiWide as Tab import Hledger import Hledger.Cli.CliOptions roimode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Roi.txt") [flagNone ["cashflow"] (setboolopt "cashflow") "show all amounts that were used to compute returns" ,flagReq ["investment"] (\s opts -> Right $ setopt "investment" s opts) "QUERY" "query to select your investment transactions" ,flagReq ["profit-loss","pnl"] (\s opts -> Right $ setopt "pnl" s opts) "QUERY" "query to select profit-and-loss or appreciation/valuation transactions" ] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- One reporting span, data OneSpan = OneSpan Day -- start date, inclusive Day -- end date, exclusive MixedAmount -- value of investment at the beginning of day on spanBegin_ MixedAmount -- value of investment at the end of day on spanEnd_ [(Day,MixedAmount)] -- all deposits and withdrawals (but not changes of value) in the DateSpan [spanBegin_,spanEnd_) [(Day,MixedAmount)] -- all PnL changes of the value of investment in the DateSpan [spanBegin_,spanEnd_) deriving (Show) roi :: CliOpts -> Journal -> IO () roi CliOpts{rawopts_=rawopts, reportspec_=rspec@ReportSpec{_rsReportOpts=ReportOpts{..}}} j = do -- We may be converting posting amounts to value, per hledger_options.m4.md "Effect of --value on reports". let -- lbl = lbl_ "roi" today = _rsDay rspec priceOracle = journalPriceOracle infer_prices_ j styles = journalCommodityStylesWith HardRounding j mixedAmountValue periodlast date = -- These calculations can generate very precise decimals. To avoid showing too many digits: -- If we have no style for the valuation commodity, generate one that will limit the precision ? -- But it's not easy to find out the valuation commodity (or commodities) here if it's implicit, -- as that information is buried in the price graph. -- Instead, do what we don't like to do: hard code a max precision, overriding commodity styles. mixedAmountSetPrecisionMax defaultMaxPrecision . maybe id (mixedAmountApplyValuation priceOracle styles periodlast today date) value_ . maybe id (mixedAmountToCost styles) conversionop_ let ropts = _rsReportOpts rspec wd = whichDate ropts showCashFlow = boolopt "cashflow" rawopts prettyTables = pretty_ makeQuery flag = do q <- either usageError (return . fst) . parseQuery today . T.pack $ stringopt flag rawopts return . simplifyQuery $ And [queryFromFlags ropts{period_=PeriodAll}, q] investmentsQuery <- makeQuery "investment" pnlQuery <- makeQuery "pnl" let filteredj = filterJournalTransactions investmentsQuery j trans = dbg3 "investments" $ jtxns filteredj when (null trans) $ do putStrLn "No relevant transactions found. Check your investments query" exitFailure let (fullPeriod, spans) = reportSpan filteredj rspec let priceDirectiveDates = dbg3 "priceDirectiveDates" $ map pddate $ jpricedirectives j let processSpan (DateSpan Nothing _) = error "Undefined start of the period - will be unable to compute the rates of return" processSpan (DateSpan _ Nothing) = error "Undefined end of the period - will be unable to compute the rates of return" processSpan spn@(DateSpan (Just begin) (Just end)) = do -- Spans are [begin,end), and end is 1 day after the actual end date we are interested in let b = fromEFDay begin e = fromEFDay end cashFlowApplyCostValue = map (\(d,amt) -> (d,mixedAmountValue e d amt)) valueBefore = mixedAmountValue e b $ total trans (And [ investmentsQuery , Date (DateSpan Nothing (Just begin))]) valueAfter = mixedAmountValue e e $ total trans (And [investmentsQuery , Date (DateSpan Nothing (Just end))]) priceDates = dbg3 "priceDates" $ nub $ filter (spanContainsDate spn) priceDirectiveDates cashFlow = ((map (,nullmixedamt) priceDates)++) $ cashFlowApplyCostValue $ calculateCashFlow wd trans (And [ Not investmentsQuery , Not pnlQuery , Date spn ] ) pnl = cashFlowApplyCostValue $ calculateCashFlow wd trans (And [ Not investmentsQuery , pnlQuery , Date spn ] ) thisSpan = dbg3 "processing span" $ OneSpan b e valueBefore valueAfter cashFlow pnl irr <- internalRateOfReturn styles showCashFlow prettyTables thisSpan (periodTwr, annualizedTwr) <- timeWeightedReturn styles showCashFlow prettyTables investmentsQuery trans mixedAmountValue thisSpan let cashFlowAmt = maNegate . maSum $ map snd cashFlow let smallIsZero x = if abs x < 0.01 then 0.0 else x return [ showDate b , showDate (addDays (-1) e) , T.pack $ showMixedAmount $ styleAmounts styles $ valueBefore , T.pack $ showMixedAmount $ styleAmounts styles $ cashFlowAmt -- , T.pack $ showMixedAmount $ -- -- dbg0With (lbl "cashflow after styling".showMixedAmountOneLine) $ -- mapMixedAmount (amountSetFullPrecisionOr (Just defaultMaxPrecision)) $ -- styleAmounts (styles -- -- & dbg0With (lbl "styles".show)) -- cashFlowAmt -- -- & dbg0With (lbl "cashflow before styling".showMixedAmountOneLine) , T.pack $ showMixedAmount $ styleAmounts styles $ valueAfter , T.pack $ showMixedAmount $ styleAmounts styles $ (valueAfter `maMinus` (valueBefore `maPlus` cashFlowAmt)) , T.pack $ printf "%0.2f%%" $ smallIsZero irr , T.pack $ printf "%0.2f%%" $ smallIsZero periodTwr , T.pack $ printf "%0.2f%%" $ smallIsZero annualizedTwr ] periodRows <- forM spans processSpan totalRow <- processSpan fullPeriod let rowTitles = Tab.Group Tab.NoLine (map (Header . T.pack . show) (take (length periodRows) [1..])) let isSingleSpan = length spans == 1 let table = Table (if isSingleSpan then rowTitles else Tab.Group Tab.SingleLine [ rowTitles, Tab.Group Tab.NoLine [ Header "Total" ]] ) (Tab.Group Tab.DoubleLine [ Tab.Group Tab.SingleLine [Header "Begin", Header "End"] , Tab.Group Tab.SingleLine [Header "Value (begin)", Header "Cashflow", Header "Value (end)", Header "PnL"] , Tab.Group Tab.SingleLine [Header "IRR"] , Tab.Group Tab.SingleLine [Header "TWR/period", Header "TWR/year"]]) (if isSingleSpan then periodRows else periodRows ++ [totalRow]) TL.putStrLn $ Tab.render prettyTables id id id table timeWeightedReturn styles showCashFlow prettyTables investmentsQuery trans mixedAmountValue (OneSpan begin end valueBeforeAmt valueAfter cashFlow pnl) = do let valueBefore = unMix valueBeforeAmt let initialUnitPrice = 100 :: Decimal let initialUnits = valueBefore / initialUnitPrice let changes = -- If cash flow and PnL changes happen on the same day, this -- will sort PnL changes to come before cash flows (on any -- given day), so that we will have better unit price computed -- first for processing cash flow. This is why pnl changes are Left -- and cashflows are Right. -- However, if the very first date in the changes list has both -- PnL and CashFlow, we would not be able to apply pnl change to 0 unit, -- which would lead to an error. We make sure that we have at least one -- cashflow entry at the front, and we know that there would be at most -- one for the given date, by construction. Empty CashFlows added -- because of a begin date before the first transaction are not seen as -- a valid cashflow entry at the front. zeroUnitsNeedsCashflowAtTheFront $ sort $ datedCashflows ++ datedPnls where zeroUnitsNeedsCashflowAtTheFront changes1 = if initialUnits > 0 then changes1 else let (leadingEmptyCashFlows, rest) = span isEmptyCashflow changes1 (leadingPnls, rest') = span (isLeft . snd) rest (firstCashflow, rest'') = splitAt 1 rest' in leadingEmptyCashFlows ++ firstCashflow ++ leadingPnls ++ rest'' isEmptyCashflow (_date, amt) = case amt of Right amt' -> mixedAmountIsZero amt' Left _ -> False datedPnls = map (second Left) $ aggregateByDate pnl datedCashflows = map (second Right) $ aggregateByDate cashFlow aggregateByDate datedAmounts = -- Aggregate all entries for a single day, assuming that intraday interest is negligible sort $ map (\date_cash -> let (dates, cash) = unzip date_cash in (head dates, maSum cash)) $ groupBy ((==) `on` fst) $ sortOn fst $ map (second maNegate) $ datedAmounts let units = tail $ scanl (\(_, _, unitPrice, unitBalance) (date, amt) -> let valueOnDate = unMix $ mixedAmountValue end date $ total trans (And [investmentsQuery, Date (DateSpan Nothing (Just $ Exact date))]) in case amt of Right amt' -> -- we are buying or selling let unitsBoughtOrSold = unMix amt' / unitPrice in (valueOnDate, unitsBoughtOrSold, unitPrice, unitBalance + unitsBoughtOrSold) Left pnl' -> -- PnL change let valueAfterDate = valueOnDate + unMix pnl' unitPrice' = valueAfterDate/unitBalance in (valueOnDate, 0, unitPrice', unitBalance)) (0, 0, initialUnitPrice, initialUnits) $ dbg3 "changes" changes let finalUnitBalance = if null units then initialUnits else let (_,_,_,u) = last units in u finalUnitPrice = if finalUnitBalance == 0 then if null units then initialUnitPrice else let (_,_,lastUnitPrice,_) = last units in lastUnitPrice else (unMix valueAfter) / finalUnitBalance -- Technically, totalTWR should be (100*(finalUnitPrice - initialUnitPrice) / initialUnitPrice), but initalUnitPrice is 100, so 100/100 == 1 totalTWR = roundTo 2 $ (finalUnitPrice - initialUnitPrice) (startYear, _, _) = toGregorian begin years = fromIntegral (diffDays end begin) / (if isLeapYear startYear then 366 else 365) :: Double annualizedTWR = 100*((1+(realToFrac totalTWR/100))**(1/years)-1) :: Double when showCashFlow $ do printf "\nTWR cash flow for %s - %s\n" (showDate begin) (showDate (addDays (-1) end)) let (dates', amts) = unzip changes cashflows' = map (fromRight nullmixedamt) amts pnls = map (fromLeft nullmixedamt) amts (valuesOnDate,unitsBoughtOrSold', unitPrices', unitBalances') = unzip4 units add x lst = if valueBefore/=0 then x:lst else lst dates = add begin dates' cashflows = add valueBeforeAmt cashflows' unitsBoughtOrSold = add initialUnits unitsBoughtOrSold' unitPrices = add initialUnitPrice unitPrices' unitBalances = add initialUnits unitBalances' TL.putStr $ Tab.render prettyTables id id T.pack (Table (Tab.Group NoLine (map (Header . showDate) dates)) (Tab.Group DoubleLine [ Tab.Group Tab.SingleLine [Tab.Header "Portfolio value", Tab.Header "Unit balance"] , Tab.Group Tab.SingleLine [Tab.Header "Pnl", Tab.Header "Cashflow", Tab.Header "Unit price", Tab.Header "Units"] , Tab.Group Tab.SingleLine [Tab.Header "New Unit Balance"]]) [ [val, oldBalance, pnl', cashflow, prc, udelta, balance] | val <- map showDecimal valuesOnDate | oldBalance <- map showDecimal (0:unitBalances) | balance <- map showDecimal unitBalances | pnl' <- map (showMixedAmount . styleAmounts styles) pnls | cashflow <- map (showMixedAmount . styleAmounts styles) cashflows | prc <- map showDecimal unitPrices | udelta <- map showDecimal unitsBoughtOrSold ]) printf "Final unit price: %s/%s units = %s\nTotal TWR: %s%%.\nPeriod: %.2f years.\nAnnualized TWR: %.2f%%\n\n" (showMixedAmount $ styleAmounts styles valueAfter) (showDecimal finalUnitBalance) (showDecimal finalUnitPrice) (showDecimal totalTWR) years annualizedTWR return ((realToFrac totalTWR) :: Double, annualizedTWR) internalRateOfReturn styles showCashFlow prettyTables (OneSpan begin end valueBefore valueAfter cashFlow _pnl) = do let prefix = (begin, maNegate valueBefore) postfix = (end, valueAfter) totalCF = filter (maIsNonZero . snd) $ prefix : (sortOn fst cashFlow) ++ [postfix] when showCashFlow $ do printf "\nIRR cash flow for %s - %s\n" (showDate begin) (showDate (addDays (-1) end)) let (dates, amts) = unzip totalCF TL.putStrLn $ Tab.render prettyTables id id id (Table (Tab.Group Tab.NoLine (map (Header . showDate) dates)) (Tab.Group Tab.SingleLine [Header "Amount"]) (map ((:[]) . T.pack . showMixedAmount . styleAmounts styles) amts)) -- 0% is always a solution, so require at least something here case totalCF of [] -> return 0 _ -> case ridders (RiddersParam 100 (AbsTol 0.00001)) (0.000000000001,10000) (interestSum end totalCF) of Root rate -> return ((rate-1)*100) NotBracketed -> error' $ "Error (NotBracketed): No solution for Internal Rate of Return (IRR).\n" ++ " Possible causes: IRR is huge (>1000000%), balance of investment becomes negative at some point in time." SearchFailed -> error' $ "Error (SearchFailed): Failed to find solution for Internal Rate of Return (IRR).\n" ++ " Either search does not converge to a solution, or converges too slowly." type CashFlow = [(Day, MixedAmount)] interestSum :: Day -> CashFlow -> Double -> Double interestSum referenceDay cf rate = sum $ map go cf where go (t,m) = realToFrac (unMix m) * rate ** (fromIntegral (referenceDay `diffDays` t) / 365) calculateCashFlow :: WhichDate -> [Transaction] -> Query -> CashFlow calculateCashFlow wd trans query = [ (postingDateOrDate2 wd p, pamount p) | p <- filter (matchesPosting query) (concatMap realPostings trans), maIsNonZero (pamount p) ] total :: [Transaction] -> Query -> MixedAmount total trans query = sumPostings . filter (matchesPosting query) $ concatMap realPostings trans unMix :: MixedAmount -> Quantity unMix a = case (unifyMixedAmount $ mixedAmountCost a) of Just a' -> aquantity a' Nothing -> error' $ "Amounts could not be converted to a single cost basis: " ++ show (map showAmount $ amounts a) ++ "\nConsider using --value to force all costs to be in a single commodity." ++ "\nFor example, \"--cost --value=end, --infer-market-prices\", where commodity is the one that was used to pay for the investment." -- Show Decimal rounded to two decimal places, unless it has less places already. This ensures that "2" won't be shown as "2.00" showDecimal :: Decimal -> String showDecimal d = if d == rounded then show d else show rounded where rounded = roundTo 2 d hledger-1.32.3/Hledger/Cli/Commands/Stats.hs0000644000000000000000000001205314555053231016660 0ustar0000000000000000{-| Print some statistics for the journal. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE NamedFieldPuns #-} module Hledger.Cli.Commands.Stats ( statsmode ,stats ) where import Data.Default (def) import Data.List (nub, sortOn) import Data.List.Extra (nubSort) import Data.Maybe (fromMaybe) import Data.HashSet (size, fromList) import qualified Data.Text as T import qualified Data.Text.Lazy.Builder as TB import Data.Time.Calendar (Day, addDays, diffDays) import System.Console.CmdArgs.Explicit hiding (Group) import Text.Printf (printf) import qualified Data.Map as Map import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Utils (writeOutputLazyText) import Text.Tabular.AsciiWide import Data.Time.Clock.POSIX (getPOSIXTime) statsmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Stats.txt") [flagReq ["output-file","o"] (\s opts -> Right $ setopt "output-file" s opts) "FILE" "write output to FILE." ] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- like Register.summarisePostings -- | Print various statistics for the journal. stats :: CliOpts -> Journal -> IO () stats opts@CliOpts{reportspec_=rspec, progstarttime_} j = do let today = _rsDay rspec q = _rsQuery rspec l = ledgerFromJournal q j intervalspans = snd $ reportSpanBothDates j rspec showstats = showLedgerStats l today (ls, txncounts) = unzip $ map showstats intervalspans numtxns = sum txncounts b = unlinesB ls writeOutputLazyText opts $ TB.toLazyText b t <- getPOSIXTime let dt = t - progstarttime_ printf "Run time (throughput) : %.2fs (%.0f txns/s)\n" (realToFrac dt :: Float) (fromIntegral numtxns / realToFrac dt :: Float) showLedgerStats :: Ledger -> Day -> DateSpan -> (TB.Builder, Int) showLedgerStats l today spn = (unlinesB $ map (renderRowB def{tableBorders=False, borderSpaces=False} . showRow) stts ,tnum) where showRow (label, val) = Group NoLine $ map (Header . textCell TopLeft) [fitText (Just w1) (Just w1) False True label `T.append` ": ", T.pack val] w1 = maximum $ map (T.length . fst) stts (stts, tnum) = ([ ("Main file", path) -- ++ " (from " ++ source ++ ")") ,("Included files", unlines $ drop 1 $ journalFilePaths j) ,("Transactions span", printf "%s to %s (%d days)" (showstart spn) (showend spn) days) ,("Last transaction", maybe "none" show lastdate ++ showelapsed lastelapsed) ,("Transactions", printf "%d (%0.1f per day)" tnum txnrate) ,("Transactions last 30 days", printf "%d (%0.1f per day)" tnum30 txnrate30) ,("Transactions last 7 days", printf "%d (%0.1f per day)" tnum7 txnrate7) ,("Payees/descriptions", show $ size $ fromList $ map (tdescription) ts) ,("Accounts", printf "%d (depth %d)" acctnum acctdepth) ,("Commodities", printf "%s (%s)" (show $ length cs) (T.intercalate ", " cs)) ,("Market prices", printf "%s (%s)" (show $ length mktprices) (T.intercalate ", " mktpricecommodities)) -- Transactions this month : %(monthtxns)s (last month in the same period: %(lastmonthtxns)s) -- Unmarked transactions : %(unmarked)s -- Days since reconciliation : %(reconcileelapsed)s -- Days since last transaction : %(recentelapsed)s ] ,tnum1) where j = ljournal l path = journalFilePath j ts = sortOn tdate $ filter (spanContainsDate spn . tdate) $ jtxns j as = nub $ map paccount $ concatMap tpostings ts cs = either error' Map.keys $ commodityStylesFromAmounts $ concatMap (amountsRaw . pamount) $ concatMap tpostings ts -- PARTIAL: lastdate | null ts = Nothing | otherwise = Just $ tdate $ last ts lastelapsed = fmap (diffDays today) lastdate showelapsed Nothing = "" showelapsed (Just dys) = printf " (%d %s)" dys' direction where dys' = abs dys direction | dys >= 0 = "days ago" :: String | otherwise = "days from now" tnum1 = length ts -- Integer would be better showstart (DateSpan (Just efd) _) = show $ fromEFDay efd showstart _ = "" showend (DateSpan _ (Just efd)) = show $ fromEFDay efd showend _ = "" days = fromMaybe 0 $ daysInSpan spn txnrate | days==0 = 0 | otherwise = fromIntegral tnum1 / fromIntegral days :: Double tnum30 = length $ filter withinlast30 ts withinlast30 t = d >= addDays (-30) today && (d<=today) where d = tdate t txnrate30 = fromIntegral tnum30 / 30 :: Double tnum7 = length $ filter withinlast7 ts withinlast7 t = d >= addDays (-7) today && (d<=today) where d = tdate t txnrate7 = fromIntegral tnum7 / 7 :: Double acctnum = length as acctdepth | null as = 0 | otherwise = maximum $ map accountNameLevel as mktprices = jpricedirectives j mktpricecommodities = nubSort $ map pdcommodity mktprices hledger-1.32.3/Hledger/Cli/Commands/Tags.hs0000644000000000000000000000436514555053231016467 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Tags ( tagsmode ,tags ) where import qualified Control.Monad.Fail as Fail import Data.List.Extra (nubSort) import qualified Data.Text as T import qualified Data.Text.IO as T import Safe import System.Console.CmdArgs.Explicit as C import Hledger import Hledger.Cli.CliOptions tagsmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Tags.txt") [flagNone ["values"] (setboolopt "values") "list tag values instead of tag names" ,flagNone ["parsed"] (setboolopt "parsed") "show tags/values in the order they were parsed, including duplicates" ] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[TAGREGEX [QUERY...]]") tags :: CliOpts -> Journal -> IO () tags CliOpts{rawopts_=rawopts,reportspec_=rspec} j = do let today = _rsDay rspec args = listofstringopt "args" rawopts -- first argument is a tag name pattern, others are a hledger query: hledger tags [TAGREGEX [QUERYARGS..]] mtagpat <- mapM (either Fail.fail pure . toRegexCI . T.pack) $ headMay args let querystr = map T.pack $ drop 1 args values = boolopt "values" rawopts parsed = boolopt "parsed" rawopts empty = empty_ $ _rsReportOpts rspec query <- either usageError (return . fst) $ parseQueryList today querystr let q = simplifyQuery $ And [queryFromFlags $ _rsReportOpts rspec, query] matchedtxns = filter (q `matchesTransaction`) $ jtxns $ journalApplyValuationFromOpts rspec j -- also list tags from matched account declarations, but not if there is -- a query for something transaction-related, like date: or amt:. matchedaccts = dbg4 "accts" $ if dbg4 "queryIsTransactionRelated" $ queryIsTransactionRelated $ dbg4 "q" q then [] else filter (matchesAccountExtra (journalAccountType j) (journalInheritedAccountTags j) q) $ map fst $ jdeclaredaccounts j tagsorvalues = (if parsed then id else nubSort) [ r | (t,v) <- concatMap (journalAccountTags j) matchedaccts ++ concatMap transactionAllTags matchedtxns , maybe True (`regexMatchText` t) mtagpat , let r = if values then v else t , not (values && T.null v && not empty) ] mapM_ T.putStrLn tagsorvalues hledger-1.32.3/Hledger/Cli/CompoundBalanceCommand.hs0000644000000000000000000003616214555053231020361 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-| Common helpers for making multi-section balance report commands like balancesheet, cashflow, and incomestatement. -} module Hledger.Cli.CompoundBalanceCommand ( CompoundBalanceCommandSpec(..) ,compoundBalanceCommandMode ,compoundBalanceCommand ) where import Data.List (foldl') import Data.Maybe (fromMaybe, mapMaybe) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Builder as TB import Data.Time.Calendar (Day, addDays) import System.Console.CmdArgs.Explicit as C import Hledger.Read.CsvUtils (CSV, printCSV, printTSV) import Lucid as L hiding (value_) import Text.Tabular.AsciiWide as Tab hiding (render) import Hledger import Hledger.Cli.Commands.Balance import Hledger.Cli.CliOptions import Hledger.Cli.Utils (unsupportedOutputFormatError, writeOutputLazyText) -- | Description of a compound balance report command, -- from which we generate the command's cmdargs mode and IO action. -- A compound balance report command shows one or more sections/subreports, -- each with its own title and subtotals row, in a certain order, -- plus a grand totals row if there's more than one section. -- Examples are the balancesheet, cashflow and incomestatement commands. -- -- Compound balance reports do sign normalisation: they show all account balances -- as normally positive, unlike the ordinary BalanceReport and most hledger commands -- which show income/liability/equity balances as normally negative. -- Each subreport specifies the normal sign of its amounts, and whether -- it should be added to or subtracted from the grand total. -- data CompoundBalanceCommandSpec = CompoundBalanceCommandSpec { cbcdoc :: CommandDoc, -- ^ the command's name(s) and documentation cbctitle :: String, -- ^ overall report title cbcqueries :: [CBCSubreportSpec DisplayName], -- ^ subreport details cbcaccum :: BalanceAccumulation -- ^ how to accumulate balances (per-period, cumulative, historical) -- (overrides command line flags) } -- | Generate a cmdargs option-parsing mode from a compound balance command -- specification. compoundBalanceCommandMode :: CompoundBalanceCommandSpec -> Mode RawOpts compoundBalanceCommandMode CompoundBalanceCommandSpec{..} = hledgerCommandMode cbcdoc ([flagNone ["sum"] (setboolopt "sum") "show sum of posting amounts (default)" ,flagNone ["valuechange"] (setboolopt "valuechange") "show total change of period-end historical balance value (caused by deposits, withdrawals, market price fluctuations)" ,flagNone ["gain"] (setboolopt "gain") "show unrealised capital gain/loss (historical balance value minus cost basis)" ,flagNone ["budget"] (setboolopt "budget") "show sum of posting amounts compared to budget goals defined by periodic transactions\n " ,flagNone ["change"] (setboolopt "change") ("accumulate amounts from column start to column end (in multicolumn reports)" ++ defaultMarker PerPeriod) ,flagNone ["cumulative"] (setboolopt "cumulative") ("accumulate amounts from report start (specified by e.g. -b/--begin) to column end" ++ defaultMarker Cumulative) ,flagNone ["historical","H"] (setboolopt "historical") ("accumulate amounts from journal start to column end (includes postings before report start date)" ++ defaultMarker Historical ++ "\n ") ] ++ flattreeflags True ++ [flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "flat mode: omit N leading account name parts" ,flagNone ["declared"] (setboolopt "declared") "include non-parent declared accounts (best used with -E)" ,flagNone ["average","A"] (setboolopt "average") "show a row average column (in multicolumn reports)" ,flagNone ["row-total","T"] (setboolopt "row-total") "show a row total column (in multicolumn reports)" ,flagNone ["summary-only"] (setboolopt "summary-only") "display only row summaries (e.g. row total, average) (in multicolumn reports)" ,flagNone ["no-total","N"] (setboolopt "no-total") "omit the final total row" ,flagNone ["no-elide"] (setboolopt "no-elide") "don't squash boring parent accounts (in tree mode)" ,flagReq ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format (in simple reports)" ,flagNone ["sort-amount","S"] (setboolopt "sort-amount") "sort by amount instead of account code/name" ,flagNone ["percent", "%"] (setboolopt "percent") "express values in percentage of each column's total" ,flagReq ["layout"] (\s opts -> Right $ setopt "layout" s opts) "ARG" (unlines ["how to show multi-commodity amounts:" ,"'wide[,WIDTH]': all commodities on one line" ,"'tall' : each commodity on a new line" ,"'bare' : bare numbers, symbols in a column" ]) ,outputFormatFlag ["txt","html","csv","tsv","json"] ,outputFileFlag ]) [generalflagsgroup1] (hiddenflags ++ [ flagNone ["commodity-column"] (setboolopt "commodity-column") "show commodity symbols in a separate column, amounts as bare numbers, one row per commodity" ]) ([], Just $ argsFlag "[QUERY]") where defaultMarker :: BalanceAccumulation -> String defaultMarker bacc | bacc == cbcaccum = " (default)" | otherwise = "" -- | Generate a runnable command from a compound balance command specification. compoundBalanceCommand :: CompoundBalanceCommandSpec -> (CliOpts -> Journal -> IO ()) compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportspec_=rspec, rawopts_=rawopts} j = do writeOutputLazyText opts $ render $ styleAmounts styles cbr where styles = journalCommodityStylesWith HardRounding j ropts@ReportOpts{..} = _rsReportOpts rspec -- use the default balance type for this report, unless the user overrides mbalanceAccumulationOverride = balanceAccumulationOverride rawopts balanceaccumulation = fromMaybe cbcaccum mbalanceAccumulationOverride -- Set balance type in the report options. ropts' = ropts{balanceaccum_=balanceaccumulation} title = T.pack cbctitle <> " " <> titledatestr <> maybe "" (" "<>) mtitleclarification <> valuationdesc where -- XXX #1078 the title of ending balance reports -- (Historical) should mention the end date(s) shown as -- column heading(s) (not the date span of the transactions). -- Also the dates should not be simplified (it should show -- "2008/01/01-2008/12/31", not "2008"). titledatestr = case balanceaccumulation of Historical -> showEndDates enddates _ -> showDateSpan requestedspan where enddates = map (addDays (-1)) . mapMaybe spanEnd $ cbrDates cbr -- these spans will always have a definite end date requestedspan = fst $ reportSpan j rspec -- when user overrides, add an indication to the report title -- Do we need to deal with overridden BalanceCalculation? mtitleclarification = case (balancecalc_, balanceaccumulation, mbalanceAccumulationOverride) of (CalcValueChange, PerPeriod, _ ) -> Just "(Period-End Value Changes)" (CalcValueChange, Cumulative, _ ) -> Just "(Cumulative Period-End Value Changes)" (CalcGain, PerPeriod, _ ) -> Just "(Incremental Gain)" (CalcGain, Cumulative, _ ) -> Just "(Cumulative Gain)" (CalcGain, Historical, _ ) -> Just "(Historical Gain)" (_, _, Just PerPeriod ) -> Just "(Balance Changes)" (_, _, Just Cumulative) -> Just "(Cumulative Ending Balances)" (_, _, Just Historical) -> Just "(Historical Ending Balances)" _ -> Nothing valuationdesc = (case conversionop_ of Just ToCost -> ", converted to cost" _ -> "") <> (case value_ of Just (AtThen _mc) -> ", valued at posting date" Just (AtEnd _mc) | changingValuation -> "" Just (AtEnd _mc) -> ", valued at period ends" Just (AtNow _mc) -> ", current value" Just (AtDate today _mc) -> ", valued at " <> showDate today Nothing -> "") changingValuation = case (balancecalc_, balanceaccum_) of (CalcValueChange, PerPeriod) -> True (CalcValueChange, Cumulative) -> True _ -> False -- make a CompoundBalanceReport. cbr' = compoundBalanceReport rspec{_rsReportOpts=ropts'} j cbcqueries cbr = cbr'{cbrTitle=title} -- render appropriately render = case outputFormatFromOpts opts of "txt" -> compoundBalanceReportAsText ropts' "csv" -> printCSV . compoundBalanceReportAsCsv ropts' "tsv" -> printTSV . compoundBalanceReportAsCsv ropts' "html" -> L.renderText . compoundBalanceReportAsHtml ropts' "json" -> toJsonText x -> error' $ unsupportedOutputFormatError x -- | Summarise one or more (inclusive) end dates, in a way that's -- visually different from showDateSpan, suggesting discrete end dates -- rather than a continuous span. showEndDates :: [Day] -> T.Text showEndDates es = case es of -- cf showPeriod (e:_:_) -> showDate e <> ".." <> showDate (last es) [e] -> showDate e [] -> "" -- | Render a compound balance report as plain text suitable for console output. {- Eg: Balance Sheet || 2017/12/31 Total Average =============++=============================== Assets || -------------++------------------------------- assets:b || 1 1 1 -------------++------------------------------- || 1 1 1 =============++=============================== Liabilities || -------------++------------------------------- -------------++------------------------------- || =============++=============================== Total || 1 1 1 -} compoundBalanceReportAsText :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> TL.Text compoundBalanceReportAsText ropts (CompoundPeriodicReport title _colspans subreports netrow) = TB.toLazyText $ TB.fromText title <> TB.fromText "\n\n" <> balanceReportTableAsText ropts bigtable' where bigtable = case map (subreportAsTable ropts) subreports of [] -> Tab.empty r:rs -> foldl' (concatTables DoubleLine) r rs bigtable' | no_total_ ropts || length subreports == 1 = bigtable | otherwise = let totalrows = multiBalanceRowAsTableText ropts netrow rh = Tab.Group NoLine $ map Header ("Net:" : replicate (length totalrows - 1) "") ch = Header [] -- ignored in ((concatTables Tab.DoubleLine) bigtable $ Table rh ch totalrows) -- | Convert a named multi balance report to a table suitable for -- concatenating with others to make a compound balance report table. subreportAsTable ropts1 (title1, r, _) = t where -- convert to table Table lefthdrs tophdrs cells = balanceReportAsTable ropts1 r -- tweak the layout t = Table (Tab.Group Tab.SingleLine [Tab.Header title1, lefthdrs]) tophdrs ([]:cells) -- | Render a compound balance report as CSV. -- Subreports' CSV is concatenated, with the headings rows replaced by a -- subreport title row, and an overall title row, one headings row, and an -- optional overall totals row is added. compoundBalanceReportAsCsv :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> CSV compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subreports netrow) = addtotals $ padRow title : ( "Account" : ["Commodity" | layout_ ropts == LayoutBare] ++ map (reportPeriodName (balanceaccum_ ropts) colspans) colspans ++ (if row_total_ ropts then ["Total"] else []) ++ (if average_ ropts then ["Average"] else []) ) : concatMap (subreportAsCsv ropts) subreports where -- | Add a subreport title row and drop the heading row. subreportAsCsv ropts1 (subreporttitle, multibalreport, _) = padRow subreporttitle : tail (multiBalanceReportAsCsv ropts1 multibalreport) padRow s = take numcols $ s : repeat "" where numcols | null subreports = 1 | otherwise = (1 +) $ -- account name column (if layout_ ropts == LayoutBare then (1+) else id) $ (if row_total_ ropts then (1+) else id) $ (if average_ ropts then (1+) else id) $ maximum $ -- depends on non-null subreports map (length . prDates . second3) subreports addtotals | no_total_ ropts || length subreports == 1 = id | otherwise = (++ fmap ("Net:" : ) (multiBalanceRowAsCsvText ropts colspans netrow)) -- | Render a compound balance report as HTML. compoundBalanceReportAsHtml :: ReportOpts -> CompoundPeriodicReport DisplayName MixedAmount -> Html () compoundBalanceReportAsHtml ropts cbr = let CompoundPeriodicReport title colspans subreports netrow = cbr colspanattr = colspan_ $ T.pack $ show $ sum [ 1, length colspans, if row_total_ ropts then 1 else 0, if average_ ropts then 1 else 0, if layout_ ropts == LayoutBare then 1 else 0 ] leftattr = style_ "text-align:left" blankrow = tr_ $ td_ [colspanattr] $ toHtmlRaw (" "::String) titlerows = (tr_ $ th_ [colspanattr, leftattr] $ h2_ $ toHtml title) : [thRow $ "" : ["Commodity" | layout_ ropts == LayoutBare] ++ map (reportPeriodName (balanceaccum_ ropts) colspans) colspans ++ (if row_total_ ropts then ["Total"] else []) ++ (if average_ ropts then ["Average"] else []) ] thRow :: [T.Text] -> Html () thRow = tr_ . mconcat . map (th_ . toHtml) -- Make rows for a subreport: its title row, not the headings row, -- the data rows, any totals row, and a blank row for whitespace. subreportrows :: (T.Text, MultiBalanceReport, Bool) -> [Html ()] subreportrows (subreporttitle, mbr, _increasestotal) = let (_,bodyrows,mtotalsrows) = multiBalanceReportHtmlRows ropts mbr in [tr_ $ th_ [colspanattr, leftattr] $ toHtml subreporttitle] ++ bodyrows ++ mtotalsrows ++ [blankrow] totalrows | no_total_ ropts || length subreports == 1 = [] | otherwise = multiBalanceReportHtmlFootRow ropts <$> (("Net:" :) <$> multiBalanceRowAsCsvText ropts colspans netrow) in do style_ (T.unlines ["" ,"td { padding:0 0.5em; }" ,"td:nth-child(1) { white-space:nowrap; }" ,"tr:nth-child(even) td { background-color:#eee; }" ]) link_ [rel_ "stylesheet", href_ "hledger.css"] table_ $ mconcat $ titlerows ++ [blankrow] ++ concatMap subreportrows subreports ++ totalrows hledger-1.32.3/Hledger/Cli/Anon.hs0000644000000000000000000000411714555425351014724 0ustar0000000000000000{-| Instances for obfuscating sensitive data (mainly text, not numbers) in various types. Currently this is deterministic and does not provide much privacy. It has been moved to a hidden --obfuscate flag, with the old --anon flag now raising an error. See https://github.com/simonmichael/hledger/issues/2133 . -} module Hledger.Cli.Anon ( Anon(..) , anonAccount ) where import Control.Arrow (first) import Data.Hashable (hash) import Data.Word (Word32) import Numeric (showHex) import qualified Data.Text as T import Hledger.Data import Data.Map (mapKeys) class Anon a where -- | Consistent converter to structure with sensitive data anonymized anon :: a -> a instance Anon Journal where -- Apply the anonymisation transformation on a journal after finalisation anon j = j { jtxns = map anon . jtxns $ j , jparseparentaccounts = map anonAccount $ jparseparentaccounts j , jparsealiases = [] -- already applied , jdeclaredaccounts = map (first anon) $ jdeclaredaccounts j , jdeclaredaccounttags = mapKeys anon $ jdeclaredaccounttags j , jdeclaredaccounttypes = (map anon) <$> jdeclaredaccounttypes j } instance Anon Posting where anon p = p { paccount = anonAccount . paccount $ p , pcomment = T.empty , ptransaction = fmap anon . ptransaction $ p -- Note that this will be overridden , poriginal = anon <$> poriginal p } instance Anon Transaction where anon txn = txnTieKnot $ txn { tpostings = map anon . tpostings $ txn , tdescription = anon . tdescription $ txn , tcode = anon . tcode $ txn , tcomment = T.empty } -- | Anonymize account name preserving hierarchy anonAccount :: AccountName -> AccountName anonAccount = T.intercalate (T.pack ":") . map anon . T.splitOn (T.pack ":") instance Anon T.Text where anon = T.pack . flip showHex "" . (fromIntegral :: Int -> Word32) . hash hledger-1.32.3/Hledger/Cli/DocFiles.hs0000644000000000000000000001142214513751565015521 0ustar0000000000000000{-# LANGUAGE TemplateHaskell, OverloadedStrings, PackageImports #-} {-| Embedded documentation files in various formats, and helpers for viewing them. |-} module Hledger.Cli.DocFiles ( Topic -- ,toolDocs -- ,toolDocNames -- ,toolDocMan -- ,toolDocTxt -- ,toolDocInfo ,printHelpForTopic ,runManForTopic ,runInfoForTopic ,runPagerForTopic ) where import Data.ByteString (ByteString) import qualified Data.ByteString.Char8 as BC import Data.Maybe (fromMaybe, isNothing) import Data.String import System.IO import System.IO.Temp import System.Process import Hledger.Utils (first3, second3, third3, embedFileRelative) import Text.Printf (printf) import System.Environment (lookupEnv) import Hledger.Utils.Debug -- The name of any hledger executable. type Tool = String -- Any heading in the hledger user manual (and perhaps later the hledger-ui/hledger-web manuals). type Topic = String -- | The main hledger manuals as source for man, info and as plain text. -- Only files under the current package directory can be embedded, -- so some of these are symlinked from the other package directories. toolDocs :: [(Tool, (ByteString, ByteString, ByteString))] toolDocs = [ ("hledger", ($(embedFileRelative "embeddedfiles/hledger.1") ,$(embedFileRelative "embeddedfiles/hledger.txt") ,$(embedFileRelative "embeddedfiles/hledger.info") )) ,("hledger-ui", ($(embedFileRelative "embeddedfiles/hledger-ui.1") ,$(embedFileRelative "embeddedfiles/hledger-ui.txt") ,$(embedFileRelative "embeddedfiles/hledger-ui.info") )) ,("hledger-web", ($(embedFileRelative "embeddedfiles/hledger-web.1") ,$(embedFileRelative "embeddedfiles/hledger-web.txt") ,$(embedFileRelative "embeddedfiles/hledger-web.info") )) ] -- toolNames :: [Tool] -- toolNames = map fst toolDocs -- | Get the manual as plain text for this tool, or a not found message. toolDocTxt :: Tool -> ByteString toolDocTxt name = maybe (fromString $ "No text manual found for tool: "++name) second3 $ lookup name toolDocs -- | Get the manual as man source (nroff) for this tool, or a not found message. toolDocMan :: Tool -> ByteString toolDocMan name = maybe (fromString $ "No man page found for tool: "++name) first3 $ lookup name toolDocs -- | Get the manual as info source (texinfo) for this tool, or a not found message. toolDocInfo :: Tool -> ByteString toolDocInfo name = maybe (fromString $ "No info manual found for tool: "++name) third3 $ lookup name toolDocs -- | Print plain text help for this tool. -- Takes an optional topic argument for convenience but it is currently ignored. printHelpForTopic :: Tool -> Maybe Topic -> IO () printHelpForTopic tool _mtopic = BC.putStr (toolDocTxt tool) -- | Display plain text help for this tool, scrolled to the given topic -- if provided, using the given pager executable. -- Note when a topic is provided we ignore the provided pager and -- use the "less" executable in $PATH. runPagerForTopic :: Tool -> Maybe Topic -> IO () runPagerForTopic tool mtopic = do -- avoids a temp file but different from the others and not sure how to make it scroll -- pager <- fromMaybe "less" <$> lookupEnv "PAGER" -- (Just inp, _, _, ph) <- createProcess (proc pager []){ -- std_in=CreatePipe -- } -- BC.hPutStrLn inp (toolDocTxt tool) -- _ <- waitForProcess ph -- return () withSystemTempFile ("hledger-"++tool++".txt") $ \f h -> do BC.hPutStrLn h $ toolDocTxt tool hClose h let defpager = "less -is" envpager <- fromMaybe defpager <$> lookupEnv "PAGER" -- force the use of less if a topic is provided, since we know how to scroll it let pager = if isNothing mtopic then envpager else defpager callCommand $ dbg1 "pager command" $ pager ++ maybe "" (printf " +'/^( )?%s'") mtopic ++ " " ++ f -- | Display a man page for this tool, scrolled to the given topic if provided, -- using the "man" executable in $PATH. Note when a topic is provided we force -- man to use the "less" executable in $PATH, ignoring $MANPAGER and $PAGER. runManForTopic :: Tool -> Maybe Topic -> IO () runManForTopic tool mtopic = withSystemTempFile ("hledger-"++tool++".nroff") $ \f h -> do BC.hPutStrLn h $ toolDocMan tool hClose h -- the temp file path will presumably have a slash in it, so man should read it callCommand $ dbg1 "man command" $ "man " ++ f ++ maybe "" (printf " -P \"less -is +'/^( )?%s'\"") mtopic -- | Display an info manual for this topic, opened at the given topic if provided, -- using the "info" executable in $PATH. runInfoForTopic :: Tool -> Maybe Topic -> IO () runInfoForTopic tool mtopic = withSystemTempFile ("hledger-"++tool++".info") $ \f h -> do BC.hPutStrLn h $ toolDocInfo tool hClose h callCommand $ dbg1 "info command" $ "info -f " ++ f ++ maybe "" (printf " -n '%s'") mtopic hledger-1.32.3/Hledger/Cli/Script.hs0000644000000000000000000000255114555423340015271 0ustar0000000000000000{-| A convenient module to import in hledger scripts, aiming to provide the most useful imports and reduce boilerplate. |-} {-# LANGUAGE PackageImports #-} module Hledger.Cli.Script ( module M ) where import Control.Applicative as M import Control.Concurrent as M import Control.Monad as M import Data.Char as M import Data.Either as M import Data.Functor as M import Data.List as M import Data.Maybe as M import Data.Ord as M -- import Data.String.QQ (s) -- https://github.com/audreyt/string-qq/pull/3 import Data.Time as M import Text.Printf as M hiding (formatString) import "text" Data.Text as M (Text, pack, unpack) -- can't re-export much of Data.Text & Data.Text.IO, they need to be qualified import Safe as M hiding (at) -- import qualified System.Console.CmdArgs.Explicit as M import System.Directory as M import System.Environment as M import System.Exit as M import System.FilePath as M import System.IO as M import System.IO.Error as M import System.Process as M -- import Hledger.Cli as M hiding (main) import Hledger.Cli as M (argsToCliOpts) import Hledger.Cli.CliOptions as M import Hledger.Cli.Commands as M import Hledger.Cli.DocFiles as M import Hledger.Cli.Utils as M import Hledger.Cli.Version as M import Hledger.Cli.CompoundBalanceCommand as M import Hledger as M import System.Console.CmdArgs.Explicit as M -- import Hledger.Cli as M (argsToCliOpts) hledger-1.32.3/Hledger/Cli/Utils.hs0000644000000000000000000003111714555425351015131 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-| Utilities for top-level modules and ghci. See also Hledger.Read and Hledger.Utils. -} module Hledger.Cli.Utils ( unsupportedOutputFormatError, withJournalDo, writeOutput, writeOutputLazyText, journalTransform, journalReload, journalReloadIfChanged, journalFileIsNewer, openBrowserOn, writeFileWithBackup, writeFileWithBackupIfChanged, pivotByOpts, anonymiseByOpts, journalSimilarTransaction, postingsOrTransactionsReportAsText, tests_Cli_Utils, ) where import Control.Monad.Except (ExceptT) import Control.Monad.IO.Class (liftIO) import Data.List import Data.Maybe import qualified Data.Text as T import qualified Data.Text.IO as T import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Builder as TB import qualified Data.Text.Lazy.IO as TL import Data.Time (Day) import Data.Time.Clock.POSIX (POSIXTime, utcTimeToPOSIXSeconds) import Lens.Micro ((^.)) import Safe (readMay, headMay) import System.Console.CmdArgs import System.Directory (getModificationTime, getDirectoryContents, copyFile, doesFileExist) import System.Exit import System.FilePath ((), splitFileName, takeDirectory) import System.Info (os) import System.Process (readProcessWithExitCode) import Text.Printf import Text.Regex.TDFA ((=~)) import Hledger.Cli.CliOptions import Hledger.Cli.Anon import Hledger.Data import Hledger.Read import Hledger.Reports import Hledger.Utils import Control.Monad (when) import Data.Functor ((<&>)) -- | Standard error message for a bad output format specified with -O/-o. unsupportedOutputFormatError :: String -> String unsupportedOutputFormatError fmt = "Sorry, output format \""++fmt++"\" is unrecognised or not yet supported for this kind of report." -- | Parse the user's specified journal file(s) as a Journal, maybe apply some -- transformations according to options, and run a hledger command with it. -- Or, throw an error. withJournalDo :: CliOpts -> (Journal -> IO a) -> IO a withJournalDo opts cmd = do -- We kludgily read the file before parsing to grab the full text, unless -- it's stdin, or it doesn't exist and we are adding. We read it strictly -- to let the add command work. journalpaths <- journalFilePathFromOpts opts j <- runExceptT $ journalTransform opts <$> readJournalFiles (inputopts_ opts) journalpaths either error' cmd j -- PARTIAL: -- | Apply some extra post-parse transformations to the journal, if enabled by options. -- These happen after parsing and finalising the journal, but before report calculation. -- They are, in processing order: -- -- - pivoting account names (--pivot) -- -- - anonymising (--anonymise). -- journalTransform :: CliOpts -> Journal -> Journal journalTransform opts = pivotByOpts opts <&> anonymiseByOpts opts <&> maybeObfuscate opts -- | Apply the pivot transformation on a journal (replacing account names by a different field's value), if option is present. pivotByOpts :: CliOpts -> Journal -> Journal pivotByOpts opts = case maybestringopt "pivot" . rawopts_ $ opts of Just tag -> journalPivot $ T.pack tag Nothing -> id -- #2133 -- | Raise an error, announcing the rename to --obfuscate and its limitations. anonymiseByOpts :: CliOpts -> Journal -> Journal anonymiseByOpts opts = if boolopt "anon" $ rawopts_ opts then error' $ unlines [ "--anon does not give privacy, and perhaps should be avoided;" ,"please see https://github.com/simonmichael/hledger/issues/2133 ." ,"For now it has been renamed to --obfuscate (a hidden flag)." ] else id -- | Apply light obfuscation to a journal, if --obfuscate is present (formerly --anon). maybeObfuscate :: CliOpts -> Journal -> Journal maybeObfuscate opts = if anon_ . inputopts_ $ opts then anon else id -- | Write some output to stdout or to a file selected by --output-file. -- If the file exists it will be overwritten. writeOutput :: CliOpts -> String -> IO () writeOutput opts s = do f <- outputFileFromOpts opts (maybe putStr writeFile f) s -- | Write some output to stdout or to a file selected by --output-file. -- If the file exists it will be overwritten. This function operates on Lazy -- Text values. writeOutputLazyText :: CliOpts -> TL.Text -> IO () writeOutputLazyText opts s = do f <- outputFileFromOpts opts (maybe TL.putStr TL.writeFile f) s -- -- | Get a journal from the given string and options, or throw an error. -- readJournal :: CliOpts -> String -> IO Journal -- readJournal opts s = readJournal def Nothing s >>= either error' return -- | Re-read the option-specified journal file(s), but only if any of -- them has changed since last read. (If the file is standard input, -- this will either do nothing or give an error, not tested yet). -- Returns a journal or error message, and a flag indicating whether -- it was re-read or not. Like withJournalDo and journalReload, reads -- the full journal, without filtering. journalReloadIfChanged :: CliOpts -> Day -> Journal -> ExceptT String IO (Journal, Bool) journalReloadIfChanged opts _d j = do let maybeChangedFilename f = do newer <- journalFileIsNewer j f return $ if newer then Just f else Nothing changedfiles <- liftIO $ catMaybes <$> mapM maybeChangedFilename (journalFilePaths j) if not $ null changedfiles then do -- XXX not sure why we use cmdarg's verbosity here, but keep it for now verbose <- liftIO isLoud when (verbose || debugLevel >= 6) . liftIO $ printf "%s has changed, reloading\n" (head changedfiles) newj <- journalReload opts return (newj, True) else return (j, False) -- | Re-read the journal file(s) specified by options, applying any -- transformations specified by options. Or return an error string. -- Reads the full journal, without filtering. journalReload :: CliOpts -> ExceptT String IO Journal journalReload opts = do journalpaths <- liftIO $ dbg6 "reloading files" <$> journalFilePathFromOpts opts journalTransform opts <$> readJournalFiles (inputopts_ opts) journalpaths -- | Has the specified file changed since the journal was last read ? -- Typically this is one of the journal's journalFilePaths. These are -- not always real files, so the file's existence is tested first; -- for non-files the answer is always no. journalFileIsNewer :: Journal -> FilePath -> IO Bool journalFileIsNewer Journal{jlastreadtime=tread} f = do mtmod <- maybeFileModificationTime f return $ case mtmod of Just tmod -> tmod > tread Nothing -> False -- | Get the last modified time of the specified file, if it exists. maybeFileModificationTime :: FilePath -> IO (Maybe POSIXTime) maybeFileModificationTime f = do exists <- doesFileExist f if exists then do utc <- getModificationTime f return . Just $ utcTimeToPOSIXSeconds utc else return Nothing -- | Attempt to open a web browser on the given url, all platforms. openBrowserOn :: String -> IO ExitCode openBrowserOn = trybrowsers browsers where trybrowsers (b:bs) u1 = do (e,_,_) <- readProcessWithExitCode b [u1] "" case e of ExitSuccess -> return ExitSuccess ExitFailure _ -> trybrowsers bs u1 trybrowsers [] u1 = do putStrLn $ printf "Could not start a web browser (tried: %s)" $ intercalate ", " browsers putStrLn $ printf "Please open your browser and visit %s" u1 return $ ExitFailure 127 browsers | os=="darwin" = ["open"] | os=="mingw32" = ["c:/Program Files/Mozilla Firefox/firefox.exe"] | otherwise = ["sensible-browser","gnome-www-browser","firefox"] -- jeffz: write a ffi binding for it using the Win32 package as a basis -- start by adding System/Win32/Shell.hsc and follow the style of any -- other module in that directory for types, headers, error handling and -- what not. -- ::ShellExecute(NULL, "open", "www.somepage.com", NULL, NULL, SW_SHOWNORMAL); -- | Back up this file with a (incrementing) numbered suffix then -- overwrite it with this new text, or give an error, but only if the text -- is different from the current file contents, and return a flag -- indicating whether we did anything. -- -- The given text should have unix line endings (\n); the existing -- file content will be normalised to unix line endings before -- comparing the two. If the file is overwritten, the new file will -- have the current system's native line endings (\n on unix, \r\n on -- windows). This could be different from the file's previous line -- endings, if working with a DOS file on unix or vice-versa. -- writeFileWithBackupIfChanged :: FilePath -> T.Text -> IO Bool writeFileWithBackupIfChanged f t = do s <- readFilePortably f if t == s then return False else backUpFile f >> T.writeFile f t >> return True -- | Back up this file with a (incrementing) numbered suffix, then -- overwrite it with this new text, or give an error. writeFileWithBackup :: FilePath -> String -> IO () writeFileWithBackup f t = backUpFile f >> writeFile f t -- | Back up this file with a (incrementing) numbered suffix, or give an error. backUpFile :: FilePath -> IO () backUpFile fp = do fs <- safeGetDirectoryContents $ takeDirectory $ fp let (d,f) = splitFileName fp versions = mapMaybe (f `backupNumber`) fs next = maximum (0:versions) + 1 f' = printf "%s.%d" f next copyFile fp (d f') safeGetDirectoryContents :: FilePath -> IO [FilePath] safeGetDirectoryContents "" = getDirectoryContents "." safeGetDirectoryContents fp = getDirectoryContents fp -- | Does the second file represent a backup of the first, and if so which version is it ? -- XXX nasty regex types intruding, add a simpler api to Hledger.Utils.Regex backupNumber :: FilePath -> FilePath -> Maybe Int backupNumber f g = case g =~ ("^" ++ f ++ "\\.([0-9]+)$") of (_::FilePath, _::FilePath, _::FilePath, [ext::FilePath]) -> readMay ext _ -> Nothing -- Identify the closest recent match for this description in past transactions. -- If the options specify a query, only matched transactions are considered. journalSimilarTransaction :: CliOpts -> Journal -> T.Text -> Maybe Transaction journalSimilarTransaction cliopts j desc = fmap fourth4 $ headMay $ journalTransactionsSimilarTo j desc q 0 1 where q = queryFromFlags $ _rsReportOpts $ reportspec_ cliopts -- | Render a 'PostingsReport' or 'AccountTransactionsReport' as Text, -- determining the appropriate starting widths and increasing as necessary. postingsOrTransactionsReportAsText :: Bool -> CliOpts -> (Int -> Int -> (a, [WideBuilder], [WideBuilder]) -> TB.Builder) -> (a -> MixedAmount) -> (a -> MixedAmount) -> [a] -> TB.Builder postingsOrTransactionsReportAsText alignAll opts itemAsText itemamt itembal report = mconcat . snd $ mapAccumL renderItem (startWidth amt, startWidth bal) itemsWithAmounts where minWidth = 12 chunkSize = 1000 renderItem (amtWidth, balWidth) item@(_, amt1, bal1) = ((amtWidth', balWidth'), itemBuilder) where itemBuilder = itemAsText amtWidth' balWidth' item amtWidth' = if alignAll then amtWidth else maximumStrict $ amtWidth : map wbWidth amt1 balWidth' = if alignAll then balWidth else maximumStrict $ balWidth : map wbWidth bal1 startWidth f = maximum $ minWidth : map wbWidth (concatMap f startAlign) where startAlign = (if alignAll then id else take chunkSize) itemsWithAmounts itemsWithAmounts = map (\x -> (x, showAmt $ itemamt x, showAmt $ itembal x)) report showAmt = showMixedAmountLinesB oneLine{displayColour=opts^.color__} amt = second3 bal = third3 tests_Cli_Utils = testGroup "Utils" [ -- testGroup "journalApplyValue" [ -- -- Print the time required to convert one of the sample journals' amounts to value. -- -- Pretty clunky, but working. -- -- XXX sample.journal has no price records, but is always present. -- -- Change to eg examples/5000x1000x10.journal to make this useful. -- testCase "time" $ do -- ej <- io $ readJournalFile definputopts "examples/3000x1000x10.journal" -- case ej of -- Left e -> crash $ T.pack e -- Right j -> do -- (t,_) <- io $ timeItT $ do -- -- Enable -V, and ensure the valuation date is later than -- -- all prices for consistent timing. -- let ropts = defreportopts{ -- value_=True, -- period_=PeriodTo $ fromGregorian 3000 01 01 -- } -- j' <- journalApplyValue ropts j -- sum (journalAmounts j') `seq` return () -- io $ printf "[%.3fs] " t -- ok -- ] ] hledger-1.32.3/Hledger/Cli/Version.hs0000644000000000000000000001100614555053231015443 0ustar0000000000000000{-# LANGUAGE CPP #-} {- Version number-related utilities. See also the Makefile. -} module Hledger.Cli.Version ( ProgramName, PackageVersion, VersionString, packageversion, packagemajorversion, progname, versionStringWith, ) where import GitHash (GitInfo, giHash, giCommitDate) -- giDirty import System.Info (os, arch) import Data.List (intercalate) import Data.Maybe (fromMaybe) import Hledger.Utils (splitAtElement) type ProgramName = String type PackageVersion = String type VersionString = String -- | The VERSION string defined with -D in this package's package.yaml/.cabal file -- (by Shake setversion), if any. Normally a dotted number string with 1-3 components. packageversion :: PackageVersion packageversion = #ifdef VERSION VERSION #else "" #endif -- | Just the first 1-2 components of packageversion. packagemajorversion :: PackageVersion packagemajorversion = intercalate "." $ take 2 $ splitAtElement '.' packageversion -- | The name of this package's main executable. progname :: ProgramName progname = "hledger" -- | Given possible git state info from the build directory (or an error message, which is ignored), -- the name of a program (executable) in the currently building package, -- and the package's version, make a complete version string. Here is the logic: -- -- * Program name, OS and architecture are always shown. -- * The package version is always shown. -- * If there is git info at build time, the latest commit hash and commit date are shown, -- and (TODO, requires githash to use -uno for giDirty): -- if the working copy has uncommitted changes a + sign is appended. -- * (TODO, requires adding --match support to githash: -- If there are tags matching THISPKG-[0-9]*, the latest one is used to calculate patch level -- (number of commits since tag), and if non-zero, it and the branch name are shown.) -- -- Some example outputs: -- -- * A homebrew binary, not built in git repo: hledger-ui 1.24, mac-aarch64 -- * A CI release build, built in git repo at release tag: hledger-ui 1.24.1-g455b35293-20211210, mac-x86_64 -- * (TODO) A dev build, built in git repo: hledger-ui 1.24.1+1-g4abd8ef10-20211210 (1.24-branch), mac-x86_64 -- -- This function requires git log to show the default (rfc2822-style) date format, -- so that must not be overridden by a log.date git config variable. -- versionStringWith :: Either String GitInfo -> ProgramName -> PackageVersion -> VersionString versionStringWith egitinfo prognam packagever = concat [ prognam , " " , version , ", " , os' , "-" , arch ] where os' | os == "darwin" = "mac" | os == "mingw32" = "windows" | otherwise = os version = case egitinfo of Left _err -> packagever Right gitinfo -> case words $ giCommitDate gitinfo of -- git log's date format is normally --date=default ("similar to --date=rfc2822") _weekday:mon:day:_localtime:year:_offset:_ -> intercalate "-" $ [packagever, hash, date] -- ++ ["+" | giDirty gitinfo] -- XXX giDirty is wrong when repo shows untracked files by default, skip it for now where hash = 'g' : take 9 (giHash gitinfo) -- like git describe date = concat [year,mm,dd] where mm = fromMaybe mon $ lookup mon $ [ ("Jan","01") ,("Feb","02") ,("Mar","03") ,("Apr","04") ,("May","05") ,("Jun","06") ,("Jul","07") ,("Aug","08") ,("Sep","09") ,("Oct","10") ,("Nov","11") ,("Dec","12") ] dd = (if length day < 2 then ('0':) else id) day -- but could be overridden by a log.date config variable in repo or user git config _ -> packageversion -- -- | Given a program name, return a precise platform-specific executable -- -- name suitable for naming downloadable binaries. Can raise an error if -- -- the version and patch level was not defined correctly at build time. -- binaryfilename :: String -> String -- binaryfilename progname = concat -- [progname, "-", buildversion, "-", os', "-", arch, suffix] -- where -- (os',suffix) | os == "darwin" = ("mac","" :: String) -- | os == "mingw32" = ("windows",".exe") -- | otherwise = (os,"") hledger-1.32.3/app/hledger-cli.hs0000755000000000000000000000034114555053231014677 0ustar0000000000000000-- the hledger command-line executable; see Hledger/Cli.hs module Main (main) where import qualified Hledger.Cli (main) -- Have to write this explicitly for GHC 9.0.1a for some reason: main :: IO () main = Hledger.Cli.main hledger-1.32.3/test/unittest.hs0000644000000000000000000000105714434445206014603 0ustar0000000000000000{- Run the hledger package's unit tests using the tasty test runner (by running the test command limited to Hledger.Cli tests). -} -- cabal missing-home-modules workaround from hledger-lib, seems not needed here -- {-# LANGUAGE PackageImports #-} -- import "hledger" Hledger.Cli (tests_Hledger_Cli) import Hledger.Cli (tests_Hledger_Cli) import System.Environment (setEnv) import Test.Tasty (defaultMain) main :: IO () main = do setEnv "TASTY_HIDE_SUCCESSES" "true" setEnv "TASTY_ANSI_TRICKS" "false" -- helps the above defaultMain tests_Hledger_Cli hledger-1.32.3/bench/bench.hs0000644000000000000000000000426714434445206014111 0ustar0000000000000000-- bench -- By default, show approximate times for some standard hledger operations on a sample journal. -- With --criterion, show accurate times (slow). import Criterion.Main (defaultMainWith, defaultConfig, bench, nfIO) -- import QuickBench (defaultMain) import Data.Default import System.Directory (getCurrentDirectory) import System.Environment (getArgs, withArgs) import System.TimeIt (timeItT) import Text.Printf import Hledger.Cli -- sample journal file to use for benchmarks inputfile = "bench/10000x1000x10.journal" outputfile = "/dev/null" -- hide output of benchmarked commands (XXX unixism) -- outputfile = "-" -- show output of benchmarked commands main = do -- withArgs ["--quickbench"] $ do -- withArgs ["--criterion"] $ do args <- getArgs if "--criterion" `elem` args then withArgs [] benchWithCriterion else -- if "--quickbench" `elem` args -- then -- benchWithQuickbench -- else benchWithTimeit benchWithTimeit = do getCurrentDirectory >>= printf "Benchmarking hledger in %s with timeit\n" let opts = defcliopts{output_file_=Just outputfile} (t0,j) <- timeit ("read "++inputfile) $ either error id <$> readJournalFile def inputfile -- PARTIAL: (t1,_) <- timeit ("print") $ print' opts j (t2,_) <- timeit ("register") $ register opts j (t3,_) <- timeit ("balance") $ balance opts j printf "Total: %0.2fs\n" (sum [t0,t1,t2,t3]) timeit :: String -> IO a -> IO (Double, a) timeit name action = do printf "%s%s" name (replicate (40 - length name) ' ') (t,a) <- timeItT action printf "[%.2fs]\n" t return (t,a) benchWithCriterion = do getCurrentDirectory >>= printf "Benchmarking hledger in %s with criterion\n" let opts = defcliopts{output_file_=Just "/dev/null"} j <- either error id <$> readJournalFile def inputfile -- PARTIAL: Criterion.Main.defaultMainWith defaultConfig $ [ bench ("read "++inputfile) $ nfIO $ (either error const <$> readJournalFile def inputfile), -- PARTIAL: bench ("print") $ nfIO $ print' opts j, bench ("register") $ nfIO $ register opts j, bench ("balance") $ nfIO $ balance opts j, bench ("stats") $ nfIO $ stats opts j ] hledger-1.32.3/CHANGES.md0000644000000000000000000044325214555435303013013 0ustar0000000000000000 User-visible changes in the hledger command line tool and library. # 1.32.3 2024-01-28 Fixes - A performance slowdown since 1.29, especially noticeable with many accounts and transactions, has been fixed. [#2153] - Balance assertions involving mixed-cost balances are checked correctly again (a regression in 1.30). [#2150] - import --catchup works again (a regression in 1.32). [#2156] - --anon is now a deprecated hidden flag that raises an error, but is still usable as --obfuscate (also hidden). [#2133] - Balance assertion error messages are clearer, and show the diff again. # 1.32.2 2023-12-31 Fixes - In CSV field assignments, %FIELD interpolation and `\n` can be used together again. [#2134] - In timedot data, numbers beginning with a decimal point are accepted again. [#2130] - In a `balance --budget` report, `--layout=tall` no longer hides commodity symbols. - Value reports seeing a pathological price chain with 1000 or more steps now write their warning to the console, not a debug log file. Improvements - Allow megaparsec 9.6 Docs - Updated: Queries, Periodic transactions, Auto postings, Assertions and costs, Budget report # 1.32.1 2023-12-07 - Fixed: `import` with multiple files now updates .latest files correctly. (#2125) - Fixed: `print --round=hard` now properly pads/rounds amounts with inferred costs. (#2123) - CSV matcher syntax: mention that ! and & can't be used in the same line yet. (#2088) - Drop the "a difference of ..." line from balance assertion failure output. I feel it made the message harder to read and isn't really necessary. - Declaring the empty payee name with `payee ""` now works, to let `hledger check payees` accept payee-less transactions. (#2119) - Built-in tags with special meaning like `type:` and `t:` are now implicitly declared, so using type: in account declarations or generating t: with timedot letters won't cause `hledger check tags` to fail. (#2119) # 1.32 2023-12-01 Breaking changes - Display styles and display precision are now managed more carefully during calculations and output, fixing a number of issues (#2111, "Precisiongeddon"). In brief: - Cost and value reports, such as `print -V`, now (1) consistently apply commodity display styles, and (2) do not add or discard decimal digits unnecessarily. (#2105) - When "infinite decimals" arise during calculations (eg in value reports, or in `prices` or `roi` output), these are now shown limited to 8 decimal digits rather than 255. - Non-print-like reports no longer add trailing decimal marks to disambiguate digit group marks (this was an unintended regression in 1.31). (#2115) - We now document number formatting adjustments made in certain reports and output formats (hledger manual > REPORTING CONCEPTS > Amount formatting, parseability). Features - Timedot format supports a new letters syntax for easier tagged time logging. (#2116) - `print` has a new `beancount` output format for exporting to Beancount. This prints journal output more likely (though not guaranteed) to be readable by Beancount. - In CSV rules, matchers using regular expressions can now interpolate their matched texts into the values they assign to fields (field assignment values can reference match groups). (#2009) (Jonathan Dowland) - In CSV rules, matchers can be negated by prepending `!`. (#2088) (bobobo1618) - Multi-column balance reports (from `bal`, `bs`, `is` etc.) can use the new `--summary-only` flag (`--summary` also works) to display just the Total and Average columns (if enabled by `--row-total` and `-A/--average`) and hide the rest. (#1012) (Stephen Morgan) - All commands that suport csv output now also support `tsv` (tab-separated values) output. The data is identical, but the fields are separated by tab characters and there is no quoting or escaping. Tab, carriage return, and newline characters in data are converted to spaces (this should rarely if ever happen in practice). (#869) (Peter Sagerson). Improvements - Journal format no longer fails to parse Ledger-style lot costs with spaces after the `{`, improving Ledger compatibility. - `import` now does not update any .latest files until it has run without error (no failing strict checks, no failure while writing the journal file). This makes it more idempotent, so you can run it again after fixing problems. - `print` now shows zeros with a commodity symbol and decimal digits when possible, preserving more information. - `print` has a new option for controlling amount rounding (#2085): - `--round=none` - show amounts with original precisions (default; like 1.31; avoids implying less or more precision than was recorded) - `--round=soft` - add/remove decimal zeros in non-cost amounts (like 1.30 but also affects balance assertion amounts) - `--round=hard` - round non-cost amounts (can hide significant digits) - `--round=all` - round all amounts and costs For the record: `print` shows four kinds of amount: posting amounts, balance assertion amounts, and costs for each of those. Past hledger versions styled and rounded these inconsistently. Since 1.31 they are all styled, and since 1.32 they are rounded as follows: | hledger-1.32 print | amt | cost | bal | balcost | |--------------------|------|------|------|---------| | (default) | none | none | none | none | | --round=soft | soft | none | soft | none | | --round=hard | hard | none | hard | none | | --round=all | hard | hard | hard | hard | - The `prices` command has had a number of fixes and improvements (#2111): - It now more accurately lists the prices that hledger would use when calculating value reports (similar to what you'd see with `hledger bal -V --debug=2`). - The --infer-reverse-prices flag was confusing, since we always infer and use reverse prices; it has been renamed to `--show-reverse`. - `--show-reverse` and `--infer-market-prices` flags now combine properly. - `--show-reverse` now ignores zero prices rather than giving an error. - Price amounts are now shown styled. - Price amounts are now shown with all their decimal digits; or with 8 decimal digits if they appear to be infinite decimals (which can arise with reverse prices). - Filtering prices with `cur:` or `amt:` now works properly. Fixes - `print` now styles balance assertion costs consistently, like other amounts. - `import` now works with `-s/--strict`. And more generally, when reading multiple input files, eg with multiple `-f` options, strict checks are done only for the overall combined journal (not for each individual file). (#2113) - `tag:` queries now work when reading CSV files. (#2114) - Using a `.json` or `.sql` file extension with `-o`/`--outputfile` now properly selects those output formats. - Auto postings no longer break redundant equity/cost detection and transaction balancing. (#2110) - Amounts set by balance assignment now affect commodity styles again. (#2091, a regression in 1.30) - Timedot quantities with units are parsed more accurately. Eg a quantity like "15m" was evaluated as 0.249999999 not 0.25, and since hledger 1.21, it was printed that way also. Now we round such quantities to two places during parsing to get exact quarter-hour amounts. (#2096) - The `demo` command no longer triggers a JSON decode error in asciinema 2.3.0. It now also shows a better error message if asciinema fails (#2094). - Failing balance assertions with a cost now show correct markers in the error message. (#2083) Docs - New: - Amount formatting, parseability - Started new code docs for developers, based in the Hledger module's haddock - Updated: - aregister - commodity directive - Commodity display style - if table - Decimal marks, digit group marks - Regular expressions - Timedot # 1.31 2023-09-03 Features - Multi-pivot: the --pivot option now accepts multiple arguments, colon-delimited, to construct account names from multiple fields. (#2050, Eric Mertens) Improvements - The `print` command now more closely replicates the original journal amount styles, which is helpful when round-tripping / cleaning up journal files: - Amounts in conversion transactions could be displayed rounded to a lower precision; this no longer happens. (#2079) - Amounts could be displayed with extra zeros after the decimal mark; this no longer happens. - Amounts could display with a different precision if the journal included a timedot file; this no longer happens. - Costs in balance assertions were not displayed with standard styles like other amounts; now they are. - Zero amounts were always shown as just "0"; now they are shown with their original commodity symbol and style. (And if an inferred amount has multiple zeros in different commodities, a posting is displayed for each of these.) - `print` no longer displays numbers with a single digit group mark and no decimal mark, which are ambiguous and hard to re-parse. Now if a number has digit group marks the decimal mark will always be shown also. Eg `1,000` (where the comma is a thousands separator) is now shown as `1,000.`. - The check command's `balancedwithautoconversion` and `balancednoautoconversion` checks have been renamed to `autobalanced` and `balanced`. - `hledger check recentassertions` now reports failures at the first posting that's more than 7 days later than the latest balance assertion (rather than at the balance assertion). This is the thing actually triggering the error, and it is more likely to be visible or at least closer when you are working at the end of a journal file. Also, the suggested sample balance assertion now uses the same commodity symbol as in the failing posting (the first, if there are more than one); and, no longer includes a cleared mark. - The import command now shows the file path being imported to. - With --pivot, `desc` is now the preferred spelling for pivoting on description. - The demo command now ignores an invalid journal file, like the other HELP commands. - Debug output for equity conversion postings has been improved, making troubleshooting easier. - Allow aeson 2.2, megaparsec 9.5. Fixes - In journal files, valid multicommodity transactions where the matching non-equity postings can't be auto-detected are no longer considered an error (as they were in hledger 1.29 and 1.30). Now, such transactions are accepted, and --infer-cost has no effect on them. This is similar to the behaviour of --cost, --infer-equity, and --infer-market-prices. (#2045) - In journal files, equity conversion postings are now detected more tolerantly, using the same precision as the conversion posting's amount (#2041). Eg, the following transaction is now accepted: 2023-01-01 Assets -84.01 USD @ 2.495 GEL ; ^ 209.60495 GEL, recognised as a match for the 209.60 below Equity:Conversion 84.01 USD Equity:Conversion -209.60 GEL Assets 209.60 GEL - The roi command now reports TWR per period and overall TWR for multi-period reports. (#2068, Dmitry Astapov) - The commands list no longer shows bar when hledger-bar is not installed (#2065), and had a few other cleanups. # 1.30.1 2023-06-02 Fixes - Add missing files to Hackage release, making it buildable. Docs - Replace note about repeated options. # 1.30 2023-06-01 Breaking changes - The CSV reader now properly skips all empty lines, as specified by docs. Previously, inner empty lines were not being skipped automatically. You might need to adjust the `skip` count in some CSV rules files. (#2024) - Timedot format now generates a single multi-posting transaction per date line, and supports comments and tags on all lines. (#1754) - Timeclock format now supports comments and tags. Descriptions can no longer contain semicolons. (#1220) Features - CSV rules files can now be read directly, as in `hledger -f foo.csv.rules CMD`. By default this will read data from foo.csv in the same directory. - CSV rules files can use a new `source FILE` rule to specify the data file, with some convenience features: - If the data file does not exist, it is treated as empty, not an error. - If FILE is a relative path, it is relative to the rules file's directory. If it is just a file name with no path, it is relative to `~/Downloads/`. - If FILE is a glob pattern, the most recently modified matched file is used. This helps remove some of the busywork of managing CSV downloads. Most of your financial institutions's default CSV filenames are different and can be recognised by a glob pattern. So you can put a rule like `source Checking1*.csv` in foo-checking.csv.rules, periodically download CSV from Foo's website accepting your browser's defaults, and then run `hledger import checking.csv.rules` to import any new transactions. The next time, if you have done no cleanup, your browser will probably save it as something like Checking1-2.csv, and hledger will still see that because of the * wild card. You can choose whether to delete CSVs after import, or keep them for a while as temporary backups, or archive them somewhere. (Experimental) - The balance command has a new --count report type which reports posting counts instead of amounts. - Full boolean queries, allowing arbitrary use of AND, OR, NOT (case insensitive) and parentheses for grouping, are now supported. For backward compatibility, these require an `expr:` prefix. Existing queries work as before, and you can mix and match the old and new styles if you like. (Chris Lemaire) - demo: This new command plays brief asciinema screencasts explaining various features and use cases. We will add more of these over time. (Experimental) Improvements - Add-on commands can now have `.js`, `.lua`, or `.php` file extensions. - Generated and modified transactions and postings have the same hidden tags (beginning with underscore) as before, but no longer have visible tags added by default. Use `--verbose-tags` if you want them added. - We now try harder to ensure `less` (and its `more` mode) show our ANSI formatting properly in help output. If you use some other $PAGER, you may have to configure it yourself to show ANSI (or disable ANSI entirely, eg by setting NO_COLOR=1). This is now documented in hledger manual > Paging. (#2015) - The print command's `--match` mode has been refined. Previously, similarity completely outweighed recency, so a slightly-more-similar transaction would always be selected no matter how old it was. Now similarity and recency are more balanced, and it should produce the desired transaction more often. There is also new debug output (at debug level 1) for troubleshooting. - Miscellaneous commands list updates. Help has been added for all published add-on commands (like hledger-lots). - The help command's documentation now mentions an issue caused by a too-old `info` program, as on mac. (#1770) Fixes - Unbalanced virtual postings with no amount always infer a zero amount. This is fixing and clarifying the status quo; they always did this, but print always showed them with no amount, even with -x, and the behaviour was undocumented. - On windows systems with multiple drive letters, the commands list could fail to show all installed add-ons. (#2040) - Balancing a transaction with a balance assignment now properly respects costs. (#2039) - The commands list no longer lists non-installed addons. (#2034) - Since hledger 1.25, "every Nth day of month" period rules with N > 28 could be calculated wrongly by a couple of days when given certain forecast start dates. Eg `~ every 31st day of month` with `--forecast='2023-03-30..'`. This is now fixed. (#2032) - Postings are now processed in correct date order when inferring balance assignments. (#2025) - Posting comment lines no longer disrupt the underline position in error messages. (#1927) - Debug output is now formatted to fit the terminal width. Docs - Miscellaneous manual cleanups. - Rewrite introductory sections, Date adjustment, Directives, Forecasting, etc. - Add Paging section. - Remove archaic mentions of `setenv`. API - Renamed: Hledger.Cli.Commands: findCommand -> findBuiltinCommand # 1.29.2 2023-04-07 Breaking changes - 1.29's cleanup of the `close` command has been continued. Here are all the changes to `close` since hledger 1.28: - The default behaviour is now to print only one transaction: a closing transaction. - To print both closing and opening transactions as before, use the new `--migrate` flag. - The accounts closed by default are now just the ALE accounts (accounts declared or inferred as type `Asset`, `Liability`, or `Equity`). If you don't have account types configured, or to close some other set of accounts, provide query arguments that match them. To close all accounts as before, use a `.` argument to match them all. - To print a retain earnings transaction for RX accounts (accounts of type `Revenue` or `Expense`), use the new `--retain` flag. - The `equity` command alias, removed in 1.29, has been restored. - The `--open-acct` option, removed in 1.29, has been restored. - The `--closing` and `--opening` flags have been renamed to `--close` and `--open`. (`--close` had been removed in 1.29 and is now restored.) - The docs have been rewritten. Also the 1.29 release notes now mention the breaking change. - The command is marked experimental again. (#2020) Fixes - `type:` queries now "see through" account aliases and pivots, as they did in hledger <1.27, and as `acct:` queries do. (#2018) - The corruption in 1.29's info manual is fixed. (#2023) - The 1.29 release notes for periodic reports'/periodic transactions' start dates have been improved. Also the hledger manual's "Date adjustment" section has been corrected and clarified. # 1.29.1 2023-03-16 Improvements - Hledger.Cli.Script now also exports Control.Applicative Control.Concurrent Data.Char Data.Functor System.IO System.IO.Error and new string helpers strip1Char stripBy strip1By - Allow building with GHC 9.6.1 (#2011) Fixes - The stats report no longer displays "Exact" in front of dates. (#2012) Docs - remove duplicate in `hledger close` docs (Yehoshua Pesach Wallach) # 1.29 2023-03-11 Breaking changes - Periodic reports will now start exactly at the start date you have specified, rather than being adjusted to a natural period boundary; see below. - The `close` command's CLI and default behaviour was changed; see below (and fixes in hledger 1.29.2+). Features - Periodic transactions and periodic reports can now start on any date. Eg, `hledger reg -M -b 1/15` now starts exactly on jan 15th, and a periodic rule like `~ monthly from 2023-01-15` now works as you'd expect instead of raising an error. This also improves our ability to read Ledger files. Inferred start/end dates, eg obtained from the journal instead of the command line, are still automatically adjusted to period boundaries, as before. Upgrade notes: in report commands which specify a start date, you might need to adjust that date to see the same periods as before. Eg: - `-p 'weekly from 202304'` (equivalent to `-p 'weekly from 20230401'`) now gives periods like `2023-04-01..2023-04-07`. Change it to start on a monday (eg `-p 'weekly from 20230403`) to restore simple week periods like `2023-04-03W14`. - `-M -b 2023/1/15` now gives periods like `2023-01-15..2023-02-14 2023-02-15..2023-03-14`. Change it to start on a first of month (eg `-M -b 2023/1`) to restore simple month periods like `Jan Feb Mar`. (#1982) - You can now freely combine @/@@ notation and conversion postings in a single transaction. This can help readability, and also allows more flexibility when recording cost. hledger will check that the two notations are in agreement, and ignore the redundancy if they are. (Conversion postings are postings to accounts with type `V`/`Conversion` or name `equity:conversion`/`equity:trade`/`equity:trading`, or subaccounts of these. See also COST.) - In journal format there is now a `tag` directive for declaring tag names, and the check command now has a `tags` check to enforce use of declared tag names. Improvements - hledger's commands list has been reorganised for clarity. More add-on commands are now recognised and categorised, and unrecognised add-on commands are listed in a more compact multi-column layout. (Simon Michael, Michael Grünewald) - hledger's commands list and command line help now use ANSI (bold headings) when supported. - hledger's commands list and command line help now use a pager (respecting $PAGER) for long output except on MS Windows. - hledger's `--version` output no longer shows `+` for dev builds made in dirty repos (it was buggy). - The add command's Description completions now also include payee names (declared with `payee` or recorded in transactions with `|`), not just full descriptions. - aregister now supports HTML output. (#1996) (Jonathan Dowland) - aregister now shows a " (matching query)" hint in report title when extra query args (other than date: or depth:) are used, to reduce confusion. - The `close` command's CLI and default behaviour were changed, attempting to make it easier to understand and use. Some of its legacy flags and aliases were also dropped, without sufficient warning. For the full details, including subsequent cleanups, see hledger 1.29.2's change notes. - register-match is now the `--match` mode of the register command. (This command was used by ledger-autosync at one point; if you still need it, hopefully `register --match` works similarly.) - print-unique has been dropped, because it doesn't support print's options, it disorders same-day transactions, I don't know of any users or use cases, and it could easily be recreated as an addon script. - print's JSON output now also includes source positions for `--forecast` transactions. (Chris Lemaire) - Journal format now allows the empty commodity symbol to be written as `""`, so it's now possible to declare market prices for it: `P 2022-01-01 "" $100`. This can be useful for timedot data. - Inferring costs from equity now happens after transaction balancing, not before. As a result, `--infer-costs` now works in transactions where an amount is left blank. - `account` declarations now reject parenthesised account names, reducing confusion. (Chris Lemaire) - Our journal reader now accepts more Ledger syntax, improving Ledger file compatibility (#1962). We now test our ability to at least read the sample journals from Ledger's baseline functional tests, and our success rate has improved from 80% to 90% since 1.28. - `since` is accepted as synonym of `from` in period expressions - `apply year` and `year` are accepted as synonyms of `Y` - `(lot notes)` in amounts and `((valuation expressions))` after amounts are now ignored - directives `A`, `assert`, `bucket`, `capture`, `check`, `define`, `expr`, `eval`, `python`, `value`, `apply fixed`, `apply tag`, `end apply fixed`, `end apply tag`, `end apply year` are now ignored - subdirectives of `payee`, `tag`, and `commodity` (other than `format`) are now ignored - `pop` directive is no longer supported - When reading CSV, we now check that assigned account names are valid (parseable). (#1978) Fixes - aregister now handles an extra account query correctly. (#2007) - balance's `--help` now mentions `--layout=tidy` - Balance commands with `--layout=bare` now generate proper table layout in HTML output. - register's `-w`/`--width` option no longer gives ugly parse error messages. - stats's `--help` no longer wrongly claims to support -O/--output-format. - Balance assignments with a cost now generate a correct balance assertion. (#1965) - The CSV reader now properly skips header lines before attempting to parse records. (#1967) Scripts/addons - Scripts can now use Hledger.Cli.Script, a convenient new prelude which helps reduce import boilerplate. It currently re-exports: Control.Monad Data.Either Data.List Data.Maybe Data.Ord Data.Time Text.Printf hiding (formatString) Data.Text (Text, pack, unpack) Safe hiding (at) System.Directory System.Environment System.Exit System.FilePath System.Process Hledger Hledger.Cli Hledger.Cli.Main (argsToCliOpts) (Not much of Data.Text/Data.Text.IO because those need to be qualified.) Docs - chunk the hledger manual into parts, rename and rearrange sections for better structure/flow - add a cheatsheet demonstrating all the main journal features that I recommend - move a number of my not-so-recommended journal features into a less visible "Other syntax" section - add: payees/descriptions completion - areg: more advice on account-matching - bal: --budget: clarify use of print --forecast - bal: budget: compare with forecasting; add some tips - balance cleanups/reorder - check: adjacentconversionpostings was dropped - cli: balance: fix link to Budgeting page - cli: fix all links to Journal > Tags / Commands > tags - codes: improve example suggested by Rob Nielsen - csv, timeclock, timedot: clarify comment lines (#1953) - csv: add new coinbase example - csv: clarify amount-in/amount-out docs (#1970) - csv: clarify skip/valid csv semantics (#1967) - csv: clarify valid CSV requirements and issues (fix #1966) - csv: cleanup, reorder, CSV rules tips -> Working with CSV - csv: fix wrong if tables doc; rewrite several sections (#1977) - csv: flatten, clean up CSV sections - csv: improve Amount field / Setting amounts - csv: note -in and -out are used together for one posting (#1970) - csv: rules factoring tips - csv: try to clarify how CSV fields and hledger fields work - document --infer-market-prices with signed costs (#1870) - fix duplicate market prices heading breaking info navigation - import: note a pitfall with multifile import - improve Directives summaries - introduction/input/output improvements - journal: cheatsheet: clarify date tag - journal: rewrite Account names, mention brackets/parentheses (#1915) - mention pivoting on a tag with multiple values (#1950) - more cost notation docs; describe Ledger and Beancount cost notation - more mention of posting order effect on inferring cost (#1959) - period expressions doc updates - Removed redundant paragraph in documentation. (J. B. Rainsberger) - rename directive sections, fix many links - reorganise commands list, like the CLI - reorganise bin/README & the Scripts page, add entries for recent scripts - replace "transaction prices" terminology with "costs" - tags: discuss multi-values/overriding (#1950) - update market price inference docs per sol - Updated section on pivoting. Used synonyms for "member" in cases where there could be confusion with the tag named "member." (Robert Nielsen) - use more standard and consistent boilerplate in hledger, ui, web man pages - virtual postings: improve wording per Robert Nielsen # 1.28 2022-12-01 Features - The `accounts` command has new flags: `--undeclared` (show accounts used but not declared), `--unused` (show accounts declared but not used), and `--find` (find the first account matched by the first command argument, a convenience for scripts). Also `-u` and `-d` short flags have been added for `--used` and `--declared`. - A new CSV rule `intra-day-reversed` helps generate transactions in correct order with CSVs where records are reversed within each day. - CSV rules can now correctly convert CSV date-times with a implicit or explicit timezone to dates in your local timezone. Previously, CSV date-times with a different time zone from yours could convert to off-by-one dates, because the CSV's timezone was ignored. Now, 1. When a CSV has date-times with an implicit timezone different from yours, you can use the `timezone` rule to declare it. 2. CSV date-times with a known timezone (either declared by `timezone` or parsed with `%Z`) will be localised to the system timezone (or to the timezone set with the `TZ` environment variable). (#1936) Improvements - print --match now respects -o and -O. - print --match now returns a non-zero exit code when there is no acceptable match. - Support megaparsec 9.3. (Felix Yan) - Support GHC 9.4. Fixes - In CSV rules, when assigning a parenthesised account name to `accountN`, extra whitespace is now ignored, allowing unbalanced postings to be detected correctly. Scripts/addons - bin/hledger-move helps record transfers involving subaccounts and costs, eg when withdrawing some or all of an investment balance containing many lots and costs. - bin/hledger-git no longer uses the non-existent git record command. (#1942) (Patrick Fiaux) - bin/watchaccounts is a small shell script for watching the account tree as you make changes. # 1.27.1 2022-09-18 Fixes - Balance commands using `-T -O html` no longer fail with an error when there is no data to report. (#1933) # 1.27 2022-09-01 Features - `hledger check recentassertions` (and flycheck-hledger in Emacs if you enable this check) requires that all balance-asserted accounts have a balance assertion within 7 days before their latest posting. This helps remind you to not only record transactions, but also to regularly check account balances against the real world, to catch errors sooner and avoid a time-consuming hunt. - The --infer-costs general flag has been added, as the inverse operation to --infer-equity. --infer-costs detects commodity conversion transactions which have been written with equity conversion postings (the traditional accounting notation) and adds PTA cost notation (@@) to them (allowing cost reporting). See https://hledger.org/hledger.html#equity-conversion-postings . (Stephen Morgan) Improvements - Many error messages have been improved. Most error messages now use a consistent, more informative format. (#1436) - The accounts command has a new --directives flag which makes it show valid account directives which you can paste into a journal. - The accounts command has a new --positions flag which shows where accounts were declared, useful for troubleshooting. (#1909) - Bump lower bounds for Diff and githash. (Andrew Lelechenko) - GHC 8.6 and 8.8 are no longer supported. Building hledger now requires GHC 8.10 or greater. Fixes - Account display order is now calculated correctly even when accounts are declared in multiple files. (#1909) - At --debug 5 and up, account declarations info is logged. (#1909) - hledger aregister and hledger-ui now show transactions correctly when there is a type: query. (#1905) - bal: Allow cumulative gain and valuechange reports. Previously, --cumulative with --gain or --valuechange would produce an empty report. This fixes this issue to produce a reasonable report. (Stephen Morgan) - bal: budget goal amounts now respect -c styles (fixes #1907) - bal: budget goals now respect -H (#1879) - bal: budget goals were ignoring rule-specified start date - cf/bs/is: Fixed non-display of child accounts when there is an intervening account of another type. (#1921) (Stephen Morgan) - roi: make sure empty cashflows are skipped when determining first cashflow (Charlotte Van Petegem) Empty cashflows are added when the begin date of the report is before the first transaction. Scripts/addons - https://hledger.org/scripts.html - an overview of scripts and addons in bin/. - paypaljson, paypaljson2csv - download txns from paypal API - hledger-check-postable.hs - check that no postings are made to accounts with a postable:(n|no) tag - hledger-addon-example.hs - script template # 1.26.1 2022-07-11 - require safe 0.3.19+ to avoid deprecation warning # 1.26 2022-06-04 Improvements - `register` and `aregister` have been made faster, by - considering only the first 1000 items for choosing column widths. You can restore the old behaviour (guaranteed alignment across all items) with the new `--align-all` flag. ([#1839](https://github.com/simonmichael/hledger/issues/1839), Stephen Morgan) - discarding cost data more aggressively, giving big speedups for large journals with many costs. ([#1828](https://github.com/simonmichael/hledger/issues/1828), Stephen Morgan) - Most error messages from the journal reader and the `check` command now use a consistent layout, with an "Error:" prefix, line and column numbers, and an excerpt highlighting the problem. Work in progress. ([#1436](https://github.com/simonmichael/hledger/issues/1436)) (Simon Michael, Stephen Morgan) - `hledger check ordereddates` now always checks all transactions (previously it could be restricted by query arguments). - The `--pivot` option now supports a `status` argument, to pivot on transaction status. - Update bash completions (Jakob Schöttl) Fixes - Value reports with `--date2` and a report interval (like `hledger bal -VM --date2`) were failing with a "expected all spans to have an end date" error since 1.22; this is now fixed. ([#1851](https://github.com/simonmichael/hledger/issues/1851), Stephen Morgan) - In CSV rules, interpolation of a non-existent field like `%999` or `%nosuchfield` is now ignored (previously it inserted that literal text). Note this means such an error will not be reported; Simon chose this as the more convenient behaviour when converting CSV. Experimental. ([#1803](https://github.com/simonmichael/hledger/issues/1803), [#1814](https://github.com/simonmichael/hledger/issues/1814)) (Stephen Morgan) - `--infer-market-price` was inferring a negative price when selling. ([#1813](https://github.com/simonmichael/hledger/issues/1813), Stephen Morgan) - Allow an escaped forward slash in regular expression account aliases. ([#982](https://github.com/simonmichael/hledger/issues/982), Stephen Morgan) - The `tags` command now also lists tags from unused account declarations. It also has improved command-line help layout. ([#1857](https://github.com/simonmichael/hledger/issues/1857)) - `hledger accounts` now shows its debug output at a more appropriate level (4). # 1.25 2022-03-04 Breaking changes - Journal format's `account NAME TYPECODE` syntax, deprecated in 1.13, has been dropped. Please use `account NAME ; type:TYPECODE` instead. (Stephen Morgan) - The rule for auto-detecting "cash" (liquid asset) accounts in the `cashflow` report has changed: it's now "all accounts under a top-level `asset` account, with `cash`, `bank`, `checking` or `saving` in their name" (case insensitive, variations allowed). So if you see a change in your `cashflow` reports, you might need to add `account` directives with `type:C` tags, declaring your top-most cash accounts. Features - The new `type:TYPECODES` query matches accounts by their accounting type. Account types are declared with a `type:` tag in account directives, or inferred from common english account names, or inherited from parent accounts, as described at [Declaring accounts > Account types]. This generalises the account type detection of `balancesheet`, `incomestatement` etc., so you can now select accounts by type without needing fragile account name regexps. Also, the `accounts` command has a new `--types` flag to show account types. Eg: hledger bal type:AL # balance report showing assets and liabilities hledger reg type:x # register of all expenses hledger acc --types # list accounts and their types ([#1820](https://github.com/simonmichael/hledger/issues/1820), [#1822](https://github.com/simonmichael/hledger/issues/1822)) (Simon Michael, Stephen Morgan) - The `tag:` query can now also match account tags, as defined in account directives. Subaccounts inherit tags from their parents. Accounts, postings and transactions can be filtered by account tag. ([#1817](https://github.com/simonmichael/hledger/issues/1817)) - The new `--infer-equity` flag replaces the `@`/`@@` price notation in commodity conversion transactions with more correct equity postings (when not using `-B/--cost`). This makes these transactions fully balanced, and preserves the accounting equation. For example: 2000-01-01 a 1 AAA @@ 2 BBB b -2 BBB $ hledger print --infer-equity 2000-01-01 a 1 AAA equity:conversion:AAA-BBB:AAA -1 AAA equity:conversion:AAA-BBB:BBB 2 BBB b -2 BBB `equity:conversion` is the account used by default. To use a different account, declare it with an account directive and the new `V` (`Conversion`) account type. Eg: account Equity:Trading ; type:V ([#1554](https://github.com/simonmichael/hledger/issues/1554)) (Stephen Morgan, Simon Michael) - Balance commands (`bal`, `bs` etc.) can now generate easy-to-process "tidy" CSV data with `-O csv --layout tidy`. In tidy data, every variable is a column and each row represents a single data point (cf ). ([#1768](https://github.com/simonmichael/hledger/issues/1768), [#1773](https://github.com/simonmichael/hledger/issues/1773), [#1775](https://github.com/simonmichael/hledger/issues/1775)) (Stephen Morgan) Improvements - Strict mode (`-s/--strict`) now also checks periodic transactions (`--forecast`) and auto postings (`--auto`). ([#1810](https://github.com/simonmichael/hledger/issues/1810)) (Stephen Morgan) - `hledger check commodities` now always accepts zero amounts which have no commodity symbol. ([#1767](https://github.com/simonmichael/hledger/issues/1767)) (Stephen Morgan) - Relative [smart dates](hledger.html#smart-dates) may now specify an arbitrary number of some period into the future or past). Some examples: - `in 5 days` - `in -6 months` - `5 weeks ahead` - `2 quarters ago` (Stephen Morgan) - CSV output now always disables digit group marks (eg, thousands separators), making it more machine readable by default. ([#1771](https://github.com/simonmichael/hledger/issues/1771)) (Stephen Morgan) - Unicode may now be used in field names/references in CSV rules files. ([#1809](https://github.com/simonmichael/hledger/issues/1809)) (Stephen Morgan) - Error messages improved: - Balance assignments - aregister - Command line parsing (less "user error") Fixes - `--layout=bare` no longer shows a commodity symbol for zero amounts. ([#1789](https://github.com/simonmichael/hledger/issues/1789)) (Stephen Morgan) - `balance --budget` no longer elides boring parents of unbudgeted accounts if they have a budget. ([#1800](https://github.com/simonmichael/hledger/issues/1800)) (Stephen Morgan) - `roi` now reports TWR correctly - when there are several PnL changes occurring on a single day - and also when investment is fully sold/withdrawn/discounted at the end of a particular reporting period. ([#1791](https://github.com/simonmichael/hledger/issues/1791)) (Dmitry Astapov) Documentation - There is a new CONVERSION & COST section, replacing COSTING. ([#1554](https://github.com/simonmichael/hledger/issues/1554)) - Some problematic interactions of account aliases with other features have been noted. ([#1788](https://github.com/simonmichael/hledger/issues/1788)) - Updated: [Declaring accounts > Account types](https://hledger.org/hledger.html#account-types) # 1.24.1 2021-12-10 Fixes - `balance --declared` is now filtered correctly by a `not:ACCT` query. (#1783) - More reliable --version output, with commit date and without patch level. API changes: - new type synonyms ProgramName, PackageVersion, VersionString - versionStringForProgname -> versionString with extra argument - versionStringFor -> versionStringWith with extra argument # 1.24 2021-12-01 Features - balance commands provide more control over how multicommodity amounts are displayed. (And they no longer elide too-wide amounts by default.) The --commodity-column flag has been deprecated and replaced by a new --layout option, with three values: - wide (the default, shows amounts on one line unelided, like older hledger versions) - tall (a new display mode, shows one amount per line) - bare (like the old --commodity-columm, shows one commodity per line with symbols in their own column) (Stephen Morgan) - The balance commands have a new `--declared` flag, causing them to include leaf (ie, non-parent) accounts declared by account directives, even if they contain no transactions yet. Together with `-E`, this shows a balance for both used and declared accounts. The idea is to be able to see a useful "complete" balance report, even when you don't have transactions in all of your declared accounts yet. (#1765) - journal files now support a `decimal-mark` directive as a more principled way (than `commodity` directives) to specify the decimal character in use in that file, to ensure accurate number parsing. (#1670, Lawrence Wu) Improvements - The stats command now shows rough but useful performance stats: run time and processing speed in transactions per second. - balance: support the --related flag, like register, showing the other postings from the transactions. (#1469, Stephen Morgan) - roi now uses posting dates when available, and honors the --date2 flag. This will not change the results computed for the typical use-case, it just makes "roi" more thorough/consistent. (Dmitry Astapov) - aregister now shows transactions' secondary date if the --date2 flag is used. (#1731) - timedot: a D default commodity (and style) declared in a parent journal file will now be applied to timedot amounts. This means they can be priced and valued/converted. - cli: The --pretty and --forecast options can now be written after the command name, like other general options. (Stephen Morgan) - register -V -H with no interval now values at report end date, like balance. (#1718, Stephen Morgan) - Allow megaparsec 9.2. - Drop the base-compat-batteries dependency. (Stephen Morgan) Fixes - prices: Do not include zero amounts when calculating amounts for balance assignments. (#1736) (Stephen Morgan) This is not usually a problem, but can get in the way of auto-inferring prices. - csv: Successfully parse an empty csv file. (#1183) (Stephen Morgan) - balance: Balance reports with --depth=0 properly report aggregated values, not zero everywhere. (#1761) (Stephen Morgan) - prices: Do not try to generate prices when there would be a zero denominator. Also correctly generate reverse prices for zero amounts. (Stephen Morgan) - csv: Allow both amount-in and amount-out fields to contain a zero. (#1733, Stephen Morgan) - balance: Balance reports should consider date: queries when calculating report span with --date2. (#1745, Stephen Morgan) - print: auto: The print command should always display inferred amounts for --auto generated postings. (#1276, Stephen Morgan) # 1.23 2021-09-21 Features - The balance command has a new `--gain` report type, showing unrealised capital gains/losses. Essentially, this is the difference between the amounts' costs and their total present value. More precisely, between the value of the amounts' costs and the value of the amounts on the valuation date(s). (Ie, you can report gain in a different currency.) ([#1623](https://github.com/simonmichael/hledger/issues/1623), [#1432](https://github.com/simonmichael/hledger/issues/1432), Stephen Morgan, Charlotte Van Petegem) - The new `-c/--commodity-style` option makes it easy to override commodity display styles at runtime, eg to adjust the number of decimal places or change the position of the symbol. ([#1593](https://github.com/simonmichael/hledger/issues/1593), Arjen Langebaerd) - The balance commands have a new `--commodity-column` flag that displays commodity symbols in a dedicated column, showing one line per commodity and all amounts as bare numbers. ([#1559](https://github.com/simonmichael/hledger/issues/1559), [#1626](https://github.com/simonmichael/hledger/issues/1626), [#1654](https://github.com/simonmichael/hledger/issues/1654), Lawrence Wu, Simon Michael, Stephen Morgan) - The `balance --budget` option can now take an argument, a case insensitive description substring which selects a subset of the journal's periodic transactions for setting budget goals. This makes it possible to keep multiple named budgets in one journal, and select the one you want with --budget's argument. ([#1612](https://github.com/simonmichael/hledger/issues/1612)) - Period expressions now support `every weekday`, `every weekendday` and `every mon,wed,...` (multiple days of the week). This is intended for periodic transaction rules used with `--forecast` (or `bal --budget`). ([#1632](https://github.com/simonmichael/hledger/issues/1632), Lawrence Wu) - The new `--today=DATE` option allows overriding today's date. This can be useful in tests and examples using relative dates, to make them reproducible. ([#1674](https://github.com/simonmichael/hledger/issues/1674), Stephen Morgan) - In CSV rules, multi-line comments are now supported. Newlines in CSV data are preserved, or newlines can be added by writing `\n` when assigning to `comment`, `comment1` etc. (Malte Brandy) Improvements - Incremental performance improvements; hledger 1.23 is the fastest hledger yet, about 10% faster than 1.22. (Stephen Morgan) - `register` no longer slows down when there are many report intervals. ([#1683](https://github.com/simonmichael/hledger/issues/1683), Stephen Morgan) - Numbers in SQL output now always use decimal period (`.`), independent of commodity display styles. (Stephen Morgan) - `--sort` now gives a more intuitive sort oder when there are multiple commodities. Negative numbers in one commodity are always less than positive numbers in another commodity. ([#1563](https://github.com/simonmichael/hledger/issues/1563), Stephen Morgan) - `--infer-market-price` has been renamed to `--infer-market-prices`. (The old spelling still works, since we accept flag prefixes.) - Our pretty-printed JSON now orders object attributes alphabetically, across all GHC and haskell lib versions. - register with a report interval starting on custom dates (eg: `hledger reg -p "every 15th day of month") now makes the date column wide enough to show the start and end dates. It also wastes less whitespace after the column. ([#1655](https://github.com/simonmichael/hledger/issues/1655), Stephen Morgan) - The --forecast option will now reject a report interval in its argument, instead of silently ignoring it. - In JSON output, object attributes are now ordered alphabetically, consistently for all GHC and haskell lib versions. ([#1618](https://github.com/simonmichael/hledger/issues/1618), Stephen Morgan) - JSON output now indents with 2 spaces rather than 4. (Stephen Morgan) - The balance commands' `-S/--sort-amount` flag now behaves more predictably and intuitively with multiple commodities. Multi-commodity amounts are sorted by comparing their amounts in each commodity, with alphabetically-first commodity symbols being most significant, and assuming zero with alphabetically-first commodity symbols being most significant, and assuming zero when a commodity is missing. ([#1563](https://github.com/simonmichael/hledger/issues/1563), [#1564](https://github.com/simonmichael/hledger/issues/1564), Stephen Morgan) - The close command now uses the later of today or journal's last day as default closing date, providing more intuitive behaviour when closing a journal with future transactions. Docs have been improved. ([#1604](https://github.com/simonmichael/hledger/issues/1604)) - Rules for selecting the forecast period (within with --forecast generates transactions) have been tweaked slightly, and some disagreement between docs and implementation has been fixed. Now, the forecast period begins on: - the start date supplied to the `--forecast` argument, if any - otherwise, the later of - the report start date if specified with -b/-p/date: - the day after the latest normal (non-periodic) transaction in the journal, if any - otherwise today. It ends on: - the end date supplied to the `--forecast` argument, if any - otherwise the report end date if specified with -e/-p/date: - otherwise 180 days (6 months) from today. This is more intuitive in some cases. (Eg: `hledger reg --forecast -b 2020-01-01` on a journal containing only periodic transaction rules now shows forecast transactions starting from 2020-01-01, rather than from today.) ([#1648](https://github.com/simonmichael/hledger/issues/1648), [#1665](https://github.com/simonmichael/hledger/issues/1665), [#1667](https://github.com/simonmichael/hledger/issues/1667), Stephen Morgan, Simon Michael) - Require base >=4.11, prevent red squares on Hackage's build matrix. (We officially support GHC 8.6+, which means base 4.12, but Hackage shows all packages building successfully with base 4.11/GHC 8.4+ somehow, so it's still allowed..) Fixes - A rare bug causing incorrect balances to be reported by the cf/bs/bse/is commands, since hledger 1.19, has been fixed. (cf/bs/bse/is with --tree --no-elide --begin DATE and certain account directives could show wrong balances). ([#1698](https://github.com/simonmichael/hledger/issues/1698), Stephen Morgan) - aregister now aligns multicommodity amounts properly (broken since 1.21). ([#1656](https://github.com/simonmichael/hledger/issues/1656), Stephen Morgan) - `balance -E` (and hledger-ui Z) now correctly show zero parent accounts, fixing a bug introduced in hledger 1.19. ([#1688](https://github.com/simonmichael/hledger/issues/1688), Stephen Morgan) - The `roi` command no longer gives an ugly error in a certain case with PnL applied on the first day of investment. (Dmitry Astapov) - `--forecast` now generates transactions up to the day before the specified report end date (instead of two days before). ([#1633](https://github.com/simonmichael/hledger/issues/1633), Stephen Morgan) - Certain errors in CSV conversion, such as a failing balance assertion, were always being reported as line 2. # 1.22.2 2021-08-07 Breaking changes - aregister no longer hides future transactions by default. This is a consequence of the fix for [#1638](https://github.com/simonmichael/hledger/issues/1638). It makes aregister consistent, so we think it's a reasonable change. So if you have future-dated transactions in your journal which you don't want reported, you now must exclude them with `-e tomorrow` or `date:-tomorrow` in the command, as with other reports. (Stephen Morgan) Improvements - Timedot format's doc has been rewritten. Fixes - Make balance assignments in forecasted transactions work again (broken in 1.22.1). Forecast transactions are now generated early and processed in the same way as other transactions. ([#1638](https://github.com/simonmichael/hledger/issues/1638), Stephen Morgan) - aregister preserves the order of same-day transactions again (broken in 1.22.1). ([#1642](https://github.com/simonmichael/hledger/issues/1642), Stephen Morgan) # 1.22.1 2021-08-02 Improvements - Bash shell completions (for hledger, hledger-ui, hledger-web) are now included in the hledger package's release tarballs, making them more likely to be installed by system packages. (Jakob Schöttl) - roi docs now discuss how to quote multi-word queries. (#1609, Dmitry Astapov) - Allow megaparsec 9.1 Fixes - `cur:` and `amt:` queries now match the original amounts before valuation and cost conversion, as they did before hledger 1.22. We believe this is the more useful behaviour in practice. (#1625) (Stephen Morgan) - Queries now work better with `register --related`, no longer showing duplicate postings when more than one posting in a transaction is matched. (#1629) (Stephen Morgan) - Valuation now works with `register --related`. (#1630) (Stephen Morgan) - Auto posting rules now also see inferred amounts, not just explicit amounts. (#1412) (Stephen Morgan) - Our info manuals now have more robust directory metadata (no subdirectory path), making them more likely to be linked in your top-level Info directory by system packages. (#1594) (Simon Michael, Damien Cassou) - The error message for a non-existent input file no longer shows excess double quotes. (#1601, Stephen Morgan) - Journal format docs: The commodity directive's scope is now correctly described (lasts until end of current file). - The aregister command now properly ignores a `depth:` argument. It might now also behave more correctly with valuation or `--txn-dates`. (#1634, Stephen Morgan) # 1.22 2021-07-03 Features - check: A new `balancednoautoconversion` check requires transactions to balance without the use of inferred transaction prices. (Explicit transaction prices are allowed.) This check is included in `--strict` mode. The old `autobalanced` check has been renamed to `balancedwithautoconversion`. (Stephen Morgan) Improvements - Many internal optimisations have been applied (cf hledger-lib changelog). Overall, you can expect most reports to be about 20% faster. The register report is more than 2x faster and uses 4x less memory. (Stephen Morgan) ~/src/hledger$ quickbench -w hledger-1.21,hledger Running 5 tests 1 times with 2 executables at 2021-06-29 13:13:26 HST: Best times: +----------------------------------------------------++--------------+---------+ | || hledger-1.21 | hledger | +====================================================++==============+=========+ | -f examples/10000x1000x10.journal print || 1.18 | 0.90 | | -f examples/10000x1000x10.journal register || 12.82 | 5.95 | | -f examples/10000x1000x10.journal balance || 1.38 | 0.86 | | -f examples/1000x1000x10.journal balance --weekly || 0.96 | 0.78 | | -f examples/10000x1000x10.journal balance --weekly || 13.07 | 10.79 | +----------------------------------------------------++--------------+---------+ - ANSI color is now disabled automatically (on stdout) when the `-o/--output-file` option is used (with a value other than `-`). (#1533) - ANSI color is now also available in debug output, determined in the usual way by `--color`, `NO_COLOR`, and whether the output (stderr) is interactive. - The --version flag shows more details of the build, when known: git tag, number of commits since the tag, commit hash, platform and architecture. (Stephen Morgan) - balance: Capitalisation of "account" and "total" (and lack of a colon in the latter) in CSV output is now consistent for single- and multi-period reports. - balance reports' CSV output now includes full account names. (#1566) (Stephen Morgan) - csv: We now accept spaces when parsing amounts from CSV. (Eric Mertens) - json: Avoid adding unnecessary decimal places in JSON output. (Don't increase them all to 10 decimal places.) (Stephen Morgan) - json: Simplify amount precision (asprecision) in JSON output. It is now just the number of decimal places, rather than an object. (Stephen Morgan) - GHC 9.0 is now officially supported, and GHC 8.0, 8.2, 8.4 are not; building hledger now requires GHC 8.6 or greater. - Added a now-required lower bound on containers. (#1514) Fixes - Auto posting rules now match postings more precisely, respecting `cur:` and `amt:` queries. (#1582) (Stephen Morgan) - balance reports: Fix empty cells when amounts are too wide to fit (broken since 1.20) (#1526). (Stephen Morgan) - csv: Fix the escaping of double quotes in CSV output (broken in 1.21). (Stephen Morgan) - register: Fix the running total when there is a report interval (broken since 1.19) (#1568). (Stephen Morgan) - stats: No longer gets confused by posting dates. (#772) (Stephen Morgan) - timeclock: `hledger print` shows timeclock amounts with just 2 decimal places again (broken in 1.21). (#1527) - When all transaction amounts have the same sign, the error message no longer adds an inferred price. (#1551) (Stephen Morgan) - Cleaned up some references to old man pages. (Felix Yan) # 1.21 2021-03-10 ## general - hledger is now generally about 10% more memory- and time-efficient, and significantly more so in certain cases, eg journals with many total transaction prices. (Stephen Morgan) - The `--help/-h` and `--version` flags are no longer position-sensitive; if there is a command argument, they now always refer to the command (where applicable). - The new `--info` flag opens the hledger info manual, if "info" is in $PATH. `hledger COMMAND --info` will open COMMAND's info node. - The `--man` flag opens the hledger man page, if "man" is in $PATH. `hledger COMMAND --man` will scroll the page to CMD's section, if "less" is in $PATH. (We force the use of "less" in this case, overriding any $PAGER or $MAN_PAGER setting.) - Some command aliases, considered deprecated, have been removed: `txns`, `equity`, and the single-letter command aliases `a`, `b`, `p`, and `r`. This was discussed at https://github.com/simonmichael/hledger/pull/1423 and on the hledger mail list. It might annoy some folks; please read the issue and do follow up there if needed. - Notable documentation updates: the separate file format manuals have been merged into the hledger manual, the topic hierarchy has been simplified, the `balance` command docs and "commands" section have been rewritten. ## valuation - Costing and valuation are now independent, and can be combined. `--value=cost` and `--value=cost,COMM` are still supported (equivalent to `--cost` and `--cost --value=then,COMM` respectively), but deprecated. (Stephen Morgan) - `-V` is now always equivalent to `--value=end`. (Stephen Morgan) - `--value=end` now includes market price directives as well as transactions when choosing a valuation date for single-period reports. (#1405, Stephen Morgan) - `--value=end` now picks a consistent valuation date for single- and and multi-period reports. (#1424, Stephen Morgan) - `--value=then` is now supported with all reports, not just register. (Stephen Morgan) - The too-vague `--infer-value` flag has been renamed to `--infer-market-price`. Tip: typing `--infer-market` or even `--infer` is sufficient. The old spelling still works, but is now deprecated. ## commands - add: Infix matches are now scored higher. If the search pattern occurs in full within the other description, that match gets a +0.5 score boost. - add: `--debug` now shows transaction matching results, useful when troubleshooting. - balance: To accomodate new report types, the `--change|--cumulative|--historical|--budget` flags have been split into two groups: report type (`--sum|--budget|...`) and accumulation type (`--change|--cumulative|--historical`). `--sum` and `--change` are the defaults, and your balance commands should still work as before. (Stephen Morgan et al, #1353) - balance: The `--valuechange` report type has been added, showing the changes in period-end values. (Stephen Morgan, #1353) - balance: With `--budget`, the first and last subperiods are enlarged to whole intervals for calculating the budget goals also. (Stephen Morgan) - balance: In multi-period balance reports, specifying a report period now also forces leading/trailing empty columns to be displayed, without having to add `-E`. This is consistent with `balancesheet` etc. (#1396, Stephen Morgan) - balancesheet, cashflow: declaring just a Cash account no longer hides other Asset accounts. - check: Various improvements: - check name arguments may be given as case-insensitive prefixes - `accounts` and `commodities` may also be specified as arguments - `ordereddates` now checks each file separately (#1493) - `ordereddates` no longer supports the `--unique` flag or query arguments - `payees` is a new check requiring payee declarations - `uniqueleafnames` now gives a fancy error message like the others - the old `checkdates`/`checkdupes` commands have been dropped - help: The `help` command now shows only the hledger (CLI) manual, its `--info/--man/--pager` flags have been renamed to `-i/-m/-p`, and `--cat` has been dropped. - help: With a TOPIC argument (any heading or heading prefix, case insensitive), it will open the manual positioned at this topic if possible. (Similar to the new `--man` and `--info` flags described above.) - payees: Add `--used`/`--declared` flags, like the `accounts` command. - print: Now always shows amounts with all decimal places, unconstrained by commodity display style. This ensures more parseable and sensible-looking output in more cases, and behaves more like Ledger's print. (There may be a cosmetic issue with trailing zeroes.) (#931, #1465) - print: With `--match`, infix matches are now scored higher, as with the add command. - print: `--match` now provides debug output useful for troubleshooting. If you forget to give `--match` an argument, it can confusingly consume a following flag. Eg if you write: hledger print --match -x somebank # should be: hledger print --match=somebank -x it gets quietly parsed as: hledger print --match="-x" Now you can at least use --debug to figure it out: hledger print --match -x somebank --debug finding best match for description: "-x" similar transactions: ... - roi: Now supports the valuation options (#1417), and uses commodity display styles. Also the manual has been simplified, with some content moved to the Cookbook. (Dmitry Astapov): ## journal format - The `commodity` directive now properly sets the display style of the no-symbol commodity. (#1461) ## csv format - More kinds of malformed signed numbers are now ignored, in particular just a sign without a number, which simplifies sign flipping with amount-in/amount-out. ## API - API changes include: ``` Hledger.Cli.Utils: +journalSimilarTransaction Hledger.Cli.Commands.Add: transactionsSimilarTo -> Hledger.Data.Journal.journalTransactionsSimilarTo and now takes a number-of-results argument ``` # 1.20.4 2021-01-29 - aregister: ignore a depth limit, as in 1.19 (#1468). In 1.20-1.20.3, aregister had stopped showing transactions in subaccounts below a depth limit. Now it properly shows all subaccount transactions, ensuring that the register's final total matches a balance report with similar arguments. # 1.20.3 2021-01-14 - When searching for price chains during valuation/currency conversion: - It no longer hangs when there are price loops. (And in case of future bugs, it will give up rather than search forever.) (#1439) - It now really finds the shortest path. (#1443) - Useful progress info is displayed with `--debug=1` or `--debug=2`. - balance, incomestatement: End-valued multi-period balance change reports (eg: `bal -MV`) have been reverted to show value-of-change, as in previous hledger versions, rather than change-of-value, for now. (#1353, #1428) (Stephen Morgan) - balance: End-valued balance change reports now choose the same final valuation date and show consistent results whether single-period or multi-period. (#1424) (Stephen Morgan) - balance: the `--drop` option now works with `csv` and `html` output. (#1456) (Ilya Konovalov) - check: the `commodities` check, and `-s`/`--strict` mode, now ignore the "AUTO" internal pseudo-commodity. (#1419) (Ilya Konovalov) - register: Then-valued multi-period register reports (eg: `register -M --value=then`) now calculate the correct values. (#1449) (Stephen Morgan) - roi: now shows a better error message when required prices are missing. (#1446) (Dmitry Astapov) - The no-symbol commodity's input number format can now be set by a `commodity` directive, like other commodities. (#1461) # 1.20.2 2020-12-28 - help: Fix loss of capitalisation in part of the hledger-ui manual. - Fix the info manuals' node structure. - Drop unused parsec dependency. # 1.20.1 2020-12-15 - bal, bs, cf, is: In amount-sorted balance reports, equal-balance accounts are now reliably sorted by name. (Simon Michael, Stephen Morgan) - help: Fix the topic hierarchy in Info manuals. # 1.20 2020-12-05 ## general - strict mode: with -s/--strict, hledger requires that all accounts and commodities are declared with directives. - Reverted a stripAnsi change in 1.19.1 that caused a 3x slowdown of amount rendering in terminal reports. (#1350) - Amount and table rendering has been improved, so that stripAnsi is no longer needed. This speeds up amount rendering in the terminal, speeding up some reports by 10% or more since 1.19. (Stephen Morgan) - Amount eliding no longer displays corrupted ANSI codes (#1352, Stephen Morgan) - Eliding of multicommodity amounts now makes better use of available space, avoiding unnecessary eliding (showing as many amounts as possible within 32 characters). (Stephen Morgan) - Command line help for --no-elide now mentions that it also disables eliding of multicommodity amounts. - Query terms containing quotes (eg to match account names containing quotes) now work properly. (#1368, Stephen Morgan) - cli, journal: Date range parsing is more robust, fixing failing/incorrect cases such as: (Stephen Morgan) - a hyphenated range with just years (`2017-2018`) - a hyphenated date with no day in a hyphenated range (`2017-07-2018`) - a dotted date with no day in a dotted range (`2017.07..2018.02`) - Debug output is prettier (eg, in colour), using pretty-simple instead of pretty-show. - csv, timedot, timeclock files now respect command line --alias options, like journal files. (#859) - Market price lookup for value reports is now more robust, fixing several bugs (and debug output is more informative). There has been a slight change in functionality: when chaining prices, we now prefer chains of all "forward" prices, even if longer, with chains involving reverse prices being the last resort. (#1402) ## commands - add: number style (eg thousands separators) no longer disturbs the value that is offered as default. (#1378) - bal: --invert now affects -S/--sort-amount, reversing the order. (#1283, #1379) (Stephen Morgan) - bal: --budget reports no longer insert an extra space inside the brackets. (Stephen Morgan) - bal: --budget reports now support CSV output (#1155) - bal, is, bs --change: Valued multiperiod balance change reports now show changes of value, rather than the value of changes. (#1353, Stephen Morgan) - bal: clearer debug output, following debug levels policy - check: A new command which consolidating the various check-* commands. It runs the default, strict, or specified checks and produces no output and a zero exit code if all is well. - check-dates: this command is deprecated and will be removed in next release; use "hledger check ordereddates" instead. - check-dupes: this command is deprecated and will be removed in next release; use "hledger check uniqueleafnames" instead. - import: The journal's commodity styles (declared or inferred) are now applied to imported amounts, overriding their original number format. - roi: TWR now handles same-day pnl changes and cashflows, calculation failure messages have been improved, and the documentation includes more detail and examples. (#1398) (Dmitry Astapov) ## journal format - The journal's commodity styles are now applied to forecasted transactions. (#1371) - journal, csv: commodity style is now inferred from the first amount, as documented, not the last. This was "working wrongly" since hledger 1.12.. - A zero market price no longer causes "Ratio has zero denominator" error in valued reports. (#1373) ## csv format - The new `decimal-mark` rule allows reliable number parsing when CSV numbers contain digit group marks (eg thousands separators). - The CSV reader's verbose "assignment" debug output is now at level 9. # 1.19.1 2020-09-07 - Fix alignment of coloured numbers (#1345, #1349, Stephen Morgan) - Fix a regression in account type autodetection for accounts with capitalised names. (#1341) - Allow megaparsec 9 # 1.19 2020-09-01 ## general - When parsing dates, the year is now required to have at least four digits. So eg we no longer accept `200/1/1` as a valid date, it would need to be written `0200/1/1`. This was done for.. reasons, and is experimental; let us know if it causes you trouble. - The --color/--colour=WHEN command line option, support for the NO_COLOR environment variable, and smarter autodetection of colour terminals have been added (#1296) - Command line options taking a numeric argument are now validated more carefully, preventing issues with unexpected negatives or Int overflow. (Stephen Morgan) - In queries, you can now specify a quarter like `2020q1` or `q4` (the q is case-insensitive). (#1247, Henning Thieleman, Stephen Morgan) - In report intervals, `fortnightly` has been added as a synonym for `biweekly`. (Stephen Morgan) - -t and -l command line flags have been added as short forms of --tree and --flat (#1286) - All reports displaying accounts now choose flat mode by default (Stephen Morgan) - Reports now show at most 2 commodities of multicommodity amounts, unless the --no-elide flag is used. This helps keep them readable by default, since multicolumn, multicommodity balance reports otherwise tend to become very wide, especially in tree mode. - Numbers with more than 255 decimal places, which we do not support, now give an error instead of silently misparsing. (#1326) - Digit groups are now limited to at most 255 digits each. (#1326) - Account aliases (on command line or in journal) containing a bad regular expression now give a more detailed error message. - A tab character could get parsed as part of a commodity symbol, with confusing results. This no longer happens. (#1301, Dmitry Astapov) - Debug output is now organised better by debug level. The levels are: 0. normal command output only (no warnings) 1. useful warnings & most common troubleshooting info (valuation, eg) 2. common troubleshooting info, more detail 3. report options selection 4. report generation 5. report generation, more detail 6. input file reading 7. input file reading, more detail 8. command line parsing 9. any other rarely needed or more in-depth info - Added a missing lower bound for aeson, making cabal installs more reliable. (#1268) - lib: parseAmountQueryTerm: allow whitespace around arg parts (#1312) Whitespace around the operator, sign, or number is now tolerated. ## commands - account,bal,bs,cf,is: --drop now also works in tree mode (Stephen Morgan) - add: fix an error in the command line help (arguments are inputs, not a query) - aregister: a new command showing a transaction-oriented account register, like hledger-ui, hledger-web, or your bank statement. Each line represents a whole transaction in one account, unlike the register command which shows individual postings possibly from multiple accounts. You might prefer aregister when reconciling real-world asset/liability accounts, and register when reviewing detailed revenues/expenses. (#1294) - bal,bs,cf,is: boring parents are now elided by default in tabular balance reports too, like single-column reports. (Stephen Morgan) - bal,bs,cf,is: monthly column headings are no longer elided to just the short month name, if multiple years are being displayed. - bal --budget's column headings are now end dates rather than periods when appropriate (ie with --cumulative or --historical). - bs,cf,is: -%/--no-total no longer forces --no-total (Stephen Morgan) - bs,cf,is: --no-total now hides subtotals as well as the grand total (Stephen Morgan) - codes: a new command for listing transaction codes - print: a new `sql` output format has been added (Dmitry Astapov) - roi: errors are now shown without a call stack - tags: add --parsed flag, hide empties without --empty. With the --parsed flag, all tags or values are shown in the order they are parsed from the input data, including duplicates. With -E/--empty, any blank/empty values will also be shown, otherwise they are omitted. ## journal format - account directives can specify a new `Cash` account type. This is a subtype of `Asset`, denoting accounts which should be displayed in `cashflow` reports. - The built-in regular expressions for choosing default account types have been tweaked, and documentation for account types has been improved. ## csv format - Inferring the appropriate default field separator based on file extension (, for .csv, ; for .ssv, \t for .tsv) now works as documented. - Conditional rule patterns can now be grouped with the `&` (AND) operator, allowing more powerful matching. (Michael Sanders) - Invalid csv rules files now give clearer parse error messages. (Dmitry Astapov) - "If tables", a compact bulk format for conditional rules, have been added. (Dmitry Astapov) - csv conversion with a lot of conditional rules is now faster (Dmitry Astapov) # 1.18.1 2020-06-21 - journal: document recursive wildcards - by default, value reports work as in 1.17; to infer market prices from transactions, add the new --infer-value flag. (#1239, #1253) - organise debug output better - print: amounts in csv output now have commodity symbol, digit group separators and prices removed (Dmitry Astapov) # 1.18 2020-06-07 ## General - The --forecast flag now takes an optional argument (--forecast=PERIODICEXPR), allowing periodic transactions to start/end on any date and to overlap recorded transactions. (#835, #1236) (Dmitry Astapov) - An upper case file extension no longer confuses file format detection. (#1225) - In the commands list, redundant source scripts are now hidden properly when a corresponding .com/.exe file exists. (#1225) - We now show `..` instead of `-` to indicate date ranges, eg in report titles, to stand out more from hyphenated dates. (Stephen Morgan) - Period expressions (eg in -p, date:, and periodic rules) now accept `to`, `until`, `-`, or `..` as synonyms. (Stephen Morgan) - When parsing amounts, whitespace between sign and number is now allowed. - A clearer error message is shown on encountering a malformed regular expression. ## commands - commands allowing different output formats now list their supported formats accurately in --help (#689) - commands allowing JSON output now actually produce JSON (#689) - bal, bs: show .. (not ,,) in report titles, like other reports ## journal format - We now also infer market prices from transactions, like Ledger. See https://hledger.org/hledger.html#market-prices (#1239). Upgrade note: this means value reports (-V, -X etc.) can give different output compared to hledger 1.17. If needed, you can prevent this by adding a P directive declaring the old price, on or after the date of the transaction causing the issue. - The include directive now accepts a file format prefix, like the -f/--file option. This works with glob patterns too, applying the prefix to each path. This can be useful when included files don't have the standard file extension, eg: include timedot:2020*.md - We now accept (and ignore) Ledger-style lot dates (`[DATE]`) and four lot price forms (`{PRICE}`, `{{PRICE}}`, `{=PRICE}`, `{{=PRICE}}`), anywhere after the posting amount but before any balance assertion. - We now accept Ledger-style parenthesised "virtual posting costs" (`(@)`, `(@@)`). In hledger these are equivalent to the unparenthesised form. - The unbalanced transaction error message is clearer, especially when postings all have the same sign, and is split into multiple lines for readability. ## csv format - You can now generate up to 99 postings in a transaction. (Vladimir Sorokin) - You can now generate postings with an explicit 0 amount. (#1112) - For each posting, when both numbered and unnumbered amount assignments are active (eg: both `amount` and `amount1`), we ignore the unnumbered ones. This makes it easier to override old `amount` rules. - Fix a 1.17.1 regression involving amount-in/amount-out. (#1226) - Assigning too many non-zero or zero values to a posting amount now gives a clearer error. (#1226) # 1.17.1.1 2020-03-19 - update bounds after some belated hledger-* version bumps # 1.17.1 2020-03-19 - csv: amount1 no longer forces a second posting or second posting amount. The "special handling for pre 1.17 rules" should now be less noticeable. amount1/amount2 no longer force a second posting or explicit amounts on both postings. (Only amount/amount-in/amount-out do that.) Error messages and handling of corner cases may be more robust, also. - journal: a commodity directive without decimal mark now gives a more verbose error message with examples - journal: inclusive balance assignments now work (#1207) - require newer Decimal, math-functions libs to ensure consistent rounding behaviour, even when built with old GHCs/snapshots. hledger uses banker's rounding (rounds to nearest even number, eg 0.5 displayed with zero decimal places is "0"). # 1.17 2020-03-01 ## General - hledger's default date format is now YYYY-MM-DD (ISO-8601 dates). (Brian Wignall, Jakob Schöttl, Simon Michael) - Drop the file format auto-detection feature. For a long time hledger has auto-detected the file format when it's not known, eg when reading from a file with unusual extension (like .dat or .txt), or from standard input (-f-), or when using the include directive (which currently ignores file extensions). This was done by trying all readers until one succeeded. This worked well in practice. But recent changes to timedot format have made this kind of auto-detection unreliable. (timedot and journal formats overlap). For predictability and to minimise confusion, hledger will no longer guess; when there's no file extension or reader prefix available, it always assumes journal format. To specify one of the other formats, you must use its standard file extension (`.timeclock`, `.timedot`, `.csv`, `.ssv`, `.tsv`), or a reader prefix (`-f csv:foo.txt`, `-f timedot:-`). Experimental, feedback welcome. - Fix extra $ symbol (Mateus Furquim) - --output-format now rejects invalid formats - Numbers in JSON output now provide a floating point Number representation as well as our native Decimal object representation, since the later can sometimes contain 255-digit integers. The floating point numbers can have up to 10 decimal digits (and an unbounded number of integer digits.) Experimental, suggestions needed. (#1195) - Fix finding latest date in queryEndDate Or queries and simplify date comparison code. (Stephen Morgan) - Fix issue 457. (Jacek Generowicz) Issue #457 pointed out that commands such as hledger ui 'amt:>200' failed. This was because the process of dispatching from `hledger ui` to `hledger-ui` (note addition of `-`) lost the quotes around `amt:>20` and the `>` character was interpreted as a shell redirection operator, rather than as part of the argument. The machinery for quoting or escaping arguments which contain characters which require quoting or escaping (thus far whitespace and quotes) already existed. This solution simply adds shell stdio redirection characters to this set. ## commands - add: you can use `<` to undo and redo previous inputs (Gaith Hallak) - bs, cf, is, bal, print, reg: support json output - bs, cf, is: fix excess subreport columns in csv output - bs, cf, is, bal: fix an issue with border intersections in --pretty-tables output. (Eric Mertens) - close: fix a rounding bug that could generate unbalanced transactions. (#1164) - close: hide cost prices by default, show them with --show-costs. close no longer preserves costs (transaction prices) unless you ask it to, since that can generate huge entries when there are many foreign currency/investment transactions. (#1165) - close: equity amounts are omitted by default, for simpler entries; -x/--explicit shows them (usually causing more postings). (#1165) - close: --interleaved generates equity postings alongside each closed account, making troubleshooting easier. - close: "equity:opening/closing balances" is now the default closing and opening account. - close: --close-desc/--open-desc customise the closing/opening transaction descriptions. (#1165) - close: some --open*/--close* flags have been simplified for memorability: --closing -> --close --opening -> --open --close-to -> --close-acct --open-from -> --open-acct The old flags are accepted as hidden aliases, and deprecated. (#1165) - print, register: a new valuation type, --value=then, shows the market value at each posting's date. - print: -V/-X/--value now imply -x/--explicit, as -B/--cost does. This avoids a bug where print -V of a transaction with an implicit commodity conversion would convert only some of its postings to value. ## journal format - The include directive no longer tries all readers. It now picks just one, based on the included file's extension, defaulting to journal. (It doesn't yet handle a reader prefix.) - The default commodity (D) directive now limits display precision too. (#1187) D directives are now fully equivalent to commodity directives for setting a commodity's display style. (Previously it couldn't limit the number of decimal places.) When both kinds of directive exist, commodity directives take precedence. When there are multiple D directives in the journal, only the last one affects display style. ## csv format - Conditional blocks can now match single fields. \o/ - The experimental --separator command line option has been dropped, replaced a new `separator` directive in CSV rule files. (Aleksandar Dimitrov) Also the `.tsv` and `.ssv` file extensions are now recognised, and set the default `separator` to TAB and semicolon respectively. (#1179) - Allow manual assignment of the "expenses:unknown" account name. (#1192) - CSV rule keywords are now case insensitive. (Aleksandar Dimitrov) ## timeclock format - Misc. fixes making parsing more robust. (Jakob Schöttl) ## timedot format - More support for org mode: org headlines can now be used for date lines and timelog items (the stars are ignored). Also, any org headlines before the first date line are ignored. - You can now write a description after a date, which will be used in all of that day's transactions. # 1.16.2 2020-01-14 - add support for megaparsec 8 (#1175) - close: mention --close-to/--open-from in docs # 1.16.1 2019-12-03 - Drop unnecessary mtl-compat dependency - Fix building with GHC 8.0, 8.2 # 1.16 2019-12-01 ## General - add support for GHC 8.8, base-compat 0.11 (#1090) - drop support for GHC 7.10 - The benchmark suite has been disabled. - The --anon flag now also anonymises transaction codes and account names declared with account directives. (Mykola Orliuk) (#901) ## commands - balance/bs/cf/is: balance commands now support the -%/--percent flag to show amounts as percentages of the column's total. (Michael Kainer) If there are multiple commodities involved in a report hledger bails with an error message. This can be avoided by using -B/--cost. Also note that if one uses -% with the balance command the chances are high that all numbers are 0. This is due to the fact that by default balance sums up to zero. If one wants to use -% in a meaningful way with balance one has to add a query. In order to keep the implementation as simple as possible --tree has no influence over how the percentages are calculated, i.e., the percentages always represent the fraction of the columns total. If one wants to know the percentages relative to a parent account, one has to use a query to narrow down the accounts. - balance: --budget no longer errors when there is neither budget nor transactions in the report period (Dmitry Astapov) - balance: --budget has improved debug output (shows budget txns) (Dmitry Astapov) - check-dates: now sets the exit status code (Amitai Burstein) - close: no longer strips zeroes after the decimal mark, and preserves parseable output (#1137) - close: the --close-to, --open-from options allow closing/opening account names to be chosen - import: create the journal if missing, like the add command Streamlines import/migration instructions. - import: --catchup marks all transactions imported, without importing - import: more informative output: mention the input files, also show a message when nothing was imported - prices: show price amounts with proper display style; always show full precision - roi: don't give an error with empty input data (Dmitry Astapov) - tests: unit tests are now run by tasty, and show coloured output by default (#1090). Test running options have changed, see the command help. Some unit tests have been collapsed, so the reported test count has dropped a little. ## journal format - Fixed: wrong dates generated by certain periodic transaction rules, eg "~ every 12 months from 2019/04". (Dmitry Astapov) (#1085) ## csv format CSV conversion is now more powerful (#1095, Dmitry Astapov, Simon Michael): - A variable number of postings can be generated, from zero to nine. (#627, #1095) - In conditional blocks, `skip` can be used to skip one or more records after a pattern match, or the new `end` rule can be used to skip all remaining records. (#1076) - The new `balance-type` CSV rule controls which kind of balance assertions are generated (=, ==, =*, ==*) - Postings with balance assignments can be generated. (#1000) - Both the amount-in/amount-out fields having a non-empty value is now accepted, as long as one of them is zero. (#570) - Line feeds/carriage returns in (quoted) CSV values are now converted to spaces during conversion. (#416, #841) - Field assignments can now unset a field (eg a posting can be suppressed by assigning no value to its account). - CSV records with varying lengths are now allowed; short records will be padded with empty fields as needed. This allows us to handle eg exported Google spreadsheets, where trailing empty fields are omitted. - Journals generated from CSV are now finalised and checked like ordinary journals (#1000). So invalid transactions generated from CSV will be rejected, amount styles will be standardised etc. - Fixed: we no longer add an extra (third) space between description and comment. - Fixed: whitespace on the line after an if block no longer causes misparsing. (#1120) - Fixed: an empty field assignment no longer consumes the next line. (#1001) - Fixed: interpolation of field names containing punctuation now works. - Docs have been rewritten and clarified. Migration notes: - When `print`ing from CSV, there is now one less space between transaction descriptions and comments, which may generate noisy diffs if you are comparing old and new reports. diff -w (--ignore-all-space) will filter these out. - CSV rules now give you more freedom to generate any journal entries you want, including malformed or unbalanced ones. The csv reader now checks the journal after conversion, so it will report any problems with the generated entries. - Balance assertions generated from CSV are not checked, currently. This is appropriate when you are downloading partial CSV data to be merged into your main journal. If you do need to check balance assertions right away, you can pipe through hledger again: $ hledger -f a.csv print | hledger -f- print # 1.15.2 2019-09-05 - -V and -X now respect a report end date (set with -e or -p or date:) when choosing the valuation date (which determines the market prices used). This is how -V works in hledger 1.14 and Ledger, and it means that -V isn't exactly equivalent to either --value=end or --value=now. Possibly some other corner cases in valuation have been fixed as well. "Effect of --value on reports" in the hledger manual has been updated and is more accurate. # 1.15.1 2019-09-02 - add commodities, descriptions, diff, notes, payees commands to manual # 1.15 2019-09-01 ## General - There is a new valuation option `--value=TYPE[,COMM]`, with backwards-compatible `-B/--cost`, `-V/--market`, `-X/--exchange=COMM` variants. These provide control over valuation date (#329), and inference of indirect market prices (similar to Ledger's -X) (#131). Experimental. - Market valuation (-V/-X/--value) is now much faster (#999): +-------------------------------------------++--------------+--------------+ | || hledger-1.14 | hledger-1.15 | +===========================================++==============+==============+ | -f examples/10000x1000x10.journal bal -Y || 2.43 | 2.44 | | -f examples/10000x1000x10.journal bal -YV || 44.91 | 6.48 | | -f examples/10000x1000x10.journal reg -Y || 4.60 | 4.15 | | -f examples/10000x1000x10.journal reg -YV || 61.09 | 7.21 | +-------------------------------------------++--------------+--------------+ - How date options like `-M` and `-p` interact has been updated and clarified. (Jakob Schöttl) (#1008, #1009, #1011) - Restore `--aux-date` and `--effective` as `--date2` aliases (#1034). These Ledger-ish spellings were dropped over the years, to improve `--help`'s layout. Now we support them again, as semi-hidden flags (`--help` doesn't list them, but they are mentioned in `--date2`'s help). ## commands - add, web: on Windows, trying to add transactions to a file path containing trailing periods (eg `hledger add -f Documents.\.hledger.journal`) now gives an error, since this could cause data loss otherwise (#1056). This affects the add command and hledger-web's add form. - bal: --budget: don't always convert to cost. - bal: --budget: don't show a percentage when budgeted and actual amounts are in different commodities. - bal/bs/bse: `-H/--historical` or `--cumulative` now disables `-T/--row-total` (#329). Multiperiod balance reports which show end balances (eg, `bal -MH` or `bs -M`) no longer show a Totals column, since summing end balances generally doesn't make sense. - bs: show end date(s) in title, not transactions date span (#1078) Compound balance reports showing ending balances (eg balancesheet), now show the ending date (single column) or range of ending dates (multi column) in their title. ,, (double comma) is used rather than - (hyphen) to suggest a sequence of discrete dates rather than a continuous span. - close: preserve transaction prices (costs) accurately (#1035). The generated closing/opening transactions were collapsing/misreporting the costs in balances involving multiple costs. Now, each separately-priced amount gets its own posting. (And only the last of these (for each commodity) gets a balance assertion.) Also the equity posting's amount is now always shown explicitly, which in multicommodity situations means that multiple equity postings are shown. The upshot is that a balance -B report will be unchanged after the closing & opening transactions generated by the close command. - descriptions, payees, notes commands added (Caleb Maclennan) - diff: Gabriel Ebner's hledger-diff is now a built in command, and https://github.com/gebner/hledger-diff is deprecated. - help: don't require a journal file - print: now also canonicalises the display style of balance assertion amounts (#1042) - reg: show negative amounts in red, like balance and Ledger - reg: fix `--average`, broken since 1.12 (#1003) - stats: show count of market prices (P directives), and the commodities covered - tags: add --values flag to list tag values. - tags: now runs much faster when there many tags ## journal format - Transactions and postings generated/modified by periodic transaction rules and/or transaction modifier rules are now marked with tags (`generated-transaction`, `generated-posting`, `modified`) for easier troubleshooting and filtering. ## csv format - When interpolating CSV values, outer whitespace is now stripped. This removes a potential snag in amount field assignments (#1051), and hopefully is harmless and acceptable otherwise. - We no longer add inter-field spaces in CSV error messages. Some CSV errors would show the problem record, eg: 2000-01-01,a,"1" with extra spaces added, eg: the CSV record is: "2000-01-01", "a", "1" which was inaccurate and not valid RFC-4180 CSV format. - CSV parse errors are human-readable again (broken since 1.11) (#1038) - CSV rules now allow the amount to be unassigned, if there is an assignment to "balance" (generating a balance assignment in this case). (#1000) # 1.14.2 2019-03-20 - require easytest <0.3 to fix build issue - fix some CSV parse errors which weren't in human readable format # 1.14.1 2019-03-01 - fix missing Commodities.txt build error # 1.14 2019-03-01 - journal: subaccount-including balance assertions have been added, with syntax =* and ==* (experimental) (#290) - new commodities command lists commodity symbols - new --invert option flips sign of amounts in reports # 1.13.2 (2019/02/04) - print, register: restore the accidentally dropped -o, -O flags (#967) # 1.13.1 (2019/02/02) - stop depending on here to avoid haskell-src-meta/stackage blockage. # 1.13 (2019/02/01) - cli: reorganised commands list. Addons now have a + prefix. - cli: the command line help and manual section for all hledger's commands are now consistent, and generated from the same source. - cli: comprehensive bash completion support is now provided (in shell-completion/). See how-to in the Cookbook. (Jakob Schöttl) - balance --budget: budget amounts now aggregate hierarchically, like account balances. Unbudgeted accounts can be shown with -E/--empty (along with zero-balance accounts), and the --show-budgeted flag has been dropped. (Dmitry Astapov) - balance: new --transpose flag switches the rows and columns of tabular balance reports (in txt and csv output formats). (Dmitry Astapov) - close: generated balance assertions now have exact amounts with all decimal digits, ignoring display precision. Also, balance assertion amounts will no longer contain prices. (#941, #824, #958) - files: now shows up in the commands list - import: be silent when there's nothing to import - roi: percentages smaller than 0.01% are displayed as zero (Dmitry Astapov) - stats, ui: correct file order is preserved when using --auto (#949) - journal: account directive: the account name can now be followed by a comment on the same line - journal: account directive: account types for the bs/bse/cf/is commands can now be set with a `type:` tag, whose value is `Asset`, `Liability`, `Equity`, `Revenue`, `Expense`, `A`, `L`, `E`, `R` or `X` (case-insensitive). The previous syntax (`account assets A`) is now deprecated. - journal: account directive: account sort codes like `account 1000` (introduced in 1.9, deprecated in 1.11) are no longer supported. - journal: transaction modifiers (auto postings) can affect periodic transactions (--auto can add postings to transactions generated with --forecast). (Dmitry Astapov) - journal: balance assertion errors now show exact amounts with all decimal digits. Previously it was possible, in case of a commodity directive limiting the display precision, to have a balance assertion error with asserted and actual amounts looking the same. (#941) - journal: fixed a periodic transaction parsing failure (#942) (Dmitry Astapov) # 1.12.1 (2018/12/03) - roi: use math-functions lib instead of statistics, be more stackage nightly compatible # 1.12 (2018/12/02) - install script: ensure a new-enough version of stack; more informative output - build with GHC 8.6/base-4.12 (Peter Simons) - add required upper bound for statistics (Samuel May) - --anon anonymises more thoroughly (including linked original postings) (Moritz Kiefer) - unbalanced transaction errors now include location info (Mykola Orliuk) - accounts command: --drop also affects the default flat output, without needing an explicit --flat flag - accounts command: the --codes flag has been dropped - accounts command: filtering by non-account-name queries now works - add command: fix transaction rendering regression during data entry and in journal file - balance command: fix wrongful eliding of zero-balance parent accounts in tree mode (Dmitry Astapov) - journal format, bs/bse/cf/is commands: account directives can declare account types (#877) Previously you had to use one of the standard english account names (assets, liabilities..) for top-level accounts, if you wanted them to appear in the right place in the balancesheet, balancesheetequity, cashflow or incomestatement reports. Now you can use your preferred account names, and use account directives to declare which accounting class (Asset, Liability, Equity, Revenue or eXpense) an account (and its subaccounts) belongs to, by writing one of the letters A, L, E, R, X after the account name, after two or more spaces. This syntax may change (see issue). Experimental. Currently we allow unlimited account type declarations anywhere in the account tree. So you could declare a liability account somewhere under assets, and maybe a revenue account under that, and another asset account even further down. In such cases you start to see oddities like accounts appearing in multiple places in a tree-mode report. I have left it this way for now in case it helps with, eg, modelling contra accounts, or combining multiple files each with their own account type declarations. (In that scenario, if we only allowed type declarations on top-level accounts, or only allowed a single account of each type, complications seem likely.) - journal format: periodic transaction rules now require a double space separator. In periodic transaction rules which specify a transaction description or same-line transaction comment, this must be separated from the period expression by two or more spaces, to prevent ambiguous parsing. Eg this will parse correctly as "monthly" thanks to the double space: ~ monthly In 2020 we'll end this monthly transaction. - journal format: exact/complete balance assertions (Samuel May). A stronger kind of balance assertion, written with a double equals sign, asserts an account's complete account balance, not just the balance in one commodity. (But only if it is a single-commodity balance, for now.) Eg: 1/1 (a) A 1 (a) B 1 (a) 0 = A 1 ; commodity A balance assertion, succeeds (a) 0 == A 1 ; complete balance assertion, fails - journal format: account directives now allow whitespace or a comment after the account name - journal format: using \~ for home directory in include directives now works (#896) (Mykola Orliuk) - journal format: prevent misleading parse error messages with cyclic include directives (#853) (Alex Chen) - journal format: transaction modifier multipliers handle total-priced amounts correctly (#928). Multipliers (*N) in transaction modifier rules did not multiply total-priced amounts properly. Now the total prices are also multiplied, keeping the transaction balanced. - journal format: do amount inference/balance assignments/assertions before transaction modifiers (#893, #908) (Jesse Rosenthal) Previously, transaction modifier (auto postings) rules were applied before missing amounts were inferred. This meant amount multipliers could generate too many missing-amount postings, making the transaction unbalanceable (#893). Now, missing amount inference (and balance assignments, and balance assertions, which are interdependent) are done earlier, before transaction modifier rules are applied (#900, #903). Also, we now disallow the combination of balance assignments and transaction modifier rules which both affect the same account, which could otherwise cause confusing balance assertion failures (#912). (Because assignments now generate amounts to satisfy balance assertions before transaction modifier rules are applied (#908).) - journal format: periodic transaction rules are now aware of Y default year directives. (#892) Ie when a default year Y is in effect, they resolve partial or relative dates using Y/1/1 as the reference date, rather than today's date. # 1.11.1 (2018/10/06) - fix wrong transaction rendering in balance assertion errors and when using the add command # 1.11 (2018/9/30) - The default display order of accounts is now influenced by the order of account directives. Accounts declared by account directives are displayed first (top-most), in declaration order, followed by undeclared accounts in alphabetical order. Numeric account codes are no longer used, and are ignored and considered deprecated. So if your accounts are displaying in a weird order after upgrading, and you want them alphabetical like before, just sort your account directives alphabetically. - Account sorting (by name, by declaration, by amount) is now more robust and supported consistently by all commands (accounts, balance, bs..) in all modes (tree & flat, tabular & non-tabular). - close: new --opening/--closing flags to print only the opening or closing transaction - files: a new command to list included files - prices: query arguments are now supported. Prices can be filtered by date, and postings providing transaction prices can also be filtered. - rewrite: help clarifies relation to print --auto (#745) - roi: a new command to compute return on investment, based on hledger-irr - test: has more verbose output, more informative failure messages, and no longer tries to read the journal - csv: We use a more robust CSV lib (cassava) and now support non-comma separators, eg --separator ';' (experimental, this flag will probably become a CSV rule) (#829) - csv: interpolated field names in values are now properly case insensitive, so this works: fields ...,Transaction_Date,... date %Transaction_Date - journal: D (default commodity) directives no longer break multiplier amounts in transaction modifiers (AKA automated postings) (#860) - journal: "Automated Postings" have been renamed to "Transaction Modifiers". - journal: transaction comments in transaction modifier rules are now parsed correctly. (#745) - journal: when include files form a cycle, we give an error instead of hanging. - upper-case day/month names in period expressions no longer give an error (#847, #852) # 1.10 (2018/6/30) - journal: many parse error messages have become more informative, and some now show the source line and error location. - journal: ;tag: is no longer parsed as a tag named ";tag" (#655) - journal: transaction price amounts having their own price amounts is now a parse error - journal: amounts with space as digit group separator and trailing whitespace now parse correctly (#780) - journal: in amounts containing digits and a single space, the space is now interpreted as a digit group separator, not a decimal separator (#749) - journal: in commodity/format/D directives, the amount must now include a decimal separator. When more precise control is needed over number parsing, our recommended solution is commodity directives. Commodity directives that don't specify the decimal separator leave things ambiguous, increasing the chance of misparsing numbers. In some cases it could cause amounts with a decimal point to be parsed as if with a digit group separator, so 1.234 became 1234. It seems the simple and really only way to do this reliably is to require an explicit decimal point character. Most folks probably do this already. Unfortunately, it makes another potential incompatibility with ledger and beancount journals. But the error message will be clear and easy to work around. - journal: directives currently have diverse and somewhat tricky semantics, especially with multiple files. The manual now describes their behaviour precisely. - journal: `alias` and `apply account` directives now affect `account` directives (#825) - journal: periodic transactions can now have all the usual transaction fields (status mark, code, description, comment), for generating more expressive forecast transactions. - journal: forecast transactions now have the generating period expression attached as a tag named "recur". - journal: periodic transactions now start on the first instance of the recurring date, rather than the day after the last regular transaction (#750) - journal: periodic transaction rules now allow period expressions relative to today's date - csv: amount-in/amount-out errors are more detailed - balance: --drop is now ignored when not in flat mode, rather than producing a corrupted report (#754) - budget: --drop now preserves the top-level account in --budget reports - register: in CSV output, the code field is now included (#746) - smart dates now allow the YYYYMM format, and are better documented - use hledger-lib 1.10 # 1.9.1 (2018/4/30) - use hledger-lib 1.9.1 - budget (balance --budget): monthly columns are displayed in the proper order. This fixes a regression in 1.9. - budget: budgets can be built from periodic transactions with different intervals again. In 1.9, budgets were restricted to a single interval, but this was a mistake. This restores the 1.5 behaviour. - budget: budget reports are more intuitive and much less likely to produce no output. - budget: when no report interval is specified, a budget report for the whole journal period is shown. - budget: periodic transactions and the requested report period can each have their own start/end dates, and the resulting report will span the union of those periods, showing zeroes where data is missing. - budget: total row and total/average columns are now calculated correctly - budget: actual, percentage, and goal amounts are now aligned in columns for better readability (usually, unless numbers get huge). - budget: combining --budget and --sort-amount is not yet supported and now gives an error. - csv: handle "-%amount" in a rule when the CSV amount is parenthesised (#736) - journal: automated postings are now generated early, before journal finalisation, so they are present for amount inference, transaction balancing, and balance assertions (#729) - journal: automated postings are now inserted right after the posting that triggered them (#729) - cli: command-line account aliases are now applied early, before journal finalisation, so they are equivalent to alias directives in the journal (#730) - journal: inferred amounts now have the appropriate standard amount style applied (setting the precision correctly, eg). (#737) - journal: when checking for balanced transactions, amount styles declared with commodity directives are also used (previously only inferred amount styles were). # 1.9 (2018/3/31) - support ghc 8.4, latest deps - journal: account directives can define a numeric account code to customize sorting. bal/bs/cf/is will sort accounts by account code, if any, then account name. - journal: support scientific number notation (#704, #706) - csv: reading a CSV file containing no records is no longer an error - cli: when the system text encoding is UTF-8, ignore any UTF-8 BOM prefix found when reading files. (Paypal's new CSV has this BOM prefix, causing a confusing parse error.) - cli: tabular reports no longer have a trailing blank line added. (This allows omitting the ">=0" delimiters in our functional tests, making them easier to read and maintain.) - acc: the accounts command now has --declared and --used flags - bal: the --invert flag flips all signs - bal: --drop now works with CSV output - bal/bs/bse/cf/is: show overall report span in title - bal/bs/bse/cf/is: show short month names as headings in monthly reports - bal/bs/bse/cf/is: these commands can now generate HTML output - bal/bs/is/cf: drop short name and indent fields from multicolumn CSV - bs/bse/cf/is: these, the "financial statement" commands, now show normal income, liability and equity balances as positive numbers. Negative numbers now indicate a contra-balance (eg an overdrawn checking account), a net loss, or a negative net worth. This makes these reports more like conventional financial statements, and easier to read and share with others. (Other commands, like balance, have not changed.) (experimental) - bs/cf/is: always show a tabular report, even with no report interval. Previously you would get a simple borderless report like the original balance command. Less code, fewer bugs. - bs/bse/cf/is: in CSV output, don't repeat the headings row for each subreport - budget: warn that CSV output with bal --budget is unimplemented - budget: bal --budget shows budget goals even with no or zero actual amounts. Makes budget reports more intuitive, at the cost of a temporary hack which may misorder columns in some cases (if actual and budget activity occur in a different range of columns). - budget: --budget uses only periodic txns with the selected interval.\ Budgets with different interval, eg a daily and weekly budget, are independent. - budget: show mostly fixed-width columns for readability - budget: fix bug where a budget report could include budget goals ending on the day before the report start date (splitSpan issue) - close: the equity command has been renamed to close. It now ignores any begin date (it always closes historical end balances). It also ignores --date2. # 1.5 (2017/12/31) - --auto adds Ledger-style automated postings to transactions (Dmitry Astapov, Mykola Orliuk) - --forecast generates Ledger-style periodic transactions in the future (Dmitry Astapov, Mykola Orliuk) - -V/--value uses today's market prices by default, not those of last transaction date. #683, #648 - add: suggest implied (parent) and declared (by account directives) account names also - bal: --budget shows performance compared to budget goals defined with periodic transactions. Accounts with budget goals are displayed folded (depth-clipped) at a depth matching the budget specification. Unbudgeted accounts are hidden, or with --show-unbudgeted, shown at their usual depth. (Dmitry Astapov) - import: the output of --dry-run is now valid journal format - print: -B shows converted amounts again, as in 1.1, even without -x. #551 (Mykola Orliuk, Simon Michael) - tag: the first argument now filters tag names, additional arguments filter transactions (#261) - remove upper bounds on all but hledger* and base (experimental) # 1.4 (2017/9/30) - cli: a @FILE argument reads flags & args from FILE, one per line - cli: reorganized commands list, added some new command aliases: - accounts: a - balance: b - print: p, txns - register: r - cli: accept -NUM as a shortcut for --depth=NUM (eg: -2) - cli: improve command-line help for --date2 (#604) - cli: make --help and -h the same, drop --man and --info for now (#579) - help: offers multiple formats, accepts topic substrings. The separate info/man commands have been dropped. help now chooses an appropriate documentation format as follows: - it uses info if available, - otherwise man if available, - otherwise $PAGER if defined, - otherwise less if available, - otherwise it prints on stdout - (and it always prints on stdout when piped). You can override this with the `--info`/`--man`/`--pager`/`--cat` flags. (#579) - bal/bs/cf/is: --sort-amount/-S sorts by largest amount instead of account name - bs/cf/is: support --output-file and --output-format=txt\|csv The CSV output should be reasonably ok for dragging into a spreadsheet and reformatting. - bal/bs/cf/is: consistent double space between columns, consistent single final blank line. Previously, amounts wider than the column headings would be separated by only a single space. - bs/is: don't let an empty subreport disable the grand totals (fixes #588) - cf: exclude asset accounts with ":fixed" in their name (Christian G. Warden, Simon Michael, #584) - new balancesheetequity command: like balancesheet but also shows equity accounts (Nicholas Niro) - new import command: adds new transactions seen in one or more input files to the main journal file - print: --new shows only transactions added since last time (saves state in .latest.JOURNALFILE file) - new tags command: lists tags in matched transactions - most addons formerly shipped in bin/ are now builtin commands. These include: check-dates, check-dupes, equity, prices, print-unique, register-match, rewrite. - refactor: new Commands module and subdirectory. Builtin commands are now gathered more tightly in a single module, Hledger.Cli.Commands, facilitating change. The legacy "convert" command has been dropped. - refactor: BalanceView -> CompoundBalanceCommand - deps: drop support for directory < 1.2 - deps: allow ansi-terminal 0.7 - deps: drop oldtime flag, require time 1.5+ - deps: simplify shakespeare bounds - deps: remove ghc < 7.6 support # 1.3.1 (2017/8/25) - bs/is: don't let an empty subreport disable the grand totals (#588) - allow megaparsec 6 (#594) - allow megaparsec-6.1 (Hans-Peter Deifel) - restore upper bounds on hledger packages # 1.3 (2017/6/30) The "uncleared" transaction/posting status, and associated UI flags and keys, have been renamed to "unmarked" to remove ambiguity and confusion. This means that we have dropped the `--uncleared` flag, and our `-U` flag now matches only unmarked things and not pending ones. See the issue and linked mail list discussion for more background. (#564) Also the -P short flag has been added for --pending, and the -U/-P/-C flags can be combined. bs/is: fix "Ratio has zero denominator" error (#535) bs/is/cf: fix --flat (#552) (Justin Le, Simon Michael) bal/bs/is/cf: show negative amounts in red (Simon Michael, Justin Le). These commands now shows negative amounts in red, when hledger detects that ANSI codes are supported, (ie when TERM is not "dumb" and stdout is not being redirected or piped). print: show pending mark on postings (fixes #563). A pending mark on postings is now displayed, just like a cleared mark. Also there will now be a space between the mark and account name. print: amounts are now better aligned, eg when there are posting status marks or virtual postings # 1.2 (2017/3/31) ## CLI "hledger" and "hledger -h" now print a better organised commands list and general usage message respectively (#297). The common reporting flags can now be used anywhere on the command line. Fixed deduplication of addons in commands list. Fixed ugly stack traces in command line parse error messages. The -V/--value flag is now a global report flag, so it works with balance, print, register, balancesheet, incomestatement, cashflow, etc. (Justin Le) The `--pivot` global reporting option replaces all account names with the value of some other field or tag. It has been improved, eg: - we don't add the field/tag name name as a prefix - when pivoting on a tag, if the tag is missing we show a blank (rather than showing mixed tag values and account names) - a pipe character delimiter may be used in descriptions to get a more accurate and useful payee report (`hledger balance --pivot payee`) options cleanups ## Addons Easier installation: move add-ons and example scripts to bin/, convert to stack scripts, add a build script to install all deps, add some functional tests, test add-ons with Travis CI, add installation docs to download page. Improved docs: all addons now contain their own documentation. Most of them (all but hledger-budget) use a new reduced-boilerplate declaration format and can show short (-h) and long (--help) command line help. (Long help is declared with pre and postambles to the generated options help, short help is that truncated at the start of the hledger common flags.) `hledger` now shows a cleaner list of addon commands, showing only the compiled version of an addon when both source and compiled versions are in $PATH. (Addons with .exe extension or no extension are considered compiled. Modification time is not checked, ie, an old compiled addon will override a newer source version. If there are three or more versions of an addon, all are shown. ) New addons added/included: - autosync - example symlink to ledger-autosync - budget - experimental budget reporting command supporting Ledger-like periodic transactions and automated transactions (Mykola Orliuk) - chart - pie-chart-generating prototype, a repackaging of the old hledger-chart tool - check - more powerful balance assertions (Michael Walker) - check-dupes - find accounts sharing the same leaf name (Stefano Rodighiero) - prices - show all market price records (Mykola Orliuk) - register-match - a helper for ledger-autosync's deduplication, finds best match for a transaction description The equity command now always generates a valid journal transaction, handles prices better, and adds balance assertions (Mykola Orliuk). The rewrite command is more robust and powerful (Mykola Orliuk): - in addition to command-line rewrite options, it understands rewrite rules defined in the journal, similar to Ledger's automated transactions (#99). Eg: = ^income (liabilities:tax) *.33 = expenses:gifts budget:gifts *-1 assets:budget *1 - it can generate diff output, allowing easier review of the proposed changes, and safe modification of original journal files (preserving file-level comments and directives). Eg: hledger-rewrite --diff Agency --add-posting 'Expenses:Taxes *0.17' | patch - rewrites can affect multiple postings in a transaction, not just one. - posting-specific dates are handled better ## balance A new --pretty-tables option uses unicode characters for rendering table borders in multicolumn reports (#522) (Moritz Kiefer) ## balancesheet/cashflow/incomestatement These commands are now more powerful, able to show multicolumn reports and generally having the same features as the balance command. (Justin Le) balancesheet has always ignored a begin date specified with a `-b` or `-p` option; now it also ignores a begin date specified with a `date:` query. (Related discussion at #531) ## print The output of print is now always a valid journal (fixes #465) (Mykola Orliuk). print now tries to preserves the format of implicit/explicit balancing amounts and prices, by default. To print with all amounts explicit, use the new `--explicit/-x` flag (fixes #442). (Mykola Orliuk) Don't lose the commodity of zero amounts/zero balance assertions (fixes #475) (Mykola Orliuk) ## Misc Fix a regression in the readability of option parsing errors (#478) (Hans-Peter Deifel) Fix an example in Cli/Main.hs (Steven R. Baker) Allow megaparsec 5.2 (#503) # 1.1 (2016/12/31) ## balance - with -V, don't ignore market prices in the future (#453, #403) - with -V and multiple same-date market prices, use the last parsed not the highest price (#403) ## misc - fix non-existent "oldtime" dependency (#431) - extra/hledger-equity.hs now generates valid journal format when there are multiple commodities # 1.0.1 (2016/10/27) - allow megaparsec 5.0 or 5.1 - fix benchmark build failure (#423) # 1.0 (2016/10/26) ## add - suggest only one commodity at a time as default amount (#383) (since we currently can't input more than one at a time) ## balance - added --change flag for consistency - -H/--historical now also affects single-column balance reports with a start date (#392). This has the same effect as just omitting the start date, but adds consistency. - in CSV output, render amounts in one-line format (#336) ## balancesheet - fix an infinite loop (#393) ## print - in CSV output, fix and rename the transaction id field ## register - fix a sorting regression with --date2 (#326) - --average/-A is now affected by --historical/-H - added --cumulative flag for consistency - in CSV output, include the transaction id and rename the total field (#391) ## stats - fixed an issue with ordering of include files ## misc - --pivot option added, groups postings by tag instead of account (#323) (Malte Brandy) - --anon option added, obfuscates account names and descriptions (#265) (Brian Scott) (Only affects the hledger tool, for now.) - try to clarify balance/register's various report modes, kinds of "balance" displayed, and related options and language. - with multiple --change/--cumulative/--historical flags, use the last one instead of complaining - don't add the "d" suffix when displaying day periods - stack-ify extra/hledger-rewrite.hs ## misc - added GHC 8 support, dropped GHC 7.6 and 7.8 support. GHC 7.8 support could be restored with small code changes and a maintainer. - a cabal.project file has been added (Moritz Kiefer) - use hpack for maintaining cabal files (#371). Instead of editing cabal files directly, we now edit the less verbose and less redundant package.yaml files and let stack (or hpack) update the cabal files. We commit both the .yaml and .cabal files. - clean up some old cabal flags - tools/simplebench has been spun off as the quickbench package. - add Appveyor CI builds, provide up-to-date binaries for Windows - extra: add a bunch of CSV rules examples ## docs - the website is simpler, clearer, and more mobile-friendly. Docs are now collected on a single page and organised by type: getting started, reference, more. - reference docs have been split into one manual for each executable and file format. This helps with maintenance and packaging and also should make it easier to see what's available and to read just what you need. - manuals are now provided in html, plain text, man and info formats generated from the same source by a new Shake-based docs build system. (#292) - versioned manuals are provided on the website, covering recent releases and the latest dev version (#385, #387) - manuals are built in to the hledger executables, allowing easy offline reading on all platforms. PROG -h shows PROG's command-line usage PROG --help shows PROG's manual (fixed width) PROG --man shows PROG's manual with man (formatted/paged) PROG --info shows PROG's manual with info (hypertext) hledger help [TOPIC] shows any manual hledger man [TOPIC] shows any manual with man hledger info [TOPIC] shows any manual with info - the general and reporting options are now listed in all executable manuals. We assume any of them which are unsupported are harmlessly ignored. - demo.hledger.org is using beancount's example journal. This is the somewhat realistic example journal from the beancount project, tweaked for hledger. - minor copyedits (jungle-boogie) ## cli - parsing multiple input files is now robust. When multiple -f options are provided, we now parse each file individually rather than just concatenating them, so they can have different formats (#320). Note this also means that directives (like \`Y\` or \`alias\`) no longer carry over from one file to the next. - -I has been added as the short flag for --ignore-assertions (this is different from Ledger's CLI, but useful for hledger-ui). - parsing an argument-less --debug option is more robust 0.27 (2015/10/30) Account aliases: - Regular expression account aliases are now fast enough that you can use lots of them without slowing things down. They now take O(aliases x accounts) time, instead of O(aliases x transactions); also, regular expressions are no longer recompiled unnecessarily. Documentation: - Each hledger package now includes one or more man pages, generated from markdown by the mighty pandoc. Currently there are six: one for each main executable and each input file format. Currently these somewhat duplicate the manual on the website; this will be resolved somehow. (#282). - The site is now built with hakyll-std, a generic hakyll script. - hledger once again has a HCAR entry. Tools: - The hledger cabal files are now generated from package.yaml files by hpack, in principle, removing a lot of error-prone duplication and boilerplate. (In practice, both files are being updated manually for the moment, until hpack supports flags and conditional blocks.) - Time/allocation and heap profiling is working again, and easier: - `make quickprof-CMD` generates a profile for CMD, which runs against one of the sample journals. (CMD must be one word, enclosing in double quotes isn't working here for some reason). - `make quickheap-CMD` generates a heap profile for CMD, in hledgerprof.ps, and tries to open it in a viewer (currently the mac-friendly "open" executable, so you may need to adjust this in the makefile). As with quickprof, CMD must be one word and runs against one of the sample journals. - `make hledgerprof` builds the hledgerprof executable used for time/allocation profiling. `make hledgercov` builds the hledgercov executable used for coverage reports. - Travis CI now tests the build on each github push and announces status changes by email and on #hledger. Journal format: - Dates must now begin with a digit (not /, eg). - The comment directive longer requires an end comment, and will extend to the end of the file(s) without it. Command-line interface: - Output (balance reports, register reports, print output etc.) containing wide characters, eg chinese/japanese/korean characters, should now align correctly, when viewed in apps and fonts that show wide characters as double width (#242). - The argument for --depth or depth: must now be positive. add: - Journal entries are now written with all amounts explicit, to avoid losing price info (#283). - Fixed a bug which sometimes (when the same letter pair was repeated) caused it not to pick the most similar past transaction for defaults. balance: - There is now a -V/--value flag to report current market value (as in Ledger). It converts all reported amounts using their "default market price". "Market price" is the new name for "historical prices", defined with the P directive. The default market price for a commodity is the most recent one found in the journal on or before the report end date. Unlike Ledger, hledger's -V uses only the market prices recorded with P directives; it does not use the "transaction prices" recorded as part of posting amounts (which are used by -B/--cost). Also, using both -B and -V at the same time is supported. - Fixed a bug in amount normalization which caused amount styles (commodity symbol placement, decimal point character, etc.) to be lost in certain cases (#230, #276). - The balance command's --format option can now adjust the rendering style of multi-commodity amounts, if you begin the format string with one of: %_ - renders amounts on multiple lines, bottom-aligned (the default) %^ - renders amounts on multiple lines, top-aligned %, - renders amounts on one line, comma-separated - The balance report's final total (and the line above it) now adapt themselves to a custom --format. print: - The --match option prints the journal entry that best matches a description (ie whose description field is most similar to the value given, and if there are several equally similar, the most recent). This was originally an add-on I used to guess account names for ledger-autosync. It's nice for quickly looking up a recent transaction from a guessed or partial description. - print now always right-aligns the amounts in an entry, even when they are wider than 12 characters. (If there is a price, it's considered part of the amount for right-alignment.) register: - Amount columns now resize automatically, using more space if it's needed and available. 0.26 (2015/7/12) Account aliases: - Account aliases are once again non-regular-expression-based, by default. (#252) The regex account aliases added in 0.24 trip up people switching between hledger and Ledger. (Also they are currently slow). This change makes the old non-regex aliases the default; they are unsurprising, useful, and pretty close in functionality to Ledger's. The new regex aliases are still available; they must be enclosed in forward slashes. (Ledger effectively ignores these.) Journal format: - We now parse, and also print, journal entries with no postings, as proposed on the mail lists. These are not well-formed General Journal entries/transactions, but here is my rationale: - Ledger and beancount parse them - if they are parsed, they should be printed - they provide a convenient way to record (and report) non-transaction events - they permit more gradual introduction and learning of the concepts. So eg a beginner can keep a simple journal before learning about accounts and postings. - Trailing whitespace after a `comment` directive is now ignored. Command-line interface: - The -f/file option may now be used multiple times. This is equivalent to concatenating the input files before running hledger. The add command adds entries to the first file specified. Queries: - real: (no argument) is now a synonym for real:1 - tag: now matches tag names with a regular expression, like most other queries - empty: is no longer supported, as it overlaps a bit confusingly with amt:0. The --empty flag is still available. - You can now match on pending status (#250) A transaction/posting status of ! (pending) was effectively equivalent to * (cleared). Now it's a separate state, not matched by --cleared. The new Ledger-compatible --pending flag matches it, and so does --uncleared. The relevant search query terms are now status:*, status:! and status: (the old status:1 and status:0 spellings are deprecated). Since we interpret --uncleared and status: as "any state except cleared", it's not currently possible to match things which are neither cleared nor pending. activity: - activity no longer excludes 0-amount postings by default. add: - Don't show quotes around the journal file path in the "Creating..." message, for consistency with the subsequent "Adding..." message. balancesheet: - Accounts beginning with "debt" or now also recognised as liabilities. print: - We now limit the display precision of inferred prices. (#262) When a transaction posts to two commodities without specifying the conversion price, we generate a price which makes it balance (cf https://hledger.org/hledger.html#prices). The print command showed this with full precision (so that manual calculations with the displayed numbers would look right), but this sometimes meant we showed 255 digits (when there are multiple postings in the commodity being priced, and the averaged unit price is an irrational number). In this case we now set the price's display precision to the sum of the (max) display precisions of the commodities involved. An example: hledgerdev -f- print <<< 1/1 c C 10.00 c C 11.00 d D -320.00 >>> 2015/01/01 c C 10.00 @ D 15.2381 c C 11.00 @ D 15.2381 d D -320.00 >>>=0 There might still be cases where this will show more price decimal places than necessary. - We now show inferred unit prices with at least 2 decimal places. When inferring prices, if the commodities involved have low display precisions, we don't do a good job of rendering accurate-looking unit prices. Eg if the journal doesn't use any decimal places, any inferred unit prices are also displayed with no decimal places, which makes them look wrong to the user. Now, we always give inferred unit prices a minimum display precision of 2, which helps a bit. register: - Postings with no amounts could give a runtime error in some obscure case, now fixed. stats: - stats now supports -o/--outputfile, like register/balance/print. - An O(n\^2) performance slowdown has been fixed, it's now much faster on large journals. +--------------------------------------++--------+--------+ | || 0.25 | 0.26 | +======================================++========+========+ | -f data/100x100x10.journal stats || 0.10 | 0.16 | | -f data/1000x1000x10.journal stats || 0.45 | 0.21 | | -f data/10000x1000x10.journal stats || 58.92 | 2.16 | +--------------------------------------++--------+--------+ Miscellaneous: - The June 30 day span was not being rendered correctly; fixed. (#272) - The bench script invoked by "cabal bench" or "stack bench" now runs some simple benchmarks. You can get more accurate benchmark times by running with --criterion. This will usually give much the same numbers and takes much longer. Or with --simplebench, it benchmarks whatever commands are configured in bench/default.bench. This mode uses the first "hledger" executable in $PATH. - The deprecated shakespeare-text dependency has been removed more thoroughly. 0.25.1 (2015/4/29) - timelog: support the description field (#247) 0.25 (2015/4/7) - GHC 7.10 compatibility (#239) - build with terminfo support on POSIX systems by default On non-windows systems, we now build with terminfo support by default, useful for detecting terminal width and other things. This requires the C curses dev libraries, which makes POSIX installation slightly harder; if it causes problems you can disable terminfo support with the new `curses` cabal flag, eg: cabal install -f-curses ... (or cabal might try this automatically, I'm not sure). - register: use the full terminal width, respect COLUMNS, allow column width adjustment On POSIX systems, register now uses the full terminal width by default. Specifically, the output width is set from: 1. a --width option 2. or a COLUMNS environment variable (NB: not the same as a bash shell var) 3. or on POSIX (non-windows) systems, the current terminal width 4. or the default, 80 characters. Also, register's --width option now accepts an optional description column width following the overall width (--width WIDTH\[,DESCWIDTH\]). This also sets the account column width, since the available space (WIDTH-41) is divided up between these two columns. Here's a diagram: <--------------------------------- width (W) ----------------------------------> date (10) description (D) account (W-41-D) amount (12) balance (12) DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA Examples: $ hledger reg # use terminal width on posix $ hledger reg -w 100 # width 100, equal description/account widths $ hledger reg -w 100,40 # width 100, wider description $ hledger reg -w $COLUMNS,100 # terminal width and set description width - balance: new -T/--row-total and -A/--average options In multicolumn balance reports, -T/--row-total now shows a row totals column and -A/--average shows a row averages column. This helps eg to see monthly average expenses (hledger bal \^expenses -MA). NB our use of -T deviates from Ledger's UI, where -T sets a custom final total expression. - balance: -N is now short for --no-total - balance: fix partially-visible totals row with --no-total A periodic (not using --cumulative or --historical) balance report with --no-total now hides the totals row properly. - journal, csv: comment lines can also start with * As in Ledger. This means you can embed emacs org/outline-mode nodes in your journal file and manipulate it like an outline. 0.24.1 (2015/3/15) - journal: fix balance accumulation across assertions (#195) A sequence of balance assertions asserting first one commodity, then another, then the first again, was not working. - timelog: show hours with two decimal places instead of one (#237) - in weekly reports, simplify week 52's heading like the others - disallow trailing garbage in a number of parsers Trailing garbage is no longer ignored when parsing the following: balance --format option, register --width option, hledger-rewrite options, hledger add's inputs, CSV amounts, posting amounts, posting dates in tags. - allow utf8-string-1 (fpco/stackage/#426) 0.24 (2014/12/25) General: - fix redundant compilation when cabal installing the hledger packages - switch to Decimal for representing amounts (#118) - report interval headings (eg in balance, register reports) are shown compactly when possible - general speedups Journal format: - detect decimal point and digit groups more robustly (#196) - check that transaction dates are followed by whitespace or newline - check that dates use a consistent separator character - balance assertions now are specific to a single commodity, like Ledger (#195) - support multi-line comments using "comment", "end comment" directives, like Ledger CSV format: - reading CSV data from stdin now works better - the rules file include directive is now relative to the current file's directory (#198) - the original order of same-day transactions is now usually preserved (if the records appear to be in reverse date order, we reverse them before finally sorting by transaction date) - CSV output is now built in to the balance, print, and register commands, controlled by -O/--output-format (and -o/--output-file, see below) CLI: - the --width and --debug options now require their argument (#149) - when an option is repeated, the last value takes precedence (#219). This is helpful eg for customising your reporting command aliases on the fly. - smart dates (used in -p/-b/-e/date:/date2:) now must use a consistent separator character, and must be parseable to the end - output destination and format selection is now built in to the balance, print and register commands, controlled by -o/--output-file and -O/--output-format options. Notes: - -o - means stdout - an output file name suffix matching a supported format will also set the output format, unless overridden by --output-format - commands' supported output formats are listed in their command-line help. Two formats are currently available: txt (the default) and csv. - balance assertions can be disabled with --ignore-assertions Account aliases: - all matching account aliases are now applied, not just one directive and one option - account aliases now match by case insensitive regular expressions matching anywhere in the account name - account aliases can replace multiple occurrences of the pattern within an account name - an account alias replacement pattern can reference matched groups with \N Queries: - date:/date2: with a malformed date now reports an error instead of being ignored - amt: now supports >= or <= - clarify status: docs and behaviour; \"*\" is no longer a synonym for "1" (fixes #227) balance: - fix: in tree mode, --drop is ignored instead of showing empty account names - a depth limit of 0 now shows summary items with account name "...", instead of an empty report (#206) - in multicolumn balance reports, -E now also shows posting-less accounts with a non-zero balance during the period (in addition to showing leading & trailing empty columns) - in multicolumn reports, multi-commodity amounts are rendered on one line for better layout (#186) - multicolumn reports' title now includes the report span register: - runs faster with large output - supports date2:, and date:/date2: combined with --date2, better (fixes #201, #221, #222) - a depth limit of 0 now shows summary items (see balance) - -A/--average now implies -E/--empty - postings with multi-commodity amounts are now top-aligned, like Ledger Extra commands: - hledger-equity: fix end date in title; print closing entry too - hledger-check-dates: added 0.23.3 (2014/9/12) - allow text 1.2+ (#207) 0.23.2 (2014/5/8) - register: also fix date sorting of postings (#184) 0.23.1 (2014/5/7) - register: fix a refactoring-related regression that the tests missed: if transactions were not ordered by date in the journal, register could include postings before the report start date in the output. (#184) - add: don't apply a default commodity to amounts on entry (#138) - cli: options before the add-on command name are now also passed to it (#182) - csv: allow the first name in a fields list to be empty (#178) - csv: don't validate fields count in skipped lines (#177) 0.23 (2014/5/1) Journal format: - A # (hash) in column 0 is now also supported for starting a top-level journal comment, like Ledger. - The "too many missing amounts" error now reminds about the 2-space rule. - Fix: . (period) is no longer parsed as a valid amount. - Fix: default commodity directives no longer limit the maximum display precision (#169). - Fix: + before an amount is no longer parsed as part of the commodity (#181). CLI: - Command-line help cleanups, layout improvements. - Descriptions are shown for known add-ons in the command list. - Command aliases have been simplified. - Add-ons can now have any of these file extensions: none, hs, lhs, pl, py, rb, rkt, sh, bat, com, exe. - Add-ons are displayed without their file extensions when possible. - Add-ons with the same name as a built-in command or alias are ignored. - Fix: add-on detection and invocation now works on windows. - Fix: add-ons with digits in the name are now found. - Fix: add-on arguments containing a single quote now work. - Fix: when -- is used to hide add-on options from the main program, it is no longer passed through as an add-on argument. Queries: - The currency/commodity query prefix (sym:) has been renamed to cur:. - Currency/commodity queries are applied more strongly in register and balance reports, filtering out unwanted currencies entirely. Eg hledger balance cur:'$' now reports only the dollar amounts even if there are multi-currency transactions or postings. - Amount queries like amt:N, amt:N, where N is not 0, now do an unsigned comparison of the amount and N. That is, they compare the absolute magnitude. To do a signed comparison instead, write N with its sign (eg amt:+N, amt:<+N, amt:>-N). - Fix: amount queries no longer give false positives on multi-commodity amounts. accounts: - An accounts command has been added, similar to Ledger's, for listing account names in flat or hierarchical mode. add: - Tab completion now works at all prompts, and will insert the default if the input area is empty. - Account and amount defaults are more robust and useful. - Transactions may also be completed by the enter key, when there are no more default postings. - Input prompts are displayed in a different colour when supported. balance: - Balance reports in flat mode now always show exclusive (subaccount-excluding) balances. - Balance reports in flat mode with --depth now aggregate deeper accounts at the depth limit instead of excluding them. - Multicolumn reports in flat mode now support --drop. - Multicolumn balance reports can now show the account hierarchy with --tree. - Multicolumn report start/end dates are adjusted to encompass the displayed report periods, so the first and last periods are "full" and comparable to the others. - Fix: zero-balance leaf accounts below a non-zero-balance parent are no longer always shown (#170). - Fix: multicolumn reports now support --date2 (cf #174). balancesheet, cashflow, incomestatement: - These commands now support --flat and --drop. print: - Tag queries (tag:) will now match a transaction if any of its postings match. register: - The --display option has been dropped. To see an accurate running total which includes the prior starting balance, use --historical/-H (like balance). - With a report interval, report start/end dates are adjusted to encompass the displayed periods, so the first and last periods are "full" and comparable to the others. - Fix: --date2 now works with report intervals (fixes #174). Miscellaneous: - Default report dates now derive from the secondary dates when --date2 is in effect. - Default report dates now notice any posting dates outside the transaction dates' span. - Debug output improvements. - New add-on example: extra/hledger-rewrite.hs, adds postings to matched entries. - Compatible with GHC 7.2 (#155) - GHC 7.8, shakespeare 2 0.22.2 (2014/4/16) - display years before 1000 with four digits, not three - avoid pretty-show to build with GHC < 7.4 - allow text 1.1, drop data-pprint to build with GHC 7.8.x 0.22.1 (2014/1/6) and older: see https://hledger.org/release-notes or doc/release-notes.md. hledger-1.32.3/README.md0000644000000000000000000000043614434445206012670 0ustar0000000000000000# hledger The command-line interface for the hledger accounting system. Its basic function is to read a plain text file describing financial transactions and produce useful reports. See also: the [project README](https://hledger.org/README.html) and [home page](https://hledger.org). hledger-1.32.3/bench/10000x1000x10.journal0000644000000000000000000454013614112603266015553 0ustar00000000000000002013-01-01 transaction 1 1 1 1:2 -1 2013-01-02 transaction 2 1:2:3 1 1:2:3:4 -1 2013-01-03 transaction 3 1:2:3:4:5 1 1:2:3:4:5:6 -1 2013-01-04 transaction 4 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2013-01-05 transaction 5 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2013-01-06 transaction 6 b 1 b:c -1 2013-01-07 transaction 7 b:c:d 1 b:c:d:e -1 2013-01-08 transaction 8 b:c:d:e:f 1 b:c:d:e:f:10 -1 2013-01-09 transaction 9 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2013-01-10 transaction 10 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2013-01-11 transaction 11 15 1 15:16 -1 2013-01-12 transaction 12 15:16:17 1 15:16:17:18 -1 2013-01-13 transaction 13 15:16:17:18:19 1 15:16:17:18:19:1a -1 2013-01-14 transaction 14 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2013-01-15 transaction 15 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2013-01-16 transaction 16 1f 1 1f:20 -1 2013-01-17 transaction 17 1f:20:21 1 1f:20:21:22 -1 2013-01-18 transaction 18 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2013-01-19 transaction 19 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2013-01-20 transaction 20 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2013-01-21 transaction 21 29 1 29:2a -1 2013-01-22 transaction 22 29:2a:2b 1 29:2a:2b:2c -1 2013-01-23 transaction 23 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2013-01-24 transaction 24 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2013-01-25 transaction 25 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2013-01-26 transaction 26 33 1 33:34 -1 2013-01-27 transaction 27 33:34:35 1 33:34:35:36 -1 2013-01-28 transaction 28 33:34:35:36:37 1 33:34:35:36:37:38 -1 2013-01-29 transaction 29 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2013-01-30 transaction 30 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2013-01-31 transaction 31 3d 1 3d:3e -1 2013-02-01 transaction 32 3d:3e:3f 1 3d:3e:3f:40 -1 2013-02-02 transaction 33 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2013-02-03 transaction 34 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2013-02-04 transaction 35 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2013-02-05 transaction 36 47 1 47:48 -1 2013-02-06 transaction 37 47:48:49 1 47:48:49:4a -1 2013-02-07 transaction 38 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2013-02-08 transaction 39 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2013-02-09 transaction 40 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2013-02-10 transaction 41 51 1 51:52 -1 2013-02-11 transaction 42 51:52:53 1 51:52:53:54 -1 2013-02-12 transaction 43 51:52:53:54:55 1 51:52:53:54:55:56 -1 2013-02-13 transaction 44 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2013-02-14 transaction 45 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2013-02-15 transaction 46 5b 1 5b:5c -1 2013-02-16 transaction 47 5b:5c:5d 1 5b:5c:5d:5e -1 2013-02-17 transaction 48 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2013-02-18 transaction 49 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2013-02-19 transaction 50 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2013-02-20 transaction 51 65 1 65:66 -1 2013-02-21 transaction 52 65:66:67 1 65:66:67:68 -1 2013-02-22 transaction 53 65:66:67:68:69 1 65:66:67:68:69:6a -1 2013-02-23 transaction 54 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2013-02-24 transaction 55 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2013-02-25 transaction 56 6f 1 6f:70 -1 2013-02-26 transaction 57 6f:70:71 1 6f:70:71:72 -1 2013-02-27 transaction 58 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2013-02-28 transaction 59 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2013-03-01 transaction 60 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2013-03-02 transaction 61 79 1 79:7a -1 2013-03-03 transaction 62 79:7a:7b 1 79:7a:7b:7c -1 2013-03-04 transaction 63 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2013-03-05 transaction 64 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2013-03-06 transaction 65 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2013-03-07 transaction 66 83 1 83:84 -1 2013-03-08 transaction 67 83:84:85 1 83:84:85:86 -1 2013-03-09 transaction 68 83:84:85:86:87 1 83:84:85:86:87:88 -1 2013-03-10 transaction 69 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2013-03-11 transaction 70 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2013-03-12 transaction 71 8d 1 8d:8e -1 2013-03-13 transaction 72 8d:8e:8f 1 8d:8e:8f:90 -1 2013-03-14 transaction 73 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2013-03-15 transaction 74 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2013-03-16 transaction 75 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2013-03-17 transaction 76 97 1 97:98 -1 2013-03-18 transaction 77 97:98:99 1 97:98:99:9a -1 2013-03-19 transaction 78 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2013-03-20 transaction 79 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2013-03-21 transaction 80 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2013-03-22 transaction 81 a1 1 a1:a2 -1 2013-03-23 transaction 82 a1:a2:a3 1 a1:a2:a3:a4 -1 2013-03-24 transaction 83 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2013-03-25 transaction 84 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2013-03-26 transaction 85 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2013-03-27 transaction 86 ab 1 ab:ac -1 2013-03-28 transaction 87 ab:ac:ad 1 ab:ac:ad:ae -1 2013-03-29 transaction 88 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2013-03-30 transaction 89 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2013-03-31 transaction 90 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2013-04-01 transaction 91 b5 1 b5:b6 -1 2013-04-02 transaction 92 b5:b6:b7 1 b5:b6:b7:b8 -1 2013-04-03 transaction 93 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2013-04-04 transaction 94 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2013-04-05 transaction 95 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2013-04-06 transaction 96 bf 1 bf:c0 -1 2013-04-07 transaction 97 bf:c0:c1 1 bf:c0:c1:c2 -1 2013-04-08 transaction 98 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2013-04-09 transaction 99 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2013-04-10 transaction 100 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2013-04-11 transaction 101 c9 1 c9:ca -1 2013-04-12 transaction 102 c9:ca:cb 1 c9:ca:cb:cc -1 2013-04-13 transaction 103 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2013-04-14 transaction 104 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2013-04-15 transaction 105 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2013-04-16 transaction 106 d3 1 d3:d4 -1 2013-04-17 transaction 107 d3:d4:d5 1 d3:d4:d5:d6 -1 2013-04-18 transaction 108 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2013-04-19 transaction 109 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2013-04-20 transaction 110 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2013-04-21 transaction 111 dd 1 dd:de -1 2013-04-22 transaction 112 dd:de:df 1 dd:de:df:e0 -1 2013-04-23 transaction 113 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2013-04-24 transaction 114 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2013-04-25 transaction 115 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2013-04-26 transaction 116 e7 1 e7:e8 -1 2013-04-27 transaction 117 e7:e8:e9 1 e7:e8:e9:ea -1 2013-04-28 transaction 118 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2013-04-29 transaction 119 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2013-04-30 transaction 120 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2013-05-01 transaction 121 f1 1 f1:f2 -1 2013-05-02 transaction 122 f1:f2:f3 1 f1:f2:f3:f4 -1 2013-05-03 transaction 123 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2013-05-04 transaction 124 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2013-05-05 transaction 125 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2013-05-06 transaction 126 fb 1 fb:fc -1 2013-05-07 transaction 127 fb:fc:fd 1 fb:fc:fd:fe -1 2013-05-08 transaction 128 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2013-05-09 transaction 129 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2013-05-10 transaction 130 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2013-05-11 transaction 131 105 1 105:106 -1 2013-05-12 transaction 132 105:106:107 1 105:106:107:108 -1 2013-05-13 transaction 133 105:106:107:108:109 1 105:106:107:108:109:10a -1 2013-05-14 transaction 134 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2013-05-15 transaction 135 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2013-05-16 transaction 136 10f 1 10f:110 -1 2013-05-17 transaction 137 10f:110:111 1 10f:110:111:112 -1 2013-05-18 transaction 138 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2013-05-19 transaction 139 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2013-05-20 transaction 140 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2013-05-21 transaction 141 119 1 119:11a -1 2013-05-22 transaction 142 119:11a:11b 1 119:11a:11b:11c -1 2013-05-23 transaction 143 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2013-05-24 transaction 144 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2013-05-25 transaction 145 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2013-05-26 transaction 146 123 1 123:124 -1 2013-05-27 transaction 147 123:124:125 1 123:124:125:126 -1 2013-05-28 transaction 148 123:124:125:126:127 1 123:124:125:126:127:128 -1 2013-05-29 transaction 149 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2013-05-30 transaction 150 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2013-05-31 transaction 151 12d 1 12d:12e -1 2013-06-01 transaction 152 12d:12e:12f 1 12d:12e:12f:130 -1 2013-06-02 transaction 153 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2013-06-03 transaction 154 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2013-06-04 transaction 155 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2013-06-05 transaction 156 137 1 137:138 -1 2013-06-06 transaction 157 137:138:139 1 137:138:139:13a -1 2013-06-07 transaction 158 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2013-06-08 transaction 159 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2013-06-09 transaction 160 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2013-06-10 transaction 161 141 1 141:142 -1 2013-06-11 transaction 162 141:142:143 1 141:142:143:144 -1 2013-06-12 transaction 163 141:142:143:144:145 1 141:142:143:144:145:146 -1 2013-06-13 transaction 164 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2013-06-14 transaction 165 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2013-06-15 transaction 166 14b 1 14b:14c -1 2013-06-16 transaction 167 14b:14c:14d 1 14b:14c:14d:14e -1 2013-06-17 transaction 168 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2013-06-18 transaction 169 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2013-06-19 transaction 170 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2013-06-20 transaction 171 155 1 155:156 -1 2013-06-21 transaction 172 155:156:157 1 155:156:157:158 -1 2013-06-22 transaction 173 155:156:157:158:159 1 155:156:157:158:159:15a -1 2013-06-23 transaction 174 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2013-06-24 transaction 175 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2013-06-25 transaction 176 15f 1 15f:160 -1 2013-06-26 transaction 177 15f:160:161 1 15f:160:161:162 -1 2013-06-27 transaction 178 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2013-06-28 transaction 179 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2013-06-29 transaction 180 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2013-06-30 transaction 181 169 1 169:16a -1 2013-07-01 transaction 182 169:16a:16b 1 169:16a:16b:16c -1 2013-07-02 transaction 183 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2013-07-03 transaction 184 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2013-07-04 transaction 185 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2013-07-05 transaction 186 173 1 173:174 -1 2013-07-06 transaction 187 173:174:175 1 173:174:175:176 -1 2013-07-07 transaction 188 173:174:175:176:177 1 173:174:175:176:177:178 -1 2013-07-08 transaction 189 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2013-07-09 transaction 190 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2013-07-10 transaction 191 17d 1 17d:17e -1 2013-07-11 transaction 192 17d:17e:17f 1 17d:17e:17f:180 -1 2013-07-12 transaction 193 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2013-07-13 transaction 194 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2013-07-14 transaction 195 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2013-07-15 transaction 196 187 1 187:188 -1 2013-07-16 transaction 197 187:188:189 1 187:188:189:18a -1 2013-07-17 transaction 198 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2013-07-18 transaction 199 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2013-07-19 transaction 200 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2013-07-20 transaction 201 191 1 191:192 -1 2013-07-21 transaction 202 191:192:193 1 191:192:193:194 -1 2013-07-22 transaction 203 191:192:193:194:195 1 191:192:193:194:195:196 -1 2013-07-23 transaction 204 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2013-07-24 transaction 205 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2013-07-25 transaction 206 19b 1 19b:19c -1 2013-07-26 transaction 207 19b:19c:19d 1 19b:19c:19d:19e -1 2013-07-27 transaction 208 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2013-07-28 transaction 209 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2013-07-29 transaction 210 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2013-07-30 transaction 211 1a5 1 1a5:1a6 -1 2013-07-31 transaction 212 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2013-08-01 transaction 213 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2013-08-02 transaction 214 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2013-08-03 transaction 215 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2013-08-04 transaction 216 1af 1 1af:1b0 -1 2013-08-05 transaction 217 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2013-08-06 transaction 218 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2013-08-07 transaction 219 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2013-08-08 transaction 220 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2013-08-09 transaction 221 1b9 1 1b9:1ba -1 2013-08-10 transaction 222 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2013-08-11 transaction 223 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2013-08-12 transaction 224 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2013-08-13 transaction 225 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2013-08-14 transaction 226 1c3 1 1c3:1c4 -1 2013-08-15 transaction 227 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2013-08-16 transaction 228 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2013-08-17 transaction 229 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2013-08-18 transaction 230 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2013-08-19 transaction 231 1cd 1 1cd:1ce -1 2013-08-20 transaction 232 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2013-08-21 transaction 233 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2013-08-22 transaction 234 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2013-08-23 transaction 235 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2013-08-24 transaction 236 1d7 1 1d7:1d8 -1 2013-08-25 transaction 237 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2013-08-26 transaction 238 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2013-08-27 transaction 239 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2013-08-28 transaction 240 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2013-08-29 transaction 241 1e1 1 1e1:1e2 -1 2013-08-30 transaction 242 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2013-08-31 transaction 243 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2013-09-01 transaction 244 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2013-09-02 transaction 245 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2013-09-03 transaction 246 1eb 1 1eb:1ec -1 2013-09-04 transaction 247 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2013-09-05 transaction 248 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2013-09-06 transaction 249 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2013-09-07 transaction 250 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2013-09-08 transaction 251 1f5 1 1f5:1f6 -1 2013-09-09 transaction 252 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2013-09-10 transaction 253 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2013-09-11 transaction 254 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2013-09-12 transaction 255 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2013-09-13 transaction 256 1ff 1 1ff:200 -1 2013-09-14 transaction 257 1ff:200:201 1 1ff:200:201:202 -1 2013-09-15 transaction 258 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2013-09-16 transaction 259 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2013-09-17 transaction 260 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2013-09-18 transaction 261 209 1 209:20a -1 2013-09-19 transaction 262 209:20a:20b 1 209:20a:20b:20c -1 2013-09-20 transaction 263 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2013-09-21 transaction 264 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2013-09-22 transaction 265 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2013-09-23 transaction 266 213 1 213:214 -1 2013-09-24 transaction 267 213:214:215 1 213:214:215:216 -1 2013-09-25 transaction 268 213:214:215:216:217 1 213:214:215:216:217:218 -1 2013-09-26 transaction 269 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2013-09-27 transaction 270 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2013-09-28 transaction 271 21d 1 21d:21e -1 2013-09-29 transaction 272 21d:21e:21f 1 21d:21e:21f:220 -1 2013-09-30 transaction 273 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2013-10-01 transaction 274 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2013-10-02 transaction 275 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2013-10-03 transaction 276 227 1 227:228 -1 2013-10-04 transaction 277 227:228:229 1 227:228:229:22a -1 2013-10-05 transaction 278 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2013-10-06 transaction 279 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2013-10-07 transaction 280 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2013-10-08 transaction 281 231 1 231:232 -1 2013-10-09 transaction 282 231:232:233 1 231:232:233:234 -1 2013-10-10 transaction 283 231:232:233:234:235 1 231:232:233:234:235:236 -1 2013-10-11 transaction 284 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2013-10-12 transaction 285 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2013-10-13 transaction 286 23b 1 23b:23c -1 2013-10-14 transaction 287 23b:23c:23d 1 23b:23c:23d:23e -1 2013-10-15 transaction 288 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2013-10-16 transaction 289 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2013-10-17 transaction 290 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2013-10-18 transaction 291 245 1 245:246 -1 2013-10-19 transaction 292 245:246:247 1 245:246:247:248 -1 2013-10-20 transaction 293 245:246:247:248:249 1 245:246:247:248:249:24a -1 2013-10-21 transaction 294 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2013-10-22 transaction 295 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2013-10-23 transaction 296 24f 1 24f:250 -1 2013-10-24 transaction 297 24f:250:251 1 24f:250:251:252 -1 2013-10-25 transaction 298 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2013-10-26 transaction 299 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2013-10-27 transaction 300 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2013-10-28 transaction 301 259 1 259:25a -1 2013-10-29 transaction 302 259:25a:25b 1 259:25a:25b:25c -1 2013-10-30 transaction 303 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2013-10-31 transaction 304 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2013-11-01 transaction 305 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2013-11-02 transaction 306 263 1 263:264 -1 2013-11-03 transaction 307 263:264:265 1 263:264:265:266 -1 2013-11-04 transaction 308 263:264:265:266:267 1 263:264:265:266:267:268 -1 2013-11-05 transaction 309 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2013-11-06 transaction 310 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2013-11-07 transaction 311 26d 1 26d:26e -1 2013-11-08 transaction 312 26d:26e:26f 1 26d:26e:26f:270 -1 2013-11-09 transaction 313 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2013-11-10 transaction 314 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2013-11-11 transaction 315 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2013-11-12 transaction 316 277 1 277:278 -1 2013-11-13 transaction 317 277:278:279 1 277:278:279:27a -1 2013-11-14 transaction 318 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2013-11-15 transaction 319 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2013-11-16 transaction 320 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2013-11-17 transaction 321 281 1 281:282 -1 2013-11-18 transaction 322 281:282:283 1 281:282:283:284 -1 2013-11-19 transaction 323 281:282:283:284:285 1 281:282:283:284:285:286 -1 2013-11-20 transaction 324 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2013-11-21 transaction 325 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2013-11-22 transaction 326 28b 1 28b:28c -1 2013-11-23 transaction 327 28b:28c:28d 1 28b:28c:28d:28e -1 2013-11-24 transaction 328 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2013-11-25 transaction 329 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2013-11-26 transaction 330 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2013-11-27 transaction 331 295 1 295:296 -1 2013-11-28 transaction 332 295:296:297 1 295:296:297:298 -1 2013-11-29 transaction 333 295:296:297:298:299 1 295:296:297:298:299:29a -1 2013-11-30 transaction 334 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2013-12-01 transaction 335 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2013-12-02 transaction 336 29f 1 29f:2a0 -1 2013-12-03 transaction 337 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2013-12-04 transaction 338 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2013-12-05 transaction 339 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2013-12-06 transaction 340 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2013-12-07 transaction 341 2a9 1 2a9:2aa -1 2013-12-08 transaction 342 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2013-12-09 transaction 343 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2013-12-10 transaction 344 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2013-12-11 transaction 345 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2013-12-12 transaction 346 2b3 1 2b3:2b4 -1 2013-12-13 transaction 347 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2013-12-14 transaction 348 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2013-12-15 transaction 349 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2013-12-16 transaction 350 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2013-12-17 transaction 351 2bd 1 2bd:2be -1 2013-12-18 transaction 352 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2013-12-19 transaction 353 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2013-12-20 transaction 354 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2013-12-21 transaction 355 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2013-12-22 transaction 356 2c7 1 2c7:2c8 -1 2013-12-23 transaction 357 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2013-12-24 transaction 358 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2013-12-25 transaction 359 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2013-12-26 transaction 360 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2013-12-27 transaction 361 2d1 1 2d1:2d2 -1 2013-12-28 transaction 362 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2013-12-29 transaction 363 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2013-12-30 transaction 364 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2013-12-31 transaction 365 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2014-01-01 transaction 366 2db 1 2db:2dc -1 2014-01-02 transaction 367 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2014-01-03 transaction 368 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2014-01-04 transaction 369 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2014-01-05 transaction 370 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2014-01-06 transaction 371 2e5 1 2e5:2e6 -1 2014-01-07 transaction 372 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2014-01-08 transaction 373 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2014-01-09 transaction 374 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2014-01-10 transaction 375 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2014-01-11 transaction 376 2ef 1 2ef:2f0 -1 2014-01-12 transaction 377 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2014-01-13 transaction 378 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2014-01-14 transaction 379 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2014-01-15 transaction 380 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2014-01-16 transaction 381 2f9 1 2f9:2fa -1 2014-01-17 transaction 382 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2014-01-18 transaction 383 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2014-01-19 transaction 384 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2014-01-20 transaction 385 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2014-01-21 transaction 386 303 1 303:304 -1 2014-01-22 transaction 387 303:304:305 1 303:304:305:306 -1 2014-01-23 transaction 388 303:304:305:306:307 1 303:304:305:306:307:308 -1 2014-01-24 transaction 389 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2014-01-25 transaction 390 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2014-01-26 transaction 391 30d 1 30d:30e -1 2014-01-27 transaction 392 30d:30e:30f 1 30d:30e:30f:310 -1 2014-01-28 transaction 393 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2014-01-29 transaction 394 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2014-01-30 transaction 395 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2014-01-31 transaction 396 317 1 317:318 -1 2014-02-01 transaction 397 317:318:319 1 317:318:319:31a -1 2014-02-02 transaction 398 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2014-02-03 transaction 399 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2014-02-04 transaction 400 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2014-02-05 transaction 401 321 1 321:322 -1 2014-02-06 transaction 402 321:322:323 1 321:322:323:324 -1 2014-02-07 transaction 403 321:322:323:324:325 1 321:322:323:324:325:326 -1 2014-02-08 transaction 404 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2014-02-09 transaction 405 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2014-02-10 transaction 406 32b 1 32b:32c -1 2014-02-11 transaction 407 32b:32c:32d 1 32b:32c:32d:32e -1 2014-02-12 transaction 408 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2014-02-13 transaction 409 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2014-02-14 transaction 410 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2014-02-15 transaction 411 335 1 335:336 -1 2014-02-16 transaction 412 335:336:337 1 335:336:337:338 -1 2014-02-17 transaction 413 335:336:337:338:339 1 335:336:337:338:339:33a -1 2014-02-18 transaction 414 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2014-02-19 transaction 415 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2014-02-20 transaction 416 33f 1 33f:340 -1 2014-02-21 transaction 417 33f:340:341 1 33f:340:341:342 -1 2014-02-22 transaction 418 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2014-02-23 transaction 419 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2014-02-24 transaction 420 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2014-02-25 transaction 421 349 1 349:34a -1 2014-02-26 transaction 422 349:34a:34b 1 349:34a:34b:34c -1 2014-02-27 transaction 423 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2014-02-28 transaction 424 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2014-03-01 transaction 425 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2014-03-02 transaction 426 353 1 353:354 -1 2014-03-03 transaction 427 353:354:355 1 353:354:355:356 -1 2014-03-04 transaction 428 353:354:355:356:357 1 353:354:355:356:357:358 -1 2014-03-05 transaction 429 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2014-03-06 transaction 430 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2014-03-07 transaction 431 35d 1 35d:35e -1 2014-03-08 transaction 432 35d:35e:35f 1 35d:35e:35f:360 -1 2014-03-09 transaction 433 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2014-03-10 transaction 434 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2014-03-11 transaction 435 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2014-03-12 transaction 436 367 1 367:368 -1 2014-03-13 transaction 437 367:368:369 1 367:368:369:36a -1 2014-03-14 transaction 438 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2014-03-15 transaction 439 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2014-03-16 transaction 440 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2014-03-17 transaction 441 371 1 371:372 -1 2014-03-18 transaction 442 371:372:373 1 371:372:373:374 -1 2014-03-19 transaction 443 371:372:373:374:375 1 371:372:373:374:375:376 -1 2014-03-20 transaction 444 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2014-03-21 transaction 445 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2014-03-22 transaction 446 37b 1 37b:37c -1 2014-03-23 transaction 447 37b:37c:37d 1 37b:37c:37d:37e -1 2014-03-24 transaction 448 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2014-03-25 transaction 449 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2014-03-26 transaction 450 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2014-03-27 transaction 451 385 1 385:386 -1 2014-03-28 transaction 452 385:386:387 1 385:386:387:388 -1 2014-03-29 transaction 453 385:386:387:388:389 1 385:386:387:388:389:38a -1 2014-03-30 transaction 454 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2014-03-31 transaction 455 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2014-04-01 transaction 456 38f 1 38f:390 -1 2014-04-02 transaction 457 38f:390:391 1 38f:390:391:392 -1 2014-04-03 transaction 458 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2014-04-04 transaction 459 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2014-04-05 transaction 460 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2014-04-06 transaction 461 399 1 399:39a -1 2014-04-07 transaction 462 399:39a:39b 1 399:39a:39b:39c -1 2014-04-08 transaction 463 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2014-04-09 transaction 464 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2014-04-10 transaction 465 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2014-04-11 transaction 466 3a3 1 3a3:3a4 -1 2014-04-12 transaction 467 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2014-04-13 transaction 468 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2014-04-14 transaction 469 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2014-04-15 transaction 470 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2014-04-16 transaction 471 3ad 1 3ad:3ae -1 2014-04-17 transaction 472 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2014-04-18 transaction 473 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2014-04-19 transaction 474 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2014-04-20 transaction 475 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2014-04-21 transaction 476 3b7 1 3b7:3b8 -1 2014-04-22 transaction 477 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2014-04-23 transaction 478 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2014-04-24 transaction 479 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2014-04-25 transaction 480 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2014-04-26 transaction 481 3c1 1 3c1:3c2 -1 2014-04-27 transaction 482 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2014-04-28 transaction 483 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2014-04-29 transaction 484 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2014-04-30 transaction 485 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2014-05-01 transaction 486 3cb 1 3cb:3cc -1 2014-05-02 transaction 487 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2014-05-03 transaction 488 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2014-05-04 transaction 489 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2014-05-05 transaction 490 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2014-05-06 transaction 491 3d5 1 3d5:3d6 -1 2014-05-07 transaction 492 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2014-05-08 transaction 493 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2014-05-09 transaction 494 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2014-05-10 transaction 495 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2014-05-11 transaction 496 3df 1 3df:3e0 -1 2014-05-12 transaction 497 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2014-05-13 transaction 498 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2014-05-14 transaction 499 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2014-05-15 transaction 500 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2014-05-16 transaction 501 1 1 1:2 -1 2014-05-17 transaction 502 1:2:3 1 1:2:3:4 -1 2014-05-18 transaction 503 1:2:3:4:5 1 1:2:3:4:5:6 -1 2014-05-19 transaction 504 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2014-05-20 transaction 505 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2014-05-21 transaction 506 b 1 b:c -1 2014-05-22 transaction 507 b:c:d 1 b:c:d:e -1 2014-05-23 transaction 508 b:c:d:e:f 1 b:c:d:e:f:10 -1 2014-05-24 transaction 509 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2014-05-25 transaction 510 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2014-05-26 transaction 511 15 1 15:16 -1 2014-05-27 transaction 512 15:16:17 1 15:16:17:18 -1 2014-05-28 transaction 513 15:16:17:18:19 1 15:16:17:18:19:1a -1 2014-05-29 transaction 514 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2014-05-30 transaction 515 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2014-05-31 transaction 516 1f 1 1f:20 -1 2014-06-01 transaction 517 1f:20:21 1 1f:20:21:22 -1 2014-06-02 transaction 518 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2014-06-03 transaction 519 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2014-06-04 transaction 520 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2014-06-05 transaction 521 29 1 29:2a -1 2014-06-06 transaction 522 29:2a:2b 1 29:2a:2b:2c -1 2014-06-07 transaction 523 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2014-06-08 transaction 524 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2014-06-09 transaction 525 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2014-06-10 transaction 526 33 1 33:34 -1 2014-06-11 transaction 527 33:34:35 1 33:34:35:36 -1 2014-06-12 transaction 528 33:34:35:36:37 1 33:34:35:36:37:38 -1 2014-06-13 transaction 529 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2014-06-14 transaction 530 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2014-06-15 transaction 531 3d 1 3d:3e -1 2014-06-16 transaction 532 3d:3e:3f 1 3d:3e:3f:40 -1 2014-06-17 transaction 533 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2014-06-18 transaction 534 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2014-06-19 transaction 535 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2014-06-20 transaction 536 47 1 47:48 -1 2014-06-21 transaction 537 47:48:49 1 47:48:49:4a -1 2014-06-22 transaction 538 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2014-06-23 transaction 539 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2014-06-24 transaction 540 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2014-06-25 transaction 541 51 1 51:52 -1 2014-06-26 transaction 542 51:52:53 1 51:52:53:54 -1 2014-06-27 transaction 543 51:52:53:54:55 1 51:52:53:54:55:56 -1 2014-06-28 transaction 544 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2014-06-29 transaction 545 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2014-06-30 transaction 546 5b 1 5b:5c -1 2014-07-01 transaction 547 5b:5c:5d 1 5b:5c:5d:5e -1 2014-07-02 transaction 548 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2014-07-03 transaction 549 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2014-07-04 transaction 550 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2014-07-05 transaction 551 65 1 65:66 -1 2014-07-06 transaction 552 65:66:67 1 65:66:67:68 -1 2014-07-07 transaction 553 65:66:67:68:69 1 65:66:67:68:69:6a -1 2014-07-08 transaction 554 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2014-07-09 transaction 555 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2014-07-10 transaction 556 6f 1 6f:70 -1 2014-07-11 transaction 557 6f:70:71 1 6f:70:71:72 -1 2014-07-12 transaction 558 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2014-07-13 transaction 559 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2014-07-14 transaction 560 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2014-07-15 transaction 561 79 1 79:7a -1 2014-07-16 transaction 562 79:7a:7b 1 79:7a:7b:7c -1 2014-07-17 transaction 563 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2014-07-18 transaction 564 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2014-07-19 transaction 565 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2014-07-20 transaction 566 83 1 83:84 -1 2014-07-21 transaction 567 83:84:85 1 83:84:85:86 -1 2014-07-22 transaction 568 83:84:85:86:87 1 83:84:85:86:87:88 -1 2014-07-23 transaction 569 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2014-07-24 transaction 570 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2014-07-25 transaction 571 8d 1 8d:8e -1 2014-07-26 transaction 572 8d:8e:8f 1 8d:8e:8f:90 -1 2014-07-27 transaction 573 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2014-07-28 transaction 574 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2014-07-29 transaction 575 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2014-07-30 transaction 576 97 1 97:98 -1 2014-07-31 transaction 577 97:98:99 1 97:98:99:9a -1 2014-08-01 transaction 578 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2014-08-02 transaction 579 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2014-08-03 transaction 580 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2014-08-04 transaction 581 a1 1 a1:a2 -1 2014-08-05 transaction 582 a1:a2:a3 1 a1:a2:a3:a4 -1 2014-08-06 transaction 583 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2014-08-07 transaction 584 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2014-08-08 transaction 585 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2014-08-09 transaction 586 ab 1 ab:ac -1 2014-08-10 transaction 587 ab:ac:ad 1 ab:ac:ad:ae -1 2014-08-11 transaction 588 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2014-08-12 transaction 589 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2014-08-13 transaction 590 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2014-08-14 transaction 591 b5 1 b5:b6 -1 2014-08-15 transaction 592 b5:b6:b7 1 b5:b6:b7:b8 -1 2014-08-16 transaction 593 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2014-08-17 transaction 594 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2014-08-18 transaction 595 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2014-08-19 transaction 596 bf 1 bf:c0 -1 2014-08-20 transaction 597 bf:c0:c1 1 bf:c0:c1:c2 -1 2014-08-21 transaction 598 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2014-08-22 transaction 599 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2014-08-23 transaction 600 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2014-08-24 transaction 601 c9 1 c9:ca -1 2014-08-25 transaction 602 c9:ca:cb 1 c9:ca:cb:cc -1 2014-08-26 transaction 603 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2014-08-27 transaction 604 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2014-08-28 transaction 605 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2014-08-29 transaction 606 d3 1 d3:d4 -1 2014-08-30 transaction 607 d3:d4:d5 1 d3:d4:d5:d6 -1 2014-08-31 transaction 608 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2014-09-01 transaction 609 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2014-09-02 transaction 610 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2014-09-03 transaction 611 dd 1 dd:de -1 2014-09-04 transaction 612 dd:de:df 1 dd:de:df:e0 -1 2014-09-05 transaction 613 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2014-09-06 transaction 614 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2014-09-07 transaction 615 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2014-09-08 transaction 616 e7 1 e7:e8 -1 2014-09-09 transaction 617 e7:e8:e9 1 e7:e8:e9:ea -1 2014-09-10 transaction 618 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2014-09-11 transaction 619 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2014-09-12 transaction 620 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2014-09-13 transaction 621 f1 1 f1:f2 -1 2014-09-14 transaction 622 f1:f2:f3 1 f1:f2:f3:f4 -1 2014-09-15 transaction 623 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2014-09-16 transaction 624 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2014-09-17 transaction 625 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2014-09-18 transaction 626 fb 1 fb:fc -1 2014-09-19 transaction 627 fb:fc:fd 1 fb:fc:fd:fe -1 2014-09-20 transaction 628 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2014-09-21 transaction 629 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2014-09-22 transaction 630 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2014-09-23 transaction 631 105 1 105:106 -1 2014-09-24 transaction 632 105:106:107 1 105:106:107:108 -1 2014-09-25 transaction 633 105:106:107:108:109 1 105:106:107:108:109:10a -1 2014-09-26 transaction 634 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2014-09-27 transaction 635 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2014-09-28 transaction 636 10f 1 10f:110 -1 2014-09-29 transaction 637 10f:110:111 1 10f:110:111:112 -1 2014-09-30 transaction 638 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2014-10-01 transaction 639 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2014-10-02 transaction 640 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2014-10-03 transaction 641 119 1 119:11a -1 2014-10-04 transaction 642 119:11a:11b 1 119:11a:11b:11c -1 2014-10-05 transaction 643 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2014-10-06 transaction 644 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2014-10-07 transaction 645 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2014-10-08 transaction 646 123 1 123:124 -1 2014-10-09 transaction 647 123:124:125 1 123:124:125:126 -1 2014-10-10 transaction 648 123:124:125:126:127 1 123:124:125:126:127:128 -1 2014-10-11 transaction 649 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2014-10-12 transaction 650 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2014-10-13 transaction 651 12d 1 12d:12e -1 2014-10-14 transaction 652 12d:12e:12f 1 12d:12e:12f:130 -1 2014-10-15 transaction 653 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2014-10-16 transaction 654 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2014-10-17 transaction 655 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2014-10-18 transaction 656 137 1 137:138 -1 2014-10-19 transaction 657 137:138:139 1 137:138:139:13a -1 2014-10-20 transaction 658 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2014-10-21 transaction 659 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2014-10-22 transaction 660 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2014-10-23 transaction 661 141 1 141:142 -1 2014-10-24 transaction 662 141:142:143 1 141:142:143:144 -1 2014-10-25 transaction 663 141:142:143:144:145 1 141:142:143:144:145:146 -1 2014-10-26 transaction 664 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2014-10-27 transaction 665 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2014-10-28 transaction 666 14b 1 14b:14c -1 2014-10-29 transaction 667 14b:14c:14d 1 14b:14c:14d:14e -1 2014-10-30 transaction 668 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2014-10-31 transaction 669 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2014-11-01 transaction 670 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2014-11-02 transaction 671 155 1 155:156 -1 2014-11-03 transaction 672 155:156:157 1 155:156:157:158 -1 2014-11-04 transaction 673 155:156:157:158:159 1 155:156:157:158:159:15a -1 2014-11-05 transaction 674 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2014-11-06 transaction 675 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2014-11-07 transaction 676 15f 1 15f:160 -1 2014-11-08 transaction 677 15f:160:161 1 15f:160:161:162 -1 2014-11-09 transaction 678 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2014-11-10 transaction 679 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2014-11-11 transaction 680 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2014-11-12 transaction 681 169 1 169:16a -1 2014-11-13 transaction 682 169:16a:16b 1 169:16a:16b:16c -1 2014-11-14 transaction 683 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2014-11-15 transaction 684 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2014-11-16 transaction 685 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2014-11-17 transaction 686 173 1 173:174 -1 2014-11-18 transaction 687 173:174:175 1 173:174:175:176 -1 2014-11-19 transaction 688 173:174:175:176:177 1 173:174:175:176:177:178 -1 2014-11-20 transaction 689 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2014-11-21 transaction 690 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2014-11-22 transaction 691 17d 1 17d:17e -1 2014-11-23 transaction 692 17d:17e:17f 1 17d:17e:17f:180 -1 2014-11-24 transaction 693 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2014-11-25 transaction 694 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2014-11-26 transaction 695 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2014-11-27 transaction 696 187 1 187:188 -1 2014-11-28 transaction 697 187:188:189 1 187:188:189:18a -1 2014-11-29 transaction 698 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2014-11-30 transaction 699 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2014-12-01 transaction 700 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2014-12-02 transaction 701 191 1 191:192 -1 2014-12-03 transaction 702 191:192:193 1 191:192:193:194 -1 2014-12-04 transaction 703 191:192:193:194:195 1 191:192:193:194:195:196 -1 2014-12-05 transaction 704 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2014-12-06 transaction 705 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2014-12-07 transaction 706 19b 1 19b:19c -1 2014-12-08 transaction 707 19b:19c:19d 1 19b:19c:19d:19e -1 2014-12-09 transaction 708 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2014-12-10 transaction 709 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2014-12-11 transaction 710 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2014-12-12 transaction 711 1a5 1 1a5:1a6 -1 2014-12-13 transaction 712 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2014-12-14 transaction 713 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2014-12-15 transaction 714 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2014-12-16 transaction 715 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2014-12-17 transaction 716 1af 1 1af:1b0 -1 2014-12-18 transaction 717 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2014-12-19 transaction 718 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2014-12-20 transaction 719 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2014-12-21 transaction 720 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2014-12-22 transaction 721 1b9 1 1b9:1ba -1 2014-12-23 transaction 722 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2014-12-24 transaction 723 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2014-12-25 transaction 724 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2014-12-26 transaction 725 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2014-12-27 transaction 726 1c3 1 1c3:1c4 -1 2014-12-28 transaction 727 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2014-12-29 transaction 728 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2014-12-30 transaction 729 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2014-12-31 transaction 730 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2015-01-01 transaction 731 1cd 1 1cd:1ce -1 2015-01-02 transaction 732 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2015-01-03 transaction 733 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2015-01-04 transaction 734 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2015-01-05 transaction 735 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2015-01-06 transaction 736 1d7 1 1d7:1d8 -1 2015-01-07 transaction 737 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2015-01-08 transaction 738 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2015-01-09 transaction 739 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2015-01-10 transaction 740 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2015-01-11 transaction 741 1e1 1 1e1:1e2 -1 2015-01-12 transaction 742 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2015-01-13 transaction 743 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2015-01-14 transaction 744 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2015-01-15 transaction 745 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2015-01-16 transaction 746 1eb 1 1eb:1ec -1 2015-01-17 transaction 747 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2015-01-18 transaction 748 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2015-01-19 transaction 749 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2015-01-20 transaction 750 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2015-01-21 transaction 751 1f5 1 1f5:1f6 -1 2015-01-22 transaction 752 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2015-01-23 transaction 753 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2015-01-24 transaction 754 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2015-01-25 transaction 755 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2015-01-26 transaction 756 1ff 1 1ff:200 -1 2015-01-27 transaction 757 1ff:200:201 1 1ff:200:201:202 -1 2015-01-28 transaction 758 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2015-01-29 transaction 759 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2015-01-30 transaction 760 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2015-01-31 transaction 761 209 1 209:20a -1 2015-02-01 transaction 762 209:20a:20b 1 209:20a:20b:20c -1 2015-02-02 transaction 763 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2015-02-03 transaction 764 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2015-02-04 transaction 765 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2015-02-05 transaction 766 213 1 213:214 -1 2015-02-06 transaction 767 213:214:215 1 213:214:215:216 -1 2015-02-07 transaction 768 213:214:215:216:217 1 213:214:215:216:217:218 -1 2015-02-08 transaction 769 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2015-02-09 transaction 770 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2015-02-10 transaction 771 21d 1 21d:21e -1 2015-02-11 transaction 772 21d:21e:21f 1 21d:21e:21f:220 -1 2015-02-12 transaction 773 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2015-02-13 transaction 774 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2015-02-14 transaction 775 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2015-02-15 transaction 776 227 1 227:228 -1 2015-02-16 transaction 777 227:228:229 1 227:228:229:22a -1 2015-02-17 transaction 778 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2015-02-18 transaction 779 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2015-02-19 transaction 780 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2015-02-20 transaction 781 231 1 231:232 -1 2015-02-21 transaction 782 231:232:233 1 231:232:233:234 -1 2015-02-22 transaction 783 231:232:233:234:235 1 231:232:233:234:235:236 -1 2015-02-23 transaction 784 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2015-02-24 transaction 785 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2015-02-25 transaction 786 23b 1 23b:23c -1 2015-02-26 transaction 787 23b:23c:23d 1 23b:23c:23d:23e -1 2015-02-27 transaction 788 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2015-02-28 transaction 789 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2015-03-01 transaction 790 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2015-03-02 transaction 791 245 1 245:246 -1 2015-03-03 transaction 792 245:246:247 1 245:246:247:248 -1 2015-03-04 transaction 793 245:246:247:248:249 1 245:246:247:248:249:24a -1 2015-03-05 transaction 794 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2015-03-06 transaction 795 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2015-03-07 transaction 796 24f 1 24f:250 -1 2015-03-08 transaction 797 24f:250:251 1 24f:250:251:252 -1 2015-03-09 transaction 798 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2015-03-10 transaction 799 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2015-03-11 transaction 800 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2015-03-12 transaction 801 259 1 259:25a -1 2015-03-13 transaction 802 259:25a:25b 1 259:25a:25b:25c -1 2015-03-14 transaction 803 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2015-03-15 transaction 804 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2015-03-16 transaction 805 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2015-03-17 transaction 806 263 1 263:264 -1 2015-03-18 transaction 807 263:264:265 1 263:264:265:266 -1 2015-03-19 transaction 808 263:264:265:266:267 1 263:264:265:266:267:268 -1 2015-03-20 transaction 809 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2015-03-21 transaction 810 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2015-03-22 transaction 811 26d 1 26d:26e -1 2015-03-23 transaction 812 26d:26e:26f 1 26d:26e:26f:270 -1 2015-03-24 transaction 813 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2015-03-25 transaction 814 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2015-03-26 transaction 815 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2015-03-27 transaction 816 277 1 277:278 -1 2015-03-28 transaction 817 277:278:279 1 277:278:279:27a -1 2015-03-29 transaction 818 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2015-03-30 transaction 819 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2015-03-31 transaction 820 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2015-04-01 transaction 821 281 1 281:282 -1 2015-04-02 transaction 822 281:282:283 1 281:282:283:284 -1 2015-04-03 transaction 823 281:282:283:284:285 1 281:282:283:284:285:286 -1 2015-04-04 transaction 824 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2015-04-05 transaction 825 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2015-04-06 transaction 826 28b 1 28b:28c -1 2015-04-07 transaction 827 28b:28c:28d 1 28b:28c:28d:28e -1 2015-04-08 transaction 828 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2015-04-09 transaction 829 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2015-04-10 transaction 830 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2015-04-11 transaction 831 295 1 295:296 -1 2015-04-12 transaction 832 295:296:297 1 295:296:297:298 -1 2015-04-13 transaction 833 295:296:297:298:299 1 295:296:297:298:299:29a -1 2015-04-14 transaction 834 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2015-04-15 transaction 835 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2015-04-16 transaction 836 29f 1 29f:2a0 -1 2015-04-17 transaction 837 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2015-04-18 transaction 838 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2015-04-19 transaction 839 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2015-04-20 transaction 840 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2015-04-21 transaction 841 2a9 1 2a9:2aa -1 2015-04-22 transaction 842 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2015-04-23 transaction 843 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2015-04-24 transaction 844 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2015-04-25 transaction 845 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2015-04-26 transaction 846 2b3 1 2b3:2b4 -1 2015-04-27 transaction 847 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2015-04-28 transaction 848 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2015-04-29 transaction 849 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2015-04-30 transaction 850 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2015-05-01 transaction 851 2bd 1 2bd:2be -1 2015-05-02 transaction 852 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2015-05-03 transaction 853 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2015-05-04 transaction 854 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2015-05-05 transaction 855 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2015-05-06 transaction 856 2c7 1 2c7:2c8 -1 2015-05-07 transaction 857 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2015-05-08 transaction 858 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2015-05-09 transaction 859 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2015-05-10 transaction 860 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2015-05-11 transaction 861 2d1 1 2d1:2d2 -1 2015-05-12 transaction 862 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2015-05-13 transaction 863 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2015-05-14 transaction 864 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2015-05-15 transaction 865 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2015-05-16 transaction 866 2db 1 2db:2dc -1 2015-05-17 transaction 867 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2015-05-18 transaction 868 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2015-05-19 transaction 869 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2015-05-20 transaction 870 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2015-05-21 transaction 871 2e5 1 2e5:2e6 -1 2015-05-22 transaction 872 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2015-05-23 transaction 873 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2015-05-24 transaction 874 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2015-05-25 transaction 875 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2015-05-26 transaction 876 2ef 1 2ef:2f0 -1 2015-05-27 transaction 877 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2015-05-28 transaction 878 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2015-05-29 transaction 879 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2015-05-30 transaction 880 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2015-05-31 transaction 881 2f9 1 2f9:2fa -1 2015-06-01 transaction 882 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2015-06-02 transaction 883 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2015-06-03 transaction 884 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2015-06-04 transaction 885 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2015-06-05 transaction 886 303 1 303:304 -1 2015-06-06 transaction 887 303:304:305 1 303:304:305:306 -1 2015-06-07 transaction 888 303:304:305:306:307 1 303:304:305:306:307:308 -1 2015-06-08 transaction 889 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2015-06-09 transaction 890 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2015-06-10 transaction 891 30d 1 30d:30e -1 2015-06-11 transaction 892 30d:30e:30f 1 30d:30e:30f:310 -1 2015-06-12 transaction 893 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2015-06-13 transaction 894 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2015-06-14 transaction 895 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2015-06-15 transaction 896 317 1 317:318 -1 2015-06-16 transaction 897 317:318:319 1 317:318:319:31a -1 2015-06-17 transaction 898 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2015-06-18 transaction 899 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2015-06-19 transaction 900 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2015-06-20 transaction 901 321 1 321:322 -1 2015-06-21 transaction 902 321:322:323 1 321:322:323:324 -1 2015-06-22 transaction 903 321:322:323:324:325 1 321:322:323:324:325:326 -1 2015-06-23 transaction 904 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2015-06-24 transaction 905 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2015-06-25 transaction 906 32b 1 32b:32c -1 2015-06-26 transaction 907 32b:32c:32d 1 32b:32c:32d:32e -1 2015-06-27 transaction 908 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2015-06-28 transaction 909 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2015-06-29 transaction 910 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2015-06-30 transaction 911 335 1 335:336 -1 2015-07-01 transaction 912 335:336:337 1 335:336:337:338 -1 2015-07-02 transaction 913 335:336:337:338:339 1 335:336:337:338:339:33a -1 2015-07-03 transaction 914 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2015-07-04 transaction 915 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2015-07-05 transaction 916 33f 1 33f:340 -1 2015-07-06 transaction 917 33f:340:341 1 33f:340:341:342 -1 2015-07-07 transaction 918 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2015-07-08 transaction 919 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2015-07-09 transaction 920 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2015-07-10 transaction 921 349 1 349:34a -1 2015-07-11 transaction 922 349:34a:34b 1 349:34a:34b:34c -1 2015-07-12 transaction 923 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2015-07-13 transaction 924 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2015-07-14 transaction 925 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2015-07-15 transaction 926 353 1 353:354 -1 2015-07-16 transaction 927 353:354:355 1 353:354:355:356 -1 2015-07-17 transaction 928 353:354:355:356:357 1 353:354:355:356:357:358 -1 2015-07-18 transaction 929 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2015-07-19 transaction 930 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2015-07-20 transaction 931 35d 1 35d:35e -1 2015-07-21 transaction 932 35d:35e:35f 1 35d:35e:35f:360 -1 2015-07-22 transaction 933 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2015-07-23 transaction 934 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2015-07-24 transaction 935 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2015-07-25 transaction 936 367 1 367:368 -1 2015-07-26 transaction 937 367:368:369 1 367:368:369:36a -1 2015-07-27 transaction 938 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2015-07-28 transaction 939 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2015-07-29 transaction 940 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2015-07-30 transaction 941 371 1 371:372 -1 2015-07-31 transaction 942 371:372:373 1 371:372:373:374 -1 2015-08-01 transaction 943 371:372:373:374:375 1 371:372:373:374:375:376 -1 2015-08-02 transaction 944 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2015-08-03 transaction 945 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2015-08-04 transaction 946 37b 1 37b:37c -1 2015-08-05 transaction 947 37b:37c:37d 1 37b:37c:37d:37e -1 2015-08-06 transaction 948 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2015-08-07 transaction 949 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2015-08-08 transaction 950 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2015-08-09 transaction 951 385 1 385:386 -1 2015-08-10 transaction 952 385:386:387 1 385:386:387:388 -1 2015-08-11 transaction 953 385:386:387:388:389 1 385:386:387:388:389:38a -1 2015-08-12 transaction 954 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2015-08-13 transaction 955 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2015-08-14 transaction 956 38f 1 38f:390 -1 2015-08-15 transaction 957 38f:390:391 1 38f:390:391:392 -1 2015-08-16 transaction 958 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2015-08-17 transaction 959 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2015-08-18 transaction 960 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2015-08-19 transaction 961 399 1 399:39a -1 2015-08-20 transaction 962 399:39a:39b 1 399:39a:39b:39c -1 2015-08-21 transaction 963 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2015-08-22 transaction 964 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2015-08-23 transaction 965 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2015-08-24 transaction 966 3a3 1 3a3:3a4 -1 2015-08-25 transaction 967 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2015-08-26 transaction 968 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2015-08-27 transaction 969 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2015-08-28 transaction 970 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2015-08-29 transaction 971 3ad 1 3ad:3ae -1 2015-08-30 transaction 972 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2015-08-31 transaction 973 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2015-09-01 transaction 974 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2015-09-02 transaction 975 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2015-09-03 transaction 976 3b7 1 3b7:3b8 -1 2015-09-04 transaction 977 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2015-09-05 transaction 978 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2015-09-06 transaction 979 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2015-09-07 transaction 980 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2015-09-08 transaction 981 3c1 1 3c1:3c2 -1 2015-09-09 transaction 982 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2015-09-10 transaction 983 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2015-09-11 transaction 984 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2015-09-12 transaction 985 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2015-09-13 transaction 986 3cb 1 3cb:3cc -1 2015-09-14 transaction 987 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2015-09-15 transaction 988 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2015-09-16 transaction 989 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2015-09-17 transaction 990 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2015-09-18 transaction 991 3d5 1 3d5:3d6 -1 2015-09-19 transaction 992 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2015-09-20 transaction 993 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2015-09-21 transaction 994 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2015-09-22 transaction 995 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2015-09-23 transaction 996 3df 1 3df:3e0 -1 2015-09-24 transaction 997 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2015-09-25 transaction 998 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2015-09-26 transaction 999 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2015-09-27 transaction 1000 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2015-09-28 transaction 1001 1 1 1:2 -1 2015-09-29 transaction 1002 1:2:3 1 1:2:3:4 -1 2015-09-30 transaction 1003 1:2:3:4:5 1 1:2:3:4:5:6 -1 2015-10-01 transaction 1004 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2015-10-02 transaction 1005 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2015-10-03 transaction 1006 b 1 b:c -1 2015-10-04 transaction 1007 b:c:d 1 b:c:d:e -1 2015-10-05 transaction 1008 b:c:d:e:f 1 b:c:d:e:f:10 -1 2015-10-06 transaction 1009 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2015-10-07 transaction 1010 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2015-10-08 transaction 1011 15 1 15:16 -1 2015-10-09 transaction 1012 15:16:17 1 15:16:17:18 -1 2015-10-10 transaction 1013 15:16:17:18:19 1 15:16:17:18:19:1a -1 2015-10-11 transaction 1014 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2015-10-12 transaction 1015 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2015-10-13 transaction 1016 1f 1 1f:20 -1 2015-10-14 transaction 1017 1f:20:21 1 1f:20:21:22 -1 2015-10-15 transaction 1018 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2015-10-16 transaction 1019 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2015-10-17 transaction 1020 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2015-10-18 transaction 1021 29 1 29:2a -1 2015-10-19 transaction 1022 29:2a:2b 1 29:2a:2b:2c -1 2015-10-20 transaction 1023 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2015-10-21 transaction 1024 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2015-10-22 transaction 1025 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2015-10-23 transaction 1026 33 1 33:34 -1 2015-10-24 transaction 1027 33:34:35 1 33:34:35:36 -1 2015-10-25 transaction 1028 33:34:35:36:37 1 33:34:35:36:37:38 -1 2015-10-26 transaction 1029 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2015-10-27 transaction 1030 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2015-10-28 transaction 1031 3d 1 3d:3e -1 2015-10-29 transaction 1032 3d:3e:3f 1 3d:3e:3f:40 -1 2015-10-30 transaction 1033 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2015-10-31 transaction 1034 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2015-11-01 transaction 1035 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2015-11-02 transaction 1036 47 1 47:48 -1 2015-11-03 transaction 1037 47:48:49 1 47:48:49:4a -1 2015-11-04 transaction 1038 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2015-11-05 transaction 1039 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2015-11-06 transaction 1040 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2015-11-07 transaction 1041 51 1 51:52 -1 2015-11-08 transaction 1042 51:52:53 1 51:52:53:54 -1 2015-11-09 transaction 1043 51:52:53:54:55 1 51:52:53:54:55:56 -1 2015-11-10 transaction 1044 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2015-11-11 transaction 1045 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2015-11-12 transaction 1046 5b 1 5b:5c -1 2015-11-13 transaction 1047 5b:5c:5d 1 5b:5c:5d:5e -1 2015-11-14 transaction 1048 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2015-11-15 transaction 1049 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2015-11-16 transaction 1050 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2015-11-17 transaction 1051 65 1 65:66 -1 2015-11-18 transaction 1052 65:66:67 1 65:66:67:68 -1 2015-11-19 transaction 1053 65:66:67:68:69 1 65:66:67:68:69:6a -1 2015-11-20 transaction 1054 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2015-11-21 transaction 1055 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2015-11-22 transaction 1056 6f 1 6f:70 -1 2015-11-23 transaction 1057 6f:70:71 1 6f:70:71:72 -1 2015-11-24 transaction 1058 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2015-11-25 transaction 1059 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2015-11-26 transaction 1060 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2015-11-27 transaction 1061 79 1 79:7a -1 2015-11-28 transaction 1062 79:7a:7b 1 79:7a:7b:7c -1 2015-11-29 transaction 1063 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2015-11-30 transaction 1064 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2015-12-01 transaction 1065 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2015-12-02 transaction 1066 83 1 83:84 -1 2015-12-03 transaction 1067 83:84:85 1 83:84:85:86 -1 2015-12-04 transaction 1068 83:84:85:86:87 1 83:84:85:86:87:88 -1 2015-12-05 transaction 1069 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2015-12-06 transaction 1070 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2015-12-07 transaction 1071 8d 1 8d:8e -1 2015-12-08 transaction 1072 8d:8e:8f 1 8d:8e:8f:90 -1 2015-12-09 transaction 1073 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2015-12-10 transaction 1074 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2015-12-11 transaction 1075 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2015-12-12 transaction 1076 97 1 97:98 -1 2015-12-13 transaction 1077 97:98:99 1 97:98:99:9a -1 2015-12-14 transaction 1078 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2015-12-15 transaction 1079 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2015-12-16 transaction 1080 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2015-12-17 transaction 1081 a1 1 a1:a2 -1 2015-12-18 transaction 1082 a1:a2:a3 1 a1:a2:a3:a4 -1 2015-12-19 transaction 1083 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2015-12-20 transaction 1084 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2015-12-21 transaction 1085 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2015-12-22 transaction 1086 ab 1 ab:ac -1 2015-12-23 transaction 1087 ab:ac:ad 1 ab:ac:ad:ae -1 2015-12-24 transaction 1088 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2015-12-25 transaction 1089 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2015-12-26 transaction 1090 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2015-12-27 transaction 1091 b5 1 b5:b6 -1 2015-12-28 transaction 1092 b5:b6:b7 1 b5:b6:b7:b8 -1 2015-12-29 transaction 1093 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2015-12-30 transaction 1094 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2015-12-31 transaction 1095 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2016-01-01 transaction 1096 bf 1 bf:c0 -1 2016-01-02 transaction 1097 bf:c0:c1 1 bf:c0:c1:c2 -1 2016-01-03 transaction 1098 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2016-01-04 transaction 1099 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2016-01-05 transaction 1100 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2016-01-06 transaction 1101 c9 1 c9:ca -1 2016-01-07 transaction 1102 c9:ca:cb 1 c9:ca:cb:cc -1 2016-01-08 transaction 1103 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2016-01-09 transaction 1104 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2016-01-10 transaction 1105 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2016-01-11 transaction 1106 d3 1 d3:d4 -1 2016-01-12 transaction 1107 d3:d4:d5 1 d3:d4:d5:d6 -1 2016-01-13 transaction 1108 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2016-01-14 transaction 1109 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2016-01-15 transaction 1110 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2016-01-16 transaction 1111 dd 1 dd:de -1 2016-01-17 transaction 1112 dd:de:df 1 dd:de:df:e0 -1 2016-01-18 transaction 1113 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2016-01-19 transaction 1114 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2016-01-20 transaction 1115 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2016-01-21 transaction 1116 e7 1 e7:e8 -1 2016-01-22 transaction 1117 e7:e8:e9 1 e7:e8:e9:ea -1 2016-01-23 transaction 1118 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2016-01-24 transaction 1119 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2016-01-25 transaction 1120 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2016-01-26 transaction 1121 f1 1 f1:f2 -1 2016-01-27 transaction 1122 f1:f2:f3 1 f1:f2:f3:f4 -1 2016-01-28 transaction 1123 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2016-01-29 transaction 1124 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2016-01-30 transaction 1125 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2016-01-31 transaction 1126 fb 1 fb:fc -1 2016-02-01 transaction 1127 fb:fc:fd 1 fb:fc:fd:fe -1 2016-02-02 transaction 1128 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2016-02-03 transaction 1129 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2016-02-04 transaction 1130 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2016-02-05 transaction 1131 105 1 105:106 -1 2016-02-06 transaction 1132 105:106:107 1 105:106:107:108 -1 2016-02-07 transaction 1133 105:106:107:108:109 1 105:106:107:108:109:10a -1 2016-02-08 transaction 1134 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2016-02-09 transaction 1135 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2016-02-10 transaction 1136 10f 1 10f:110 -1 2016-02-11 transaction 1137 10f:110:111 1 10f:110:111:112 -1 2016-02-12 transaction 1138 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2016-02-13 transaction 1139 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2016-02-14 transaction 1140 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2016-02-15 transaction 1141 119 1 119:11a -1 2016-02-16 transaction 1142 119:11a:11b 1 119:11a:11b:11c -1 2016-02-17 transaction 1143 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2016-02-18 transaction 1144 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2016-02-19 transaction 1145 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2016-02-20 transaction 1146 123 1 123:124 -1 2016-02-21 transaction 1147 123:124:125 1 123:124:125:126 -1 2016-02-22 transaction 1148 123:124:125:126:127 1 123:124:125:126:127:128 -1 2016-02-23 transaction 1149 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2016-02-24 transaction 1150 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2016-02-25 transaction 1151 12d 1 12d:12e -1 2016-02-26 transaction 1152 12d:12e:12f 1 12d:12e:12f:130 -1 2016-02-27 transaction 1153 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2016-02-28 transaction 1154 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2016-02-29 transaction 1155 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2016-03-01 transaction 1156 137 1 137:138 -1 2016-03-02 transaction 1157 137:138:139 1 137:138:139:13a -1 2016-03-03 transaction 1158 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2016-03-04 transaction 1159 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2016-03-05 transaction 1160 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2016-03-06 transaction 1161 141 1 141:142 -1 2016-03-07 transaction 1162 141:142:143 1 141:142:143:144 -1 2016-03-08 transaction 1163 141:142:143:144:145 1 141:142:143:144:145:146 -1 2016-03-09 transaction 1164 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2016-03-10 transaction 1165 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2016-03-11 transaction 1166 14b 1 14b:14c -1 2016-03-12 transaction 1167 14b:14c:14d 1 14b:14c:14d:14e -1 2016-03-13 transaction 1168 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2016-03-14 transaction 1169 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2016-03-15 transaction 1170 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2016-03-16 transaction 1171 155 1 155:156 -1 2016-03-17 transaction 1172 155:156:157 1 155:156:157:158 -1 2016-03-18 transaction 1173 155:156:157:158:159 1 155:156:157:158:159:15a -1 2016-03-19 transaction 1174 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2016-03-20 transaction 1175 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2016-03-21 transaction 1176 15f 1 15f:160 -1 2016-03-22 transaction 1177 15f:160:161 1 15f:160:161:162 -1 2016-03-23 transaction 1178 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2016-03-24 transaction 1179 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2016-03-25 transaction 1180 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2016-03-26 transaction 1181 169 1 169:16a -1 2016-03-27 transaction 1182 169:16a:16b 1 169:16a:16b:16c -1 2016-03-28 transaction 1183 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2016-03-29 transaction 1184 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2016-03-30 transaction 1185 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2016-03-31 transaction 1186 173 1 173:174 -1 2016-04-01 transaction 1187 173:174:175 1 173:174:175:176 -1 2016-04-02 transaction 1188 173:174:175:176:177 1 173:174:175:176:177:178 -1 2016-04-03 transaction 1189 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2016-04-04 transaction 1190 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2016-04-05 transaction 1191 17d 1 17d:17e -1 2016-04-06 transaction 1192 17d:17e:17f 1 17d:17e:17f:180 -1 2016-04-07 transaction 1193 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2016-04-08 transaction 1194 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2016-04-09 transaction 1195 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2016-04-10 transaction 1196 187 1 187:188 -1 2016-04-11 transaction 1197 187:188:189 1 187:188:189:18a -1 2016-04-12 transaction 1198 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2016-04-13 transaction 1199 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2016-04-14 transaction 1200 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2016-04-15 transaction 1201 191 1 191:192 -1 2016-04-16 transaction 1202 191:192:193 1 191:192:193:194 -1 2016-04-17 transaction 1203 191:192:193:194:195 1 191:192:193:194:195:196 -1 2016-04-18 transaction 1204 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2016-04-19 transaction 1205 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2016-04-20 transaction 1206 19b 1 19b:19c -1 2016-04-21 transaction 1207 19b:19c:19d 1 19b:19c:19d:19e -1 2016-04-22 transaction 1208 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2016-04-23 transaction 1209 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2016-04-24 transaction 1210 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2016-04-25 transaction 1211 1a5 1 1a5:1a6 -1 2016-04-26 transaction 1212 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2016-04-27 transaction 1213 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2016-04-28 transaction 1214 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2016-04-29 transaction 1215 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2016-04-30 transaction 1216 1af 1 1af:1b0 -1 2016-05-01 transaction 1217 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2016-05-02 transaction 1218 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2016-05-03 transaction 1219 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2016-05-04 transaction 1220 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2016-05-05 transaction 1221 1b9 1 1b9:1ba -1 2016-05-06 transaction 1222 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2016-05-07 transaction 1223 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2016-05-08 transaction 1224 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2016-05-09 transaction 1225 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2016-05-10 transaction 1226 1c3 1 1c3:1c4 -1 2016-05-11 transaction 1227 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2016-05-12 transaction 1228 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2016-05-13 transaction 1229 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2016-05-14 transaction 1230 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2016-05-15 transaction 1231 1cd 1 1cd:1ce -1 2016-05-16 transaction 1232 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2016-05-17 transaction 1233 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2016-05-18 transaction 1234 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2016-05-19 transaction 1235 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2016-05-20 transaction 1236 1d7 1 1d7:1d8 -1 2016-05-21 transaction 1237 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2016-05-22 transaction 1238 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2016-05-23 transaction 1239 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2016-05-24 transaction 1240 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2016-05-25 transaction 1241 1e1 1 1e1:1e2 -1 2016-05-26 transaction 1242 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2016-05-27 transaction 1243 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2016-05-28 transaction 1244 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2016-05-29 transaction 1245 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2016-05-30 transaction 1246 1eb 1 1eb:1ec -1 2016-05-31 transaction 1247 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2016-06-01 transaction 1248 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2016-06-02 transaction 1249 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2016-06-03 transaction 1250 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2016-06-04 transaction 1251 1f5 1 1f5:1f6 -1 2016-06-05 transaction 1252 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2016-06-06 transaction 1253 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2016-06-07 transaction 1254 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2016-06-08 transaction 1255 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2016-06-09 transaction 1256 1ff 1 1ff:200 -1 2016-06-10 transaction 1257 1ff:200:201 1 1ff:200:201:202 -1 2016-06-11 transaction 1258 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2016-06-12 transaction 1259 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2016-06-13 transaction 1260 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2016-06-14 transaction 1261 209 1 209:20a -1 2016-06-15 transaction 1262 209:20a:20b 1 209:20a:20b:20c -1 2016-06-16 transaction 1263 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2016-06-17 transaction 1264 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2016-06-18 transaction 1265 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2016-06-19 transaction 1266 213 1 213:214 -1 2016-06-20 transaction 1267 213:214:215 1 213:214:215:216 -1 2016-06-21 transaction 1268 213:214:215:216:217 1 213:214:215:216:217:218 -1 2016-06-22 transaction 1269 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2016-06-23 transaction 1270 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2016-06-24 transaction 1271 21d 1 21d:21e -1 2016-06-25 transaction 1272 21d:21e:21f 1 21d:21e:21f:220 -1 2016-06-26 transaction 1273 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2016-06-27 transaction 1274 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2016-06-28 transaction 1275 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2016-06-29 transaction 1276 227 1 227:228 -1 2016-06-30 transaction 1277 227:228:229 1 227:228:229:22a -1 2016-07-01 transaction 1278 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2016-07-02 transaction 1279 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2016-07-03 transaction 1280 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2016-07-04 transaction 1281 231 1 231:232 -1 2016-07-05 transaction 1282 231:232:233 1 231:232:233:234 -1 2016-07-06 transaction 1283 231:232:233:234:235 1 231:232:233:234:235:236 -1 2016-07-07 transaction 1284 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2016-07-08 transaction 1285 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2016-07-09 transaction 1286 23b 1 23b:23c -1 2016-07-10 transaction 1287 23b:23c:23d 1 23b:23c:23d:23e -1 2016-07-11 transaction 1288 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2016-07-12 transaction 1289 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2016-07-13 transaction 1290 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2016-07-14 transaction 1291 245 1 245:246 -1 2016-07-15 transaction 1292 245:246:247 1 245:246:247:248 -1 2016-07-16 transaction 1293 245:246:247:248:249 1 245:246:247:248:249:24a -1 2016-07-17 transaction 1294 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2016-07-18 transaction 1295 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2016-07-19 transaction 1296 24f 1 24f:250 -1 2016-07-20 transaction 1297 24f:250:251 1 24f:250:251:252 -1 2016-07-21 transaction 1298 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2016-07-22 transaction 1299 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2016-07-23 transaction 1300 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2016-07-24 transaction 1301 259 1 259:25a -1 2016-07-25 transaction 1302 259:25a:25b 1 259:25a:25b:25c -1 2016-07-26 transaction 1303 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2016-07-27 transaction 1304 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2016-07-28 transaction 1305 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2016-07-29 transaction 1306 263 1 263:264 -1 2016-07-30 transaction 1307 263:264:265 1 263:264:265:266 -1 2016-07-31 transaction 1308 263:264:265:266:267 1 263:264:265:266:267:268 -1 2016-08-01 transaction 1309 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2016-08-02 transaction 1310 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2016-08-03 transaction 1311 26d 1 26d:26e -1 2016-08-04 transaction 1312 26d:26e:26f 1 26d:26e:26f:270 -1 2016-08-05 transaction 1313 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2016-08-06 transaction 1314 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2016-08-07 transaction 1315 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2016-08-08 transaction 1316 277 1 277:278 -1 2016-08-09 transaction 1317 277:278:279 1 277:278:279:27a -1 2016-08-10 transaction 1318 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2016-08-11 transaction 1319 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2016-08-12 transaction 1320 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2016-08-13 transaction 1321 281 1 281:282 -1 2016-08-14 transaction 1322 281:282:283 1 281:282:283:284 -1 2016-08-15 transaction 1323 281:282:283:284:285 1 281:282:283:284:285:286 -1 2016-08-16 transaction 1324 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2016-08-17 transaction 1325 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2016-08-18 transaction 1326 28b 1 28b:28c -1 2016-08-19 transaction 1327 28b:28c:28d 1 28b:28c:28d:28e -1 2016-08-20 transaction 1328 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2016-08-21 transaction 1329 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2016-08-22 transaction 1330 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2016-08-23 transaction 1331 295 1 295:296 -1 2016-08-24 transaction 1332 295:296:297 1 295:296:297:298 -1 2016-08-25 transaction 1333 295:296:297:298:299 1 295:296:297:298:299:29a -1 2016-08-26 transaction 1334 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2016-08-27 transaction 1335 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2016-08-28 transaction 1336 29f 1 29f:2a0 -1 2016-08-29 transaction 1337 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2016-08-30 transaction 1338 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2016-08-31 transaction 1339 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2016-09-01 transaction 1340 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2016-09-02 transaction 1341 2a9 1 2a9:2aa -1 2016-09-03 transaction 1342 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2016-09-04 transaction 1343 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2016-09-05 transaction 1344 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2016-09-06 transaction 1345 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2016-09-07 transaction 1346 2b3 1 2b3:2b4 -1 2016-09-08 transaction 1347 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2016-09-09 transaction 1348 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2016-09-10 transaction 1349 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2016-09-11 transaction 1350 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2016-09-12 transaction 1351 2bd 1 2bd:2be -1 2016-09-13 transaction 1352 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2016-09-14 transaction 1353 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2016-09-15 transaction 1354 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2016-09-16 transaction 1355 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2016-09-17 transaction 1356 2c7 1 2c7:2c8 -1 2016-09-18 transaction 1357 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2016-09-19 transaction 1358 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2016-09-20 transaction 1359 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2016-09-21 transaction 1360 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2016-09-22 transaction 1361 2d1 1 2d1:2d2 -1 2016-09-23 transaction 1362 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2016-09-24 transaction 1363 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2016-09-25 transaction 1364 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2016-09-26 transaction 1365 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2016-09-27 transaction 1366 2db 1 2db:2dc -1 2016-09-28 transaction 1367 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2016-09-29 transaction 1368 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2016-09-30 transaction 1369 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2016-10-01 transaction 1370 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2016-10-02 transaction 1371 2e5 1 2e5:2e6 -1 2016-10-03 transaction 1372 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2016-10-04 transaction 1373 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2016-10-05 transaction 1374 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2016-10-06 transaction 1375 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2016-10-07 transaction 1376 2ef 1 2ef:2f0 -1 2016-10-08 transaction 1377 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2016-10-09 transaction 1378 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2016-10-10 transaction 1379 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2016-10-11 transaction 1380 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2016-10-12 transaction 1381 2f9 1 2f9:2fa -1 2016-10-13 transaction 1382 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2016-10-14 transaction 1383 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2016-10-15 transaction 1384 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2016-10-16 transaction 1385 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2016-10-17 transaction 1386 303 1 303:304 -1 2016-10-18 transaction 1387 303:304:305 1 303:304:305:306 -1 2016-10-19 transaction 1388 303:304:305:306:307 1 303:304:305:306:307:308 -1 2016-10-20 transaction 1389 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2016-10-21 transaction 1390 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2016-10-22 transaction 1391 30d 1 30d:30e -1 2016-10-23 transaction 1392 30d:30e:30f 1 30d:30e:30f:310 -1 2016-10-24 transaction 1393 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2016-10-25 transaction 1394 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2016-10-26 transaction 1395 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2016-10-27 transaction 1396 317 1 317:318 -1 2016-10-28 transaction 1397 317:318:319 1 317:318:319:31a -1 2016-10-29 transaction 1398 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2016-10-30 transaction 1399 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2016-10-31 transaction 1400 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2016-11-01 transaction 1401 321 1 321:322 -1 2016-11-02 transaction 1402 321:322:323 1 321:322:323:324 -1 2016-11-03 transaction 1403 321:322:323:324:325 1 321:322:323:324:325:326 -1 2016-11-04 transaction 1404 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2016-11-05 transaction 1405 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2016-11-06 transaction 1406 32b 1 32b:32c -1 2016-11-07 transaction 1407 32b:32c:32d 1 32b:32c:32d:32e -1 2016-11-08 transaction 1408 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2016-11-09 transaction 1409 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2016-11-10 transaction 1410 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2016-11-11 transaction 1411 335 1 335:336 -1 2016-11-12 transaction 1412 335:336:337 1 335:336:337:338 -1 2016-11-13 transaction 1413 335:336:337:338:339 1 335:336:337:338:339:33a -1 2016-11-14 transaction 1414 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2016-11-15 transaction 1415 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2016-11-16 transaction 1416 33f 1 33f:340 -1 2016-11-17 transaction 1417 33f:340:341 1 33f:340:341:342 -1 2016-11-18 transaction 1418 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2016-11-19 transaction 1419 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2016-11-20 transaction 1420 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2016-11-21 transaction 1421 349 1 349:34a -1 2016-11-22 transaction 1422 349:34a:34b 1 349:34a:34b:34c -1 2016-11-23 transaction 1423 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2016-11-24 transaction 1424 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2016-11-25 transaction 1425 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2016-11-26 transaction 1426 353 1 353:354 -1 2016-11-27 transaction 1427 353:354:355 1 353:354:355:356 -1 2016-11-28 transaction 1428 353:354:355:356:357 1 353:354:355:356:357:358 -1 2016-11-29 transaction 1429 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2016-11-30 transaction 1430 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2016-12-01 transaction 1431 35d 1 35d:35e -1 2016-12-02 transaction 1432 35d:35e:35f 1 35d:35e:35f:360 -1 2016-12-03 transaction 1433 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2016-12-04 transaction 1434 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2016-12-05 transaction 1435 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2016-12-06 transaction 1436 367 1 367:368 -1 2016-12-07 transaction 1437 367:368:369 1 367:368:369:36a -1 2016-12-08 transaction 1438 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2016-12-09 transaction 1439 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2016-12-10 transaction 1440 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2016-12-11 transaction 1441 371 1 371:372 -1 2016-12-12 transaction 1442 371:372:373 1 371:372:373:374 -1 2016-12-13 transaction 1443 371:372:373:374:375 1 371:372:373:374:375:376 -1 2016-12-14 transaction 1444 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2016-12-15 transaction 1445 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2016-12-16 transaction 1446 37b 1 37b:37c -1 2016-12-17 transaction 1447 37b:37c:37d 1 37b:37c:37d:37e -1 2016-12-18 transaction 1448 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2016-12-19 transaction 1449 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2016-12-20 transaction 1450 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2016-12-21 transaction 1451 385 1 385:386 -1 2016-12-22 transaction 1452 385:386:387 1 385:386:387:388 -1 2016-12-23 transaction 1453 385:386:387:388:389 1 385:386:387:388:389:38a -1 2016-12-24 transaction 1454 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2016-12-25 transaction 1455 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2016-12-26 transaction 1456 38f 1 38f:390 -1 2016-12-27 transaction 1457 38f:390:391 1 38f:390:391:392 -1 2016-12-28 transaction 1458 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2016-12-29 transaction 1459 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2016-12-30 transaction 1460 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2016-12-31 transaction 1461 399 1 399:39a -1 2017-01-01 transaction 1462 399:39a:39b 1 399:39a:39b:39c -1 2017-01-02 transaction 1463 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2017-01-03 transaction 1464 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2017-01-04 transaction 1465 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2017-01-05 transaction 1466 3a3 1 3a3:3a4 -1 2017-01-06 transaction 1467 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2017-01-07 transaction 1468 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2017-01-08 transaction 1469 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2017-01-09 transaction 1470 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2017-01-10 transaction 1471 3ad 1 3ad:3ae -1 2017-01-11 transaction 1472 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2017-01-12 transaction 1473 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2017-01-13 transaction 1474 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2017-01-14 transaction 1475 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2017-01-15 transaction 1476 3b7 1 3b7:3b8 -1 2017-01-16 transaction 1477 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2017-01-17 transaction 1478 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2017-01-18 transaction 1479 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2017-01-19 transaction 1480 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2017-01-20 transaction 1481 3c1 1 3c1:3c2 -1 2017-01-21 transaction 1482 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2017-01-22 transaction 1483 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2017-01-23 transaction 1484 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2017-01-24 transaction 1485 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2017-01-25 transaction 1486 3cb 1 3cb:3cc -1 2017-01-26 transaction 1487 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2017-01-27 transaction 1488 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2017-01-28 transaction 1489 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2017-01-29 transaction 1490 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2017-01-30 transaction 1491 3d5 1 3d5:3d6 -1 2017-01-31 transaction 1492 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2017-02-01 transaction 1493 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2017-02-02 transaction 1494 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2017-02-03 transaction 1495 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2017-02-04 transaction 1496 3df 1 3df:3e0 -1 2017-02-05 transaction 1497 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2017-02-06 transaction 1498 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2017-02-07 transaction 1499 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2017-02-08 transaction 1500 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2017-02-09 transaction 1501 1 1 1:2 -1 2017-02-10 transaction 1502 1:2:3 1 1:2:3:4 -1 2017-02-11 transaction 1503 1:2:3:4:5 1 1:2:3:4:5:6 -1 2017-02-12 transaction 1504 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2017-02-13 transaction 1505 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2017-02-14 transaction 1506 b 1 b:c -1 2017-02-15 transaction 1507 b:c:d 1 b:c:d:e -1 2017-02-16 transaction 1508 b:c:d:e:f 1 b:c:d:e:f:10 -1 2017-02-17 transaction 1509 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2017-02-18 transaction 1510 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2017-02-19 transaction 1511 15 1 15:16 -1 2017-02-20 transaction 1512 15:16:17 1 15:16:17:18 -1 2017-02-21 transaction 1513 15:16:17:18:19 1 15:16:17:18:19:1a -1 2017-02-22 transaction 1514 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2017-02-23 transaction 1515 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2017-02-24 transaction 1516 1f 1 1f:20 -1 2017-02-25 transaction 1517 1f:20:21 1 1f:20:21:22 -1 2017-02-26 transaction 1518 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2017-02-27 transaction 1519 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2017-02-28 transaction 1520 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2017-03-01 transaction 1521 29 1 29:2a -1 2017-03-02 transaction 1522 29:2a:2b 1 29:2a:2b:2c -1 2017-03-03 transaction 1523 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2017-03-04 transaction 1524 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2017-03-05 transaction 1525 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2017-03-06 transaction 1526 33 1 33:34 -1 2017-03-07 transaction 1527 33:34:35 1 33:34:35:36 -1 2017-03-08 transaction 1528 33:34:35:36:37 1 33:34:35:36:37:38 -1 2017-03-09 transaction 1529 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2017-03-10 transaction 1530 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2017-03-11 transaction 1531 3d 1 3d:3e -1 2017-03-12 transaction 1532 3d:3e:3f 1 3d:3e:3f:40 -1 2017-03-13 transaction 1533 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2017-03-14 transaction 1534 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2017-03-15 transaction 1535 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2017-03-16 transaction 1536 47 1 47:48 -1 2017-03-17 transaction 1537 47:48:49 1 47:48:49:4a -1 2017-03-18 transaction 1538 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2017-03-19 transaction 1539 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2017-03-20 transaction 1540 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2017-03-21 transaction 1541 51 1 51:52 -1 2017-03-22 transaction 1542 51:52:53 1 51:52:53:54 -1 2017-03-23 transaction 1543 51:52:53:54:55 1 51:52:53:54:55:56 -1 2017-03-24 transaction 1544 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2017-03-25 transaction 1545 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2017-03-26 transaction 1546 5b 1 5b:5c -1 2017-03-27 transaction 1547 5b:5c:5d 1 5b:5c:5d:5e -1 2017-03-28 transaction 1548 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2017-03-29 transaction 1549 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2017-03-30 transaction 1550 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2017-03-31 transaction 1551 65 1 65:66 -1 2017-04-01 transaction 1552 65:66:67 1 65:66:67:68 -1 2017-04-02 transaction 1553 65:66:67:68:69 1 65:66:67:68:69:6a -1 2017-04-03 transaction 1554 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2017-04-04 transaction 1555 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2017-04-05 transaction 1556 6f 1 6f:70 -1 2017-04-06 transaction 1557 6f:70:71 1 6f:70:71:72 -1 2017-04-07 transaction 1558 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2017-04-08 transaction 1559 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2017-04-09 transaction 1560 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2017-04-10 transaction 1561 79 1 79:7a -1 2017-04-11 transaction 1562 79:7a:7b 1 79:7a:7b:7c -1 2017-04-12 transaction 1563 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2017-04-13 transaction 1564 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2017-04-14 transaction 1565 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2017-04-15 transaction 1566 83 1 83:84 -1 2017-04-16 transaction 1567 83:84:85 1 83:84:85:86 -1 2017-04-17 transaction 1568 83:84:85:86:87 1 83:84:85:86:87:88 -1 2017-04-18 transaction 1569 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2017-04-19 transaction 1570 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2017-04-20 transaction 1571 8d 1 8d:8e -1 2017-04-21 transaction 1572 8d:8e:8f 1 8d:8e:8f:90 -1 2017-04-22 transaction 1573 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2017-04-23 transaction 1574 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2017-04-24 transaction 1575 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2017-04-25 transaction 1576 97 1 97:98 -1 2017-04-26 transaction 1577 97:98:99 1 97:98:99:9a -1 2017-04-27 transaction 1578 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2017-04-28 transaction 1579 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2017-04-29 transaction 1580 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2017-04-30 transaction 1581 a1 1 a1:a2 -1 2017-05-01 transaction 1582 a1:a2:a3 1 a1:a2:a3:a4 -1 2017-05-02 transaction 1583 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2017-05-03 transaction 1584 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2017-05-04 transaction 1585 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2017-05-05 transaction 1586 ab 1 ab:ac -1 2017-05-06 transaction 1587 ab:ac:ad 1 ab:ac:ad:ae -1 2017-05-07 transaction 1588 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2017-05-08 transaction 1589 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2017-05-09 transaction 1590 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2017-05-10 transaction 1591 b5 1 b5:b6 -1 2017-05-11 transaction 1592 b5:b6:b7 1 b5:b6:b7:b8 -1 2017-05-12 transaction 1593 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2017-05-13 transaction 1594 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2017-05-14 transaction 1595 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2017-05-15 transaction 1596 bf 1 bf:c0 -1 2017-05-16 transaction 1597 bf:c0:c1 1 bf:c0:c1:c2 -1 2017-05-17 transaction 1598 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2017-05-18 transaction 1599 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2017-05-19 transaction 1600 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2017-05-20 transaction 1601 c9 1 c9:ca -1 2017-05-21 transaction 1602 c9:ca:cb 1 c9:ca:cb:cc -1 2017-05-22 transaction 1603 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2017-05-23 transaction 1604 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2017-05-24 transaction 1605 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2017-05-25 transaction 1606 d3 1 d3:d4 -1 2017-05-26 transaction 1607 d3:d4:d5 1 d3:d4:d5:d6 -1 2017-05-27 transaction 1608 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2017-05-28 transaction 1609 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2017-05-29 transaction 1610 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2017-05-30 transaction 1611 dd 1 dd:de -1 2017-05-31 transaction 1612 dd:de:df 1 dd:de:df:e0 -1 2017-06-01 transaction 1613 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2017-06-02 transaction 1614 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2017-06-03 transaction 1615 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2017-06-04 transaction 1616 e7 1 e7:e8 -1 2017-06-05 transaction 1617 e7:e8:e9 1 e7:e8:e9:ea -1 2017-06-06 transaction 1618 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2017-06-07 transaction 1619 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2017-06-08 transaction 1620 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2017-06-09 transaction 1621 f1 1 f1:f2 -1 2017-06-10 transaction 1622 f1:f2:f3 1 f1:f2:f3:f4 -1 2017-06-11 transaction 1623 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2017-06-12 transaction 1624 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2017-06-13 transaction 1625 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2017-06-14 transaction 1626 fb 1 fb:fc -1 2017-06-15 transaction 1627 fb:fc:fd 1 fb:fc:fd:fe -1 2017-06-16 transaction 1628 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2017-06-17 transaction 1629 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2017-06-18 transaction 1630 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2017-06-19 transaction 1631 105 1 105:106 -1 2017-06-20 transaction 1632 105:106:107 1 105:106:107:108 -1 2017-06-21 transaction 1633 105:106:107:108:109 1 105:106:107:108:109:10a -1 2017-06-22 transaction 1634 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2017-06-23 transaction 1635 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2017-06-24 transaction 1636 10f 1 10f:110 -1 2017-06-25 transaction 1637 10f:110:111 1 10f:110:111:112 -1 2017-06-26 transaction 1638 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2017-06-27 transaction 1639 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2017-06-28 transaction 1640 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2017-06-29 transaction 1641 119 1 119:11a -1 2017-06-30 transaction 1642 119:11a:11b 1 119:11a:11b:11c -1 2017-07-01 transaction 1643 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2017-07-02 transaction 1644 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2017-07-03 transaction 1645 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2017-07-04 transaction 1646 123 1 123:124 -1 2017-07-05 transaction 1647 123:124:125 1 123:124:125:126 -1 2017-07-06 transaction 1648 123:124:125:126:127 1 123:124:125:126:127:128 -1 2017-07-07 transaction 1649 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2017-07-08 transaction 1650 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2017-07-09 transaction 1651 12d 1 12d:12e -1 2017-07-10 transaction 1652 12d:12e:12f 1 12d:12e:12f:130 -1 2017-07-11 transaction 1653 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2017-07-12 transaction 1654 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2017-07-13 transaction 1655 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2017-07-14 transaction 1656 137 1 137:138 -1 2017-07-15 transaction 1657 137:138:139 1 137:138:139:13a -1 2017-07-16 transaction 1658 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2017-07-17 transaction 1659 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2017-07-18 transaction 1660 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2017-07-19 transaction 1661 141 1 141:142 -1 2017-07-20 transaction 1662 141:142:143 1 141:142:143:144 -1 2017-07-21 transaction 1663 141:142:143:144:145 1 141:142:143:144:145:146 -1 2017-07-22 transaction 1664 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2017-07-23 transaction 1665 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2017-07-24 transaction 1666 14b 1 14b:14c -1 2017-07-25 transaction 1667 14b:14c:14d 1 14b:14c:14d:14e -1 2017-07-26 transaction 1668 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2017-07-27 transaction 1669 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2017-07-28 transaction 1670 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2017-07-29 transaction 1671 155 1 155:156 -1 2017-07-30 transaction 1672 155:156:157 1 155:156:157:158 -1 2017-07-31 transaction 1673 155:156:157:158:159 1 155:156:157:158:159:15a -1 2017-08-01 transaction 1674 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2017-08-02 transaction 1675 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2017-08-03 transaction 1676 15f 1 15f:160 -1 2017-08-04 transaction 1677 15f:160:161 1 15f:160:161:162 -1 2017-08-05 transaction 1678 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2017-08-06 transaction 1679 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2017-08-07 transaction 1680 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2017-08-08 transaction 1681 169 1 169:16a -1 2017-08-09 transaction 1682 169:16a:16b 1 169:16a:16b:16c -1 2017-08-10 transaction 1683 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2017-08-11 transaction 1684 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2017-08-12 transaction 1685 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2017-08-13 transaction 1686 173 1 173:174 -1 2017-08-14 transaction 1687 173:174:175 1 173:174:175:176 -1 2017-08-15 transaction 1688 173:174:175:176:177 1 173:174:175:176:177:178 -1 2017-08-16 transaction 1689 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2017-08-17 transaction 1690 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2017-08-18 transaction 1691 17d 1 17d:17e -1 2017-08-19 transaction 1692 17d:17e:17f 1 17d:17e:17f:180 -1 2017-08-20 transaction 1693 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2017-08-21 transaction 1694 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2017-08-22 transaction 1695 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2017-08-23 transaction 1696 187 1 187:188 -1 2017-08-24 transaction 1697 187:188:189 1 187:188:189:18a -1 2017-08-25 transaction 1698 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2017-08-26 transaction 1699 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2017-08-27 transaction 1700 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2017-08-28 transaction 1701 191 1 191:192 -1 2017-08-29 transaction 1702 191:192:193 1 191:192:193:194 -1 2017-08-30 transaction 1703 191:192:193:194:195 1 191:192:193:194:195:196 -1 2017-08-31 transaction 1704 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2017-09-01 transaction 1705 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2017-09-02 transaction 1706 19b 1 19b:19c -1 2017-09-03 transaction 1707 19b:19c:19d 1 19b:19c:19d:19e -1 2017-09-04 transaction 1708 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2017-09-05 transaction 1709 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2017-09-06 transaction 1710 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2017-09-07 transaction 1711 1a5 1 1a5:1a6 -1 2017-09-08 transaction 1712 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2017-09-09 transaction 1713 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2017-09-10 transaction 1714 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2017-09-11 transaction 1715 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2017-09-12 transaction 1716 1af 1 1af:1b0 -1 2017-09-13 transaction 1717 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2017-09-14 transaction 1718 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2017-09-15 transaction 1719 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2017-09-16 transaction 1720 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2017-09-17 transaction 1721 1b9 1 1b9:1ba -1 2017-09-18 transaction 1722 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2017-09-19 transaction 1723 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2017-09-20 transaction 1724 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2017-09-21 transaction 1725 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2017-09-22 transaction 1726 1c3 1 1c3:1c4 -1 2017-09-23 transaction 1727 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2017-09-24 transaction 1728 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2017-09-25 transaction 1729 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2017-09-26 transaction 1730 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2017-09-27 transaction 1731 1cd 1 1cd:1ce -1 2017-09-28 transaction 1732 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2017-09-29 transaction 1733 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2017-09-30 transaction 1734 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2017-10-01 transaction 1735 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2017-10-02 transaction 1736 1d7 1 1d7:1d8 -1 2017-10-03 transaction 1737 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2017-10-04 transaction 1738 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2017-10-05 transaction 1739 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2017-10-06 transaction 1740 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2017-10-07 transaction 1741 1e1 1 1e1:1e2 -1 2017-10-08 transaction 1742 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2017-10-09 transaction 1743 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2017-10-10 transaction 1744 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2017-10-11 transaction 1745 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2017-10-12 transaction 1746 1eb 1 1eb:1ec -1 2017-10-13 transaction 1747 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2017-10-14 transaction 1748 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2017-10-15 transaction 1749 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2017-10-16 transaction 1750 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2017-10-17 transaction 1751 1f5 1 1f5:1f6 -1 2017-10-18 transaction 1752 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2017-10-19 transaction 1753 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2017-10-20 transaction 1754 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2017-10-21 transaction 1755 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2017-10-22 transaction 1756 1ff 1 1ff:200 -1 2017-10-23 transaction 1757 1ff:200:201 1 1ff:200:201:202 -1 2017-10-24 transaction 1758 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2017-10-25 transaction 1759 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2017-10-26 transaction 1760 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2017-10-27 transaction 1761 209 1 209:20a -1 2017-10-28 transaction 1762 209:20a:20b 1 209:20a:20b:20c -1 2017-10-29 transaction 1763 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2017-10-30 transaction 1764 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2017-10-31 transaction 1765 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2017-11-01 transaction 1766 213 1 213:214 -1 2017-11-02 transaction 1767 213:214:215 1 213:214:215:216 -1 2017-11-03 transaction 1768 213:214:215:216:217 1 213:214:215:216:217:218 -1 2017-11-04 transaction 1769 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2017-11-05 transaction 1770 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2017-11-06 transaction 1771 21d 1 21d:21e -1 2017-11-07 transaction 1772 21d:21e:21f 1 21d:21e:21f:220 -1 2017-11-08 transaction 1773 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2017-11-09 transaction 1774 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2017-11-10 transaction 1775 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2017-11-11 transaction 1776 227 1 227:228 -1 2017-11-12 transaction 1777 227:228:229 1 227:228:229:22a -1 2017-11-13 transaction 1778 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2017-11-14 transaction 1779 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2017-11-15 transaction 1780 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2017-11-16 transaction 1781 231 1 231:232 -1 2017-11-17 transaction 1782 231:232:233 1 231:232:233:234 -1 2017-11-18 transaction 1783 231:232:233:234:235 1 231:232:233:234:235:236 -1 2017-11-19 transaction 1784 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2017-11-20 transaction 1785 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2017-11-21 transaction 1786 23b 1 23b:23c -1 2017-11-22 transaction 1787 23b:23c:23d 1 23b:23c:23d:23e -1 2017-11-23 transaction 1788 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2017-11-24 transaction 1789 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2017-11-25 transaction 1790 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2017-11-26 transaction 1791 245 1 245:246 -1 2017-11-27 transaction 1792 245:246:247 1 245:246:247:248 -1 2017-11-28 transaction 1793 245:246:247:248:249 1 245:246:247:248:249:24a -1 2017-11-29 transaction 1794 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2017-11-30 transaction 1795 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2017-12-01 transaction 1796 24f 1 24f:250 -1 2017-12-02 transaction 1797 24f:250:251 1 24f:250:251:252 -1 2017-12-03 transaction 1798 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2017-12-04 transaction 1799 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2017-12-05 transaction 1800 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2017-12-06 transaction 1801 259 1 259:25a -1 2017-12-07 transaction 1802 259:25a:25b 1 259:25a:25b:25c -1 2017-12-08 transaction 1803 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2017-12-09 transaction 1804 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2017-12-10 transaction 1805 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2017-12-11 transaction 1806 263 1 263:264 -1 2017-12-12 transaction 1807 263:264:265 1 263:264:265:266 -1 2017-12-13 transaction 1808 263:264:265:266:267 1 263:264:265:266:267:268 -1 2017-12-14 transaction 1809 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2017-12-15 transaction 1810 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2017-12-16 transaction 1811 26d 1 26d:26e -1 2017-12-17 transaction 1812 26d:26e:26f 1 26d:26e:26f:270 -1 2017-12-18 transaction 1813 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2017-12-19 transaction 1814 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2017-12-20 transaction 1815 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2017-12-21 transaction 1816 277 1 277:278 -1 2017-12-22 transaction 1817 277:278:279 1 277:278:279:27a -1 2017-12-23 transaction 1818 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2017-12-24 transaction 1819 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2017-12-25 transaction 1820 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2017-12-26 transaction 1821 281 1 281:282 -1 2017-12-27 transaction 1822 281:282:283 1 281:282:283:284 -1 2017-12-28 transaction 1823 281:282:283:284:285 1 281:282:283:284:285:286 -1 2017-12-29 transaction 1824 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2017-12-30 transaction 1825 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2017-12-31 transaction 1826 28b 1 28b:28c -1 2018-01-01 transaction 1827 28b:28c:28d 1 28b:28c:28d:28e -1 2018-01-02 transaction 1828 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2018-01-03 transaction 1829 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2018-01-04 transaction 1830 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2018-01-05 transaction 1831 295 1 295:296 -1 2018-01-06 transaction 1832 295:296:297 1 295:296:297:298 -1 2018-01-07 transaction 1833 295:296:297:298:299 1 295:296:297:298:299:29a -1 2018-01-08 transaction 1834 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2018-01-09 transaction 1835 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2018-01-10 transaction 1836 29f 1 29f:2a0 -1 2018-01-11 transaction 1837 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2018-01-12 transaction 1838 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2018-01-13 transaction 1839 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2018-01-14 transaction 1840 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2018-01-15 transaction 1841 2a9 1 2a9:2aa -1 2018-01-16 transaction 1842 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2018-01-17 transaction 1843 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2018-01-18 transaction 1844 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2018-01-19 transaction 1845 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2018-01-20 transaction 1846 2b3 1 2b3:2b4 -1 2018-01-21 transaction 1847 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2018-01-22 transaction 1848 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2018-01-23 transaction 1849 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2018-01-24 transaction 1850 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2018-01-25 transaction 1851 2bd 1 2bd:2be -1 2018-01-26 transaction 1852 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2018-01-27 transaction 1853 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2018-01-28 transaction 1854 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2018-01-29 transaction 1855 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2018-01-30 transaction 1856 2c7 1 2c7:2c8 -1 2018-01-31 transaction 1857 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2018-02-01 transaction 1858 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2018-02-02 transaction 1859 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2018-02-03 transaction 1860 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2018-02-04 transaction 1861 2d1 1 2d1:2d2 -1 2018-02-05 transaction 1862 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2018-02-06 transaction 1863 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2018-02-07 transaction 1864 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2018-02-08 transaction 1865 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2018-02-09 transaction 1866 2db 1 2db:2dc -1 2018-02-10 transaction 1867 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2018-02-11 transaction 1868 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2018-02-12 transaction 1869 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2018-02-13 transaction 1870 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2018-02-14 transaction 1871 2e5 1 2e5:2e6 -1 2018-02-15 transaction 1872 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2018-02-16 transaction 1873 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2018-02-17 transaction 1874 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2018-02-18 transaction 1875 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2018-02-19 transaction 1876 2ef 1 2ef:2f0 -1 2018-02-20 transaction 1877 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2018-02-21 transaction 1878 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2018-02-22 transaction 1879 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2018-02-23 transaction 1880 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2018-02-24 transaction 1881 2f9 1 2f9:2fa -1 2018-02-25 transaction 1882 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2018-02-26 transaction 1883 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2018-02-27 transaction 1884 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2018-02-28 transaction 1885 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2018-03-01 transaction 1886 303 1 303:304 -1 2018-03-02 transaction 1887 303:304:305 1 303:304:305:306 -1 2018-03-03 transaction 1888 303:304:305:306:307 1 303:304:305:306:307:308 -1 2018-03-04 transaction 1889 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2018-03-05 transaction 1890 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2018-03-06 transaction 1891 30d 1 30d:30e -1 2018-03-07 transaction 1892 30d:30e:30f 1 30d:30e:30f:310 -1 2018-03-08 transaction 1893 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2018-03-09 transaction 1894 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2018-03-10 transaction 1895 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2018-03-11 transaction 1896 317 1 317:318 -1 2018-03-12 transaction 1897 317:318:319 1 317:318:319:31a -1 2018-03-13 transaction 1898 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2018-03-14 transaction 1899 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2018-03-15 transaction 1900 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2018-03-16 transaction 1901 321 1 321:322 -1 2018-03-17 transaction 1902 321:322:323 1 321:322:323:324 -1 2018-03-18 transaction 1903 321:322:323:324:325 1 321:322:323:324:325:326 -1 2018-03-19 transaction 1904 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2018-03-20 transaction 1905 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2018-03-21 transaction 1906 32b 1 32b:32c -1 2018-03-22 transaction 1907 32b:32c:32d 1 32b:32c:32d:32e -1 2018-03-23 transaction 1908 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2018-03-24 transaction 1909 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2018-03-25 transaction 1910 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2018-03-26 transaction 1911 335 1 335:336 -1 2018-03-27 transaction 1912 335:336:337 1 335:336:337:338 -1 2018-03-28 transaction 1913 335:336:337:338:339 1 335:336:337:338:339:33a -1 2018-03-29 transaction 1914 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2018-03-30 transaction 1915 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2018-03-31 transaction 1916 33f 1 33f:340 -1 2018-04-01 transaction 1917 33f:340:341 1 33f:340:341:342 -1 2018-04-02 transaction 1918 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2018-04-03 transaction 1919 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2018-04-04 transaction 1920 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2018-04-05 transaction 1921 349 1 349:34a -1 2018-04-06 transaction 1922 349:34a:34b 1 349:34a:34b:34c -1 2018-04-07 transaction 1923 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2018-04-08 transaction 1924 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2018-04-09 transaction 1925 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2018-04-10 transaction 1926 353 1 353:354 -1 2018-04-11 transaction 1927 353:354:355 1 353:354:355:356 -1 2018-04-12 transaction 1928 353:354:355:356:357 1 353:354:355:356:357:358 -1 2018-04-13 transaction 1929 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2018-04-14 transaction 1930 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2018-04-15 transaction 1931 35d 1 35d:35e -1 2018-04-16 transaction 1932 35d:35e:35f 1 35d:35e:35f:360 -1 2018-04-17 transaction 1933 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2018-04-18 transaction 1934 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2018-04-19 transaction 1935 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2018-04-20 transaction 1936 367 1 367:368 -1 2018-04-21 transaction 1937 367:368:369 1 367:368:369:36a -1 2018-04-22 transaction 1938 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2018-04-23 transaction 1939 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2018-04-24 transaction 1940 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2018-04-25 transaction 1941 371 1 371:372 -1 2018-04-26 transaction 1942 371:372:373 1 371:372:373:374 -1 2018-04-27 transaction 1943 371:372:373:374:375 1 371:372:373:374:375:376 -1 2018-04-28 transaction 1944 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2018-04-29 transaction 1945 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2018-04-30 transaction 1946 37b 1 37b:37c -1 2018-05-01 transaction 1947 37b:37c:37d 1 37b:37c:37d:37e -1 2018-05-02 transaction 1948 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2018-05-03 transaction 1949 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2018-05-04 transaction 1950 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2018-05-05 transaction 1951 385 1 385:386 -1 2018-05-06 transaction 1952 385:386:387 1 385:386:387:388 -1 2018-05-07 transaction 1953 385:386:387:388:389 1 385:386:387:388:389:38a -1 2018-05-08 transaction 1954 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2018-05-09 transaction 1955 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2018-05-10 transaction 1956 38f 1 38f:390 -1 2018-05-11 transaction 1957 38f:390:391 1 38f:390:391:392 -1 2018-05-12 transaction 1958 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2018-05-13 transaction 1959 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2018-05-14 transaction 1960 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2018-05-15 transaction 1961 399 1 399:39a -1 2018-05-16 transaction 1962 399:39a:39b 1 399:39a:39b:39c -1 2018-05-17 transaction 1963 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2018-05-18 transaction 1964 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2018-05-19 transaction 1965 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2018-05-20 transaction 1966 3a3 1 3a3:3a4 -1 2018-05-21 transaction 1967 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2018-05-22 transaction 1968 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2018-05-23 transaction 1969 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2018-05-24 transaction 1970 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2018-05-25 transaction 1971 3ad 1 3ad:3ae -1 2018-05-26 transaction 1972 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2018-05-27 transaction 1973 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2018-05-28 transaction 1974 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2018-05-29 transaction 1975 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2018-05-30 transaction 1976 3b7 1 3b7:3b8 -1 2018-05-31 transaction 1977 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2018-06-01 transaction 1978 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2018-06-02 transaction 1979 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2018-06-03 transaction 1980 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2018-06-04 transaction 1981 3c1 1 3c1:3c2 -1 2018-06-05 transaction 1982 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2018-06-06 transaction 1983 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2018-06-07 transaction 1984 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2018-06-08 transaction 1985 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2018-06-09 transaction 1986 3cb 1 3cb:3cc -1 2018-06-10 transaction 1987 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2018-06-11 transaction 1988 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2018-06-12 transaction 1989 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2018-06-13 transaction 1990 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2018-06-14 transaction 1991 3d5 1 3d5:3d6 -1 2018-06-15 transaction 1992 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2018-06-16 transaction 1993 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2018-06-17 transaction 1994 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2018-06-18 transaction 1995 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2018-06-19 transaction 1996 3df 1 3df:3e0 -1 2018-06-20 transaction 1997 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2018-06-21 transaction 1998 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2018-06-22 transaction 1999 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2018-06-23 transaction 2000 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2018-06-24 transaction 2001 1 1 1:2 -1 2018-06-25 transaction 2002 1:2:3 1 1:2:3:4 -1 2018-06-26 transaction 2003 1:2:3:4:5 1 1:2:3:4:5:6 -1 2018-06-27 transaction 2004 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2018-06-28 transaction 2005 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2018-06-29 transaction 2006 b 1 b:c -1 2018-06-30 transaction 2007 b:c:d 1 b:c:d:e -1 2018-07-01 transaction 2008 b:c:d:e:f 1 b:c:d:e:f:10 -1 2018-07-02 transaction 2009 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2018-07-03 transaction 2010 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2018-07-04 transaction 2011 15 1 15:16 -1 2018-07-05 transaction 2012 15:16:17 1 15:16:17:18 -1 2018-07-06 transaction 2013 15:16:17:18:19 1 15:16:17:18:19:1a -1 2018-07-07 transaction 2014 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2018-07-08 transaction 2015 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2018-07-09 transaction 2016 1f 1 1f:20 -1 2018-07-10 transaction 2017 1f:20:21 1 1f:20:21:22 -1 2018-07-11 transaction 2018 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2018-07-12 transaction 2019 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2018-07-13 transaction 2020 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2018-07-14 transaction 2021 29 1 29:2a -1 2018-07-15 transaction 2022 29:2a:2b 1 29:2a:2b:2c -1 2018-07-16 transaction 2023 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2018-07-17 transaction 2024 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2018-07-18 transaction 2025 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2018-07-19 transaction 2026 33 1 33:34 -1 2018-07-20 transaction 2027 33:34:35 1 33:34:35:36 -1 2018-07-21 transaction 2028 33:34:35:36:37 1 33:34:35:36:37:38 -1 2018-07-22 transaction 2029 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2018-07-23 transaction 2030 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2018-07-24 transaction 2031 3d 1 3d:3e -1 2018-07-25 transaction 2032 3d:3e:3f 1 3d:3e:3f:40 -1 2018-07-26 transaction 2033 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2018-07-27 transaction 2034 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2018-07-28 transaction 2035 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2018-07-29 transaction 2036 47 1 47:48 -1 2018-07-30 transaction 2037 47:48:49 1 47:48:49:4a -1 2018-07-31 transaction 2038 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2018-08-01 transaction 2039 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2018-08-02 transaction 2040 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2018-08-03 transaction 2041 51 1 51:52 -1 2018-08-04 transaction 2042 51:52:53 1 51:52:53:54 -1 2018-08-05 transaction 2043 51:52:53:54:55 1 51:52:53:54:55:56 -1 2018-08-06 transaction 2044 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2018-08-07 transaction 2045 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2018-08-08 transaction 2046 5b 1 5b:5c -1 2018-08-09 transaction 2047 5b:5c:5d 1 5b:5c:5d:5e -1 2018-08-10 transaction 2048 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2018-08-11 transaction 2049 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2018-08-12 transaction 2050 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2018-08-13 transaction 2051 65 1 65:66 -1 2018-08-14 transaction 2052 65:66:67 1 65:66:67:68 -1 2018-08-15 transaction 2053 65:66:67:68:69 1 65:66:67:68:69:6a -1 2018-08-16 transaction 2054 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2018-08-17 transaction 2055 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2018-08-18 transaction 2056 6f 1 6f:70 -1 2018-08-19 transaction 2057 6f:70:71 1 6f:70:71:72 -1 2018-08-20 transaction 2058 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2018-08-21 transaction 2059 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2018-08-22 transaction 2060 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2018-08-23 transaction 2061 79 1 79:7a -1 2018-08-24 transaction 2062 79:7a:7b 1 79:7a:7b:7c -1 2018-08-25 transaction 2063 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2018-08-26 transaction 2064 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2018-08-27 transaction 2065 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2018-08-28 transaction 2066 83 1 83:84 -1 2018-08-29 transaction 2067 83:84:85 1 83:84:85:86 -1 2018-08-30 transaction 2068 83:84:85:86:87 1 83:84:85:86:87:88 -1 2018-08-31 transaction 2069 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2018-09-01 transaction 2070 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2018-09-02 transaction 2071 8d 1 8d:8e -1 2018-09-03 transaction 2072 8d:8e:8f 1 8d:8e:8f:90 -1 2018-09-04 transaction 2073 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2018-09-05 transaction 2074 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2018-09-06 transaction 2075 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2018-09-07 transaction 2076 97 1 97:98 -1 2018-09-08 transaction 2077 97:98:99 1 97:98:99:9a -1 2018-09-09 transaction 2078 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2018-09-10 transaction 2079 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2018-09-11 transaction 2080 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2018-09-12 transaction 2081 a1 1 a1:a2 -1 2018-09-13 transaction 2082 a1:a2:a3 1 a1:a2:a3:a4 -1 2018-09-14 transaction 2083 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2018-09-15 transaction 2084 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2018-09-16 transaction 2085 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2018-09-17 transaction 2086 ab 1 ab:ac -1 2018-09-18 transaction 2087 ab:ac:ad 1 ab:ac:ad:ae -1 2018-09-19 transaction 2088 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2018-09-20 transaction 2089 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2018-09-21 transaction 2090 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2018-09-22 transaction 2091 b5 1 b5:b6 -1 2018-09-23 transaction 2092 b5:b6:b7 1 b5:b6:b7:b8 -1 2018-09-24 transaction 2093 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2018-09-25 transaction 2094 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2018-09-26 transaction 2095 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2018-09-27 transaction 2096 bf 1 bf:c0 -1 2018-09-28 transaction 2097 bf:c0:c1 1 bf:c0:c1:c2 -1 2018-09-29 transaction 2098 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2018-09-30 transaction 2099 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2018-10-01 transaction 2100 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2018-10-02 transaction 2101 c9 1 c9:ca -1 2018-10-03 transaction 2102 c9:ca:cb 1 c9:ca:cb:cc -1 2018-10-04 transaction 2103 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2018-10-05 transaction 2104 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2018-10-06 transaction 2105 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2018-10-07 transaction 2106 d3 1 d3:d4 -1 2018-10-08 transaction 2107 d3:d4:d5 1 d3:d4:d5:d6 -1 2018-10-09 transaction 2108 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2018-10-10 transaction 2109 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2018-10-11 transaction 2110 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2018-10-12 transaction 2111 dd 1 dd:de -1 2018-10-13 transaction 2112 dd:de:df 1 dd:de:df:e0 -1 2018-10-14 transaction 2113 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2018-10-15 transaction 2114 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2018-10-16 transaction 2115 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2018-10-17 transaction 2116 e7 1 e7:e8 -1 2018-10-18 transaction 2117 e7:e8:e9 1 e7:e8:e9:ea -1 2018-10-19 transaction 2118 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2018-10-20 transaction 2119 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2018-10-21 transaction 2120 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2018-10-22 transaction 2121 f1 1 f1:f2 -1 2018-10-23 transaction 2122 f1:f2:f3 1 f1:f2:f3:f4 -1 2018-10-24 transaction 2123 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2018-10-25 transaction 2124 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2018-10-26 transaction 2125 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2018-10-27 transaction 2126 fb 1 fb:fc -1 2018-10-28 transaction 2127 fb:fc:fd 1 fb:fc:fd:fe -1 2018-10-29 transaction 2128 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2018-10-30 transaction 2129 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2018-10-31 transaction 2130 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2018-11-01 transaction 2131 105 1 105:106 -1 2018-11-02 transaction 2132 105:106:107 1 105:106:107:108 -1 2018-11-03 transaction 2133 105:106:107:108:109 1 105:106:107:108:109:10a -1 2018-11-04 transaction 2134 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2018-11-05 transaction 2135 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2018-11-06 transaction 2136 10f 1 10f:110 -1 2018-11-07 transaction 2137 10f:110:111 1 10f:110:111:112 -1 2018-11-08 transaction 2138 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2018-11-09 transaction 2139 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2018-11-10 transaction 2140 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2018-11-11 transaction 2141 119 1 119:11a -1 2018-11-12 transaction 2142 119:11a:11b 1 119:11a:11b:11c -1 2018-11-13 transaction 2143 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2018-11-14 transaction 2144 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2018-11-15 transaction 2145 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2018-11-16 transaction 2146 123 1 123:124 -1 2018-11-17 transaction 2147 123:124:125 1 123:124:125:126 -1 2018-11-18 transaction 2148 123:124:125:126:127 1 123:124:125:126:127:128 -1 2018-11-19 transaction 2149 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2018-11-20 transaction 2150 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2018-11-21 transaction 2151 12d 1 12d:12e -1 2018-11-22 transaction 2152 12d:12e:12f 1 12d:12e:12f:130 -1 2018-11-23 transaction 2153 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2018-11-24 transaction 2154 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2018-11-25 transaction 2155 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2018-11-26 transaction 2156 137 1 137:138 -1 2018-11-27 transaction 2157 137:138:139 1 137:138:139:13a -1 2018-11-28 transaction 2158 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2018-11-29 transaction 2159 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2018-11-30 transaction 2160 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2018-12-01 transaction 2161 141 1 141:142 -1 2018-12-02 transaction 2162 141:142:143 1 141:142:143:144 -1 2018-12-03 transaction 2163 141:142:143:144:145 1 141:142:143:144:145:146 -1 2018-12-04 transaction 2164 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2018-12-05 transaction 2165 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2018-12-06 transaction 2166 14b 1 14b:14c -1 2018-12-07 transaction 2167 14b:14c:14d 1 14b:14c:14d:14e -1 2018-12-08 transaction 2168 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2018-12-09 transaction 2169 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2018-12-10 transaction 2170 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2018-12-11 transaction 2171 155 1 155:156 -1 2018-12-12 transaction 2172 155:156:157 1 155:156:157:158 -1 2018-12-13 transaction 2173 155:156:157:158:159 1 155:156:157:158:159:15a -1 2018-12-14 transaction 2174 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2018-12-15 transaction 2175 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2018-12-16 transaction 2176 15f 1 15f:160 -1 2018-12-17 transaction 2177 15f:160:161 1 15f:160:161:162 -1 2018-12-18 transaction 2178 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2018-12-19 transaction 2179 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2018-12-20 transaction 2180 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2018-12-21 transaction 2181 169 1 169:16a -1 2018-12-22 transaction 2182 169:16a:16b 1 169:16a:16b:16c -1 2018-12-23 transaction 2183 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2018-12-24 transaction 2184 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2018-12-25 transaction 2185 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2018-12-26 transaction 2186 173 1 173:174 -1 2018-12-27 transaction 2187 173:174:175 1 173:174:175:176 -1 2018-12-28 transaction 2188 173:174:175:176:177 1 173:174:175:176:177:178 -1 2018-12-29 transaction 2189 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2018-12-30 transaction 2190 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2018-12-31 transaction 2191 17d 1 17d:17e -1 2019-01-01 transaction 2192 17d:17e:17f 1 17d:17e:17f:180 -1 2019-01-02 transaction 2193 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2019-01-03 transaction 2194 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2019-01-04 transaction 2195 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2019-01-05 transaction 2196 187 1 187:188 -1 2019-01-06 transaction 2197 187:188:189 1 187:188:189:18a -1 2019-01-07 transaction 2198 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2019-01-08 transaction 2199 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2019-01-09 transaction 2200 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2019-01-10 transaction 2201 191 1 191:192 -1 2019-01-11 transaction 2202 191:192:193 1 191:192:193:194 -1 2019-01-12 transaction 2203 191:192:193:194:195 1 191:192:193:194:195:196 -1 2019-01-13 transaction 2204 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2019-01-14 transaction 2205 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2019-01-15 transaction 2206 19b 1 19b:19c -1 2019-01-16 transaction 2207 19b:19c:19d 1 19b:19c:19d:19e -1 2019-01-17 transaction 2208 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2019-01-18 transaction 2209 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2019-01-19 transaction 2210 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2019-01-20 transaction 2211 1a5 1 1a5:1a6 -1 2019-01-21 transaction 2212 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2019-01-22 transaction 2213 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2019-01-23 transaction 2214 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2019-01-24 transaction 2215 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2019-01-25 transaction 2216 1af 1 1af:1b0 -1 2019-01-26 transaction 2217 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2019-01-27 transaction 2218 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2019-01-28 transaction 2219 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2019-01-29 transaction 2220 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2019-01-30 transaction 2221 1b9 1 1b9:1ba -1 2019-01-31 transaction 2222 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2019-02-01 transaction 2223 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2019-02-02 transaction 2224 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2019-02-03 transaction 2225 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2019-02-04 transaction 2226 1c3 1 1c3:1c4 -1 2019-02-05 transaction 2227 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2019-02-06 transaction 2228 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2019-02-07 transaction 2229 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2019-02-08 transaction 2230 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2019-02-09 transaction 2231 1cd 1 1cd:1ce -1 2019-02-10 transaction 2232 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2019-02-11 transaction 2233 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2019-02-12 transaction 2234 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2019-02-13 transaction 2235 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2019-02-14 transaction 2236 1d7 1 1d7:1d8 -1 2019-02-15 transaction 2237 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2019-02-16 transaction 2238 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2019-02-17 transaction 2239 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2019-02-18 transaction 2240 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2019-02-19 transaction 2241 1e1 1 1e1:1e2 -1 2019-02-20 transaction 2242 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2019-02-21 transaction 2243 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2019-02-22 transaction 2244 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2019-02-23 transaction 2245 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2019-02-24 transaction 2246 1eb 1 1eb:1ec -1 2019-02-25 transaction 2247 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2019-02-26 transaction 2248 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2019-02-27 transaction 2249 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2019-02-28 transaction 2250 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2019-03-01 transaction 2251 1f5 1 1f5:1f6 -1 2019-03-02 transaction 2252 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2019-03-03 transaction 2253 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2019-03-04 transaction 2254 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2019-03-05 transaction 2255 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2019-03-06 transaction 2256 1ff 1 1ff:200 -1 2019-03-07 transaction 2257 1ff:200:201 1 1ff:200:201:202 -1 2019-03-08 transaction 2258 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2019-03-09 transaction 2259 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2019-03-10 transaction 2260 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2019-03-11 transaction 2261 209 1 209:20a -1 2019-03-12 transaction 2262 209:20a:20b 1 209:20a:20b:20c -1 2019-03-13 transaction 2263 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2019-03-14 transaction 2264 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2019-03-15 transaction 2265 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2019-03-16 transaction 2266 213 1 213:214 -1 2019-03-17 transaction 2267 213:214:215 1 213:214:215:216 -1 2019-03-18 transaction 2268 213:214:215:216:217 1 213:214:215:216:217:218 -1 2019-03-19 transaction 2269 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2019-03-20 transaction 2270 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2019-03-21 transaction 2271 21d 1 21d:21e -1 2019-03-22 transaction 2272 21d:21e:21f 1 21d:21e:21f:220 -1 2019-03-23 transaction 2273 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2019-03-24 transaction 2274 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2019-03-25 transaction 2275 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2019-03-26 transaction 2276 227 1 227:228 -1 2019-03-27 transaction 2277 227:228:229 1 227:228:229:22a -1 2019-03-28 transaction 2278 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2019-03-29 transaction 2279 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2019-03-30 transaction 2280 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2019-03-31 transaction 2281 231 1 231:232 -1 2019-04-01 transaction 2282 231:232:233 1 231:232:233:234 -1 2019-04-02 transaction 2283 231:232:233:234:235 1 231:232:233:234:235:236 -1 2019-04-03 transaction 2284 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2019-04-04 transaction 2285 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2019-04-05 transaction 2286 23b 1 23b:23c -1 2019-04-06 transaction 2287 23b:23c:23d 1 23b:23c:23d:23e -1 2019-04-07 transaction 2288 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2019-04-08 transaction 2289 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2019-04-09 transaction 2290 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2019-04-10 transaction 2291 245 1 245:246 -1 2019-04-11 transaction 2292 245:246:247 1 245:246:247:248 -1 2019-04-12 transaction 2293 245:246:247:248:249 1 245:246:247:248:249:24a -1 2019-04-13 transaction 2294 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2019-04-14 transaction 2295 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2019-04-15 transaction 2296 24f 1 24f:250 -1 2019-04-16 transaction 2297 24f:250:251 1 24f:250:251:252 -1 2019-04-17 transaction 2298 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2019-04-18 transaction 2299 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2019-04-19 transaction 2300 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2019-04-20 transaction 2301 259 1 259:25a -1 2019-04-21 transaction 2302 259:25a:25b 1 259:25a:25b:25c -1 2019-04-22 transaction 2303 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2019-04-23 transaction 2304 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2019-04-24 transaction 2305 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2019-04-25 transaction 2306 263 1 263:264 -1 2019-04-26 transaction 2307 263:264:265 1 263:264:265:266 -1 2019-04-27 transaction 2308 263:264:265:266:267 1 263:264:265:266:267:268 -1 2019-04-28 transaction 2309 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2019-04-29 transaction 2310 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2019-04-30 transaction 2311 26d 1 26d:26e -1 2019-05-01 transaction 2312 26d:26e:26f 1 26d:26e:26f:270 -1 2019-05-02 transaction 2313 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2019-05-03 transaction 2314 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2019-05-04 transaction 2315 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2019-05-05 transaction 2316 277 1 277:278 -1 2019-05-06 transaction 2317 277:278:279 1 277:278:279:27a -1 2019-05-07 transaction 2318 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2019-05-08 transaction 2319 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2019-05-09 transaction 2320 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2019-05-10 transaction 2321 281 1 281:282 -1 2019-05-11 transaction 2322 281:282:283 1 281:282:283:284 -1 2019-05-12 transaction 2323 281:282:283:284:285 1 281:282:283:284:285:286 -1 2019-05-13 transaction 2324 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2019-05-14 transaction 2325 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2019-05-15 transaction 2326 28b 1 28b:28c -1 2019-05-16 transaction 2327 28b:28c:28d 1 28b:28c:28d:28e -1 2019-05-17 transaction 2328 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2019-05-18 transaction 2329 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2019-05-19 transaction 2330 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2019-05-20 transaction 2331 295 1 295:296 -1 2019-05-21 transaction 2332 295:296:297 1 295:296:297:298 -1 2019-05-22 transaction 2333 295:296:297:298:299 1 295:296:297:298:299:29a -1 2019-05-23 transaction 2334 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2019-05-24 transaction 2335 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2019-05-25 transaction 2336 29f 1 29f:2a0 -1 2019-05-26 transaction 2337 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2019-05-27 transaction 2338 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2019-05-28 transaction 2339 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2019-05-29 transaction 2340 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2019-05-30 transaction 2341 2a9 1 2a9:2aa -1 2019-05-31 transaction 2342 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2019-06-01 transaction 2343 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2019-06-02 transaction 2344 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2019-06-03 transaction 2345 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2019-06-04 transaction 2346 2b3 1 2b3:2b4 -1 2019-06-05 transaction 2347 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2019-06-06 transaction 2348 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2019-06-07 transaction 2349 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2019-06-08 transaction 2350 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2019-06-09 transaction 2351 2bd 1 2bd:2be -1 2019-06-10 transaction 2352 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2019-06-11 transaction 2353 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2019-06-12 transaction 2354 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2019-06-13 transaction 2355 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2019-06-14 transaction 2356 2c7 1 2c7:2c8 -1 2019-06-15 transaction 2357 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2019-06-16 transaction 2358 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2019-06-17 transaction 2359 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2019-06-18 transaction 2360 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2019-06-19 transaction 2361 2d1 1 2d1:2d2 -1 2019-06-20 transaction 2362 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2019-06-21 transaction 2363 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2019-06-22 transaction 2364 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2019-06-23 transaction 2365 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2019-06-24 transaction 2366 2db 1 2db:2dc -1 2019-06-25 transaction 2367 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2019-06-26 transaction 2368 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2019-06-27 transaction 2369 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2019-06-28 transaction 2370 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2019-06-29 transaction 2371 2e5 1 2e5:2e6 -1 2019-06-30 transaction 2372 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2019-07-01 transaction 2373 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2019-07-02 transaction 2374 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2019-07-03 transaction 2375 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2019-07-04 transaction 2376 2ef 1 2ef:2f0 -1 2019-07-05 transaction 2377 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2019-07-06 transaction 2378 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2019-07-07 transaction 2379 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2019-07-08 transaction 2380 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2019-07-09 transaction 2381 2f9 1 2f9:2fa -1 2019-07-10 transaction 2382 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2019-07-11 transaction 2383 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2019-07-12 transaction 2384 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2019-07-13 transaction 2385 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2019-07-14 transaction 2386 303 1 303:304 -1 2019-07-15 transaction 2387 303:304:305 1 303:304:305:306 -1 2019-07-16 transaction 2388 303:304:305:306:307 1 303:304:305:306:307:308 -1 2019-07-17 transaction 2389 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2019-07-18 transaction 2390 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2019-07-19 transaction 2391 30d 1 30d:30e -1 2019-07-20 transaction 2392 30d:30e:30f 1 30d:30e:30f:310 -1 2019-07-21 transaction 2393 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2019-07-22 transaction 2394 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2019-07-23 transaction 2395 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2019-07-24 transaction 2396 317 1 317:318 -1 2019-07-25 transaction 2397 317:318:319 1 317:318:319:31a -1 2019-07-26 transaction 2398 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2019-07-27 transaction 2399 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2019-07-28 transaction 2400 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2019-07-29 transaction 2401 321 1 321:322 -1 2019-07-30 transaction 2402 321:322:323 1 321:322:323:324 -1 2019-07-31 transaction 2403 321:322:323:324:325 1 321:322:323:324:325:326 -1 2019-08-01 transaction 2404 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2019-08-02 transaction 2405 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2019-08-03 transaction 2406 32b 1 32b:32c -1 2019-08-04 transaction 2407 32b:32c:32d 1 32b:32c:32d:32e -1 2019-08-05 transaction 2408 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2019-08-06 transaction 2409 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2019-08-07 transaction 2410 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2019-08-08 transaction 2411 335 1 335:336 -1 2019-08-09 transaction 2412 335:336:337 1 335:336:337:338 -1 2019-08-10 transaction 2413 335:336:337:338:339 1 335:336:337:338:339:33a -1 2019-08-11 transaction 2414 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2019-08-12 transaction 2415 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2019-08-13 transaction 2416 33f 1 33f:340 -1 2019-08-14 transaction 2417 33f:340:341 1 33f:340:341:342 -1 2019-08-15 transaction 2418 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2019-08-16 transaction 2419 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2019-08-17 transaction 2420 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2019-08-18 transaction 2421 349 1 349:34a -1 2019-08-19 transaction 2422 349:34a:34b 1 349:34a:34b:34c -1 2019-08-20 transaction 2423 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2019-08-21 transaction 2424 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2019-08-22 transaction 2425 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2019-08-23 transaction 2426 353 1 353:354 -1 2019-08-24 transaction 2427 353:354:355 1 353:354:355:356 -1 2019-08-25 transaction 2428 353:354:355:356:357 1 353:354:355:356:357:358 -1 2019-08-26 transaction 2429 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2019-08-27 transaction 2430 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2019-08-28 transaction 2431 35d 1 35d:35e -1 2019-08-29 transaction 2432 35d:35e:35f 1 35d:35e:35f:360 -1 2019-08-30 transaction 2433 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2019-08-31 transaction 2434 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2019-09-01 transaction 2435 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2019-09-02 transaction 2436 367 1 367:368 -1 2019-09-03 transaction 2437 367:368:369 1 367:368:369:36a -1 2019-09-04 transaction 2438 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2019-09-05 transaction 2439 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2019-09-06 transaction 2440 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2019-09-07 transaction 2441 371 1 371:372 -1 2019-09-08 transaction 2442 371:372:373 1 371:372:373:374 -1 2019-09-09 transaction 2443 371:372:373:374:375 1 371:372:373:374:375:376 -1 2019-09-10 transaction 2444 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2019-09-11 transaction 2445 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2019-09-12 transaction 2446 37b 1 37b:37c -1 2019-09-13 transaction 2447 37b:37c:37d 1 37b:37c:37d:37e -1 2019-09-14 transaction 2448 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2019-09-15 transaction 2449 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2019-09-16 transaction 2450 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2019-09-17 transaction 2451 385 1 385:386 -1 2019-09-18 transaction 2452 385:386:387 1 385:386:387:388 -1 2019-09-19 transaction 2453 385:386:387:388:389 1 385:386:387:388:389:38a -1 2019-09-20 transaction 2454 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2019-09-21 transaction 2455 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2019-09-22 transaction 2456 38f 1 38f:390 -1 2019-09-23 transaction 2457 38f:390:391 1 38f:390:391:392 -1 2019-09-24 transaction 2458 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2019-09-25 transaction 2459 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2019-09-26 transaction 2460 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2019-09-27 transaction 2461 399 1 399:39a -1 2019-09-28 transaction 2462 399:39a:39b 1 399:39a:39b:39c -1 2019-09-29 transaction 2463 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2019-09-30 transaction 2464 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2019-10-01 transaction 2465 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2019-10-02 transaction 2466 3a3 1 3a3:3a4 -1 2019-10-03 transaction 2467 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2019-10-04 transaction 2468 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2019-10-05 transaction 2469 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2019-10-06 transaction 2470 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2019-10-07 transaction 2471 3ad 1 3ad:3ae -1 2019-10-08 transaction 2472 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2019-10-09 transaction 2473 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2019-10-10 transaction 2474 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2019-10-11 transaction 2475 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2019-10-12 transaction 2476 3b7 1 3b7:3b8 -1 2019-10-13 transaction 2477 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2019-10-14 transaction 2478 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2019-10-15 transaction 2479 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2019-10-16 transaction 2480 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2019-10-17 transaction 2481 3c1 1 3c1:3c2 -1 2019-10-18 transaction 2482 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2019-10-19 transaction 2483 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2019-10-20 transaction 2484 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2019-10-21 transaction 2485 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2019-10-22 transaction 2486 3cb 1 3cb:3cc -1 2019-10-23 transaction 2487 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2019-10-24 transaction 2488 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2019-10-25 transaction 2489 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2019-10-26 transaction 2490 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2019-10-27 transaction 2491 3d5 1 3d5:3d6 -1 2019-10-28 transaction 2492 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2019-10-29 transaction 2493 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2019-10-30 transaction 2494 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2019-10-31 transaction 2495 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2019-11-01 transaction 2496 3df 1 3df:3e0 -1 2019-11-02 transaction 2497 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2019-11-03 transaction 2498 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2019-11-04 transaction 2499 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2019-11-05 transaction 2500 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2019-11-06 transaction 2501 1 1 1:2 -1 2019-11-07 transaction 2502 1:2:3 1 1:2:3:4 -1 2019-11-08 transaction 2503 1:2:3:4:5 1 1:2:3:4:5:6 -1 2019-11-09 transaction 2504 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2019-11-10 transaction 2505 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2019-11-11 transaction 2506 b 1 b:c -1 2019-11-12 transaction 2507 b:c:d 1 b:c:d:e -1 2019-11-13 transaction 2508 b:c:d:e:f 1 b:c:d:e:f:10 -1 2019-11-14 transaction 2509 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2019-11-15 transaction 2510 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2019-11-16 transaction 2511 15 1 15:16 -1 2019-11-17 transaction 2512 15:16:17 1 15:16:17:18 -1 2019-11-18 transaction 2513 15:16:17:18:19 1 15:16:17:18:19:1a -1 2019-11-19 transaction 2514 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2019-11-20 transaction 2515 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2019-11-21 transaction 2516 1f 1 1f:20 -1 2019-11-22 transaction 2517 1f:20:21 1 1f:20:21:22 -1 2019-11-23 transaction 2518 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2019-11-24 transaction 2519 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2019-11-25 transaction 2520 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2019-11-26 transaction 2521 29 1 29:2a -1 2019-11-27 transaction 2522 29:2a:2b 1 29:2a:2b:2c -1 2019-11-28 transaction 2523 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2019-11-29 transaction 2524 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2019-11-30 transaction 2525 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2019-12-01 transaction 2526 33 1 33:34 -1 2019-12-02 transaction 2527 33:34:35 1 33:34:35:36 -1 2019-12-03 transaction 2528 33:34:35:36:37 1 33:34:35:36:37:38 -1 2019-12-04 transaction 2529 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2019-12-05 transaction 2530 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2019-12-06 transaction 2531 3d 1 3d:3e -1 2019-12-07 transaction 2532 3d:3e:3f 1 3d:3e:3f:40 -1 2019-12-08 transaction 2533 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2019-12-09 transaction 2534 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2019-12-10 transaction 2535 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2019-12-11 transaction 2536 47 1 47:48 -1 2019-12-12 transaction 2537 47:48:49 1 47:48:49:4a -1 2019-12-13 transaction 2538 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2019-12-14 transaction 2539 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2019-12-15 transaction 2540 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2019-12-16 transaction 2541 51 1 51:52 -1 2019-12-17 transaction 2542 51:52:53 1 51:52:53:54 -1 2019-12-18 transaction 2543 51:52:53:54:55 1 51:52:53:54:55:56 -1 2019-12-19 transaction 2544 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2019-12-20 transaction 2545 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2019-12-21 transaction 2546 5b 1 5b:5c -1 2019-12-22 transaction 2547 5b:5c:5d 1 5b:5c:5d:5e -1 2019-12-23 transaction 2548 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2019-12-24 transaction 2549 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2019-12-25 transaction 2550 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2019-12-26 transaction 2551 65 1 65:66 -1 2019-12-27 transaction 2552 65:66:67 1 65:66:67:68 -1 2019-12-28 transaction 2553 65:66:67:68:69 1 65:66:67:68:69:6a -1 2019-12-29 transaction 2554 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2019-12-30 transaction 2555 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2019-12-31 transaction 2556 6f 1 6f:70 -1 2020-01-01 transaction 2557 6f:70:71 1 6f:70:71:72 -1 2020-01-02 transaction 2558 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2020-01-03 transaction 2559 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2020-01-04 transaction 2560 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2020-01-05 transaction 2561 79 1 79:7a -1 2020-01-06 transaction 2562 79:7a:7b 1 79:7a:7b:7c -1 2020-01-07 transaction 2563 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2020-01-08 transaction 2564 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2020-01-09 transaction 2565 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2020-01-10 transaction 2566 83 1 83:84 -1 2020-01-11 transaction 2567 83:84:85 1 83:84:85:86 -1 2020-01-12 transaction 2568 83:84:85:86:87 1 83:84:85:86:87:88 -1 2020-01-13 transaction 2569 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2020-01-14 transaction 2570 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2020-01-15 transaction 2571 8d 1 8d:8e -1 2020-01-16 transaction 2572 8d:8e:8f 1 8d:8e:8f:90 -1 2020-01-17 transaction 2573 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2020-01-18 transaction 2574 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2020-01-19 transaction 2575 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2020-01-20 transaction 2576 97 1 97:98 -1 2020-01-21 transaction 2577 97:98:99 1 97:98:99:9a -1 2020-01-22 transaction 2578 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2020-01-23 transaction 2579 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2020-01-24 transaction 2580 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2020-01-25 transaction 2581 a1 1 a1:a2 -1 2020-01-26 transaction 2582 a1:a2:a3 1 a1:a2:a3:a4 -1 2020-01-27 transaction 2583 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2020-01-28 transaction 2584 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2020-01-29 transaction 2585 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2020-01-30 transaction 2586 ab 1 ab:ac -1 2020-01-31 transaction 2587 ab:ac:ad 1 ab:ac:ad:ae -1 2020-02-01 transaction 2588 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2020-02-02 transaction 2589 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2020-02-03 transaction 2590 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2020-02-04 transaction 2591 b5 1 b5:b6 -1 2020-02-05 transaction 2592 b5:b6:b7 1 b5:b6:b7:b8 -1 2020-02-06 transaction 2593 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2020-02-07 transaction 2594 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2020-02-08 transaction 2595 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2020-02-09 transaction 2596 bf 1 bf:c0 -1 2020-02-10 transaction 2597 bf:c0:c1 1 bf:c0:c1:c2 -1 2020-02-11 transaction 2598 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2020-02-12 transaction 2599 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2020-02-13 transaction 2600 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2020-02-14 transaction 2601 c9 1 c9:ca -1 2020-02-15 transaction 2602 c9:ca:cb 1 c9:ca:cb:cc -1 2020-02-16 transaction 2603 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2020-02-17 transaction 2604 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2020-02-18 transaction 2605 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2020-02-19 transaction 2606 d3 1 d3:d4 -1 2020-02-20 transaction 2607 d3:d4:d5 1 d3:d4:d5:d6 -1 2020-02-21 transaction 2608 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2020-02-22 transaction 2609 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2020-02-23 transaction 2610 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2020-02-24 transaction 2611 dd 1 dd:de -1 2020-02-25 transaction 2612 dd:de:df 1 dd:de:df:e0 -1 2020-02-26 transaction 2613 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2020-02-27 transaction 2614 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2020-02-28 transaction 2615 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2020-02-29 transaction 2616 e7 1 e7:e8 -1 2020-03-01 transaction 2617 e7:e8:e9 1 e7:e8:e9:ea -1 2020-03-02 transaction 2618 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2020-03-03 transaction 2619 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2020-03-04 transaction 2620 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2020-03-05 transaction 2621 f1 1 f1:f2 -1 2020-03-06 transaction 2622 f1:f2:f3 1 f1:f2:f3:f4 -1 2020-03-07 transaction 2623 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2020-03-08 transaction 2624 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2020-03-09 transaction 2625 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2020-03-10 transaction 2626 fb 1 fb:fc -1 2020-03-11 transaction 2627 fb:fc:fd 1 fb:fc:fd:fe -1 2020-03-12 transaction 2628 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2020-03-13 transaction 2629 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2020-03-14 transaction 2630 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2020-03-15 transaction 2631 105 1 105:106 -1 2020-03-16 transaction 2632 105:106:107 1 105:106:107:108 -1 2020-03-17 transaction 2633 105:106:107:108:109 1 105:106:107:108:109:10a -1 2020-03-18 transaction 2634 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2020-03-19 transaction 2635 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2020-03-20 transaction 2636 10f 1 10f:110 -1 2020-03-21 transaction 2637 10f:110:111 1 10f:110:111:112 -1 2020-03-22 transaction 2638 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2020-03-23 transaction 2639 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2020-03-24 transaction 2640 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2020-03-25 transaction 2641 119 1 119:11a -1 2020-03-26 transaction 2642 119:11a:11b 1 119:11a:11b:11c -1 2020-03-27 transaction 2643 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2020-03-28 transaction 2644 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2020-03-29 transaction 2645 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2020-03-30 transaction 2646 123 1 123:124 -1 2020-03-31 transaction 2647 123:124:125 1 123:124:125:126 -1 2020-04-01 transaction 2648 123:124:125:126:127 1 123:124:125:126:127:128 -1 2020-04-02 transaction 2649 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2020-04-03 transaction 2650 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2020-04-04 transaction 2651 12d 1 12d:12e -1 2020-04-05 transaction 2652 12d:12e:12f 1 12d:12e:12f:130 -1 2020-04-06 transaction 2653 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2020-04-07 transaction 2654 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2020-04-08 transaction 2655 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2020-04-09 transaction 2656 137 1 137:138 -1 2020-04-10 transaction 2657 137:138:139 1 137:138:139:13a -1 2020-04-11 transaction 2658 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2020-04-12 transaction 2659 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2020-04-13 transaction 2660 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2020-04-14 transaction 2661 141 1 141:142 -1 2020-04-15 transaction 2662 141:142:143 1 141:142:143:144 -1 2020-04-16 transaction 2663 141:142:143:144:145 1 141:142:143:144:145:146 -1 2020-04-17 transaction 2664 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2020-04-18 transaction 2665 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2020-04-19 transaction 2666 14b 1 14b:14c -1 2020-04-20 transaction 2667 14b:14c:14d 1 14b:14c:14d:14e -1 2020-04-21 transaction 2668 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2020-04-22 transaction 2669 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2020-04-23 transaction 2670 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2020-04-24 transaction 2671 155 1 155:156 -1 2020-04-25 transaction 2672 155:156:157 1 155:156:157:158 -1 2020-04-26 transaction 2673 155:156:157:158:159 1 155:156:157:158:159:15a -1 2020-04-27 transaction 2674 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2020-04-28 transaction 2675 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2020-04-29 transaction 2676 15f 1 15f:160 -1 2020-04-30 transaction 2677 15f:160:161 1 15f:160:161:162 -1 2020-05-01 transaction 2678 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2020-05-02 transaction 2679 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2020-05-03 transaction 2680 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2020-05-04 transaction 2681 169 1 169:16a -1 2020-05-05 transaction 2682 169:16a:16b 1 169:16a:16b:16c -1 2020-05-06 transaction 2683 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2020-05-07 transaction 2684 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2020-05-08 transaction 2685 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2020-05-09 transaction 2686 173 1 173:174 -1 2020-05-10 transaction 2687 173:174:175 1 173:174:175:176 -1 2020-05-11 transaction 2688 173:174:175:176:177 1 173:174:175:176:177:178 -1 2020-05-12 transaction 2689 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2020-05-13 transaction 2690 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2020-05-14 transaction 2691 17d 1 17d:17e -1 2020-05-15 transaction 2692 17d:17e:17f 1 17d:17e:17f:180 -1 2020-05-16 transaction 2693 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2020-05-17 transaction 2694 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2020-05-18 transaction 2695 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2020-05-19 transaction 2696 187 1 187:188 -1 2020-05-20 transaction 2697 187:188:189 1 187:188:189:18a -1 2020-05-21 transaction 2698 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2020-05-22 transaction 2699 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2020-05-23 transaction 2700 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2020-05-24 transaction 2701 191 1 191:192 -1 2020-05-25 transaction 2702 191:192:193 1 191:192:193:194 -1 2020-05-26 transaction 2703 191:192:193:194:195 1 191:192:193:194:195:196 -1 2020-05-27 transaction 2704 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2020-05-28 transaction 2705 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2020-05-29 transaction 2706 19b 1 19b:19c -1 2020-05-30 transaction 2707 19b:19c:19d 1 19b:19c:19d:19e -1 2020-05-31 transaction 2708 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2020-06-01 transaction 2709 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2020-06-02 transaction 2710 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2020-06-03 transaction 2711 1a5 1 1a5:1a6 -1 2020-06-04 transaction 2712 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2020-06-05 transaction 2713 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2020-06-06 transaction 2714 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2020-06-07 transaction 2715 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2020-06-08 transaction 2716 1af 1 1af:1b0 -1 2020-06-09 transaction 2717 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2020-06-10 transaction 2718 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2020-06-11 transaction 2719 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2020-06-12 transaction 2720 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2020-06-13 transaction 2721 1b9 1 1b9:1ba -1 2020-06-14 transaction 2722 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2020-06-15 transaction 2723 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2020-06-16 transaction 2724 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2020-06-17 transaction 2725 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2020-06-18 transaction 2726 1c3 1 1c3:1c4 -1 2020-06-19 transaction 2727 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2020-06-20 transaction 2728 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2020-06-21 transaction 2729 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2020-06-22 transaction 2730 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2020-06-23 transaction 2731 1cd 1 1cd:1ce -1 2020-06-24 transaction 2732 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2020-06-25 transaction 2733 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2020-06-26 transaction 2734 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2020-06-27 transaction 2735 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2020-06-28 transaction 2736 1d7 1 1d7:1d8 -1 2020-06-29 transaction 2737 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2020-06-30 transaction 2738 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2020-07-01 transaction 2739 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2020-07-02 transaction 2740 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2020-07-03 transaction 2741 1e1 1 1e1:1e2 -1 2020-07-04 transaction 2742 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2020-07-05 transaction 2743 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2020-07-06 transaction 2744 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2020-07-07 transaction 2745 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2020-07-08 transaction 2746 1eb 1 1eb:1ec -1 2020-07-09 transaction 2747 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2020-07-10 transaction 2748 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2020-07-11 transaction 2749 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2020-07-12 transaction 2750 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2020-07-13 transaction 2751 1f5 1 1f5:1f6 -1 2020-07-14 transaction 2752 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2020-07-15 transaction 2753 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2020-07-16 transaction 2754 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2020-07-17 transaction 2755 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2020-07-18 transaction 2756 1ff 1 1ff:200 -1 2020-07-19 transaction 2757 1ff:200:201 1 1ff:200:201:202 -1 2020-07-20 transaction 2758 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2020-07-21 transaction 2759 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2020-07-22 transaction 2760 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2020-07-23 transaction 2761 209 1 209:20a -1 2020-07-24 transaction 2762 209:20a:20b 1 209:20a:20b:20c -1 2020-07-25 transaction 2763 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2020-07-26 transaction 2764 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2020-07-27 transaction 2765 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2020-07-28 transaction 2766 213 1 213:214 -1 2020-07-29 transaction 2767 213:214:215 1 213:214:215:216 -1 2020-07-30 transaction 2768 213:214:215:216:217 1 213:214:215:216:217:218 -1 2020-07-31 transaction 2769 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2020-08-01 transaction 2770 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2020-08-02 transaction 2771 21d 1 21d:21e -1 2020-08-03 transaction 2772 21d:21e:21f 1 21d:21e:21f:220 -1 2020-08-04 transaction 2773 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2020-08-05 transaction 2774 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2020-08-06 transaction 2775 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2020-08-07 transaction 2776 227 1 227:228 -1 2020-08-08 transaction 2777 227:228:229 1 227:228:229:22a -1 2020-08-09 transaction 2778 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2020-08-10 transaction 2779 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2020-08-11 transaction 2780 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2020-08-12 transaction 2781 231 1 231:232 -1 2020-08-13 transaction 2782 231:232:233 1 231:232:233:234 -1 2020-08-14 transaction 2783 231:232:233:234:235 1 231:232:233:234:235:236 -1 2020-08-15 transaction 2784 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2020-08-16 transaction 2785 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2020-08-17 transaction 2786 23b 1 23b:23c -1 2020-08-18 transaction 2787 23b:23c:23d 1 23b:23c:23d:23e -1 2020-08-19 transaction 2788 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2020-08-20 transaction 2789 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2020-08-21 transaction 2790 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2020-08-22 transaction 2791 245 1 245:246 -1 2020-08-23 transaction 2792 245:246:247 1 245:246:247:248 -1 2020-08-24 transaction 2793 245:246:247:248:249 1 245:246:247:248:249:24a -1 2020-08-25 transaction 2794 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2020-08-26 transaction 2795 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2020-08-27 transaction 2796 24f 1 24f:250 -1 2020-08-28 transaction 2797 24f:250:251 1 24f:250:251:252 -1 2020-08-29 transaction 2798 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2020-08-30 transaction 2799 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2020-08-31 transaction 2800 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2020-09-01 transaction 2801 259 1 259:25a -1 2020-09-02 transaction 2802 259:25a:25b 1 259:25a:25b:25c -1 2020-09-03 transaction 2803 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2020-09-04 transaction 2804 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2020-09-05 transaction 2805 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2020-09-06 transaction 2806 263 1 263:264 -1 2020-09-07 transaction 2807 263:264:265 1 263:264:265:266 -1 2020-09-08 transaction 2808 263:264:265:266:267 1 263:264:265:266:267:268 -1 2020-09-09 transaction 2809 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2020-09-10 transaction 2810 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2020-09-11 transaction 2811 26d 1 26d:26e -1 2020-09-12 transaction 2812 26d:26e:26f 1 26d:26e:26f:270 -1 2020-09-13 transaction 2813 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2020-09-14 transaction 2814 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2020-09-15 transaction 2815 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2020-09-16 transaction 2816 277 1 277:278 -1 2020-09-17 transaction 2817 277:278:279 1 277:278:279:27a -1 2020-09-18 transaction 2818 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2020-09-19 transaction 2819 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2020-09-20 transaction 2820 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2020-09-21 transaction 2821 281 1 281:282 -1 2020-09-22 transaction 2822 281:282:283 1 281:282:283:284 -1 2020-09-23 transaction 2823 281:282:283:284:285 1 281:282:283:284:285:286 -1 2020-09-24 transaction 2824 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2020-09-25 transaction 2825 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2020-09-26 transaction 2826 28b 1 28b:28c -1 2020-09-27 transaction 2827 28b:28c:28d 1 28b:28c:28d:28e -1 2020-09-28 transaction 2828 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2020-09-29 transaction 2829 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2020-09-30 transaction 2830 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2020-10-01 transaction 2831 295 1 295:296 -1 2020-10-02 transaction 2832 295:296:297 1 295:296:297:298 -1 2020-10-03 transaction 2833 295:296:297:298:299 1 295:296:297:298:299:29a -1 2020-10-04 transaction 2834 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2020-10-05 transaction 2835 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2020-10-06 transaction 2836 29f 1 29f:2a0 -1 2020-10-07 transaction 2837 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2020-10-08 transaction 2838 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2020-10-09 transaction 2839 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2020-10-10 transaction 2840 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2020-10-11 transaction 2841 2a9 1 2a9:2aa -1 2020-10-12 transaction 2842 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2020-10-13 transaction 2843 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2020-10-14 transaction 2844 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2020-10-15 transaction 2845 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2020-10-16 transaction 2846 2b3 1 2b3:2b4 -1 2020-10-17 transaction 2847 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2020-10-18 transaction 2848 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2020-10-19 transaction 2849 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2020-10-20 transaction 2850 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2020-10-21 transaction 2851 2bd 1 2bd:2be -1 2020-10-22 transaction 2852 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2020-10-23 transaction 2853 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2020-10-24 transaction 2854 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2020-10-25 transaction 2855 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2020-10-26 transaction 2856 2c7 1 2c7:2c8 -1 2020-10-27 transaction 2857 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2020-10-28 transaction 2858 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2020-10-29 transaction 2859 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2020-10-30 transaction 2860 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2020-10-31 transaction 2861 2d1 1 2d1:2d2 -1 2020-11-01 transaction 2862 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2020-11-02 transaction 2863 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2020-11-03 transaction 2864 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2020-11-04 transaction 2865 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2020-11-05 transaction 2866 2db 1 2db:2dc -1 2020-11-06 transaction 2867 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2020-11-07 transaction 2868 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2020-11-08 transaction 2869 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2020-11-09 transaction 2870 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2020-11-10 transaction 2871 2e5 1 2e5:2e6 -1 2020-11-11 transaction 2872 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2020-11-12 transaction 2873 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2020-11-13 transaction 2874 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2020-11-14 transaction 2875 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2020-11-15 transaction 2876 2ef 1 2ef:2f0 -1 2020-11-16 transaction 2877 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2020-11-17 transaction 2878 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2020-11-18 transaction 2879 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2020-11-19 transaction 2880 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2020-11-20 transaction 2881 2f9 1 2f9:2fa -1 2020-11-21 transaction 2882 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2020-11-22 transaction 2883 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2020-11-23 transaction 2884 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2020-11-24 transaction 2885 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2020-11-25 transaction 2886 303 1 303:304 -1 2020-11-26 transaction 2887 303:304:305 1 303:304:305:306 -1 2020-11-27 transaction 2888 303:304:305:306:307 1 303:304:305:306:307:308 -1 2020-11-28 transaction 2889 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2020-11-29 transaction 2890 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2020-11-30 transaction 2891 30d 1 30d:30e -1 2020-12-01 transaction 2892 30d:30e:30f 1 30d:30e:30f:310 -1 2020-12-02 transaction 2893 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2020-12-03 transaction 2894 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2020-12-04 transaction 2895 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2020-12-05 transaction 2896 317 1 317:318 -1 2020-12-06 transaction 2897 317:318:319 1 317:318:319:31a -1 2020-12-07 transaction 2898 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2020-12-08 transaction 2899 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2020-12-09 transaction 2900 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2020-12-10 transaction 2901 321 1 321:322 -1 2020-12-11 transaction 2902 321:322:323 1 321:322:323:324 -1 2020-12-12 transaction 2903 321:322:323:324:325 1 321:322:323:324:325:326 -1 2020-12-13 transaction 2904 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2020-12-14 transaction 2905 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2020-12-15 transaction 2906 32b 1 32b:32c -1 2020-12-16 transaction 2907 32b:32c:32d 1 32b:32c:32d:32e -1 2020-12-17 transaction 2908 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2020-12-18 transaction 2909 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2020-12-19 transaction 2910 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2020-12-20 transaction 2911 335 1 335:336 -1 2020-12-21 transaction 2912 335:336:337 1 335:336:337:338 -1 2020-12-22 transaction 2913 335:336:337:338:339 1 335:336:337:338:339:33a -1 2020-12-23 transaction 2914 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2020-12-24 transaction 2915 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2020-12-25 transaction 2916 33f 1 33f:340 -1 2020-12-26 transaction 2917 33f:340:341 1 33f:340:341:342 -1 2020-12-27 transaction 2918 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2020-12-28 transaction 2919 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2020-12-29 transaction 2920 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2020-12-30 transaction 2921 349 1 349:34a -1 2020-12-31 transaction 2922 349:34a:34b 1 349:34a:34b:34c -1 2021-01-01 transaction 2923 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2021-01-02 transaction 2924 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2021-01-03 transaction 2925 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2021-01-04 transaction 2926 353 1 353:354 -1 2021-01-05 transaction 2927 353:354:355 1 353:354:355:356 -1 2021-01-06 transaction 2928 353:354:355:356:357 1 353:354:355:356:357:358 -1 2021-01-07 transaction 2929 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2021-01-08 transaction 2930 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2021-01-09 transaction 2931 35d 1 35d:35e -1 2021-01-10 transaction 2932 35d:35e:35f 1 35d:35e:35f:360 -1 2021-01-11 transaction 2933 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2021-01-12 transaction 2934 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2021-01-13 transaction 2935 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2021-01-14 transaction 2936 367 1 367:368 -1 2021-01-15 transaction 2937 367:368:369 1 367:368:369:36a -1 2021-01-16 transaction 2938 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2021-01-17 transaction 2939 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2021-01-18 transaction 2940 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2021-01-19 transaction 2941 371 1 371:372 -1 2021-01-20 transaction 2942 371:372:373 1 371:372:373:374 -1 2021-01-21 transaction 2943 371:372:373:374:375 1 371:372:373:374:375:376 -1 2021-01-22 transaction 2944 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2021-01-23 transaction 2945 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2021-01-24 transaction 2946 37b 1 37b:37c -1 2021-01-25 transaction 2947 37b:37c:37d 1 37b:37c:37d:37e -1 2021-01-26 transaction 2948 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2021-01-27 transaction 2949 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2021-01-28 transaction 2950 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2021-01-29 transaction 2951 385 1 385:386 -1 2021-01-30 transaction 2952 385:386:387 1 385:386:387:388 -1 2021-01-31 transaction 2953 385:386:387:388:389 1 385:386:387:388:389:38a -1 2021-02-01 transaction 2954 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2021-02-02 transaction 2955 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2021-02-03 transaction 2956 38f 1 38f:390 -1 2021-02-04 transaction 2957 38f:390:391 1 38f:390:391:392 -1 2021-02-05 transaction 2958 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2021-02-06 transaction 2959 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2021-02-07 transaction 2960 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2021-02-08 transaction 2961 399 1 399:39a -1 2021-02-09 transaction 2962 399:39a:39b 1 399:39a:39b:39c -1 2021-02-10 transaction 2963 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2021-02-11 transaction 2964 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2021-02-12 transaction 2965 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2021-02-13 transaction 2966 3a3 1 3a3:3a4 -1 2021-02-14 transaction 2967 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2021-02-15 transaction 2968 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2021-02-16 transaction 2969 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2021-02-17 transaction 2970 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2021-02-18 transaction 2971 3ad 1 3ad:3ae -1 2021-02-19 transaction 2972 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2021-02-20 transaction 2973 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2021-02-21 transaction 2974 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2021-02-22 transaction 2975 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2021-02-23 transaction 2976 3b7 1 3b7:3b8 -1 2021-02-24 transaction 2977 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2021-02-25 transaction 2978 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2021-02-26 transaction 2979 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2021-02-27 transaction 2980 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2021-02-28 transaction 2981 3c1 1 3c1:3c2 -1 2021-03-01 transaction 2982 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2021-03-02 transaction 2983 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2021-03-03 transaction 2984 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2021-03-04 transaction 2985 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2021-03-05 transaction 2986 3cb 1 3cb:3cc -1 2021-03-06 transaction 2987 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2021-03-07 transaction 2988 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2021-03-08 transaction 2989 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2021-03-09 transaction 2990 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2021-03-10 transaction 2991 3d5 1 3d5:3d6 -1 2021-03-11 transaction 2992 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2021-03-12 transaction 2993 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2021-03-13 transaction 2994 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2021-03-14 transaction 2995 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2021-03-15 transaction 2996 3df 1 3df:3e0 -1 2021-03-16 transaction 2997 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2021-03-17 transaction 2998 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2021-03-18 transaction 2999 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2021-03-19 transaction 3000 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2021-03-20 transaction 3001 1 1 1:2 -1 2021-03-21 transaction 3002 1:2:3 1 1:2:3:4 -1 2021-03-22 transaction 3003 1:2:3:4:5 1 1:2:3:4:5:6 -1 2021-03-23 transaction 3004 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2021-03-24 transaction 3005 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2021-03-25 transaction 3006 b 1 b:c -1 2021-03-26 transaction 3007 b:c:d 1 b:c:d:e -1 2021-03-27 transaction 3008 b:c:d:e:f 1 b:c:d:e:f:10 -1 2021-03-28 transaction 3009 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2021-03-29 transaction 3010 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2021-03-30 transaction 3011 15 1 15:16 -1 2021-03-31 transaction 3012 15:16:17 1 15:16:17:18 -1 2021-04-01 transaction 3013 15:16:17:18:19 1 15:16:17:18:19:1a -1 2021-04-02 transaction 3014 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2021-04-03 transaction 3015 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2021-04-04 transaction 3016 1f 1 1f:20 -1 2021-04-05 transaction 3017 1f:20:21 1 1f:20:21:22 -1 2021-04-06 transaction 3018 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2021-04-07 transaction 3019 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2021-04-08 transaction 3020 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2021-04-09 transaction 3021 29 1 29:2a -1 2021-04-10 transaction 3022 29:2a:2b 1 29:2a:2b:2c -1 2021-04-11 transaction 3023 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2021-04-12 transaction 3024 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2021-04-13 transaction 3025 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2021-04-14 transaction 3026 33 1 33:34 -1 2021-04-15 transaction 3027 33:34:35 1 33:34:35:36 -1 2021-04-16 transaction 3028 33:34:35:36:37 1 33:34:35:36:37:38 -1 2021-04-17 transaction 3029 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2021-04-18 transaction 3030 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2021-04-19 transaction 3031 3d 1 3d:3e -1 2021-04-20 transaction 3032 3d:3e:3f 1 3d:3e:3f:40 -1 2021-04-21 transaction 3033 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2021-04-22 transaction 3034 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2021-04-23 transaction 3035 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2021-04-24 transaction 3036 47 1 47:48 -1 2021-04-25 transaction 3037 47:48:49 1 47:48:49:4a -1 2021-04-26 transaction 3038 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2021-04-27 transaction 3039 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2021-04-28 transaction 3040 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2021-04-29 transaction 3041 51 1 51:52 -1 2021-04-30 transaction 3042 51:52:53 1 51:52:53:54 -1 2021-05-01 transaction 3043 51:52:53:54:55 1 51:52:53:54:55:56 -1 2021-05-02 transaction 3044 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2021-05-03 transaction 3045 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2021-05-04 transaction 3046 5b 1 5b:5c -1 2021-05-05 transaction 3047 5b:5c:5d 1 5b:5c:5d:5e -1 2021-05-06 transaction 3048 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2021-05-07 transaction 3049 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2021-05-08 transaction 3050 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2021-05-09 transaction 3051 65 1 65:66 -1 2021-05-10 transaction 3052 65:66:67 1 65:66:67:68 -1 2021-05-11 transaction 3053 65:66:67:68:69 1 65:66:67:68:69:6a -1 2021-05-12 transaction 3054 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2021-05-13 transaction 3055 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2021-05-14 transaction 3056 6f 1 6f:70 -1 2021-05-15 transaction 3057 6f:70:71 1 6f:70:71:72 -1 2021-05-16 transaction 3058 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2021-05-17 transaction 3059 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2021-05-18 transaction 3060 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2021-05-19 transaction 3061 79 1 79:7a -1 2021-05-20 transaction 3062 79:7a:7b 1 79:7a:7b:7c -1 2021-05-21 transaction 3063 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2021-05-22 transaction 3064 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2021-05-23 transaction 3065 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2021-05-24 transaction 3066 83 1 83:84 -1 2021-05-25 transaction 3067 83:84:85 1 83:84:85:86 -1 2021-05-26 transaction 3068 83:84:85:86:87 1 83:84:85:86:87:88 -1 2021-05-27 transaction 3069 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2021-05-28 transaction 3070 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2021-05-29 transaction 3071 8d 1 8d:8e -1 2021-05-30 transaction 3072 8d:8e:8f 1 8d:8e:8f:90 -1 2021-05-31 transaction 3073 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2021-06-01 transaction 3074 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2021-06-02 transaction 3075 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2021-06-03 transaction 3076 97 1 97:98 -1 2021-06-04 transaction 3077 97:98:99 1 97:98:99:9a -1 2021-06-05 transaction 3078 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2021-06-06 transaction 3079 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2021-06-07 transaction 3080 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2021-06-08 transaction 3081 a1 1 a1:a2 -1 2021-06-09 transaction 3082 a1:a2:a3 1 a1:a2:a3:a4 -1 2021-06-10 transaction 3083 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2021-06-11 transaction 3084 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2021-06-12 transaction 3085 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2021-06-13 transaction 3086 ab 1 ab:ac -1 2021-06-14 transaction 3087 ab:ac:ad 1 ab:ac:ad:ae -1 2021-06-15 transaction 3088 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2021-06-16 transaction 3089 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2021-06-17 transaction 3090 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2021-06-18 transaction 3091 b5 1 b5:b6 -1 2021-06-19 transaction 3092 b5:b6:b7 1 b5:b6:b7:b8 -1 2021-06-20 transaction 3093 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2021-06-21 transaction 3094 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2021-06-22 transaction 3095 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2021-06-23 transaction 3096 bf 1 bf:c0 -1 2021-06-24 transaction 3097 bf:c0:c1 1 bf:c0:c1:c2 -1 2021-06-25 transaction 3098 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2021-06-26 transaction 3099 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2021-06-27 transaction 3100 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2021-06-28 transaction 3101 c9 1 c9:ca -1 2021-06-29 transaction 3102 c9:ca:cb 1 c9:ca:cb:cc -1 2021-06-30 transaction 3103 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2021-07-01 transaction 3104 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2021-07-02 transaction 3105 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2021-07-03 transaction 3106 d3 1 d3:d4 -1 2021-07-04 transaction 3107 d3:d4:d5 1 d3:d4:d5:d6 -1 2021-07-05 transaction 3108 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2021-07-06 transaction 3109 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2021-07-07 transaction 3110 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2021-07-08 transaction 3111 dd 1 dd:de -1 2021-07-09 transaction 3112 dd:de:df 1 dd:de:df:e0 -1 2021-07-10 transaction 3113 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2021-07-11 transaction 3114 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2021-07-12 transaction 3115 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2021-07-13 transaction 3116 e7 1 e7:e8 -1 2021-07-14 transaction 3117 e7:e8:e9 1 e7:e8:e9:ea -1 2021-07-15 transaction 3118 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2021-07-16 transaction 3119 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2021-07-17 transaction 3120 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2021-07-18 transaction 3121 f1 1 f1:f2 -1 2021-07-19 transaction 3122 f1:f2:f3 1 f1:f2:f3:f4 -1 2021-07-20 transaction 3123 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2021-07-21 transaction 3124 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2021-07-22 transaction 3125 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2021-07-23 transaction 3126 fb 1 fb:fc -1 2021-07-24 transaction 3127 fb:fc:fd 1 fb:fc:fd:fe -1 2021-07-25 transaction 3128 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2021-07-26 transaction 3129 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2021-07-27 transaction 3130 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2021-07-28 transaction 3131 105 1 105:106 -1 2021-07-29 transaction 3132 105:106:107 1 105:106:107:108 -1 2021-07-30 transaction 3133 105:106:107:108:109 1 105:106:107:108:109:10a -1 2021-07-31 transaction 3134 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2021-08-01 transaction 3135 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2021-08-02 transaction 3136 10f 1 10f:110 -1 2021-08-03 transaction 3137 10f:110:111 1 10f:110:111:112 -1 2021-08-04 transaction 3138 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2021-08-05 transaction 3139 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2021-08-06 transaction 3140 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2021-08-07 transaction 3141 119 1 119:11a -1 2021-08-08 transaction 3142 119:11a:11b 1 119:11a:11b:11c -1 2021-08-09 transaction 3143 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2021-08-10 transaction 3144 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2021-08-11 transaction 3145 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2021-08-12 transaction 3146 123 1 123:124 -1 2021-08-13 transaction 3147 123:124:125 1 123:124:125:126 -1 2021-08-14 transaction 3148 123:124:125:126:127 1 123:124:125:126:127:128 -1 2021-08-15 transaction 3149 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2021-08-16 transaction 3150 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2021-08-17 transaction 3151 12d 1 12d:12e -1 2021-08-18 transaction 3152 12d:12e:12f 1 12d:12e:12f:130 -1 2021-08-19 transaction 3153 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2021-08-20 transaction 3154 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2021-08-21 transaction 3155 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2021-08-22 transaction 3156 137 1 137:138 -1 2021-08-23 transaction 3157 137:138:139 1 137:138:139:13a -1 2021-08-24 transaction 3158 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2021-08-25 transaction 3159 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2021-08-26 transaction 3160 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2021-08-27 transaction 3161 141 1 141:142 -1 2021-08-28 transaction 3162 141:142:143 1 141:142:143:144 -1 2021-08-29 transaction 3163 141:142:143:144:145 1 141:142:143:144:145:146 -1 2021-08-30 transaction 3164 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2021-08-31 transaction 3165 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2021-09-01 transaction 3166 14b 1 14b:14c -1 2021-09-02 transaction 3167 14b:14c:14d 1 14b:14c:14d:14e -1 2021-09-03 transaction 3168 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2021-09-04 transaction 3169 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2021-09-05 transaction 3170 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2021-09-06 transaction 3171 155 1 155:156 -1 2021-09-07 transaction 3172 155:156:157 1 155:156:157:158 -1 2021-09-08 transaction 3173 155:156:157:158:159 1 155:156:157:158:159:15a -1 2021-09-09 transaction 3174 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2021-09-10 transaction 3175 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2021-09-11 transaction 3176 15f 1 15f:160 -1 2021-09-12 transaction 3177 15f:160:161 1 15f:160:161:162 -1 2021-09-13 transaction 3178 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2021-09-14 transaction 3179 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2021-09-15 transaction 3180 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2021-09-16 transaction 3181 169 1 169:16a -1 2021-09-17 transaction 3182 169:16a:16b 1 169:16a:16b:16c -1 2021-09-18 transaction 3183 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2021-09-19 transaction 3184 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2021-09-20 transaction 3185 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2021-09-21 transaction 3186 173 1 173:174 -1 2021-09-22 transaction 3187 173:174:175 1 173:174:175:176 -1 2021-09-23 transaction 3188 173:174:175:176:177 1 173:174:175:176:177:178 -1 2021-09-24 transaction 3189 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2021-09-25 transaction 3190 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2021-09-26 transaction 3191 17d 1 17d:17e -1 2021-09-27 transaction 3192 17d:17e:17f 1 17d:17e:17f:180 -1 2021-09-28 transaction 3193 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2021-09-29 transaction 3194 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2021-09-30 transaction 3195 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2021-10-01 transaction 3196 187 1 187:188 -1 2021-10-02 transaction 3197 187:188:189 1 187:188:189:18a -1 2021-10-03 transaction 3198 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2021-10-04 transaction 3199 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2021-10-05 transaction 3200 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2021-10-06 transaction 3201 191 1 191:192 -1 2021-10-07 transaction 3202 191:192:193 1 191:192:193:194 -1 2021-10-08 transaction 3203 191:192:193:194:195 1 191:192:193:194:195:196 -1 2021-10-09 transaction 3204 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2021-10-10 transaction 3205 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2021-10-11 transaction 3206 19b 1 19b:19c -1 2021-10-12 transaction 3207 19b:19c:19d 1 19b:19c:19d:19e -1 2021-10-13 transaction 3208 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2021-10-14 transaction 3209 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2021-10-15 transaction 3210 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2021-10-16 transaction 3211 1a5 1 1a5:1a6 -1 2021-10-17 transaction 3212 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2021-10-18 transaction 3213 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2021-10-19 transaction 3214 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2021-10-20 transaction 3215 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2021-10-21 transaction 3216 1af 1 1af:1b0 -1 2021-10-22 transaction 3217 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2021-10-23 transaction 3218 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2021-10-24 transaction 3219 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2021-10-25 transaction 3220 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2021-10-26 transaction 3221 1b9 1 1b9:1ba -1 2021-10-27 transaction 3222 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2021-10-28 transaction 3223 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2021-10-29 transaction 3224 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2021-10-30 transaction 3225 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2021-10-31 transaction 3226 1c3 1 1c3:1c4 -1 2021-11-01 transaction 3227 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2021-11-02 transaction 3228 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2021-11-03 transaction 3229 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2021-11-04 transaction 3230 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2021-11-05 transaction 3231 1cd 1 1cd:1ce -1 2021-11-06 transaction 3232 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2021-11-07 transaction 3233 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2021-11-08 transaction 3234 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2021-11-09 transaction 3235 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2021-11-10 transaction 3236 1d7 1 1d7:1d8 -1 2021-11-11 transaction 3237 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2021-11-12 transaction 3238 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2021-11-13 transaction 3239 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2021-11-14 transaction 3240 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2021-11-15 transaction 3241 1e1 1 1e1:1e2 -1 2021-11-16 transaction 3242 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2021-11-17 transaction 3243 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2021-11-18 transaction 3244 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2021-11-19 transaction 3245 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2021-11-20 transaction 3246 1eb 1 1eb:1ec -1 2021-11-21 transaction 3247 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2021-11-22 transaction 3248 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2021-11-23 transaction 3249 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2021-11-24 transaction 3250 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2021-11-25 transaction 3251 1f5 1 1f5:1f6 -1 2021-11-26 transaction 3252 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2021-11-27 transaction 3253 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2021-11-28 transaction 3254 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2021-11-29 transaction 3255 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2021-11-30 transaction 3256 1ff 1 1ff:200 -1 2021-12-01 transaction 3257 1ff:200:201 1 1ff:200:201:202 -1 2021-12-02 transaction 3258 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2021-12-03 transaction 3259 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2021-12-04 transaction 3260 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2021-12-05 transaction 3261 209 1 209:20a -1 2021-12-06 transaction 3262 209:20a:20b 1 209:20a:20b:20c -1 2021-12-07 transaction 3263 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2021-12-08 transaction 3264 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2021-12-09 transaction 3265 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2021-12-10 transaction 3266 213 1 213:214 -1 2021-12-11 transaction 3267 213:214:215 1 213:214:215:216 -1 2021-12-12 transaction 3268 213:214:215:216:217 1 213:214:215:216:217:218 -1 2021-12-13 transaction 3269 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2021-12-14 transaction 3270 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2021-12-15 transaction 3271 21d 1 21d:21e -1 2021-12-16 transaction 3272 21d:21e:21f 1 21d:21e:21f:220 -1 2021-12-17 transaction 3273 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2021-12-18 transaction 3274 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2021-12-19 transaction 3275 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2021-12-20 transaction 3276 227 1 227:228 -1 2021-12-21 transaction 3277 227:228:229 1 227:228:229:22a -1 2021-12-22 transaction 3278 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2021-12-23 transaction 3279 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2021-12-24 transaction 3280 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2021-12-25 transaction 3281 231 1 231:232 -1 2021-12-26 transaction 3282 231:232:233 1 231:232:233:234 -1 2021-12-27 transaction 3283 231:232:233:234:235 1 231:232:233:234:235:236 -1 2021-12-28 transaction 3284 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2021-12-29 transaction 3285 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2021-12-30 transaction 3286 23b 1 23b:23c -1 2021-12-31 transaction 3287 23b:23c:23d 1 23b:23c:23d:23e -1 2022-01-01 transaction 3288 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2022-01-02 transaction 3289 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2022-01-03 transaction 3290 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2022-01-04 transaction 3291 245 1 245:246 -1 2022-01-05 transaction 3292 245:246:247 1 245:246:247:248 -1 2022-01-06 transaction 3293 245:246:247:248:249 1 245:246:247:248:249:24a -1 2022-01-07 transaction 3294 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2022-01-08 transaction 3295 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2022-01-09 transaction 3296 24f 1 24f:250 -1 2022-01-10 transaction 3297 24f:250:251 1 24f:250:251:252 -1 2022-01-11 transaction 3298 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2022-01-12 transaction 3299 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2022-01-13 transaction 3300 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2022-01-14 transaction 3301 259 1 259:25a -1 2022-01-15 transaction 3302 259:25a:25b 1 259:25a:25b:25c -1 2022-01-16 transaction 3303 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2022-01-17 transaction 3304 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2022-01-18 transaction 3305 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2022-01-19 transaction 3306 263 1 263:264 -1 2022-01-20 transaction 3307 263:264:265 1 263:264:265:266 -1 2022-01-21 transaction 3308 263:264:265:266:267 1 263:264:265:266:267:268 -1 2022-01-22 transaction 3309 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2022-01-23 transaction 3310 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2022-01-24 transaction 3311 26d 1 26d:26e -1 2022-01-25 transaction 3312 26d:26e:26f 1 26d:26e:26f:270 -1 2022-01-26 transaction 3313 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2022-01-27 transaction 3314 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2022-01-28 transaction 3315 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2022-01-29 transaction 3316 277 1 277:278 -1 2022-01-30 transaction 3317 277:278:279 1 277:278:279:27a -1 2022-01-31 transaction 3318 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2022-02-01 transaction 3319 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2022-02-02 transaction 3320 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2022-02-03 transaction 3321 281 1 281:282 -1 2022-02-04 transaction 3322 281:282:283 1 281:282:283:284 -1 2022-02-05 transaction 3323 281:282:283:284:285 1 281:282:283:284:285:286 -1 2022-02-06 transaction 3324 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2022-02-07 transaction 3325 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2022-02-08 transaction 3326 28b 1 28b:28c -1 2022-02-09 transaction 3327 28b:28c:28d 1 28b:28c:28d:28e -1 2022-02-10 transaction 3328 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2022-02-11 transaction 3329 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2022-02-12 transaction 3330 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2022-02-13 transaction 3331 295 1 295:296 -1 2022-02-14 transaction 3332 295:296:297 1 295:296:297:298 -1 2022-02-15 transaction 3333 295:296:297:298:299 1 295:296:297:298:299:29a -1 2022-02-16 transaction 3334 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2022-02-17 transaction 3335 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2022-02-18 transaction 3336 29f 1 29f:2a0 -1 2022-02-19 transaction 3337 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2022-02-20 transaction 3338 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2022-02-21 transaction 3339 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2022-02-22 transaction 3340 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2022-02-23 transaction 3341 2a9 1 2a9:2aa -1 2022-02-24 transaction 3342 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2022-02-25 transaction 3343 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2022-02-26 transaction 3344 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2022-02-27 transaction 3345 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2022-02-28 transaction 3346 2b3 1 2b3:2b4 -1 2022-03-01 transaction 3347 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2022-03-02 transaction 3348 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2022-03-03 transaction 3349 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2022-03-04 transaction 3350 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2022-03-05 transaction 3351 2bd 1 2bd:2be -1 2022-03-06 transaction 3352 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2022-03-07 transaction 3353 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2022-03-08 transaction 3354 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2022-03-09 transaction 3355 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2022-03-10 transaction 3356 2c7 1 2c7:2c8 -1 2022-03-11 transaction 3357 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2022-03-12 transaction 3358 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2022-03-13 transaction 3359 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2022-03-14 transaction 3360 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2022-03-15 transaction 3361 2d1 1 2d1:2d2 -1 2022-03-16 transaction 3362 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2022-03-17 transaction 3363 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2022-03-18 transaction 3364 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2022-03-19 transaction 3365 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2022-03-20 transaction 3366 2db 1 2db:2dc -1 2022-03-21 transaction 3367 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2022-03-22 transaction 3368 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2022-03-23 transaction 3369 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2022-03-24 transaction 3370 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2022-03-25 transaction 3371 2e5 1 2e5:2e6 -1 2022-03-26 transaction 3372 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2022-03-27 transaction 3373 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2022-03-28 transaction 3374 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2022-03-29 transaction 3375 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2022-03-30 transaction 3376 2ef 1 2ef:2f0 -1 2022-03-31 transaction 3377 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2022-04-01 transaction 3378 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2022-04-02 transaction 3379 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2022-04-03 transaction 3380 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2022-04-04 transaction 3381 2f9 1 2f9:2fa -1 2022-04-05 transaction 3382 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2022-04-06 transaction 3383 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2022-04-07 transaction 3384 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2022-04-08 transaction 3385 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2022-04-09 transaction 3386 303 1 303:304 -1 2022-04-10 transaction 3387 303:304:305 1 303:304:305:306 -1 2022-04-11 transaction 3388 303:304:305:306:307 1 303:304:305:306:307:308 -1 2022-04-12 transaction 3389 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2022-04-13 transaction 3390 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2022-04-14 transaction 3391 30d 1 30d:30e -1 2022-04-15 transaction 3392 30d:30e:30f 1 30d:30e:30f:310 -1 2022-04-16 transaction 3393 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2022-04-17 transaction 3394 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2022-04-18 transaction 3395 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2022-04-19 transaction 3396 317 1 317:318 -1 2022-04-20 transaction 3397 317:318:319 1 317:318:319:31a -1 2022-04-21 transaction 3398 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2022-04-22 transaction 3399 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2022-04-23 transaction 3400 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2022-04-24 transaction 3401 321 1 321:322 -1 2022-04-25 transaction 3402 321:322:323 1 321:322:323:324 -1 2022-04-26 transaction 3403 321:322:323:324:325 1 321:322:323:324:325:326 -1 2022-04-27 transaction 3404 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2022-04-28 transaction 3405 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2022-04-29 transaction 3406 32b 1 32b:32c -1 2022-04-30 transaction 3407 32b:32c:32d 1 32b:32c:32d:32e -1 2022-05-01 transaction 3408 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2022-05-02 transaction 3409 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2022-05-03 transaction 3410 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2022-05-04 transaction 3411 335 1 335:336 -1 2022-05-05 transaction 3412 335:336:337 1 335:336:337:338 -1 2022-05-06 transaction 3413 335:336:337:338:339 1 335:336:337:338:339:33a -1 2022-05-07 transaction 3414 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2022-05-08 transaction 3415 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2022-05-09 transaction 3416 33f 1 33f:340 -1 2022-05-10 transaction 3417 33f:340:341 1 33f:340:341:342 -1 2022-05-11 transaction 3418 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2022-05-12 transaction 3419 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2022-05-13 transaction 3420 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2022-05-14 transaction 3421 349 1 349:34a -1 2022-05-15 transaction 3422 349:34a:34b 1 349:34a:34b:34c -1 2022-05-16 transaction 3423 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2022-05-17 transaction 3424 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2022-05-18 transaction 3425 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2022-05-19 transaction 3426 353 1 353:354 -1 2022-05-20 transaction 3427 353:354:355 1 353:354:355:356 -1 2022-05-21 transaction 3428 353:354:355:356:357 1 353:354:355:356:357:358 -1 2022-05-22 transaction 3429 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2022-05-23 transaction 3430 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2022-05-24 transaction 3431 35d 1 35d:35e -1 2022-05-25 transaction 3432 35d:35e:35f 1 35d:35e:35f:360 -1 2022-05-26 transaction 3433 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2022-05-27 transaction 3434 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2022-05-28 transaction 3435 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2022-05-29 transaction 3436 367 1 367:368 -1 2022-05-30 transaction 3437 367:368:369 1 367:368:369:36a -1 2022-05-31 transaction 3438 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2022-06-01 transaction 3439 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2022-06-02 transaction 3440 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2022-06-03 transaction 3441 371 1 371:372 -1 2022-06-04 transaction 3442 371:372:373 1 371:372:373:374 -1 2022-06-05 transaction 3443 371:372:373:374:375 1 371:372:373:374:375:376 -1 2022-06-06 transaction 3444 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2022-06-07 transaction 3445 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2022-06-08 transaction 3446 37b 1 37b:37c -1 2022-06-09 transaction 3447 37b:37c:37d 1 37b:37c:37d:37e -1 2022-06-10 transaction 3448 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2022-06-11 transaction 3449 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2022-06-12 transaction 3450 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2022-06-13 transaction 3451 385 1 385:386 -1 2022-06-14 transaction 3452 385:386:387 1 385:386:387:388 -1 2022-06-15 transaction 3453 385:386:387:388:389 1 385:386:387:388:389:38a -1 2022-06-16 transaction 3454 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2022-06-17 transaction 3455 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2022-06-18 transaction 3456 38f 1 38f:390 -1 2022-06-19 transaction 3457 38f:390:391 1 38f:390:391:392 -1 2022-06-20 transaction 3458 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2022-06-21 transaction 3459 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2022-06-22 transaction 3460 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2022-06-23 transaction 3461 399 1 399:39a -1 2022-06-24 transaction 3462 399:39a:39b 1 399:39a:39b:39c -1 2022-06-25 transaction 3463 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2022-06-26 transaction 3464 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2022-06-27 transaction 3465 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2022-06-28 transaction 3466 3a3 1 3a3:3a4 -1 2022-06-29 transaction 3467 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2022-06-30 transaction 3468 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2022-07-01 transaction 3469 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2022-07-02 transaction 3470 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2022-07-03 transaction 3471 3ad 1 3ad:3ae -1 2022-07-04 transaction 3472 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2022-07-05 transaction 3473 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2022-07-06 transaction 3474 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2022-07-07 transaction 3475 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2022-07-08 transaction 3476 3b7 1 3b7:3b8 -1 2022-07-09 transaction 3477 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2022-07-10 transaction 3478 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2022-07-11 transaction 3479 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2022-07-12 transaction 3480 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2022-07-13 transaction 3481 3c1 1 3c1:3c2 -1 2022-07-14 transaction 3482 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2022-07-15 transaction 3483 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2022-07-16 transaction 3484 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2022-07-17 transaction 3485 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2022-07-18 transaction 3486 3cb 1 3cb:3cc -1 2022-07-19 transaction 3487 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2022-07-20 transaction 3488 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2022-07-21 transaction 3489 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2022-07-22 transaction 3490 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2022-07-23 transaction 3491 3d5 1 3d5:3d6 -1 2022-07-24 transaction 3492 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2022-07-25 transaction 3493 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2022-07-26 transaction 3494 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2022-07-27 transaction 3495 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2022-07-28 transaction 3496 3df 1 3df:3e0 -1 2022-07-29 transaction 3497 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2022-07-30 transaction 3498 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2022-07-31 transaction 3499 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2022-08-01 transaction 3500 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2022-08-02 transaction 3501 1 1 1:2 -1 2022-08-03 transaction 3502 1:2:3 1 1:2:3:4 -1 2022-08-04 transaction 3503 1:2:3:4:5 1 1:2:3:4:5:6 -1 2022-08-05 transaction 3504 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2022-08-06 transaction 3505 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2022-08-07 transaction 3506 b 1 b:c -1 2022-08-08 transaction 3507 b:c:d 1 b:c:d:e -1 2022-08-09 transaction 3508 b:c:d:e:f 1 b:c:d:e:f:10 -1 2022-08-10 transaction 3509 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2022-08-11 transaction 3510 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2022-08-12 transaction 3511 15 1 15:16 -1 2022-08-13 transaction 3512 15:16:17 1 15:16:17:18 -1 2022-08-14 transaction 3513 15:16:17:18:19 1 15:16:17:18:19:1a -1 2022-08-15 transaction 3514 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2022-08-16 transaction 3515 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2022-08-17 transaction 3516 1f 1 1f:20 -1 2022-08-18 transaction 3517 1f:20:21 1 1f:20:21:22 -1 2022-08-19 transaction 3518 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2022-08-20 transaction 3519 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2022-08-21 transaction 3520 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2022-08-22 transaction 3521 29 1 29:2a -1 2022-08-23 transaction 3522 29:2a:2b 1 29:2a:2b:2c -1 2022-08-24 transaction 3523 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2022-08-25 transaction 3524 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2022-08-26 transaction 3525 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2022-08-27 transaction 3526 33 1 33:34 -1 2022-08-28 transaction 3527 33:34:35 1 33:34:35:36 -1 2022-08-29 transaction 3528 33:34:35:36:37 1 33:34:35:36:37:38 -1 2022-08-30 transaction 3529 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2022-08-31 transaction 3530 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2022-09-01 transaction 3531 3d 1 3d:3e -1 2022-09-02 transaction 3532 3d:3e:3f 1 3d:3e:3f:40 -1 2022-09-03 transaction 3533 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2022-09-04 transaction 3534 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2022-09-05 transaction 3535 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2022-09-06 transaction 3536 47 1 47:48 -1 2022-09-07 transaction 3537 47:48:49 1 47:48:49:4a -1 2022-09-08 transaction 3538 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2022-09-09 transaction 3539 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2022-09-10 transaction 3540 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2022-09-11 transaction 3541 51 1 51:52 -1 2022-09-12 transaction 3542 51:52:53 1 51:52:53:54 -1 2022-09-13 transaction 3543 51:52:53:54:55 1 51:52:53:54:55:56 -1 2022-09-14 transaction 3544 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2022-09-15 transaction 3545 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2022-09-16 transaction 3546 5b 1 5b:5c -1 2022-09-17 transaction 3547 5b:5c:5d 1 5b:5c:5d:5e -1 2022-09-18 transaction 3548 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2022-09-19 transaction 3549 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2022-09-20 transaction 3550 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2022-09-21 transaction 3551 65 1 65:66 -1 2022-09-22 transaction 3552 65:66:67 1 65:66:67:68 -1 2022-09-23 transaction 3553 65:66:67:68:69 1 65:66:67:68:69:6a -1 2022-09-24 transaction 3554 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2022-09-25 transaction 3555 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2022-09-26 transaction 3556 6f 1 6f:70 -1 2022-09-27 transaction 3557 6f:70:71 1 6f:70:71:72 -1 2022-09-28 transaction 3558 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2022-09-29 transaction 3559 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2022-09-30 transaction 3560 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2022-10-01 transaction 3561 79 1 79:7a -1 2022-10-02 transaction 3562 79:7a:7b 1 79:7a:7b:7c -1 2022-10-03 transaction 3563 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2022-10-04 transaction 3564 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2022-10-05 transaction 3565 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2022-10-06 transaction 3566 83 1 83:84 -1 2022-10-07 transaction 3567 83:84:85 1 83:84:85:86 -1 2022-10-08 transaction 3568 83:84:85:86:87 1 83:84:85:86:87:88 -1 2022-10-09 transaction 3569 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2022-10-10 transaction 3570 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2022-10-11 transaction 3571 8d 1 8d:8e -1 2022-10-12 transaction 3572 8d:8e:8f 1 8d:8e:8f:90 -1 2022-10-13 transaction 3573 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2022-10-14 transaction 3574 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2022-10-15 transaction 3575 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2022-10-16 transaction 3576 97 1 97:98 -1 2022-10-17 transaction 3577 97:98:99 1 97:98:99:9a -1 2022-10-18 transaction 3578 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2022-10-19 transaction 3579 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2022-10-20 transaction 3580 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2022-10-21 transaction 3581 a1 1 a1:a2 -1 2022-10-22 transaction 3582 a1:a2:a3 1 a1:a2:a3:a4 -1 2022-10-23 transaction 3583 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2022-10-24 transaction 3584 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2022-10-25 transaction 3585 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2022-10-26 transaction 3586 ab 1 ab:ac -1 2022-10-27 transaction 3587 ab:ac:ad 1 ab:ac:ad:ae -1 2022-10-28 transaction 3588 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2022-10-29 transaction 3589 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2022-10-30 transaction 3590 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2022-10-31 transaction 3591 b5 1 b5:b6 -1 2022-11-01 transaction 3592 b5:b6:b7 1 b5:b6:b7:b8 -1 2022-11-02 transaction 3593 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2022-11-03 transaction 3594 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2022-11-04 transaction 3595 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2022-11-05 transaction 3596 bf 1 bf:c0 -1 2022-11-06 transaction 3597 bf:c0:c1 1 bf:c0:c1:c2 -1 2022-11-07 transaction 3598 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2022-11-08 transaction 3599 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2022-11-09 transaction 3600 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2022-11-10 transaction 3601 c9 1 c9:ca -1 2022-11-11 transaction 3602 c9:ca:cb 1 c9:ca:cb:cc -1 2022-11-12 transaction 3603 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2022-11-13 transaction 3604 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2022-11-14 transaction 3605 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2022-11-15 transaction 3606 d3 1 d3:d4 -1 2022-11-16 transaction 3607 d3:d4:d5 1 d3:d4:d5:d6 -1 2022-11-17 transaction 3608 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2022-11-18 transaction 3609 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2022-11-19 transaction 3610 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2022-11-20 transaction 3611 dd 1 dd:de -1 2022-11-21 transaction 3612 dd:de:df 1 dd:de:df:e0 -1 2022-11-22 transaction 3613 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2022-11-23 transaction 3614 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2022-11-24 transaction 3615 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2022-11-25 transaction 3616 e7 1 e7:e8 -1 2022-11-26 transaction 3617 e7:e8:e9 1 e7:e8:e9:ea -1 2022-11-27 transaction 3618 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2022-11-28 transaction 3619 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2022-11-29 transaction 3620 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2022-11-30 transaction 3621 f1 1 f1:f2 -1 2022-12-01 transaction 3622 f1:f2:f3 1 f1:f2:f3:f4 -1 2022-12-02 transaction 3623 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2022-12-03 transaction 3624 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2022-12-04 transaction 3625 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2022-12-05 transaction 3626 fb 1 fb:fc -1 2022-12-06 transaction 3627 fb:fc:fd 1 fb:fc:fd:fe -1 2022-12-07 transaction 3628 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2022-12-08 transaction 3629 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2022-12-09 transaction 3630 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2022-12-10 transaction 3631 105 1 105:106 -1 2022-12-11 transaction 3632 105:106:107 1 105:106:107:108 -1 2022-12-12 transaction 3633 105:106:107:108:109 1 105:106:107:108:109:10a -1 2022-12-13 transaction 3634 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2022-12-14 transaction 3635 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2022-12-15 transaction 3636 10f 1 10f:110 -1 2022-12-16 transaction 3637 10f:110:111 1 10f:110:111:112 -1 2022-12-17 transaction 3638 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2022-12-18 transaction 3639 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2022-12-19 transaction 3640 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2022-12-20 transaction 3641 119 1 119:11a -1 2022-12-21 transaction 3642 119:11a:11b 1 119:11a:11b:11c -1 2022-12-22 transaction 3643 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2022-12-23 transaction 3644 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2022-12-24 transaction 3645 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2022-12-25 transaction 3646 123 1 123:124 -1 2022-12-26 transaction 3647 123:124:125 1 123:124:125:126 -1 2022-12-27 transaction 3648 123:124:125:126:127 1 123:124:125:126:127:128 -1 2022-12-28 transaction 3649 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2022-12-29 transaction 3650 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2022-12-30 transaction 3651 12d 1 12d:12e -1 2022-12-31 transaction 3652 12d:12e:12f 1 12d:12e:12f:130 -1 2023-01-01 transaction 3653 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2023-01-02 transaction 3654 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2023-01-03 transaction 3655 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2023-01-04 transaction 3656 137 1 137:138 -1 2023-01-05 transaction 3657 137:138:139 1 137:138:139:13a -1 2023-01-06 transaction 3658 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2023-01-07 transaction 3659 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2023-01-08 transaction 3660 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2023-01-09 transaction 3661 141 1 141:142 -1 2023-01-10 transaction 3662 141:142:143 1 141:142:143:144 -1 2023-01-11 transaction 3663 141:142:143:144:145 1 141:142:143:144:145:146 -1 2023-01-12 transaction 3664 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2023-01-13 transaction 3665 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2023-01-14 transaction 3666 14b 1 14b:14c -1 2023-01-15 transaction 3667 14b:14c:14d 1 14b:14c:14d:14e -1 2023-01-16 transaction 3668 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2023-01-17 transaction 3669 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2023-01-18 transaction 3670 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2023-01-19 transaction 3671 155 1 155:156 -1 2023-01-20 transaction 3672 155:156:157 1 155:156:157:158 -1 2023-01-21 transaction 3673 155:156:157:158:159 1 155:156:157:158:159:15a -1 2023-01-22 transaction 3674 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2023-01-23 transaction 3675 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2023-01-24 transaction 3676 15f 1 15f:160 -1 2023-01-25 transaction 3677 15f:160:161 1 15f:160:161:162 -1 2023-01-26 transaction 3678 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2023-01-27 transaction 3679 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2023-01-28 transaction 3680 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2023-01-29 transaction 3681 169 1 169:16a -1 2023-01-30 transaction 3682 169:16a:16b 1 169:16a:16b:16c -1 2023-01-31 transaction 3683 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2023-02-01 transaction 3684 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2023-02-02 transaction 3685 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2023-02-03 transaction 3686 173 1 173:174 -1 2023-02-04 transaction 3687 173:174:175 1 173:174:175:176 -1 2023-02-05 transaction 3688 173:174:175:176:177 1 173:174:175:176:177:178 -1 2023-02-06 transaction 3689 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2023-02-07 transaction 3690 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2023-02-08 transaction 3691 17d 1 17d:17e -1 2023-02-09 transaction 3692 17d:17e:17f 1 17d:17e:17f:180 -1 2023-02-10 transaction 3693 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2023-02-11 transaction 3694 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2023-02-12 transaction 3695 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2023-02-13 transaction 3696 187 1 187:188 -1 2023-02-14 transaction 3697 187:188:189 1 187:188:189:18a -1 2023-02-15 transaction 3698 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2023-02-16 transaction 3699 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2023-02-17 transaction 3700 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2023-02-18 transaction 3701 191 1 191:192 -1 2023-02-19 transaction 3702 191:192:193 1 191:192:193:194 -1 2023-02-20 transaction 3703 191:192:193:194:195 1 191:192:193:194:195:196 -1 2023-02-21 transaction 3704 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2023-02-22 transaction 3705 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2023-02-23 transaction 3706 19b 1 19b:19c -1 2023-02-24 transaction 3707 19b:19c:19d 1 19b:19c:19d:19e -1 2023-02-25 transaction 3708 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2023-02-26 transaction 3709 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2023-02-27 transaction 3710 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2023-02-28 transaction 3711 1a5 1 1a5:1a6 -1 2023-03-01 transaction 3712 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2023-03-02 transaction 3713 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2023-03-03 transaction 3714 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2023-03-04 transaction 3715 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2023-03-05 transaction 3716 1af 1 1af:1b0 -1 2023-03-06 transaction 3717 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2023-03-07 transaction 3718 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2023-03-08 transaction 3719 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2023-03-09 transaction 3720 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2023-03-10 transaction 3721 1b9 1 1b9:1ba -1 2023-03-11 transaction 3722 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2023-03-12 transaction 3723 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2023-03-13 transaction 3724 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2023-03-14 transaction 3725 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2023-03-15 transaction 3726 1c3 1 1c3:1c4 -1 2023-03-16 transaction 3727 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2023-03-17 transaction 3728 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2023-03-18 transaction 3729 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2023-03-19 transaction 3730 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2023-03-20 transaction 3731 1cd 1 1cd:1ce -1 2023-03-21 transaction 3732 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2023-03-22 transaction 3733 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2023-03-23 transaction 3734 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2023-03-24 transaction 3735 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2023-03-25 transaction 3736 1d7 1 1d7:1d8 -1 2023-03-26 transaction 3737 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2023-03-27 transaction 3738 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2023-03-28 transaction 3739 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2023-03-29 transaction 3740 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2023-03-30 transaction 3741 1e1 1 1e1:1e2 -1 2023-03-31 transaction 3742 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2023-04-01 transaction 3743 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2023-04-02 transaction 3744 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2023-04-03 transaction 3745 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2023-04-04 transaction 3746 1eb 1 1eb:1ec -1 2023-04-05 transaction 3747 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2023-04-06 transaction 3748 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2023-04-07 transaction 3749 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2023-04-08 transaction 3750 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2023-04-09 transaction 3751 1f5 1 1f5:1f6 -1 2023-04-10 transaction 3752 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2023-04-11 transaction 3753 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2023-04-12 transaction 3754 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2023-04-13 transaction 3755 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2023-04-14 transaction 3756 1ff 1 1ff:200 -1 2023-04-15 transaction 3757 1ff:200:201 1 1ff:200:201:202 -1 2023-04-16 transaction 3758 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2023-04-17 transaction 3759 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2023-04-18 transaction 3760 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2023-04-19 transaction 3761 209 1 209:20a -1 2023-04-20 transaction 3762 209:20a:20b 1 209:20a:20b:20c -1 2023-04-21 transaction 3763 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2023-04-22 transaction 3764 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2023-04-23 transaction 3765 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2023-04-24 transaction 3766 213 1 213:214 -1 2023-04-25 transaction 3767 213:214:215 1 213:214:215:216 -1 2023-04-26 transaction 3768 213:214:215:216:217 1 213:214:215:216:217:218 -1 2023-04-27 transaction 3769 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2023-04-28 transaction 3770 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2023-04-29 transaction 3771 21d 1 21d:21e -1 2023-04-30 transaction 3772 21d:21e:21f 1 21d:21e:21f:220 -1 2023-05-01 transaction 3773 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2023-05-02 transaction 3774 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2023-05-03 transaction 3775 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2023-05-04 transaction 3776 227 1 227:228 -1 2023-05-05 transaction 3777 227:228:229 1 227:228:229:22a -1 2023-05-06 transaction 3778 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2023-05-07 transaction 3779 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2023-05-08 transaction 3780 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2023-05-09 transaction 3781 231 1 231:232 -1 2023-05-10 transaction 3782 231:232:233 1 231:232:233:234 -1 2023-05-11 transaction 3783 231:232:233:234:235 1 231:232:233:234:235:236 -1 2023-05-12 transaction 3784 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2023-05-13 transaction 3785 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2023-05-14 transaction 3786 23b 1 23b:23c -1 2023-05-15 transaction 3787 23b:23c:23d 1 23b:23c:23d:23e -1 2023-05-16 transaction 3788 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2023-05-17 transaction 3789 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2023-05-18 transaction 3790 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2023-05-19 transaction 3791 245 1 245:246 -1 2023-05-20 transaction 3792 245:246:247 1 245:246:247:248 -1 2023-05-21 transaction 3793 245:246:247:248:249 1 245:246:247:248:249:24a -1 2023-05-22 transaction 3794 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2023-05-23 transaction 3795 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2023-05-24 transaction 3796 24f 1 24f:250 -1 2023-05-25 transaction 3797 24f:250:251 1 24f:250:251:252 -1 2023-05-26 transaction 3798 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2023-05-27 transaction 3799 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2023-05-28 transaction 3800 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2023-05-29 transaction 3801 259 1 259:25a -1 2023-05-30 transaction 3802 259:25a:25b 1 259:25a:25b:25c -1 2023-05-31 transaction 3803 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2023-06-01 transaction 3804 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2023-06-02 transaction 3805 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2023-06-03 transaction 3806 263 1 263:264 -1 2023-06-04 transaction 3807 263:264:265 1 263:264:265:266 -1 2023-06-05 transaction 3808 263:264:265:266:267 1 263:264:265:266:267:268 -1 2023-06-06 transaction 3809 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2023-06-07 transaction 3810 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2023-06-08 transaction 3811 26d 1 26d:26e -1 2023-06-09 transaction 3812 26d:26e:26f 1 26d:26e:26f:270 -1 2023-06-10 transaction 3813 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2023-06-11 transaction 3814 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2023-06-12 transaction 3815 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2023-06-13 transaction 3816 277 1 277:278 -1 2023-06-14 transaction 3817 277:278:279 1 277:278:279:27a -1 2023-06-15 transaction 3818 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2023-06-16 transaction 3819 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2023-06-17 transaction 3820 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2023-06-18 transaction 3821 281 1 281:282 -1 2023-06-19 transaction 3822 281:282:283 1 281:282:283:284 -1 2023-06-20 transaction 3823 281:282:283:284:285 1 281:282:283:284:285:286 -1 2023-06-21 transaction 3824 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2023-06-22 transaction 3825 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2023-06-23 transaction 3826 28b 1 28b:28c -1 2023-06-24 transaction 3827 28b:28c:28d 1 28b:28c:28d:28e -1 2023-06-25 transaction 3828 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2023-06-26 transaction 3829 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2023-06-27 transaction 3830 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2023-06-28 transaction 3831 295 1 295:296 -1 2023-06-29 transaction 3832 295:296:297 1 295:296:297:298 -1 2023-06-30 transaction 3833 295:296:297:298:299 1 295:296:297:298:299:29a -1 2023-07-01 transaction 3834 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2023-07-02 transaction 3835 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2023-07-03 transaction 3836 29f 1 29f:2a0 -1 2023-07-04 transaction 3837 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2023-07-05 transaction 3838 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2023-07-06 transaction 3839 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2023-07-07 transaction 3840 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2023-07-08 transaction 3841 2a9 1 2a9:2aa -1 2023-07-09 transaction 3842 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2023-07-10 transaction 3843 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2023-07-11 transaction 3844 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2023-07-12 transaction 3845 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2023-07-13 transaction 3846 2b3 1 2b3:2b4 -1 2023-07-14 transaction 3847 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2023-07-15 transaction 3848 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2023-07-16 transaction 3849 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2023-07-17 transaction 3850 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2023-07-18 transaction 3851 2bd 1 2bd:2be -1 2023-07-19 transaction 3852 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2023-07-20 transaction 3853 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2023-07-21 transaction 3854 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2023-07-22 transaction 3855 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2023-07-23 transaction 3856 2c7 1 2c7:2c8 -1 2023-07-24 transaction 3857 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2023-07-25 transaction 3858 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2023-07-26 transaction 3859 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2023-07-27 transaction 3860 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2023-07-28 transaction 3861 2d1 1 2d1:2d2 -1 2023-07-29 transaction 3862 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2023-07-30 transaction 3863 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2023-07-31 transaction 3864 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2023-08-01 transaction 3865 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2023-08-02 transaction 3866 2db 1 2db:2dc -1 2023-08-03 transaction 3867 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2023-08-04 transaction 3868 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2023-08-05 transaction 3869 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2023-08-06 transaction 3870 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2023-08-07 transaction 3871 2e5 1 2e5:2e6 -1 2023-08-08 transaction 3872 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2023-08-09 transaction 3873 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2023-08-10 transaction 3874 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2023-08-11 transaction 3875 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2023-08-12 transaction 3876 2ef 1 2ef:2f0 -1 2023-08-13 transaction 3877 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2023-08-14 transaction 3878 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2023-08-15 transaction 3879 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2023-08-16 transaction 3880 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2023-08-17 transaction 3881 2f9 1 2f9:2fa -1 2023-08-18 transaction 3882 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2023-08-19 transaction 3883 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2023-08-20 transaction 3884 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2023-08-21 transaction 3885 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2023-08-22 transaction 3886 303 1 303:304 -1 2023-08-23 transaction 3887 303:304:305 1 303:304:305:306 -1 2023-08-24 transaction 3888 303:304:305:306:307 1 303:304:305:306:307:308 -1 2023-08-25 transaction 3889 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2023-08-26 transaction 3890 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2023-08-27 transaction 3891 30d 1 30d:30e -1 2023-08-28 transaction 3892 30d:30e:30f 1 30d:30e:30f:310 -1 2023-08-29 transaction 3893 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2023-08-30 transaction 3894 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2023-08-31 transaction 3895 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2023-09-01 transaction 3896 317 1 317:318 -1 2023-09-02 transaction 3897 317:318:319 1 317:318:319:31a -1 2023-09-03 transaction 3898 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2023-09-04 transaction 3899 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2023-09-05 transaction 3900 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2023-09-06 transaction 3901 321 1 321:322 -1 2023-09-07 transaction 3902 321:322:323 1 321:322:323:324 -1 2023-09-08 transaction 3903 321:322:323:324:325 1 321:322:323:324:325:326 -1 2023-09-09 transaction 3904 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2023-09-10 transaction 3905 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2023-09-11 transaction 3906 32b 1 32b:32c -1 2023-09-12 transaction 3907 32b:32c:32d 1 32b:32c:32d:32e -1 2023-09-13 transaction 3908 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2023-09-14 transaction 3909 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2023-09-15 transaction 3910 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2023-09-16 transaction 3911 335 1 335:336 -1 2023-09-17 transaction 3912 335:336:337 1 335:336:337:338 -1 2023-09-18 transaction 3913 335:336:337:338:339 1 335:336:337:338:339:33a -1 2023-09-19 transaction 3914 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2023-09-20 transaction 3915 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2023-09-21 transaction 3916 33f 1 33f:340 -1 2023-09-22 transaction 3917 33f:340:341 1 33f:340:341:342 -1 2023-09-23 transaction 3918 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2023-09-24 transaction 3919 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2023-09-25 transaction 3920 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2023-09-26 transaction 3921 349 1 349:34a -1 2023-09-27 transaction 3922 349:34a:34b 1 349:34a:34b:34c -1 2023-09-28 transaction 3923 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2023-09-29 transaction 3924 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2023-09-30 transaction 3925 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2023-10-01 transaction 3926 353 1 353:354 -1 2023-10-02 transaction 3927 353:354:355 1 353:354:355:356 -1 2023-10-03 transaction 3928 353:354:355:356:357 1 353:354:355:356:357:358 -1 2023-10-04 transaction 3929 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2023-10-05 transaction 3930 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2023-10-06 transaction 3931 35d 1 35d:35e -1 2023-10-07 transaction 3932 35d:35e:35f 1 35d:35e:35f:360 -1 2023-10-08 transaction 3933 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2023-10-09 transaction 3934 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2023-10-10 transaction 3935 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2023-10-11 transaction 3936 367 1 367:368 -1 2023-10-12 transaction 3937 367:368:369 1 367:368:369:36a -1 2023-10-13 transaction 3938 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2023-10-14 transaction 3939 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2023-10-15 transaction 3940 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2023-10-16 transaction 3941 371 1 371:372 -1 2023-10-17 transaction 3942 371:372:373 1 371:372:373:374 -1 2023-10-18 transaction 3943 371:372:373:374:375 1 371:372:373:374:375:376 -1 2023-10-19 transaction 3944 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2023-10-20 transaction 3945 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2023-10-21 transaction 3946 37b 1 37b:37c -1 2023-10-22 transaction 3947 37b:37c:37d 1 37b:37c:37d:37e -1 2023-10-23 transaction 3948 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2023-10-24 transaction 3949 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2023-10-25 transaction 3950 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2023-10-26 transaction 3951 385 1 385:386 -1 2023-10-27 transaction 3952 385:386:387 1 385:386:387:388 -1 2023-10-28 transaction 3953 385:386:387:388:389 1 385:386:387:388:389:38a -1 2023-10-29 transaction 3954 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2023-10-30 transaction 3955 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2023-10-31 transaction 3956 38f 1 38f:390 -1 2023-11-01 transaction 3957 38f:390:391 1 38f:390:391:392 -1 2023-11-02 transaction 3958 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2023-11-03 transaction 3959 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2023-11-04 transaction 3960 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2023-11-05 transaction 3961 399 1 399:39a -1 2023-11-06 transaction 3962 399:39a:39b 1 399:39a:39b:39c -1 2023-11-07 transaction 3963 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2023-11-08 transaction 3964 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2023-11-09 transaction 3965 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2023-11-10 transaction 3966 3a3 1 3a3:3a4 -1 2023-11-11 transaction 3967 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2023-11-12 transaction 3968 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2023-11-13 transaction 3969 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2023-11-14 transaction 3970 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2023-11-15 transaction 3971 3ad 1 3ad:3ae -1 2023-11-16 transaction 3972 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2023-11-17 transaction 3973 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2023-11-18 transaction 3974 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2023-11-19 transaction 3975 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2023-11-20 transaction 3976 3b7 1 3b7:3b8 -1 2023-11-21 transaction 3977 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2023-11-22 transaction 3978 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2023-11-23 transaction 3979 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2023-11-24 transaction 3980 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2023-11-25 transaction 3981 3c1 1 3c1:3c2 -1 2023-11-26 transaction 3982 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2023-11-27 transaction 3983 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2023-11-28 transaction 3984 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2023-11-29 transaction 3985 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2023-11-30 transaction 3986 3cb 1 3cb:3cc -1 2023-12-01 transaction 3987 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2023-12-02 transaction 3988 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2023-12-03 transaction 3989 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2023-12-04 transaction 3990 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2023-12-05 transaction 3991 3d5 1 3d5:3d6 -1 2023-12-06 transaction 3992 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2023-12-07 transaction 3993 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2023-12-08 transaction 3994 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2023-12-09 transaction 3995 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2023-12-10 transaction 3996 3df 1 3df:3e0 -1 2023-12-11 transaction 3997 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2023-12-12 transaction 3998 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2023-12-13 transaction 3999 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2023-12-14 transaction 4000 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2023-12-15 transaction 4001 1 1 1:2 -1 2023-12-16 transaction 4002 1:2:3 1 1:2:3:4 -1 2023-12-17 transaction 4003 1:2:3:4:5 1 1:2:3:4:5:6 -1 2023-12-18 transaction 4004 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2023-12-19 transaction 4005 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2023-12-20 transaction 4006 b 1 b:c -1 2023-12-21 transaction 4007 b:c:d 1 b:c:d:e -1 2023-12-22 transaction 4008 b:c:d:e:f 1 b:c:d:e:f:10 -1 2023-12-23 transaction 4009 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2023-12-24 transaction 4010 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2023-12-25 transaction 4011 15 1 15:16 -1 2023-12-26 transaction 4012 15:16:17 1 15:16:17:18 -1 2023-12-27 transaction 4013 15:16:17:18:19 1 15:16:17:18:19:1a -1 2023-12-28 transaction 4014 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2023-12-29 transaction 4015 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2023-12-30 transaction 4016 1f 1 1f:20 -1 2023-12-31 transaction 4017 1f:20:21 1 1f:20:21:22 -1 2024-01-01 transaction 4018 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2024-01-02 transaction 4019 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2024-01-03 transaction 4020 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2024-01-04 transaction 4021 29 1 29:2a -1 2024-01-05 transaction 4022 29:2a:2b 1 29:2a:2b:2c -1 2024-01-06 transaction 4023 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2024-01-07 transaction 4024 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2024-01-08 transaction 4025 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2024-01-09 transaction 4026 33 1 33:34 -1 2024-01-10 transaction 4027 33:34:35 1 33:34:35:36 -1 2024-01-11 transaction 4028 33:34:35:36:37 1 33:34:35:36:37:38 -1 2024-01-12 transaction 4029 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2024-01-13 transaction 4030 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2024-01-14 transaction 4031 3d 1 3d:3e -1 2024-01-15 transaction 4032 3d:3e:3f 1 3d:3e:3f:40 -1 2024-01-16 transaction 4033 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2024-01-17 transaction 4034 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2024-01-18 transaction 4035 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2024-01-19 transaction 4036 47 1 47:48 -1 2024-01-20 transaction 4037 47:48:49 1 47:48:49:4a -1 2024-01-21 transaction 4038 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2024-01-22 transaction 4039 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2024-01-23 transaction 4040 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2024-01-24 transaction 4041 51 1 51:52 -1 2024-01-25 transaction 4042 51:52:53 1 51:52:53:54 -1 2024-01-26 transaction 4043 51:52:53:54:55 1 51:52:53:54:55:56 -1 2024-01-27 transaction 4044 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2024-01-28 transaction 4045 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2024-01-29 transaction 4046 5b 1 5b:5c -1 2024-01-30 transaction 4047 5b:5c:5d 1 5b:5c:5d:5e -1 2024-01-31 transaction 4048 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2024-02-01 transaction 4049 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2024-02-02 transaction 4050 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2024-02-03 transaction 4051 65 1 65:66 -1 2024-02-04 transaction 4052 65:66:67 1 65:66:67:68 -1 2024-02-05 transaction 4053 65:66:67:68:69 1 65:66:67:68:69:6a -1 2024-02-06 transaction 4054 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2024-02-07 transaction 4055 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2024-02-08 transaction 4056 6f 1 6f:70 -1 2024-02-09 transaction 4057 6f:70:71 1 6f:70:71:72 -1 2024-02-10 transaction 4058 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2024-02-11 transaction 4059 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2024-02-12 transaction 4060 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2024-02-13 transaction 4061 79 1 79:7a -1 2024-02-14 transaction 4062 79:7a:7b 1 79:7a:7b:7c -1 2024-02-15 transaction 4063 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2024-02-16 transaction 4064 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2024-02-17 transaction 4065 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2024-02-18 transaction 4066 83 1 83:84 -1 2024-02-19 transaction 4067 83:84:85 1 83:84:85:86 -1 2024-02-20 transaction 4068 83:84:85:86:87 1 83:84:85:86:87:88 -1 2024-02-21 transaction 4069 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2024-02-22 transaction 4070 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2024-02-23 transaction 4071 8d 1 8d:8e -1 2024-02-24 transaction 4072 8d:8e:8f 1 8d:8e:8f:90 -1 2024-02-25 transaction 4073 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2024-02-26 transaction 4074 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2024-02-27 transaction 4075 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2024-02-28 transaction 4076 97 1 97:98 -1 2024-02-29 transaction 4077 97:98:99 1 97:98:99:9a -1 2024-03-01 transaction 4078 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2024-03-02 transaction 4079 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2024-03-03 transaction 4080 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2024-03-04 transaction 4081 a1 1 a1:a2 -1 2024-03-05 transaction 4082 a1:a2:a3 1 a1:a2:a3:a4 -1 2024-03-06 transaction 4083 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2024-03-07 transaction 4084 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2024-03-08 transaction 4085 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2024-03-09 transaction 4086 ab 1 ab:ac -1 2024-03-10 transaction 4087 ab:ac:ad 1 ab:ac:ad:ae -1 2024-03-11 transaction 4088 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2024-03-12 transaction 4089 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2024-03-13 transaction 4090 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2024-03-14 transaction 4091 b5 1 b5:b6 -1 2024-03-15 transaction 4092 b5:b6:b7 1 b5:b6:b7:b8 -1 2024-03-16 transaction 4093 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2024-03-17 transaction 4094 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2024-03-18 transaction 4095 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2024-03-19 transaction 4096 bf 1 bf:c0 -1 2024-03-20 transaction 4097 bf:c0:c1 1 bf:c0:c1:c2 -1 2024-03-21 transaction 4098 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2024-03-22 transaction 4099 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2024-03-23 transaction 4100 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2024-03-24 transaction 4101 c9 1 c9:ca -1 2024-03-25 transaction 4102 c9:ca:cb 1 c9:ca:cb:cc -1 2024-03-26 transaction 4103 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2024-03-27 transaction 4104 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2024-03-28 transaction 4105 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2024-03-29 transaction 4106 d3 1 d3:d4 -1 2024-03-30 transaction 4107 d3:d4:d5 1 d3:d4:d5:d6 -1 2024-03-31 transaction 4108 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2024-04-01 transaction 4109 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2024-04-02 transaction 4110 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2024-04-03 transaction 4111 dd 1 dd:de -1 2024-04-04 transaction 4112 dd:de:df 1 dd:de:df:e0 -1 2024-04-05 transaction 4113 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2024-04-06 transaction 4114 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2024-04-07 transaction 4115 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2024-04-08 transaction 4116 e7 1 e7:e8 -1 2024-04-09 transaction 4117 e7:e8:e9 1 e7:e8:e9:ea -1 2024-04-10 transaction 4118 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2024-04-11 transaction 4119 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2024-04-12 transaction 4120 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2024-04-13 transaction 4121 f1 1 f1:f2 -1 2024-04-14 transaction 4122 f1:f2:f3 1 f1:f2:f3:f4 -1 2024-04-15 transaction 4123 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2024-04-16 transaction 4124 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2024-04-17 transaction 4125 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2024-04-18 transaction 4126 fb 1 fb:fc -1 2024-04-19 transaction 4127 fb:fc:fd 1 fb:fc:fd:fe -1 2024-04-20 transaction 4128 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2024-04-21 transaction 4129 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2024-04-22 transaction 4130 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2024-04-23 transaction 4131 105 1 105:106 -1 2024-04-24 transaction 4132 105:106:107 1 105:106:107:108 -1 2024-04-25 transaction 4133 105:106:107:108:109 1 105:106:107:108:109:10a -1 2024-04-26 transaction 4134 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2024-04-27 transaction 4135 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2024-04-28 transaction 4136 10f 1 10f:110 -1 2024-04-29 transaction 4137 10f:110:111 1 10f:110:111:112 -1 2024-04-30 transaction 4138 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2024-05-01 transaction 4139 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2024-05-02 transaction 4140 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2024-05-03 transaction 4141 119 1 119:11a -1 2024-05-04 transaction 4142 119:11a:11b 1 119:11a:11b:11c -1 2024-05-05 transaction 4143 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2024-05-06 transaction 4144 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2024-05-07 transaction 4145 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2024-05-08 transaction 4146 123 1 123:124 -1 2024-05-09 transaction 4147 123:124:125 1 123:124:125:126 -1 2024-05-10 transaction 4148 123:124:125:126:127 1 123:124:125:126:127:128 -1 2024-05-11 transaction 4149 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2024-05-12 transaction 4150 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2024-05-13 transaction 4151 12d 1 12d:12e -1 2024-05-14 transaction 4152 12d:12e:12f 1 12d:12e:12f:130 -1 2024-05-15 transaction 4153 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2024-05-16 transaction 4154 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2024-05-17 transaction 4155 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2024-05-18 transaction 4156 137 1 137:138 -1 2024-05-19 transaction 4157 137:138:139 1 137:138:139:13a -1 2024-05-20 transaction 4158 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2024-05-21 transaction 4159 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2024-05-22 transaction 4160 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2024-05-23 transaction 4161 141 1 141:142 -1 2024-05-24 transaction 4162 141:142:143 1 141:142:143:144 -1 2024-05-25 transaction 4163 141:142:143:144:145 1 141:142:143:144:145:146 -1 2024-05-26 transaction 4164 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2024-05-27 transaction 4165 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2024-05-28 transaction 4166 14b 1 14b:14c -1 2024-05-29 transaction 4167 14b:14c:14d 1 14b:14c:14d:14e -1 2024-05-30 transaction 4168 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2024-05-31 transaction 4169 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2024-06-01 transaction 4170 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2024-06-02 transaction 4171 155 1 155:156 -1 2024-06-03 transaction 4172 155:156:157 1 155:156:157:158 -1 2024-06-04 transaction 4173 155:156:157:158:159 1 155:156:157:158:159:15a -1 2024-06-05 transaction 4174 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2024-06-06 transaction 4175 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2024-06-07 transaction 4176 15f 1 15f:160 -1 2024-06-08 transaction 4177 15f:160:161 1 15f:160:161:162 -1 2024-06-09 transaction 4178 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2024-06-10 transaction 4179 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2024-06-11 transaction 4180 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2024-06-12 transaction 4181 169 1 169:16a -1 2024-06-13 transaction 4182 169:16a:16b 1 169:16a:16b:16c -1 2024-06-14 transaction 4183 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2024-06-15 transaction 4184 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2024-06-16 transaction 4185 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2024-06-17 transaction 4186 173 1 173:174 -1 2024-06-18 transaction 4187 173:174:175 1 173:174:175:176 -1 2024-06-19 transaction 4188 173:174:175:176:177 1 173:174:175:176:177:178 -1 2024-06-20 transaction 4189 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2024-06-21 transaction 4190 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2024-06-22 transaction 4191 17d 1 17d:17e -1 2024-06-23 transaction 4192 17d:17e:17f 1 17d:17e:17f:180 -1 2024-06-24 transaction 4193 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2024-06-25 transaction 4194 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2024-06-26 transaction 4195 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2024-06-27 transaction 4196 187 1 187:188 -1 2024-06-28 transaction 4197 187:188:189 1 187:188:189:18a -1 2024-06-29 transaction 4198 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2024-06-30 transaction 4199 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2024-07-01 transaction 4200 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2024-07-02 transaction 4201 191 1 191:192 -1 2024-07-03 transaction 4202 191:192:193 1 191:192:193:194 -1 2024-07-04 transaction 4203 191:192:193:194:195 1 191:192:193:194:195:196 -1 2024-07-05 transaction 4204 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2024-07-06 transaction 4205 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2024-07-07 transaction 4206 19b 1 19b:19c -1 2024-07-08 transaction 4207 19b:19c:19d 1 19b:19c:19d:19e -1 2024-07-09 transaction 4208 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2024-07-10 transaction 4209 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2024-07-11 transaction 4210 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2024-07-12 transaction 4211 1a5 1 1a5:1a6 -1 2024-07-13 transaction 4212 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2024-07-14 transaction 4213 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2024-07-15 transaction 4214 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2024-07-16 transaction 4215 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2024-07-17 transaction 4216 1af 1 1af:1b0 -1 2024-07-18 transaction 4217 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2024-07-19 transaction 4218 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2024-07-20 transaction 4219 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2024-07-21 transaction 4220 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2024-07-22 transaction 4221 1b9 1 1b9:1ba -1 2024-07-23 transaction 4222 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2024-07-24 transaction 4223 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2024-07-25 transaction 4224 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2024-07-26 transaction 4225 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2024-07-27 transaction 4226 1c3 1 1c3:1c4 -1 2024-07-28 transaction 4227 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2024-07-29 transaction 4228 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2024-07-30 transaction 4229 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2024-07-31 transaction 4230 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2024-08-01 transaction 4231 1cd 1 1cd:1ce -1 2024-08-02 transaction 4232 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2024-08-03 transaction 4233 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2024-08-04 transaction 4234 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2024-08-05 transaction 4235 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2024-08-06 transaction 4236 1d7 1 1d7:1d8 -1 2024-08-07 transaction 4237 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2024-08-08 transaction 4238 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2024-08-09 transaction 4239 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2024-08-10 transaction 4240 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2024-08-11 transaction 4241 1e1 1 1e1:1e2 -1 2024-08-12 transaction 4242 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2024-08-13 transaction 4243 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2024-08-14 transaction 4244 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2024-08-15 transaction 4245 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2024-08-16 transaction 4246 1eb 1 1eb:1ec -1 2024-08-17 transaction 4247 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2024-08-18 transaction 4248 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2024-08-19 transaction 4249 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2024-08-20 transaction 4250 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2024-08-21 transaction 4251 1f5 1 1f5:1f6 -1 2024-08-22 transaction 4252 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2024-08-23 transaction 4253 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2024-08-24 transaction 4254 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2024-08-25 transaction 4255 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2024-08-26 transaction 4256 1ff 1 1ff:200 -1 2024-08-27 transaction 4257 1ff:200:201 1 1ff:200:201:202 -1 2024-08-28 transaction 4258 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2024-08-29 transaction 4259 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2024-08-30 transaction 4260 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2024-08-31 transaction 4261 209 1 209:20a -1 2024-09-01 transaction 4262 209:20a:20b 1 209:20a:20b:20c -1 2024-09-02 transaction 4263 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2024-09-03 transaction 4264 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2024-09-04 transaction 4265 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2024-09-05 transaction 4266 213 1 213:214 -1 2024-09-06 transaction 4267 213:214:215 1 213:214:215:216 -1 2024-09-07 transaction 4268 213:214:215:216:217 1 213:214:215:216:217:218 -1 2024-09-08 transaction 4269 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2024-09-09 transaction 4270 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2024-09-10 transaction 4271 21d 1 21d:21e -1 2024-09-11 transaction 4272 21d:21e:21f 1 21d:21e:21f:220 -1 2024-09-12 transaction 4273 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2024-09-13 transaction 4274 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2024-09-14 transaction 4275 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2024-09-15 transaction 4276 227 1 227:228 -1 2024-09-16 transaction 4277 227:228:229 1 227:228:229:22a -1 2024-09-17 transaction 4278 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2024-09-18 transaction 4279 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2024-09-19 transaction 4280 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2024-09-20 transaction 4281 231 1 231:232 -1 2024-09-21 transaction 4282 231:232:233 1 231:232:233:234 -1 2024-09-22 transaction 4283 231:232:233:234:235 1 231:232:233:234:235:236 -1 2024-09-23 transaction 4284 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2024-09-24 transaction 4285 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2024-09-25 transaction 4286 23b 1 23b:23c -1 2024-09-26 transaction 4287 23b:23c:23d 1 23b:23c:23d:23e -1 2024-09-27 transaction 4288 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2024-09-28 transaction 4289 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2024-09-29 transaction 4290 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2024-09-30 transaction 4291 245 1 245:246 -1 2024-10-01 transaction 4292 245:246:247 1 245:246:247:248 -1 2024-10-02 transaction 4293 245:246:247:248:249 1 245:246:247:248:249:24a -1 2024-10-03 transaction 4294 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2024-10-04 transaction 4295 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2024-10-05 transaction 4296 24f 1 24f:250 -1 2024-10-06 transaction 4297 24f:250:251 1 24f:250:251:252 -1 2024-10-07 transaction 4298 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2024-10-08 transaction 4299 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2024-10-09 transaction 4300 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2024-10-10 transaction 4301 259 1 259:25a -1 2024-10-11 transaction 4302 259:25a:25b 1 259:25a:25b:25c -1 2024-10-12 transaction 4303 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2024-10-13 transaction 4304 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2024-10-14 transaction 4305 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2024-10-15 transaction 4306 263 1 263:264 -1 2024-10-16 transaction 4307 263:264:265 1 263:264:265:266 -1 2024-10-17 transaction 4308 263:264:265:266:267 1 263:264:265:266:267:268 -1 2024-10-18 transaction 4309 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2024-10-19 transaction 4310 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2024-10-20 transaction 4311 26d 1 26d:26e -1 2024-10-21 transaction 4312 26d:26e:26f 1 26d:26e:26f:270 -1 2024-10-22 transaction 4313 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2024-10-23 transaction 4314 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2024-10-24 transaction 4315 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2024-10-25 transaction 4316 277 1 277:278 -1 2024-10-26 transaction 4317 277:278:279 1 277:278:279:27a -1 2024-10-27 transaction 4318 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2024-10-28 transaction 4319 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2024-10-29 transaction 4320 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2024-10-30 transaction 4321 281 1 281:282 -1 2024-10-31 transaction 4322 281:282:283 1 281:282:283:284 -1 2024-11-01 transaction 4323 281:282:283:284:285 1 281:282:283:284:285:286 -1 2024-11-02 transaction 4324 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2024-11-03 transaction 4325 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2024-11-04 transaction 4326 28b 1 28b:28c -1 2024-11-05 transaction 4327 28b:28c:28d 1 28b:28c:28d:28e -1 2024-11-06 transaction 4328 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2024-11-07 transaction 4329 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2024-11-08 transaction 4330 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2024-11-09 transaction 4331 295 1 295:296 -1 2024-11-10 transaction 4332 295:296:297 1 295:296:297:298 -1 2024-11-11 transaction 4333 295:296:297:298:299 1 295:296:297:298:299:29a -1 2024-11-12 transaction 4334 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2024-11-13 transaction 4335 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2024-11-14 transaction 4336 29f 1 29f:2a0 -1 2024-11-15 transaction 4337 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2024-11-16 transaction 4338 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2024-11-17 transaction 4339 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2024-11-18 transaction 4340 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2024-11-19 transaction 4341 2a9 1 2a9:2aa -1 2024-11-20 transaction 4342 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2024-11-21 transaction 4343 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2024-11-22 transaction 4344 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2024-11-23 transaction 4345 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2024-11-24 transaction 4346 2b3 1 2b3:2b4 -1 2024-11-25 transaction 4347 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2024-11-26 transaction 4348 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2024-11-27 transaction 4349 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2024-11-28 transaction 4350 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2024-11-29 transaction 4351 2bd 1 2bd:2be -1 2024-11-30 transaction 4352 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2024-12-01 transaction 4353 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2024-12-02 transaction 4354 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2024-12-03 transaction 4355 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2024-12-04 transaction 4356 2c7 1 2c7:2c8 -1 2024-12-05 transaction 4357 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2024-12-06 transaction 4358 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2024-12-07 transaction 4359 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2024-12-08 transaction 4360 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2024-12-09 transaction 4361 2d1 1 2d1:2d2 -1 2024-12-10 transaction 4362 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2024-12-11 transaction 4363 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2024-12-12 transaction 4364 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2024-12-13 transaction 4365 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2024-12-14 transaction 4366 2db 1 2db:2dc -1 2024-12-15 transaction 4367 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2024-12-16 transaction 4368 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2024-12-17 transaction 4369 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2024-12-18 transaction 4370 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2024-12-19 transaction 4371 2e5 1 2e5:2e6 -1 2024-12-20 transaction 4372 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2024-12-21 transaction 4373 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2024-12-22 transaction 4374 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2024-12-23 transaction 4375 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2024-12-24 transaction 4376 2ef 1 2ef:2f0 -1 2024-12-25 transaction 4377 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2024-12-26 transaction 4378 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2024-12-27 transaction 4379 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2024-12-28 transaction 4380 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2024-12-29 transaction 4381 2f9 1 2f9:2fa -1 2024-12-30 transaction 4382 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2024-12-31 transaction 4383 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2025-01-01 transaction 4384 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2025-01-02 transaction 4385 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2025-01-03 transaction 4386 303 1 303:304 -1 2025-01-04 transaction 4387 303:304:305 1 303:304:305:306 -1 2025-01-05 transaction 4388 303:304:305:306:307 1 303:304:305:306:307:308 -1 2025-01-06 transaction 4389 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2025-01-07 transaction 4390 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2025-01-08 transaction 4391 30d 1 30d:30e -1 2025-01-09 transaction 4392 30d:30e:30f 1 30d:30e:30f:310 -1 2025-01-10 transaction 4393 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2025-01-11 transaction 4394 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2025-01-12 transaction 4395 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2025-01-13 transaction 4396 317 1 317:318 -1 2025-01-14 transaction 4397 317:318:319 1 317:318:319:31a -1 2025-01-15 transaction 4398 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2025-01-16 transaction 4399 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2025-01-17 transaction 4400 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2025-01-18 transaction 4401 321 1 321:322 -1 2025-01-19 transaction 4402 321:322:323 1 321:322:323:324 -1 2025-01-20 transaction 4403 321:322:323:324:325 1 321:322:323:324:325:326 -1 2025-01-21 transaction 4404 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2025-01-22 transaction 4405 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2025-01-23 transaction 4406 32b 1 32b:32c -1 2025-01-24 transaction 4407 32b:32c:32d 1 32b:32c:32d:32e -1 2025-01-25 transaction 4408 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2025-01-26 transaction 4409 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2025-01-27 transaction 4410 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2025-01-28 transaction 4411 335 1 335:336 -1 2025-01-29 transaction 4412 335:336:337 1 335:336:337:338 -1 2025-01-30 transaction 4413 335:336:337:338:339 1 335:336:337:338:339:33a -1 2025-01-31 transaction 4414 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2025-02-01 transaction 4415 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2025-02-02 transaction 4416 33f 1 33f:340 -1 2025-02-03 transaction 4417 33f:340:341 1 33f:340:341:342 -1 2025-02-04 transaction 4418 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2025-02-05 transaction 4419 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2025-02-06 transaction 4420 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2025-02-07 transaction 4421 349 1 349:34a -1 2025-02-08 transaction 4422 349:34a:34b 1 349:34a:34b:34c -1 2025-02-09 transaction 4423 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2025-02-10 transaction 4424 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2025-02-11 transaction 4425 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2025-02-12 transaction 4426 353 1 353:354 -1 2025-02-13 transaction 4427 353:354:355 1 353:354:355:356 -1 2025-02-14 transaction 4428 353:354:355:356:357 1 353:354:355:356:357:358 -1 2025-02-15 transaction 4429 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2025-02-16 transaction 4430 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2025-02-17 transaction 4431 35d 1 35d:35e -1 2025-02-18 transaction 4432 35d:35e:35f 1 35d:35e:35f:360 -1 2025-02-19 transaction 4433 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2025-02-20 transaction 4434 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2025-02-21 transaction 4435 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2025-02-22 transaction 4436 367 1 367:368 -1 2025-02-23 transaction 4437 367:368:369 1 367:368:369:36a -1 2025-02-24 transaction 4438 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2025-02-25 transaction 4439 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2025-02-26 transaction 4440 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2025-02-27 transaction 4441 371 1 371:372 -1 2025-02-28 transaction 4442 371:372:373 1 371:372:373:374 -1 2025-03-01 transaction 4443 371:372:373:374:375 1 371:372:373:374:375:376 -1 2025-03-02 transaction 4444 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2025-03-03 transaction 4445 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2025-03-04 transaction 4446 37b 1 37b:37c -1 2025-03-05 transaction 4447 37b:37c:37d 1 37b:37c:37d:37e -1 2025-03-06 transaction 4448 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2025-03-07 transaction 4449 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2025-03-08 transaction 4450 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2025-03-09 transaction 4451 385 1 385:386 -1 2025-03-10 transaction 4452 385:386:387 1 385:386:387:388 -1 2025-03-11 transaction 4453 385:386:387:388:389 1 385:386:387:388:389:38a -1 2025-03-12 transaction 4454 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2025-03-13 transaction 4455 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2025-03-14 transaction 4456 38f 1 38f:390 -1 2025-03-15 transaction 4457 38f:390:391 1 38f:390:391:392 -1 2025-03-16 transaction 4458 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2025-03-17 transaction 4459 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2025-03-18 transaction 4460 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2025-03-19 transaction 4461 399 1 399:39a -1 2025-03-20 transaction 4462 399:39a:39b 1 399:39a:39b:39c -1 2025-03-21 transaction 4463 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2025-03-22 transaction 4464 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2025-03-23 transaction 4465 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2025-03-24 transaction 4466 3a3 1 3a3:3a4 -1 2025-03-25 transaction 4467 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2025-03-26 transaction 4468 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2025-03-27 transaction 4469 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2025-03-28 transaction 4470 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2025-03-29 transaction 4471 3ad 1 3ad:3ae -1 2025-03-30 transaction 4472 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2025-03-31 transaction 4473 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2025-04-01 transaction 4474 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2025-04-02 transaction 4475 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2025-04-03 transaction 4476 3b7 1 3b7:3b8 -1 2025-04-04 transaction 4477 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2025-04-05 transaction 4478 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2025-04-06 transaction 4479 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2025-04-07 transaction 4480 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2025-04-08 transaction 4481 3c1 1 3c1:3c2 -1 2025-04-09 transaction 4482 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2025-04-10 transaction 4483 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2025-04-11 transaction 4484 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2025-04-12 transaction 4485 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2025-04-13 transaction 4486 3cb 1 3cb:3cc -1 2025-04-14 transaction 4487 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2025-04-15 transaction 4488 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2025-04-16 transaction 4489 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2025-04-17 transaction 4490 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2025-04-18 transaction 4491 3d5 1 3d5:3d6 -1 2025-04-19 transaction 4492 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2025-04-20 transaction 4493 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2025-04-21 transaction 4494 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2025-04-22 transaction 4495 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2025-04-23 transaction 4496 3df 1 3df:3e0 -1 2025-04-24 transaction 4497 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2025-04-25 transaction 4498 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2025-04-26 transaction 4499 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2025-04-27 transaction 4500 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2025-04-28 transaction 4501 1 1 1:2 -1 2025-04-29 transaction 4502 1:2:3 1 1:2:3:4 -1 2025-04-30 transaction 4503 1:2:3:4:5 1 1:2:3:4:5:6 -1 2025-05-01 transaction 4504 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2025-05-02 transaction 4505 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2025-05-03 transaction 4506 b 1 b:c -1 2025-05-04 transaction 4507 b:c:d 1 b:c:d:e -1 2025-05-05 transaction 4508 b:c:d:e:f 1 b:c:d:e:f:10 -1 2025-05-06 transaction 4509 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2025-05-07 transaction 4510 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2025-05-08 transaction 4511 15 1 15:16 -1 2025-05-09 transaction 4512 15:16:17 1 15:16:17:18 -1 2025-05-10 transaction 4513 15:16:17:18:19 1 15:16:17:18:19:1a -1 2025-05-11 transaction 4514 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2025-05-12 transaction 4515 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2025-05-13 transaction 4516 1f 1 1f:20 -1 2025-05-14 transaction 4517 1f:20:21 1 1f:20:21:22 -1 2025-05-15 transaction 4518 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2025-05-16 transaction 4519 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2025-05-17 transaction 4520 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2025-05-18 transaction 4521 29 1 29:2a -1 2025-05-19 transaction 4522 29:2a:2b 1 29:2a:2b:2c -1 2025-05-20 transaction 4523 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2025-05-21 transaction 4524 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2025-05-22 transaction 4525 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2025-05-23 transaction 4526 33 1 33:34 -1 2025-05-24 transaction 4527 33:34:35 1 33:34:35:36 -1 2025-05-25 transaction 4528 33:34:35:36:37 1 33:34:35:36:37:38 -1 2025-05-26 transaction 4529 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2025-05-27 transaction 4530 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2025-05-28 transaction 4531 3d 1 3d:3e -1 2025-05-29 transaction 4532 3d:3e:3f 1 3d:3e:3f:40 -1 2025-05-30 transaction 4533 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2025-05-31 transaction 4534 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2025-06-01 transaction 4535 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2025-06-02 transaction 4536 47 1 47:48 -1 2025-06-03 transaction 4537 47:48:49 1 47:48:49:4a -1 2025-06-04 transaction 4538 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2025-06-05 transaction 4539 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2025-06-06 transaction 4540 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2025-06-07 transaction 4541 51 1 51:52 -1 2025-06-08 transaction 4542 51:52:53 1 51:52:53:54 -1 2025-06-09 transaction 4543 51:52:53:54:55 1 51:52:53:54:55:56 -1 2025-06-10 transaction 4544 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2025-06-11 transaction 4545 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2025-06-12 transaction 4546 5b 1 5b:5c -1 2025-06-13 transaction 4547 5b:5c:5d 1 5b:5c:5d:5e -1 2025-06-14 transaction 4548 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2025-06-15 transaction 4549 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2025-06-16 transaction 4550 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2025-06-17 transaction 4551 65 1 65:66 -1 2025-06-18 transaction 4552 65:66:67 1 65:66:67:68 -1 2025-06-19 transaction 4553 65:66:67:68:69 1 65:66:67:68:69:6a -1 2025-06-20 transaction 4554 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2025-06-21 transaction 4555 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2025-06-22 transaction 4556 6f 1 6f:70 -1 2025-06-23 transaction 4557 6f:70:71 1 6f:70:71:72 -1 2025-06-24 transaction 4558 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2025-06-25 transaction 4559 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2025-06-26 transaction 4560 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2025-06-27 transaction 4561 79 1 79:7a -1 2025-06-28 transaction 4562 79:7a:7b 1 79:7a:7b:7c -1 2025-06-29 transaction 4563 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2025-06-30 transaction 4564 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2025-07-01 transaction 4565 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2025-07-02 transaction 4566 83 1 83:84 -1 2025-07-03 transaction 4567 83:84:85 1 83:84:85:86 -1 2025-07-04 transaction 4568 83:84:85:86:87 1 83:84:85:86:87:88 -1 2025-07-05 transaction 4569 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2025-07-06 transaction 4570 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2025-07-07 transaction 4571 8d 1 8d:8e -1 2025-07-08 transaction 4572 8d:8e:8f 1 8d:8e:8f:90 -1 2025-07-09 transaction 4573 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2025-07-10 transaction 4574 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2025-07-11 transaction 4575 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2025-07-12 transaction 4576 97 1 97:98 -1 2025-07-13 transaction 4577 97:98:99 1 97:98:99:9a -1 2025-07-14 transaction 4578 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2025-07-15 transaction 4579 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2025-07-16 transaction 4580 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2025-07-17 transaction 4581 a1 1 a1:a2 -1 2025-07-18 transaction 4582 a1:a2:a3 1 a1:a2:a3:a4 -1 2025-07-19 transaction 4583 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2025-07-20 transaction 4584 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2025-07-21 transaction 4585 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2025-07-22 transaction 4586 ab 1 ab:ac -1 2025-07-23 transaction 4587 ab:ac:ad 1 ab:ac:ad:ae -1 2025-07-24 transaction 4588 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2025-07-25 transaction 4589 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2025-07-26 transaction 4590 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2025-07-27 transaction 4591 b5 1 b5:b6 -1 2025-07-28 transaction 4592 b5:b6:b7 1 b5:b6:b7:b8 -1 2025-07-29 transaction 4593 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2025-07-30 transaction 4594 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2025-07-31 transaction 4595 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2025-08-01 transaction 4596 bf 1 bf:c0 -1 2025-08-02 transaction 4597 bf:c0:c1 1 bf:c0:c1:c2 -1 2025-08-03 transaction 4598 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2025-08-04 transaction 4599 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2025-08-05 transaction 4600 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2025-08-06 transaction 4601 c9 1 c9:ca -1 2025-08-07 transaction 4602 c9:ca:cb 1 c9:ca:cb:cc -1 2025-08-08 transaction 4603 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2025-08-09 transaction 4604 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2025-08-10 transaction 4605 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2025-08-11 transaction 4606 d3 1 d3:d4 -1 2025-08-12 transaction 4607 d3:d4:d5 1 d3:d4:d5:d6 -1 2025-08-13 transaction 4608 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2025-08-14 transaction 4609 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2025-08-15 transaction 4610 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2025-08-16 transaction 4611 dd 1 dd:de -1 2025-08-17 transaction 4612 dd:de:df 1 dd:de:df:e0 -1 2025-08-18 transaction 4613 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2025-08-19 transaction 4614 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2025-08-20 transaction 4615 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2025-08-21 transaction 4616 e7 1 e7:e8 -1 2025-08-22 transaction 4617 e7:e8:e9 1 e7:e8:e9:ea -1 2025-08-23 transaction 4618 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2025-08-24 transaction 4619 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2025-08-25 transaction 4620 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2025-08-26 transaction 4621 f1 1 f1:f2 -1 2025-08-27 transaction 4622 f1:f2:f3 1 f1:f2:f3:f4 -1 2025-08-28 transaction 4623 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2025-08-29 transaction 4624 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2025-08-30 transaction 4625 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2025-08-31 transaction 4626 fb 1 fb:fc -1 2025-09-01 transaction 4627 fb:fc:fd 1 fb:fc:fd:fe -1 2025-09-02 transaction 4628 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2025-09-03 transaction 4629 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2025-09-04 transaction 4630 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2025-09-05 transaction 4631 105 1 105:106 -1 2025-09-06 transaction 4632 105:106:107 1 105:106:107:108 -1 2025-09-07 transaction 4633 105:106:107:108:109 1 105:106:107:108:109:10a -1 2025-09-08 transaction 4634 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2025-09-09 transaction 4635 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2025-09-10 transaction 4636 10f 1 10f:110 -1 2025-09-11 transaction 4637 10f:110:111 1 10f:110:111:112 -1 2025-09-12 transaction 4638 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2025-09-13 transaction 4639 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2025-09-14 transaction 4640 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2025-09-15 transaction 4641 119 1 119:11a -1 2025-09-16 transaction 4642 119:11a:11b 1 119:11a:11b:11c -1 2025-09-17 transaction 4643 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2025-09-18 transaction 4644 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2025-09-19 transaction 4645 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2025-09-20 transaction 4646 123 1 123:124 -1 2025-09-21 transaction 4647 123:124:125 1 123:124:125:126 -1 2025-09-22 transaction 4648 123:124:125:126:127 1 123:124:125:126:127:128 -1 2025-09-23 transaction 4649 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2025-09-24 transaction 4650 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2025-09-25 transaction 4651 12d 1 12d:12e -1 2025-09-26 transaction 4652 12d:12e:12f 1 12d:12e:12f:130 -1 2025-09-27 transaction 4653 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2025-09-28 transaction 4654 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2025-09-29 transaction 4655 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2025-09-30 transaction 4656 137 1 137:138 -1 2025-10-01 transaction 4657 137:138:139 1 137:138:139:13a -1 2025-10-02 transaction 4658 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2025-10-03 transaction 4659 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2025-10-04 transaction 4660 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2025-10-05 transaction 4661 141 1 141:142 -1 2025-10-06 transaction 4662 141:142:143 1 141:142:143:144 -1 2025-10-07 transaction 4663 141:142:143:144:145 1 141:142:143:144:145:146 -1 2025-10-08 transaction 4664 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2025-10-09 transaction 4665 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2025-10-10 transaction 4666 14b 1 14b:14c -1 2025-10-11 transaction 4667 14b:14c:14d 1 14b:14c:14d:14e -1 2025-10-12 transaction 4668 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2025-10-13 transaction 4669 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2025-10-14 transaction 4670 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2025-10-15 transaction 4671 155 1 155:156 -1 2025-10-16 transaction 4672 155:156:157 1 155:156:157:158 -1 2025-10-17 transaction 4673 155:156:157:158:159 1 155:156:157:158:159:15a -1 2025-10-18 transaction 4674 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2025-10-19 transaction 4675 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2025-10-20 transaction 4676 15f 1 15f:160 -1 2025-10-21 transaction 4677 15f:160:161 1 15f:160:161:162 -1 2025-10-22 transaction 4678 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2025-10-23 transaction 4679 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2025-10-24 transaction 4680 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2025-10-25 transaction 4681 169 1 169:16a -1 2025-10-26 transaction 4682 169:16a:16b 1 169:16a:16b:16c -1 2025-10-27 transaction 4683 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2025-10-28 transaction 4684 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2025-10-29 transaction 4685 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2025-10-30 transaction 4686 173 1 173:174 -1 2025-10-31 transaction 4687 173:174:175 1 173:174:175:176 -1 2025-11-01 transaction 4688 173:174:175:176:177 1 173:174:175:176:177:178 -1 2025-11-02 transaction 4689 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2025-11-03 transaction 4690 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2025-11-04 transaction 4691 17d 1 17d:17e -1 2025-11-05 transaction 4692 17d:17e:17f 1 17d:17e:17f:180 -1 2025-11-06 transaction 4693 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2025-11-07 transaction 4694 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2025-11-08 transaction 4695 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2025-11-09 transaction 4696 187 1 187:188 -1 2025-11-10 transaction 4697 187:188:189 1 187:188:189:18a -1 2025-11-11 transaction 4698 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2025-11-12 transaction 4699 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2025-11-13 transaction 4700 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2025-11-14 transaction 4701 191 1 191:192 -1 2025-11-15 transaction 4702 191:192:193 1 191:192:193:194 -1 2025-11-16 transaction 4703 191:192:193:194:195 1 191:192:193:194:195:196 -1 2025-11-17 transaction 4704 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2025-11-18 transaction 4705 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2025-11-19 transaction 4706 19b 1 19b:19c -1 2025-11-20 transaction 4707 19b:19c:19d 1 19b:19c:19d:19e -1 2025-11-21 transaction 4708 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2025-11-22 transaction 4709 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2025-11-23 transaction 4710 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2025-11-24 transaction 4711 1a5 1 1a5:1a6 -1 2025-11-25 transaction 4712 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2025-11-26 transaction 4713 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2025-11-27 transaction 4714 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2025-11-28 transaction 4715 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2025-11-29 transaction 4716 1af 1 1af:1b0 -1 2025-11-30 transaction 4717 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2025-12-01 transaction 4718 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2025-12-02 transaction 4719 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2025-12-03 transaction 4720 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2025-12-04 transaction 4721 1b9 1 1b9:1ba -1 2025-12-05 transaction 4722 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2025-12-06 transaction 4723 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2025-12-07 transaction 4724 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2025-12-08 transaction 4725 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2025-12-09 transaction 4726 1c3 1 1c3:1c4 -1 2025-12-10 transaction 4727 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2025-12-11 transaction 4728 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2025-12-12 transaction 4729 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2025-12-13 transaction 4730 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2025-12-14 transaction 4731 1cd 1 1cd:1ce -1 2025-12-15 transaction 4732 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2025-12-16 transaction 4733 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2025-12-17 transaction 4734 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2025-12-18 transaction 4735 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2025-12-19 transaction 4736 1d7 1 1d7:1d8 -1 2025-12-20 transaction 4737 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2025-12-21 transaction 4738 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2025-12-22 transaction 4739 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2025-12-23 transaction 4740 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2025-12-24 transaction 4741 1e1 1 1e1:1e2 -1 2025-12-25 transaction 4742 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2025-12-26 transaction 4743 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2025-12-27 transaction 4744 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2025-12-28 transaction 4745 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2025-12-29 transaction 4746 1eb 1 1eb:1ec -1 2025-12-30 transaction 4747 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2025-12-31 transaction 4748 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2026-01-01 transaction 4749 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2026-01-02 transaction 4750 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2026-01-03 transaction 4751 1f5 1 1f5:1f6 -1 2026-01-04 transaction 4752 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2026-01-05 transaction 4753 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2026-01-06 transaction 4754 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2026-01-07 transaction 4755 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2026-01-08 transaction 4756 1ff 1 1ff:200 -1 2026-01-09 transaction 4757 1ff:200:201 1 1ff:200:201:202 -1 2026-01-10 transaction 4758 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2026-01-11 transaction 4759 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2026-01-12 transaction 4760 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2026-01-13 transaction 4761 209 1 209:20a -1 2026-01-14 transaction 4762 209:20a:20b 1 209:20a:20b:20c -1 2026-01-15 transaction 4763 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2026-01-16 transaction 4764 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2026-01-17 transaction 4765 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2026-01-18 transaction 4766 213 1 213:214 -1 2026-01-19 transaction 4767 213:214:215 1 213:214:215:216 -1 2026-01-20 transaction 4768 213:214:215:216:217 1 213:214:215:216:217:218 -1 2026-01-21 transaction 4769 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2026-01-22 transaction 4770 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2026-01-23 transaction 4771 21d 1 21d:21e -1 2026-01-24 transaction 4772 21d:21e:21f 1 21d:21e:21f:220 -1 2026-01-25 transaction 4773 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2026-01-26 transaction 4774 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2026-01-27 transaction 4775 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2026-01-28 transaction 4776 227 1 227:228 -1 2026-01-29 transaction 4777 227:228:229 1 227:228:229:22a -1 2026-01-30 transaction 4778 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2026-01-31 transaction 4779 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2026-02-01 transaction 4780 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2026-02-02 transaction 4781 231 1 231:232 -1 2026-02-03 transaction 4782 231:232:233 1 231:232:233:234 -1 2026-02-04 transaction 4783 231:232:233:234:235 1 231:232:233:234:235:236 -1 2026-02-05 transaction 4784 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2026-02-06 transaction 4785 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2026-02-07 transaction 4786 23b 1 23b:23c -1 2026-02-08 transaction 4787 23b:23c:23d 1 23b:23c:23d:23e -1 2026-02-09 transaction 4788 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2026-02-10 transaction 4789 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2026-02-11 transaction 4790 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2026-02-12 transaction 4791 245 1 245:246 -1 2026-02-13 transaction 4792 245:246:247 1 245:246:247:248 -1 2026-02-14 transaction 4793 245:246:247:248:249 1 245:246:247:248:249:24a -1 2026-02-15 transaction 4794 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2026-02-16 transaction 4795 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2026-02-17 transaction 4796 24f 1 24f:250 -1 2026-02-18 transaction 4797 24f:250:251 1 24f:250:251:252 -1 2026-02-19 transaction 4798 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2026-02-20 transaction 4799 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2026-02-21 transaction 4800 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2026-02-22 transaction 4801 259 1 259:25a -1 2026-02-23 transaction 4802 259:25a:25b 1 259:25a:25b:25c -1 2026-02-24 transaction 4803 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2026-02-25 transaction 4804 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2026-02-26 transaction 4805 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2026-02-27 transaction 4806 263 1 263:264 -1 2026-02-28 transaction 4807 263:264:265 1 263:264:265:266 -1 2026-03-01 transaction 4808 263:264:265:266:267 1 263:264:265:266:267:268 -1 2026-03-02 transaction 4809 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2026-03-03 transaction 4810 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2026-03-04 transaction 4811 26d 1 26d:26e -1 2026-03-05 transaction 4812 26d:26e:26f 1 26d:26e:26f:270 -1 2026-03-06 transaction 4813 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2026-03-07 transaction 4814 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2026-03-08 transaction 4815 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2026-03-09 transaction 4816 277 1 277:278 -1 2026-03-10 transaction 4817 277:278:279 1 277:278:279:27a -1 2026-03-11 transaction 4818 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2026-03-12 transaction 4819 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2026-03-13 transaction 4820 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2026-03-14 transaction 4821 281 1 281:282 -1 2026-03-15 transaction 4822 281:282:283 1 281:282:283:284 -1 2026-03-16 transaction 4823 281:282:283:284:285 1 281:282:283:284:285:286 -1 2026-03-17 transaction 4824 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2026-03-18 transaction 4825 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2026-03-19 transaction 4826 28b 1 28b:28c -1 2026-03-20 transaction 4827 28b:28c:28d 1 28b:28c:28d:28e -1 2026-03-21 transaction 4828 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2026-03-22 transaction 4829 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2026-03-23 transaction 4830 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2026-03-24 transaction 4831 295 1 295:296 -1 2026-03-25 transaction 4832 295:296:297 1 295:296:297:298 -1 2026-03-26 transaction 4833 295:296:297:298:299 1 295:296:297:298:299:29a -1 2026-03-27 transaction 4834 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2026-03-28 transaction 4835 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2026-03-29 transaction 4836 29f 1 29f:2a0 -1 2026-03-30 transaction 4837 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2026-03-31 transaction 4838 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2026-04-01 transaction 4839 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2026-04-02 transaction 4840 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2026-04-03 transaction 4841 2a9 1 2a9:2aa -1 2026-04-04 transaction 4842 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2026-04-05 transaction 4843 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2026-04-06 transaction 4844 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2026-04-07 transaction 4845 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2026-04-08 transaction 4846 2b3 1 2b3:2b4 -1 2026-04-09 transaction 4847 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2026-04-10 transaction 4848 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2026-04-11 transaction 4849 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2026-04-12 transaction 4850 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2026-04-13 transaction 4851 2bd 1 2bd:2be -1 2026-04-14 transaction 4852 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2026-04-15 transaction 4853 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2026-04-16 transaction 4854 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2026-04-17 transaction 4855 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2026-04-18 transaction 4856 2c7 1 2c7:2c8 -1 2026-04-19 transaction 4857 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2026-04-20 transaction 4858 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2026-04-21 transaction 4859 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2026-04-22 transaction 4860 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2026-04-23 transaction 4861 2d1 1 2d1:2d2 -1 2026-04-24 transaction 4862 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2026-04-25 transaction 4863 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2026-04-26 transaction 4864 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2026-04-27 transaction 4865 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2026-04-28 transaction 4866 2db 1 2db:2dc -1 2026-04-29 transaction 4867 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2026-04-30 transaction 4868 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2026-05-01 transaction 4869 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2026-05-02 transaction 4870 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2026-05-03 transaction 4871 2e5 1 2e5:2e6 -1 2026-05-04 transaction 4872 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2026-05-05 transaction 4873 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2026-05-06 transaction 4874 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2026-05-07 transaction 4875 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2026-05-08 transaction 4876 2ef 1 2ef:2f0 -1 2026-05-09 transaction 4877 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2026-05-10 transaction 4878 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2026-05-11 transaction 4879 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2026-05-12 transaction 4880 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2026-05-13 transaction 4881 2f9 1 2f9:2fa -1 2026-05-14 transaction 4882 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2026-05-15 transaction 4883 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2026-05-16 transaction 4884 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2026-05-17 transaction 4885 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2026-05-18 transaction 4886 303 1 303:304 -1 2026-05-19 transaction 4887 303:304:305 1 303:304:305:306 -1 2026-05-20 transaction 4888 303:304:305:306:307 1 303:304:305:306:307:308 -1 2026-05-21 transaction 4889 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2026-05-22 transaction 4890 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2026-05-23 transaction 4891 30d 1 30d:30e -1 2026-05-24 transaction 4892 30d:30e:30f 1 30d:30e:30f:310 -1 2026-05-25 transaction 4893 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2026-05-26 transaction 4894 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2026-05-27 transaction 4895 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2026-05-28 transaction 4896 317 1 317:318 -1 2026-05-29 transaction 4897 317:318:319 1 317:318:319:31a -1 2026-05-30 transaction 4898 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2026-05-31 transaction 4899 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2026-06-01 transaction 4900 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2026-06-02 transaction 4901 321 1 321:322 -1 2026-06-03 transaction 4902 321:322:323 1 321:322:323:324 -1 2026-06-04 transaction 4903 321:322:323:324:325 1 321:322:323:324:325:326 -1 2026-06-05 transaction 4904 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2026-06-06 transaction 4905 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2026-06-07 transaction 4906 32b 1 32b:32c -1 2026-06-08 transaction 4907 32b:32c:32d 1 32b:32c:32d:32e -1 2026-06-09 transaction 4908 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2026-06-10 transaction 4909 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2026-06-11 transaction 4910 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2026-06-12 transaction 4911 335 1 335:336 -1 2026-06-13 transaction 4912 335:336:337 1 335:336:337:338 -1 2026-06-14 transaction 4913 335:336:337:338:339 1 335:336:337:338:339:33a -1 2026-06-15 transaction 4914 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2026-06-16 transaction 4915 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2026-06-17 transaction 4916 33f 1 33f:340 -1 2026-06-18 transaction 4917 33f:340:341 1 33f:340:341:342 -1 2026-06-19 transaction 4918 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2026-06-20 transaction 4919 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2026-06-21 transaction 4920 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2026-06-22 transaction 4921 349 1 349:34a -1 2026-06-23 transaction 4922 349:34a:34b 1 349:34a:34b:34c -1 2026-06-24 transaction 4923 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2026-06-25 transaction 4924 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2026-06-26 transaction 4925 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2026-06-27 transaction 4926 353 1 353:354 -1 2026-06-28 transaction 4927 353:354:355 1 353:354:355:356 -1 2026-06-29 transaction 4928 353:354:355:356:357 1 353:354:355:356:357:358 -1 2026-06-30 transaction 4929 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2026-07-01 transaction 4930 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2026-07-02 transaction 4931 35d 1 35d:35e -1 2026-07-03 transaction 4932 35d:35e:35f 1 35d:35e:35f:360 -1 2026-07-04 transaction 4933 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2026-07-05 transaction 4934 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2026-07-06 transaction 4935 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2026-07-07 transaction 4936 367 1 367:368 -1 2026-07-08 transaction 4937 367:368:369 1 367:368:369:36a -1 2026-07-09 transaction 4938 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2026-07-10 transaction 4939 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2026-07-11 transaction 4940 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2026-07-12 transaction 4941 371 1 371:372 -1 2026-07-13 transaction 4942 371:372:373 1 371:372:373:374 -1 2026-07-14 transaction 4943 371:372:373:374:375 1 371:372:373:374:375:376 -1 2026-07-15 transaction 4944 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2026-07-16 transaction 4945 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2026-07-17 transaction 4946 37b 1 37b:37c -1 2026-07-18 transaction 4947 37b:37c:37d 1 37b:37c:37d:37e -1 2026-07-19 transaction 4948 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2026-07-20 transaction 4949 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2026-07-21 transaction 4950 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2026-07-22 transaction 4951 385 1 385:386 -1 2026-07-23 transaction 4952 385:386:387 1 385:386:387:388 -1 2026-07-24 transaction 4953 385:386:387:388:389 1 385:386:387:388:389:38a -1 2026-07-25 transaction 4954 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2026-07-26 transaction 4955 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2026-07-27 transaction 4956 38f 1 38f:390 -1 2026-07-28 transaction 4957 38f:390:391 1 38f:390:391:392 -1 2026-07-29 transaction 4958 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2026-07-30 transaction 4959 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2026-07-31 transaction 4960 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2026-08-01 transaction 4961 399 1 399:39a -1 2026-08-02 transaction 4962 399:39a:39b 1 399:39a:39b:39c -1 2026-08-03 transaction 4963 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2026-08-04 transaction 4964 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2026-08-05 transaction 4965 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2026-08-06 transaction 4966 3a3 1 3a3:3a4 -1 2026-08-07 transaction 4967 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2026-08-08 transaction 4968 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2026-08-09 transaction 4969 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2026-08-10 transaction 4970 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2026-08-11 transaction 4971 3ad 1 3ad:3ae -1 2026-08-12 transaction 4972 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2026-08-13 transaction 4973 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2026-08-14 transaction 4974 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2026-08-15 transaction 4975 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2026-08-16 transaction 4976 3b7 1 3b7:3b8 -1 2026-08-17 transaction 4977 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2026-08-18 transaction 4978 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2026-08-19 transaction 4979 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2026-08-20 transaction 4980 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2026-08-21 transaction 4981 3c1 1 3c1:3c2 -1 2026-08-22 transaction 4982 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2026-08-23 transaction 4983 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2026-08-24 transaction 4984 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2026-08-25 transaction 4985 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2026-08-26 transaction 4986 3cb 1 3cb:3cc -1 2026-08-27 transaction 4987 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2026-08-28 transaction 4988 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2026-08-29 transaction 4989 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2026-08-30 transaction 4990 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2026-08-31 transaction 4991 3d5 1 3d5:3d6 -1 2026-09-01 transaction 4992 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2026-09-02 transaction 4993 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2026-09-03 transaction 4994 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2026-09-04 transaction 4995 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2026-09-05 transaction 4996 3df 1 3df:3e0 -1 2026-09-06 transaction 4997 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2026-09-07 transaction 4998 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2026-09-08 transaction 4999 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2026-09-09 transaction 5000 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2026-09-10 transaction 5001 1 1 1:2 -1 2026-09-11 transaction 5002 1:2:3 1 1:2:3:4 -1 2026-09-12 transaction 5003 1:2:3:4:5 1 1:2:3:4:5:6 -1 2026-09-13 transaction 5004 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2026-09-14 transaction 5005 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2026-09-15 transaction 5006 b 1 b:c -1 2026-09-16 transaction 5007 b:c:d 1 b:c:d:e -1 2026-09-17 transaction 5008 b:c:d:e:f 1 b:c:d:e:f:10 -1 2026-09-18 transaction 5009 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2026-09-19 transaction 5010 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2026-09-20 transaction 5011 15 1 15:16 -1 2026-09-21 transaction 5012 15:16:17 1 15:16:17:18 -1 2026-09-22 transaction 5013 15:16:17:18:19 1 15:16:17:18:19:1a -1 2026-09-23 transaction 5014 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2026-09-24 transaction 5015 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2026-09-25 transaction 5016 1f 1 1f:20 -1 2026-09-26 transaction 5017 1f:20:21 1 1f:20:21:22 -1 2026-09-27 transaction 5018 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2026-09-28 transaction 5019 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2026-09-29 transaction 5020 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2026-09-30 transaction 5021 29 1 29:2a -1 2026-10-01 transaction 5022 29:2a:2b 1 29:2a:2b:2c -1 2026-10-02 transaction 5023 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2026-10-03 transaction 5024 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2026-10-04 transaction 5025 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2026-10-05 transaction 5026 33 1 33:34 -1 2026-10-06 transaction 5027 33:34:35 1 33:34:35:36 -1 2026-10-07 transaction 5028 33:34:35:36:37 1 33:34:35:36:37:38 -1 2026-10-08 transaction 5029 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2026-10-09 transaction 5030 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2026-10-10 transaction 5031 3d 1 3d:3e -1 2026-10-11 transaction 5032 3d:3e:3f 1 3d:3e:3f:40 -1 2026-10-12 transaction 5033 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2026-10-13 transaction 5034 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2026-10-14 transaction 5035 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2026-10-15 transaction 5036 47 1 47:48 -1 2026-10-16 transaction 5037 47:48:49 1 47:48:49:4a -1 2026-10-17 transaction 5038 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2026-10-18 transaction 5039 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2026-10-19 transaction 5040 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2026-10-20 transaction 5041 51 1 51:52 -1 2026-10-21 transaction 5042 51:52:53 1 51:52:53:54 -1 2026-10-22 transaction 5043 51:52:53:54:55 1 51:52:53:54:55:56 -1 2026-10-23 transaction 5044 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2026-10-24 transaction 5045 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2026-10-25 transaction 5046 5b 1 5b:5c -1 2026-10-26 transaction 5047 5b:5c:5d 1 5b:5c:5d:5e -1 2026-10-27 transaction 5048 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2026-10-28 transaction 5049 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2026-10-29 transaction 5050 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2026-10-30 transaction 5051 65 1 65:66 -1 2026-10-31 transaction 5052 65:66:67 1 65:66:67:68 -1 2026-11-01 transaction 5053 65:66:67:68:69 1 65:66:67:68:69:6a -1 2026-11-02 transaction 5054 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2026-11-03 transaction 5055 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2026-11-04 transaction 5056 6f 1 6f:70 -1 2026-11-05 transaction 5057 6f:70:71 1 6f:70:71:72 -1 2026-11-06 transaction 5058 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2026-11-07 transaction 5059 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2026-11-08 transaction 5060 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2026-11-09 transaction 5061 79 1 79:7a -1 2026-11-10 transaction 5062 79:7a:7b 1 79:7a:7b:7c -1 2026-11-11 transaction 5063 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2026-11-12 transaction 5064 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2026-11-13 transaction 5065 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2026-11-14 transaction 5066 83 1 83:84 -1 2026-11-15 transaction 5067 83:84:85 1 83:84:85:86 -1 2026-11-16 transaction 5068 83:84:85:86:87 1 83:84:85:86:87:88 -1 2026-11-17 transaction 5069 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2026-11-18 transaction 5070 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2026-11-19 transaction 5071 8d 1 8d:8e -1 2026-11-20 transaction 5072 8d:8e:8f 1 8d:8e:8f:90 -1 2026-11-21 transaction 5073 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2026-11-22 transaction 5074 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2026-11-23 transaction 5075 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2026-11-24 transaction 5076 97 1 97:98 -1 2026-11-25 transaction 5077 97:98:99 1 97:98:99:9a -1 2026-11-26 transaction 5078 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2026-11-27 transaction 5079 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2026-11-28 transaction 5080 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2026-11-29 transaction 5081 a1 1 a1:a2 -1 2026-11-30 transaction 5082 a1:a2:a3 1 a1:a2:a3:a4 -1 2026-12-01 transaction 5083 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2026-12-02 transaction 5084 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2026-12-03 transaction 5085 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2026-12-04 transaction 5086 ab 1 ab:ac -1 2026-12-05 transaction 5087 ab:ac:ad 1 ab:ac:ad:ae -1 2026-12-06 transaction 5088 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2026-12-07 transaction 5089 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2026-12-08 transaction 5090 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2026-12-09 transaction 5091 b5 1 b5:b6 -1 2026-12-10 transaction 5092 b5:b6:b7 1 b5:b6:b7:b8 -1 2026-12-11 transaction 5093 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2026-12-12 transaction 5094 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2026-12-13 transaction 5095 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2026-12-14 transaction 5096 bf 1 bf:c0 -1 2026-12-15 transaction 5097 bf:c0:c1 1 bf:c0:c1:c2 -1 2026-12-16 transaction 5098 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2026-12-17 transaction 5099 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2026-12-18 transaction 5100 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2026-12-19 transaction 5101 c9 1 c9:ca -1 2026-12-20 transaction 5102 c9:ca:cb 1 c9:ca:cb:cc -1 2026-12-21 transaction 5103 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2026-12-22 transaction 5104 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2026-12-23 transaction 5105 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2026-12-24 transaction 5106 d3 1 d3:d4 -1 2026-12-25 transaction 5107 d3:d4:d5 1 d3:d4:d5:d6 -1 2026-12-26 transaction 5108 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2026-12-27 transaction 5109 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2026-12-28 transaction 5110 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2026-12-29 transaction 5111 dd 1 dd:de -1 2026-12-30 transaction 5112 dd:de:df 1 dd:de:df:e0 -1 2026-12-31 transaction 5113 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2027-01-01 transaction 5114 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2027-01-02 transaction 5115 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2027-01-03 transaction 5116 e7 1 e7:e8 -1 2027-01-04 transaction 5117 e7:e8:e9 1 e7:e8:e9:ea -1 2027-01-05 transaction 5118 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2027-01-06 transaction 5119 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2027-01-07 transaction 5120 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2027-01-08 transaction 5121 f1 1 f1:f2 -1 2027-01-09 transaction 5122 f1:f2:f3 1 f1:f2:f3:f4 -1 2027-01-10 transaction 5123 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2027-01-11 transaction 5124 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2027-01-12 transaction 5125 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2027-01-13 transaction 5126 fb 1 fb:fc -1 2027-01-14 transaction 5127 fb:fc:fd 1 fb:fc:fd:fe -1 2027-01-15 transaction 5128 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2027-01-16 transaction 5129 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2027-01-17 transaction 5130 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2027-01-18 transaction 5131 105 1 105:106 -1 2027-01-19 transaction 5132 105:106:107 1 105:106:107:108 -1 2027-01-20 transaction 5133 105:106:107:108:109 1 105:106:107:108:109:10a -1 2027-01-21 transaction 5134 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2027-01-22 transaction 5135 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2027-01-23 transaction 5136 10f 1 10f:110 -1 2027-01-24 transaction 5137 10f:110:111 1 10f:110:111:112 -1 2027-01-25 transaction 5138 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2027-01-26 transaction 5139 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2027-01-27 transaction 5140 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2027-01-28 transaction 5141 119 1 119:11a -1 2027-01-29 transaction 5142 119:11a:11b 1 119:11a:11b:11c -1 2027-01-30 transaction 5143 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2027-01-31 transaction 5144 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2027-02-01 transaction 5145 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2027-02-02 transaction 5146 123 1 123:124 -1 2027-02-03 transaction 5147 123:124:125 1 123:124:125:126 -1 2027-02-04 transaction 5148 123:124:125:126:127 1 123:124:125:126:127:128 -1 2027-02-05 transaction 5149 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2027-02-06 transaction 5150 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2027-02-07 transaction 5151 12d 1 12d:12e -1 2027-02-08 transaction 5152 12d:12e:12f 1 12d:12e:12f:130 -1 2027-02-09 transaction 5153 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2027-02-10 transaction 5154 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2027-02-11 transaction 5155 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2027-02-12 transaction 5156 137 1 137:138 -1 2027-02-13 transaction 5157 137:138:139 1 137:138:139:13a -1 2027-02-14 transaction 5158 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2027-02-15 transaction 5159 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2027-02-16 transaction 5160 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2027-02-17 transaction 5161 141 1 141:142 -1 2027-02-18 transaction 5162 141:142:143 1 141:142:143:144 -1 2027-02-19 transaction 5163 141:142:143:144:145 1 141:142:143:144:145:146 -1 2027-02-20 transaction 5164 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2027-02-21 transaction 5165 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2027-02-22 transaction 5166 14b 1 14b:14c -1 2027-02-23 transaction 5167 14b:14c:14d 1 14b:14c:14d:14e -1 2027-02-24 transaction 5168 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2027-02-25 transaction 5169 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2027-02-26 transaction 5170 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2027-02-27 transaction 5171 155 1 155:156 -1 2027-02-28 transaction 5172 155:156:157 1 155:156:157:158 -1 2027-03-01 transaction 5173 155:156:157:158:159 1 155:156:157:158:159:15a -1 2027-03-02 transaction 5174 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2027-03-03 transaction 5175 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2027-03-04 transaction 5176 15f 1 15f:160 -1 2027-03-05 transaction 5177 15f:160:161 1 15f:160:161:162 -1 2027-03-06 transaction 5178 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2027-03-07 transaction 5179 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2027-03-08 transaction 5180 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2027-03-09 transaction 5181 169 1 169:16a -1 2027-03-10 transaction 5182 169:16a:16b 1 169:16a:16b:16c -1 2027-03-11 transaction 5183 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2027-03-12 transaction 5184 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2027-03-13 transaction 5185 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2027-03-14 transaction 5186 173 1 173:174 -1 2027-03-15 transaction 5187 173:174:175 1 173:174:175:176 -1 2027-03-16 transaction 5188 173:174:175:176:177 1 173:174:175:176:177:178 -1 2027-03-17 transaction 5189 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2027-03-18 transaction 5190 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2027-03-19 transaction 5191 17d 1 17d:17e -1 2027-03-20 transaction 5192 17d:17e:17f 1 17d:17e:17f:180 -1 2027-03-21 transaction 5193 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2027-03-22 transaction 5194 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2027-03-23 transaction 5195 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2027-03-24 transaction 5196 187 1 187:188 -1 2027-03-25 transaction 5197 187:188:189 1 187:188:189:18a -1 2027-03-26 transaction 5198 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2027-03-27 transaction 5199 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2027-03-28 transaction 5200 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2027-03-29 transaction 5201 191 1 191:192 -1 2027-03-30 transaction 5202 191:192:193 1 191:192:193:194 -1 2027-03-31 transaction 5203 191:192:193:194:195 1 191:192:193:194:195:196 -1 2027-04-01 transaction 5204 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2027-04-02 transaction 5205 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2027-04-03 transaction 5206 19b 1 19b:19c -1 2027-04-04 transaction 5207 19b:19c:19d 1 19b:19c:19d:19e -1 2027-04-05 transaction 5208 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2027-04-06 transaction 5209 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2027-04-07 transaction 5210 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2027-04-08 transaction 5211 1a5 1 1a5:1a6 -1 2027-04-09 transaction 5212 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2027-04-10 transaction 5213 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2027-04-11 transaction 5214 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2027-04-12 transaction 5215 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2027-04-13 transaction 5216 1af 1 1af:1b0 -1 2027-04-14 transaction 5217 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2027-04-15 transaction 5218 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2027-04-16 transaction 5219 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2027-04-17 transaction 5220 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2027-04-18 transaction 5221 1b9 1 1b9:1ba -1 2027-04-19 transaction 5222 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2027-04-20 transaction 5223 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2027-04-21 transaction 5224 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2027-04-22 transaction 5225 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2027-04-23 transaction 5226 1c3 1 1c3:1c4 -1 2027-04-24 transaction 5227 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2027-04-25 transaction 5228 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2027-04-26 transaction 5229 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2027-04-27 transaction 5230 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2027-04-28 transaction 5231 1cd 1 1cd:1ce -1 2027-04-29 transaction 5232 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2027-04-30 transaction 5233 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2027-05-01 transaction 5234 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2027-05-02 transaction 5235 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2027-05-03 transaction 5236 1d7 1 1d7:1d8 -1 2027-05-04 transaction 5237 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2027-05-05 transaction 5238 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2027-05-06 transaction 5239 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2027-05-07 transaction 5240 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2027-05-08 transaction 5241 1e1 1 1e1:1e2 -1 2027-05-09 transaction 5242 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2027-05-10 transaction 5243 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2027-05-11 transaction 5244 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2027-05-12 transaction 5245 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2027-05-13 transaction 5246 1eb 1 1eb:1ec -1 2027-05-14 transaction 5247 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2027-05-15 transaction 5248 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2027-05-16 transaction 5249 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2027-05-17 transaction 5250 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2027-05-18 transaction 5251 1f5 1 1f5:1f6 -1 2027-05-19 transaction 5252 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2027-05-20 transaction 5253 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2027-05-21 transaction 5254 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2027-05-22 transaction 5255 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2027-05-23 transaction 5256 1ff 1 1ff:200 -1 2027-05-24 transaction 5257 1ff:200:201 1 1ff:200:201:202 -1 2027-05-25 transaction 5258 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2027-05-26 transaction 5259 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2027-05-27 transaction 5260 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2027-05-28 transaction 5261 209 1 209:20a -1 2027-05-29 transaction 5262 209:20a:20b 1 209:20a:20b:20c -1 2027-05-30 transaction 5263 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2027-05-31 transaction 5264 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2027-06-01 transaction 5265 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2027-06-02 transaction 5266 213 1 213:214 -1 2027-06-03 transaction 5267 213:214:215 1 213:214:215:216 -1 2027-06-04 transaction 5268 213:214:215:216:217 1 213:214:215:216:217:218 -1 2027-06-05 transaction 5269 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2027-06-06 transaction 5270 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2027-06-07 transaction 5271 21d 1 21d:21e -1 2027-06-08 transaction 5272 21d:21e:21f 1 21d:21e:21f:220 -1 2027-06-09 transaction 5273 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2027-06-10 transaction 5274 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2027-06-11 transaction 5275 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2027-06-12 transaction 5276 227 1 227:228 -1 2027-06-13 transaction 5277 227:228:229 1 227:228:229:22a -1 2027-06-14 transaction 5278 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2027-06-15 transaction 5279 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2027-06-16 transaction 5280 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2027-06-17 transaction 5281 231 1 231:232 -1 2027-06-18 transaction 5282 231:232:233 1 231:232:233:234 -1 2027-06-19 transaction 5283 231:232:233:234:235 1 231:232:233:234:235:236 -1 2027-06-20 transaction 5284 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2027-06-21 transaction 5285 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2027-06-22 transaction 5286 23b 1 23b:23c -1 2027-06-23 transaction 5287 23b:23c:23d 1 23b:23c:23d:23e -1 2027-06-24 transaction 5288 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2027-06-25 transaction 5289 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2027-06-26 transaction 5290 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2027-06-27 transaction 5291 245 1 245:246 -1 2027-06-28 transaction 5292 245:246:247 1 245:246:247:248 -1 2027-06-29 transaction 5293 245:246:247:248:249 1 245:246:247:248:249:24a -1 2027-06-30 transaction 5294 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2027-07-01 transaction 5295 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2027-07-02 transaction 5296 24f 1 24f:250 -1 2027-07-03 transaction 5297 24f:250:251 1 24f:250:251:252 -1 2027-07-04 transaction 5298 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2027-07-05 transaction 5299 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2027-07-06 transaction 5300 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2027-07-07 transaction 5301 259 1 259:25a -1 2027-07-08 transaction 5302 259:25a:25b 1 259:25a:25b:25c -1 2027-07-09 transaction 5303 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2027-07-10 transaction 5304 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2027-07-11 transaction 5305 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2027-07-12 transaction 5306 263 1 263:264 -1 2027-07-13 transaction 5307 263:264:265 1 263:264:265:266 -1 2027-07-14 transaction 5308 263:264:265:266:267 1 263:264:265:266:267:268 -1 2027-07-15 transaction 5309 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2027-07-16 transaction 5310 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2027-07-17 transaction 5311 26d 1 26d:26e -1 2027-07-18 transaction 5312 26d:26e:26f 1 26d:26e:26f:270 -1 2027-07-19 transaction 5313 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2027-07-20 transaction 5314 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2027-07-21 transaction 5315 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2027-07-22 transaction 5316 277 1 277:278 -1 2027-07-23 transaction 5317 277:278:279 1 277:278:279:27a -1 2027-07-24 transaction 5318 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2027-07-25 transaction 5319 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2027-07-26 transaction 5320 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2027-07-27 transaction 5321 281 1 281:282 -1 2027-07-28 transaction 5322 281:282:283 1 281:282:283:284 -1 2027-07-29 transaction 5323 281:282:283:284:285 1 281:282:283:284:285:286 -1 2027-07-30 transaction 5324 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2027-07-31 transaction 5325 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2027-08-01 transaction 5326 28b 1 28b:28c -1 2027-08-02 transaction 5327 28b:28c:28d 1 28b:28c:28d:28e -1 2027-08-03 transaction 5328 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2027-08-04 transaction 5329 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2027-08-05 transaction 5330 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2027-08-06 transaction 5331 295 1 295:296 -1 2027-08-07 transaction 5332 295:296:297 1 295:296:297:298 -1 2027-08-08 transaction 5333 295:296:297:298:299 1 295:296:297:298:299:29a -1 2027-08-09 transaction 5334 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2027-08-10 transaction 5335 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2027-08-11 transaction 5336 29f 1 29f:2a0 -1 2027-08-12 transaction 5337 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2027-08-13 transaction 5338 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2027-08-14 transaction 5339 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2027-08-15 transaction 5340 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2027-08-16 transaction 5341 2a9 1 2a9:2aa -1 2027-08-17 transaction 5342 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2027-08-18 transaction 5343 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2027-08-19 transaction 5344 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2027-08-20 transaction 5345 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2027-08-21 transaction 5346 2b3 1 2b3:2b4 -1 2027-08-22 transaction 5347 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2027-08-23 transaction 5348 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2027-08-24 transaction 5349 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2027-08-25 transaction 5350 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2027-08-26 transaction 5351 2bd 1 2bd:2be -1 2027-08-27 transaction 5352 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2027-08-28 transaction 5353 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2027-08-29 transaction 5354 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2027-08-30 transaction 5355 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2027-08-31 transaction 5356 2c7 1 2c7:2c8 -1 2027-09-01 transaction 5357 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2027-09-02 transaction 5358 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2027-09-03 transaction 5359 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2027-09-04 transaction 5360 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2027-09-05 transaction 5361 2d1 1 2d1:2d2 -1 2027-09-06 transaction 5362 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2027-09-07 transaction 5363 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2027-09-08 transaction 5364 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2027-09-09 transaction 5365 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2027-09-10 transaction 5366 2db 1 2db:2dc -1 2027-09-11 transaction 5367 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2027-09-12 transaction 5368 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2027-09-13 transaction 5369 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2027-09-14 transaction 5370 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2027-09-15 transaction 5371 2e5 1 2e5:2e6 -1 2027-09-16 transaction 5372 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2027-09-17 transaction 5373 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2027-09-18 transaction 5374 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2027-09-19 transaction 5375 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2027-09-20 transaction 5376 2ef 1 2ef:2f0 -1 2027-09-21 transaction 5377 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2027-09-22 transaction 5378 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2027-09-23 transaction 5379 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2027-09-24 transaction 5380 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2027-09-25 transaction 5381 2f9 1 2f9:2fa -1 2027-09-26 transaction 5382 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2027-09-27 transaction 5383 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2027-09-28 transaction 5384 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2027-09-29 transaction 5385 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2027-09-30 transaction 5386 303 1 303:304 -1 2027-10-01 transaction 5387 303:304:305 1 303:304:305:306 -1 2027-10-02 transaction 5388 303:304:305:306:307 1 303:304:305:306:307:308 -1 2027-10-03 transaction 5389 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2027-10-04 transaction 5390 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2027-10-05 transaction 5391 30d 1 30d:30e -1 2027-10-06 transaction 5392 30d:30e:30f 1 30d:30e:30f:310 -1 2027-10-07 transaction 5393 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2027-10-08 transaction 5394 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2027-10-09 transaction 5395 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2027-10-10 transaction 5396 317 1 317:318 -1 2027-10-11 transaction 5397 317:318:319 1 317:318:319:31a -1 2027-10-12 transaction 5398 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2027-10-13 transaction 5399 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2027-10-14 transaction 5400 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2027-10-15 transaction 5401 321 1 321:322 -1 2027-10-16 transaction 5402 321:322:323 1 321:322:323:324 -1 2027-10-17 transaction 5403 321:322:323:324:325 1 321:322:323:324:325:326 -1 2027-10-18 transaction 5404 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2027-10-19 transaction 5405 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2027-10-20 transaction 5406 32b 1 32b:32c -1 2027-10-21 transaction 5407 32b:32c:32d 1 32b:32c:32d:32e -1 2027-10-22 transaction 5408 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2027-10-23 transaction 5409 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2027-10-24 transaction 5410 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2027-10-25 transaction 5411 335 1 335:336 -1 2027-10-26 transaction 5412 335:336:337 1 335:336:337:338 -1 2027-10-27 transaction 5413 335:336:337:338:339 1 335:336:337:338:339:33a -1 2027-10-28 transaction 5414 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2027-10-29 transaction 5415 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2027-10-30 transaction 5416 33f 1 33f:340 -1 2027-10-31 transaction 5417 33f:340:341 1 33f:340:341:342 -1 2027-11-01 transaction 5418 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2027-11-02 transaction 5419 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2027-11-03 transaction 5420 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2027-11-04 transaction 5421 349 1 349:34a -1 2027-11-05 transaction 5422 349:34a:34b 1 349:34a:34b:34c -1 2027-11-06 transaction 5423 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2027-11-07 transaction 5424 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2027-11-08 transaction 5425 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2027-11-09 transaction 5426 353 1 353:354 -1 2027-11-10 transaction 5427 353:354:355 1 353:354:355:356 -1 2027-11-11 transaction 5428 353:354:355:356:357 1 353:354:355:356:357:358 -1 2027-11-12 transaction 5429 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2027-11-13 transaction 5430 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2027-11-14 transaction 5431 35d 1 35d:35e -1 2027-11-15 transaction 5432 35d:35e:35f 1 35d:35e:35f:360 -1 2027-11-16 transaction 5433 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2027-11-17 transaction 5434 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2027-11-18 transaction 5435 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2027-11-19 transaction 5436 367 1 367:368 -1 2027-11-20 transaction 5437 367:368:369 1 367:368:369:36a -1 2027-11-21 transaction 5438 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2027-11-22 transaction 5439 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2027-11-23 transaction 5440 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2027-11-24 transaction 5441 371 1 371:372 -1 2027-11-25 transaction 5442 371:372:373 1 371:372:373:374 -1 2027-11-26 transaction 5443 371:372:373:374:375 1 371:372:373:374:375:376 -1 2027-11-27 transaction 5444 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2027-11-28 transaction 5445 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2027-11-29 transaction 5446 37b 1 37b:37c -1 2027-11-30 transaction 5447 37b:37c:37d 1 37b:37c:37d:37e -1 2027-12-01 transaction 5448 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2027-12-02 transaction 5449 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2027-12-03 transaction 5450 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2027-12-04 transaction 5451 385 1 385:386 -1 2027-12-05 transaction 5452 385:386:387 1 385:386:387:388 -1 2027-12-06 transaction 5453 385:386:387:388:389 1 385:386:387:388:389:38a -1 2027-12-07 transaction 5454 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2027-12-08 transaction 5455 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2027-12-09 transaction 5456 38f 1 38f:390 -1 2027-12-10 transaction 5457 38f:390:391 1 38f:390:391:392 -1 2027-12-11 transaction 5458 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2027-12-12 transaction 5459 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2027-12-13 transaction 5460 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2027-12-14 transaction 5461 399 1 399:39a -1 2027-12-15 transaction 5462 399:39a:39b 1 399:39a:39b:39c -1 2027-12-16 transaction 5463 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2027-12-17 transaction 5464 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2027-12-18 transaction 5465 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2027-12-19 transaction 5466 3a3 1 3a3:3a4 -1 2027-12-20 transaction 5467 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2027-12-21 transaction 5468 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2027-12-22 transaction 5469 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2027-12-23 transaction 5470 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2027-12-24 transaction 5471 3ad 1 3ad:3ae -1 2027-12-25 transaction 5472 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2027-12-26 transaction 5473 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2027-12-27 transaction 5474 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2027-12-28 transaction 5475 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2027-12-29 transaction 5476 3b7 1 3b7:3b8 -1 2027-12-30 transaction 5477 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2027-12-31 transaction 5478 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2028-01-01 transaction 5479 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2028-01-02 transaction 5480 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2028-01-03 transaction 5481 3c1 1 3c1:3c2 -1 2028-01-04 transaction 5482 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2028-01-05 transaction 5483 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2028-01-06 transaction 5484 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2028-01-07 transaction 5485 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2028-01-08 transaction 5486 3cb 1 3cb:3cc -1 2028-01-09 transaction 5487 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2028-01-10 transaction 5488 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2028-01-11 transaction 5489 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2028-01-12 transaction 5490 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2028-01-13 transaction 5491 3d5 1 3d5:3d6 -1 2028-01-14 transaction 5492 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2028-01-15 transaction 5493 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2028-01-16 transaction 5494 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2028-01-17 transaction 5495 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2028-01-18 transaction 5496 3df 1 3df:3e0 -1 2028-01-19 transaction 5497 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2028-01-20 transaction 5498 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2028-01-21 transaction 5499 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2028-01-22 transaction 5500 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2028-01-23 transaction 5501 1 1 1:2 -1 2028-01-24 transaction 5502 1:2:3 1 1:2:3:4 -1 2028-01-25 transaction 5503 1:2:3:4:5 1 1:2:3:4:5:6 -1 2028-01-26 transaction 5504 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2028-01-27 transaction 5505 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2028-01-28 transaction 5506 b 1 b:c -1 2028-01-29 transaction 5507 b:c:d 1 b:c:d:e -1 2028-01-30 transaction 5508 b:c:d:e:f 1 b:c:d:e:f:10 -1 2028-01-31 transaction 5509 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2028-02-01 transaction 5510 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2028-02-02 transaction 5511 15 1 15:16 -1 2028-02-03 transaction 5512 15:16:17 1 15:16:17:18 -1 2028-02-04 transaction 5513 15:16:17:18:19 1 15:16:17:18:19:1a -1 2028-02-05 transaction 5514 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2028-02-06 transaction 5515 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2028-02-07 transaction 5516 1f 1 1f:20 -1 2028-02-08 transaction 5517 1f:20:21 1 1f:20:21:22 -1 2028-02-09 transaction 5518 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2028-02-10 transaction 5519 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2028-02-11 transaction 5520 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2028-02-12 transaction 5521 29 1 29:2a -1 2028-02-13 transaction 5522 29:2a:2b 1 29:2a:2b:2c -1 2028-02-14 transaction 5523 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2028-02-15 transaction 5524 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2028-02-16 transaction 5525 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2028-02-17 transaction 5526 33 1 33:34 -1 2028-02-18 transaction 5527 33:34:35 1 33:34:35:36 -1 2028-02-19 transaction 5528 33:34:35:36:37 1 33:34:35:36:37:38 -1 2028-02-20 transaction 5529 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2028-02-21 transaction 5530 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2028-02-22 transaction 5531 3d 1 3d:3e -1 2028-02-23 transaction 5532 3d:3e:3f 1 3d:3e:3f:40 -1 2028-02-24 transaction 5533 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2028-02-25 transaction 5534 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2028-02-26 transaction 5535 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2028-02-27 transaction 5536 47 1 47:48 -1 2028-02-28 transaction 5537 47:48:49 1 47:48:49:4a -1 2028-02-29 transaction 5538 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2028-03-01 transaction 5539 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2028-03-02 transaction 5540 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2028-03-03 transaction 5541 51 1 51:52 -1 2028-03-04 transaction 5542 51:52:53 1 51:52:53:54 -1 2028-03-05 transaction 5543 51:52:53:54:55 1 51:52:53:54:55:56 -1 2028-03-06 transaction 5544 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2028-03-07 transaction 5545 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2028-03-08 transaction 5546 5b 1 5b:5c -1 2028-03-09 transaction 5547 5b:5c:5d 1 5b:5c:5d:5e -1 2028-03-10 transaction 5548 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2028-03-11 transaction 5549 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2028-03-12 transaction 5550 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2028-03-13 transaction 5551 65 1 65:66 -1 2028-03-14 transaction 5552 65:66:67 1 65:66:67:68 -1 2028-03-15 transaction 5553 65:66:67:68:69 1 65:66:67:68:69:6a -1 2028-03-16 transaction 5554 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2028-03-17 transaction 5555 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2028-03-18 transaction 5556 6f 1 6f:70 -1 2028-03-19 transaction 5557 6f:70:71 1 6f:70:71:72 -1 2028-03-20 transaction 5558 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2028-03-21 transaction 5559 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2028-03-22 transaction 5560 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2028-03-23 transaction 5561 79 1 79:7a -1 2028-03-24 transaction 5562 79:7a:7b 1 79:7a:7b:7c -1 2028-03-25 transaction 5563 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2028-03-26 transaction 5564 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2028-03-27 transaction 5565 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2028-03-28 transaction 5566 83 1 83:84 -1 2028-03-29 transaction 5567 83:84:85 1 83:84:85:86 -1 2028-03-30 transaction 5568 83:84:85:86:87 1 83:84:85:86:87:88 -1 2028-03-31 transaction 5569 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2028-04-01 transaction 5570 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2028-04-02 transaction 5571 8d 1 8d:8e -1 2028-04-03 transaction 5572 8d:8e:8f 1 8d:8e:8f:90 -1 2028-04-04 transaction 5573 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2028-04-05 transaction 5574 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2028-04-06 transaction 5575 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2028-04-07 transaction 5576 97 1 97:98 -1 2028-04-08 transaction 5577 97:98:99 1 97:98:99:9a -1 2028-04-09 transaction 5578 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2028-04-10 transaction 5579 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2028-04-11 transaction 5580 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2028-04-12 transaction 5581 a1 1 a1:a2 -1 2028-04-13 transaction 5582 a1:a2:a3 1 a1:a2:a3:a4 -1 2028-04-14 transaction 5583 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2028-04-15 transaction 5584 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2028-04-16 transaction 5585 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2028-04-17 transaction 5586 ab 1 ab:ac -1 2028-04-18 transaction 5587 ab:ac:ad 1 ab:ac:ad:ae -1 2028-04-19 transaction 5588 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2028-04-20 transaction 5589 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2028-04-21 transaction 5590 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2028-04-22 transaction 5591 b5 1 b5:b6 -1 2028-04-23 transaction 5592 b5:b6:b7 1 b5:b6:b7:b8 -1 2028-04-24 transaction 5593 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2028-04-25 transaction 5594 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2028-04-26 transaction 5595 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2028-04-27 transaction 5596 bf 1 bf:c0 -1 2028-04-28 transaction 5597 bf:c0:c1 1 bf:c0:c1:c2 -1 2028-04-29 transaction 5598 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2028-04-30 transaction 5599 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2028-05-01 transaction 5600 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2028-05-02 transaction 5601 c9 1 c9:ca -1 2028-05-03 transaction 5602 c9:ca:cb 1 c9:ca:cb:cc -1 2028-05-04 transaction 5603 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2028-05-05 transaction 5604 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2028-05-06 transaction 5605 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2028-05-07 transaction 5606 d3 1 d3:d4 -1 2028-05-08 transaction 5607 d3:d4:d5 1 d3:d4:d5:d6 -1 2028-05-09 transaction 5608 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2028-05-10 transaction 5609 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2028-05-11 transaction 5610 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2028-05-12 transaction 5611 dd 1 dd:de -1 2028-05-13 transaction 5612 dd:de:df 1 dd:de:df:e0 -1 2028-05-14 transaction 5613 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2028-05-15 transaction 5614 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2028-05-16 transaction 5615 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2028-05-17 transaction 5616 e7 1 e7:e8 -1 2028-05-18 transaction 5617 e7:e8:e9 1 e7:e8:e9:ea -1 2028-05-19 transaction 5618 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2028-05-20 transaction 5619 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2028-05-21 transaction 5620 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2028-05-22 transaction 5621 f1 1 f1:f2 -1 2028-05-23 transaction 5622 f1:f2:f3 1 f1:f2:f3:f4 -1 2028-05-24 transaction 5623 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2028-05-25 transaction 5624 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2028-05-26 transaction 5625 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2028-05-27 transaction 5626 fb 1 fb:fc -1 2028-05-28 transaction 5627 fb:fc:fd 1 fb:fc:fd:fe -1 2028-05-29 transaction 5628 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2028-05-30 transaction 5629 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2028-05-31 transaction 5630 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2028-06-01 transaction 5631 105 1 105:106 -1 2028-06-02 transaction 5632 105:106:107 1 105:106:107:108 -1 2028-06-03 transaction 5633 105:106:107:108:109 1 105:106:107:108:109:10a -1 2028-06-04 transaction 5634 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2028-06-05 transaction 5635 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2028-06-06 transaction 5636 10f 1 10f:110 -1 2028-06-07 transaction 5637 10f:110:111 1 10f:110:111:112 -1 2028-06-08 transaction 5638 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2028-06-09 transaction 5639 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2028-06-10 transaction 5640 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2028-06-11 transaction 5641 119 1 119:11a -1 2028-06-12 transaction 5642 119:11a:11b 1 119:11a:11b:11c -1 2028-06-13 transaction 5643 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2028-06-14 transaction 5644 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2028-06-15 transaction 5645 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2028-06-16 transaction 5646 123 1 123:124 -1 2028-06-17 transaction 5647 123:124:125 1 123:124:125:126 -1 2028-06-18 transaction 5648 123:124:125:126:127 1 123:124:125:126:127:128 -1 2028-06-19 transaction 5649 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2028-06-20 transaction 5650 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2028-06-21 transaction 5651 12d 1 12d:12e -1 2028-06-22 transaction 5652 12d:12e:12f 1 12d:12e:12f:130 -1 2028-06-23 transaction 5653 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2028-06-24 transaction 5654 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2028-06-25 transaction 5655 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2028-06-26 transaction 5656 137 1 137:138 -1 2028-06-27 transaction 5657 137:138:139 1 137:138:139:13a -1 2028-06-28 transaction 5658 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2028-06-29 transaction 5659 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2028-06-30 transaction 5660 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2028-07-01 transaction 5661 141 1 141:142 -1 2028-07-02 transaction 5662 141:142:143 1 141:142:143:144 -1 2028-07-03 transaction 5663 141:142:143:144:145 1 141:142:143:144:145:146 -1 2028-07-04 transaction 5664 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2028-07-05 transaction 5665 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2028-07-06 transaction 5666 14b 1 14b:14c -1 2028-07-07 transaction 5667 14b:14c:14d 1 14b:14c:14d:14e -1 2028-07-08 transaction 5668 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2028-07-09 transaction 5669 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2028-07-10 transaction 5670 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2028-07-11 transaction 5671 155 1 155:156 -1 2028-07-12 transaction 5672 155:156:157 1 155:156:157:158 -1 2028-07-13 transaction 5673 155:156:157:158:159 1 155:156:157:158:159:15a -1 2028-07-14 transaction 5674 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2028-07-15 transaction 5675 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2028-07-16 transaction 5676 15f 1 15f:160 -1 2028-07-17 transaction 5677 15f:160:161 1 15f:160:161:162 -1 2028-07-18 transaction 5678 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2028-07-19 transaction 5679 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2028-07-20 transaction 5680 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2028-07-21 transaction 5681 169 1 169:16a -1 2028-07-22 transaction 5682 169:16a:16b 1 169:16a:16b:16c -1 2028-07-23 transaction 5683 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2028-07-24 transaction 5684 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2028-07-25 transaction 5685 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2028-07-26 transaction 5686 173 1 173:174 -1 2028-07-27 transaction 5687 173:174:175 1 173:174:175:176 -1 2028-07-28 transaction 5688 173:174:175:176:177 1 173:174:175:176:177:178 -1 2028-07-29 transaction 5689 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2028-07-30 transaction 5690 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2028-07-31 transaction 5691 17d 1 17d:17e -1 2028-08-01 transaction 5692 17d:17e:17f 1 17d:17e:17f:180 -1 2028-08-02 transaction 5693 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2028-08-03 transaction 5694 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2028-08-04 transaction 5695 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2028-08-05 transaction 5696 187 1 187:188 -1 2028-08-06 transaction 5697 187:188:189 1 187:188:189:18a -1 2028-08-07 transaction 5698 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2028-08-08 transaction 5699 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2028-08-09 transaction 5700 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2028-08-10 transaction 5701 191 1 191:192 -1 2028-08-11 transaction 5702 191:192:193 1 191:192:193:194 -1 2028-08-12 transaction 5703 191:192:193:194:195 1 191:192:193:194:195:196 -1 2028-08-13 transaction 5704 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2028-08-14 transaction 5705 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2028-08-15 transaction 5706 19b 1 19b:19c -1 2028-08-16 transaction 5707 19b:19c:19d 1 19b:19c:19d:19e -1 2028-08-17 transaction 5708 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2028-08-18 transaction 5709 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2028-08-19 transaction 5710 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2028-08-20 transaction 5711 1a5 1 1a5:1a6 -1 2028-08-21 transaction 5712 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2028-08-22 transaction 5713 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2028-08-23 transaction 5714 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2028-08-24 transaction 5715 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2028-08-25 transaction 5716 1af 1 1af:1b0 -1 2028-08-26 transaction 5717 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2028-08-27 transaction 5718 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2028-08-28 transaction 5719 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2028-08-29 transaction 5720 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2028-08-30 transaction 5721 1b9 1 1b9:1ba -1 2028-08-31 transaction 5722 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2028-09-01 transaction 5723 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2028-09-02 transaction 5724 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2028-09-03 transaction 5725 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2028-09-04 transaction 5726 1c3 1 1c3:1c4 -1 2028-09-05 transaction 5727 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2028-09-06 transaction 5728 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2028-09-07 transaction 5729 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2028-09-08 transaction 5730 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2028-09-09 transaction 5731 1cd 1 1cd:1ce -1 2028-09-10 transaction 5732 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2028-09-11 transaction 5733 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2028-09-12 transaction 5734 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2028-09-13 transaction 5735 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2028-09-14 transaction 5736 1d7 1 1d7:1d8 -1 2028-09-15 transaction 5737 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2028-09-16 transaction 5738 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2028-09-17 transaction 5739 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2028-09-18 transaction 5740 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2028-09-19 transaction 5741 1e1 1 1e1:1e2 -1 2028-09-20 transaction 5742 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2028-09-21 transaction 5743 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2028-09-22 transaction 5744 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2028-09-23 transaction 5745 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2028-09-24 transaction 5746 1eb 1 1eb:1ec -1 2028-09-25 transaction 5747 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2028-09-26 transaction 5748 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2028-09-27 transaction 5749 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2028-09-28 transaction 5750 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2028-09-29 transaction 5751 1f5 1 1f5:1f6 -1 2028-09-30 transaction 5752 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2028-10-01 transaction 5753 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2028-10-02 transaction 5754 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2028-10-03 transaction 5755 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2028-10-04 transaction 5756 1ff 1 1ff:200 -1 2028-10-05 transaction 5757 1ff:200:201 1 1ff:200:201:202 -1 2028-10-06 transaction 5758 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2028-10-07 transaction 5759 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2028-10-08 transaction 5760 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2028-10-09 transaction 5761 209 1 209:20a -1 2028-10-10 transaction 5762 209:20a:20b 1 209:20a:20b:20c -1 2028-10-11 transaction 5763 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2028-10-12 transaction 5764 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2028-10-13 transaction 5765 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2028-10-14 transaction 5766 213 1 213:214 -1 2028-10-15 transaction 5767 213:214:215 1 213:214:215:216 -1 2028-10-16 transaction 5768 213:214:215:216:217 1 213:214:215:216:217:218 -1 2028-10-17 transaction 5769 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2028-10-18 transaction 5770 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2028-10-19 transaction 5771 21d 1 21d:21e -1 2028-10-20 transaction 5772 21d:21e:21f 1 21d:21e:21f:220 -1 2028-10-21 transaction 5773 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2028-10-22 transaction 5774 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2028-10-23 transaction 5775 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2028-10-24 transaction 5776 227 1 227:228 -1 2028-10-25 transaction 5777 227:228:229 1 227:228:229:22a -1 2028-10-26 transaction 5778 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2028-10-27 transaction 5779 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2028-10-28 transaction 5780 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2028-10-29 transaction 5781 231 1 231:232 -1 2028-10-30 transaction 5782 231:232:233 1 231:232:233:234 -1 2028-10-31 transaction 5783 231:232:233:234:235 1 231:232:233:234:235:236 -1 2028-11-01 transaction 5784 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2028-11-02 transaction 5785 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2028-11-03 transaction 5786 23b 1 23b:23c -1 2028-11-04 transaction 5787 23b:23c:23d 1 23b:23c:23d:23e -1 2028-11-05 transaction 5788 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2028-11-06 transaction 5789 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2028-11-07 transaction 5790 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2028-11-08 transaction 5791 245 1 245:246 -1 2028-11-09 transaction 5792 245:246:247 1 245:246:247:248 -1 2028-11-10 transaction 5793 245:246:247:248:249 1 245:246:247:248:249:24a -1 2028-11-11 transaction 5794 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2028-11-12 transaction 5795 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2028-11-13 transaction 5796 24f 1 24f:250 -1 2028-11-14 transaction 5797 24f:250:251 1 24f:250:251:252 -1 2028-11-15 transaction 5798 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2028-11-16 transaction 5799 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2028-11-17 transaction 5800 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2028-11-18 transaction 5801 259 1 259:25a -1 2028-11-19 transaction 5802 259:25a:25b 1 259:25a:25b:25c -1 2028-11-20 transaction 5803 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2028-11-21 transaction 5804 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2028-11-22 transaction 5805 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2028-11-23 transaction 5806 263 1 263:264 -1 2028-11-24 transaction 5807 263:264:265 1 263:264:265:266 -1 2028-11-25 transaction 5808 263:264:265:266:267 1 263:264:265:266:267:268 -1 2028-11-26 transaction 5809 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2028-11-27 transaction 5810 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2028-11-28 transaction 5811 26d 1 26d:26e -1 2028-11-29 transaction 5812 26d:26e:26f 1 26d:26e:26f:270 -1 2028-11-30 transaction 5813 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2028-12-01 transaction 5814 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2028-12-02 transaction 5815 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2028-12-03 transaction 5816 277 1 277:278 -1 2028-12-04 transaction 5817 277:278:279 1 277:278:279:27a -1 2028-12-05 transaction 5818 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2028-12-06 transaction 5819 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2028-12-07 transaction 5820 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2028-12-08 transaction 5821 281 1 281:282 -1 2028-12-09 transaction 5822 281:282:283 1 281:282:283:284 -1 2028-12-10 transaction 5823 281:282:283:284:285 1 281:282:283:284:285:286 -1 2028-12-11 transaction 5824 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2028-12-12 transaction 5825 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2028-12-13 transaction 5826 28b 1 28b:28c -1 2028-12-14 transaction 5827 28b:28c:28d 1 28b:28c:28d:28e -1 2028-12-15 transaction 5828 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2028-12-16 transaction 5829 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2028-12-17 transaction 5830 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2028-12-18 transaction 5831 295 1 295:296 -1 2028-12-19 transaction 5832 295:296:297 1 295:296:297:298 -1 2028-12-20 transaction 5833 295:296:297:298:299 1 295:296:297:298:299:29a -1 2028-12-21 transaction 5834 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2028-12-22 transaction 5835 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2028-12-23 transaction 5836 29f 1 29f:2a0 -1 2028-12-24 transaction 5837 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2028-12-25 transaction 5838 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2028-12-26 transaction 5839 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2028-12-27 transaction 5840 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2028-12-28 transaction 5841 2a9 1 2a9:2aa -1 2028-12-29 transaction 5842 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2028-12-30 transaction 5843 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2028-12-31 transaction 5844 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2029-01-01 transaction 5845 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2029-01-02 transaction 5846 2b3 1 2b3:2b4 -1 2029-01-03 transaction 5847 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2029-01-04 transaction 5848 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2029-01-05 transaction 5849 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2029-01-06 transaction 5850 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2029-01-07 transaction 5851 2bd 1 2bd:2be -1 2029-01-08 transaction 5852 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2029-01-09 transaction 5853 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2029-01-10 transaction 5854 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2029-01-11 transaction 5855 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2029-01-12 transaction 5856 2c7 1 2c7:2c8 -1 2029-01-13 transaction 5857 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2029-01-14 transaction 5858 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2029-01-15 transaction 5859 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2029-01-16 transaction 5860 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2029-01-17 transaction 5861 2d1 1 2d1:2d2 -1 2029-01-18 transaction 5862 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2029-01-19 transaction 5863 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2029-01-20 transaction 5864 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2029-01-21 transaction 5865 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2029-01-22 transaction 5866 2db 1 2db:2dc -1 2029-01-23 transaction 5867 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2029-01-24 transaction 5868 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2029-01-25 transaction 5869 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2029-01-26 transaction 5870 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2029-01-27 transaction 5871 2e5 1 2e5:2e6 -1 2029-01-28 transaction 5872 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2029-01-29 transaction 5873 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2029-01-30 transaction 5874 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2029-01-31 transaction 5875 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2029-02-01 transaction 5876 2ef 1 2ef:2f0 -1 2029-02-02 transaction 5877 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2029-02-03 transaction 5878 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2029-02-04 transaction 5879 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2029-02-05 transaction 5880 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2029-02-06 transaction 5881 2f9 1 2f9:2fa -1 2029-02-07 transaction 5882 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2029-02-08 transaction 5883 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2029-02-09 transaction 5884 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2029-02-10 transaction 5885 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2029-02-11 transaction 5886 303 1 303:304 -1 2029-02-12 transaction 5887 303:304:305 1 303:304:305:306 -1 2029-02-13 transaction 5888 303:304:305:306:307 1 303:304:305:306:307:308 -1 2029-02-14 transaction 5889 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2029-02-15 transaction 5890 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2029-02-16 transaction 5891 30d 1 30d:30e -1 2029-02-17 transaction 5892 30d:30e:30f 1 30d:30e:30f:310 -1 2029-02-18 transaction 5893 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2029-02-19 transaction 5894 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2029-02-20 transaction 5895 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2029-02-21 transaction 5896 317 1 317:318 -1 2029-02-22 transaction 5897 317:318:319 1 317:318:319:31a -1 2029-02-23 transaction 5898 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2029-02-24 transaction 5899 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2029-02-25 transaction 5900 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2029-02-26 transaction 5901 321 1 321:322 -1 2029-02-27 transaction 5902 321:322:323 1 321:322:323:324 -1 2029-02-28 transaction 5903 321:322:323:324:325 1 321:322:323:324:325:326 -1 2029-03-01 transaction 5904 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2029-03-02 transaction 5905 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2029-03-03 transaction 5906 32b 1 32b:32c -1 2029-03-04 transaction 5907 32b:32c:32d 1 32b:32c:32d:32e -1 2029-03-05 transaction 5908 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2029-03-06 transaction 5909 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2029-03-07 transaction 5910 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2029-03-08 transaction 5911 335 1 335:336 -1 2029-03-09 transaction 5912 335:336:337 1 335:336:337:338 -1 2029-03-10 transaction 5913 335:336:337:338:339 1 335:336:337:338:339:33a -1 2029-03-11 transaction 5914 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2029-03-12 transaction 5915 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2029-03-13 transaction 5916 33f 1 33f:340 -1 2029-03-14 transaction 5917 33f:340:341 1 33f:340:341:342 -1 2029-03-15 transaction 5918 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2029-03-16 transaction 5919 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2029-03-17 transaction 5920 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2029-03-18 transaction 5921 349 1 349:34a -1 2029-03-19 transaction 5922 349:34a:34b 1 349:34a:34b:34c -1 2029-03-20 transaction 5923 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2029-03-21 transaction 5924 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2029-03-22 transaction 5925 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2029-03-23 transaction 5926 353 1 353:354 -1 2029-03-24 transaction 5927 353:354:355 1 353:354:355:356 -1 2029-03-25 transaction 5928 353:354:355:356:357 1 353:354:355:356:357:358 -1 2029-03-26 transaction 5929 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2029-03-27 transaction 5930 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2029-03-28 transaction 5931 35d 1 35d:35e -1 2029-03-29 transaction 5932 35d:35e:35f 1 35d:35e:35f:360 -1 2029-03-30 transaction 5933 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2029-03-31 transaction 5934 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2029-04-01 transaction 5935 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2029-04-02 transaction 5936 367 1 367:368 -1 2029-04-03 transaction 5937 367:368:369 1 367:368:369:36a -1 2029-04-04 transaction 5938 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2029-04-05 transaction 5939 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2029-04-06 transaction 5940 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2029-04-07 transaction 5941 371 1 371:372 -1 2029-04-08 transaction 5942 371:372:373 1 371:372:373:374 -1 2029-04-09 transaction 5943 371:372:373:374:375 1 371:372:373:374:375:376 -1 2029-04-10 transaction 5944 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2029-04-11 transaction 5945 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2029-04-12 transaction 5946 37b 1 37b:37c -1 2029-04-13 transaction 5947 37b:37c:37d 1 37b:37c:37d:37e -1 2029-04-14 transaction 5948 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2029-04-15 transaction 5949 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2029-04-16 transaction 5950 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2029-04-17 transaction 5951 385 1 385:386 -1 2029-04-18 transaction 5952 385:386:387 1 385:386:387:388 -1 2029-04-19 transaction 5953 385:386:387:388:389 1 385:386:387:388:389:38a -1 2029-04-20 transaction 5954 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2029-04-21 transaction 5955 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2029-04-22 transaction 5956 38f 1 38f:390 -1 2029-04-23 transaction 5957 38f:390:391 1 38f:390:391:392 -1 2029-04-24 transaction 5958 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2029-04-25 transaction 5959 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2029-04-26 transaction 5960 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2029-04-27 transaction 5961 399 1 399:39a -1 2029-04-28 transaction 5962 399:39a:39b 1 399:39a:39b:39c -1 2029-04-29 transaction 5963 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2029-04-30 transaction 5964 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2029-05-01 transaction 5965 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2029-05-02 transaction 5966 3a3 1 3a3:3a4 -1 2029-05-03 transaction 5967 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2029-05-04 transaction 5968 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2029-05-05 transaction 5969 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2029-05-06 transaction 5970 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2029-05-07 transaction 5971 3ad 1 3ad:3ae -1 2029-05-08 transaction 5972 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2029-05-09 transaction 5973 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2029-05-10 transaction 5974 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2029-05-11 transaction 5975 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2029-05-12 transaction 5976 3b7 1 3b7:3b8 -1 2029-05-13 transaction 5977 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2029-05-14 transaction 5978 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2029-05-15 transaction 5979 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2029-05-16 transaction 5980 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2029-05-17 transaction 5981 3c1 1 3c1:3c2 -1 2029-05-18 transaction 5982 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2029-05-19 transaction 5983 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2029-05-20 transaction 5984 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2029-05-21 transaction 5985 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2029-05-22 transaction 5986 3cb 1 3cb:3cc -1 2029-05-23 transaction 5987 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2029-05-24 transaction 5988 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2029-05-25 transaction 5989 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2029-05-26 transaction 5990 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2029-05-27 transaction 5991 3d5 1 3d5:3d6 -1 2029-05-28 transaction 5992 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2029-05-29 transaction 5993 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2029-05-30 transaction 5994 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2029-05-31 transaction 5995 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2029-06-01 transaction 5996 3df 1 3df:3e0 -1 2029-06-02 transaction 5997 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2029-06-03 transaction 5998 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2029-06-04 transaction 5999 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2029-06-05 transaction 6000 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2029-06-06 transaction 6001 1 1 1:2 -1 2029-06-07 transaction 6002 1:2:3 1 1:2:3:4 -1 2029-06-08 transaction 6003 1:2:3:4:5 1 1:2:3:4:5:6 -1 2029-06-09 transaction 6004 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2029-06-10 transaction 6005 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2029-06-11 transaction 6006 b 1 b:c -1 2029-06-12 transaction 6007 b:c:d 1 b:c:d:e -1 2029-06-13 transaction 6008 b:c:d:e:f 1 b:c:d:e:f:10 -1 2029-06-14 transaction 6009 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2029-06-15 transaction 6010 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2029-06-16 transaction 6011 15 1 15:16 -1 2029-06-17 transaction 6012 15:16:17 1 15:16:17:18 -1 2029-06-18 transaction 6013 15:16:17:18:19 1 15:16:17:18:19:1a -1 2029-06-19 transaction 6014 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2029-06-20 transaction 6015 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2029-06-21 transaction 6016 1f 1 1f:20 -1 2029-06-22 transaction 6017 1f:20:21 1 1f:20:21:22 -1 2029-06-23 transaction 6018 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2029-06-24 transaction 6019 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2029-06-25 transaction 6020 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2029-06-26 transaction 6021 29 1 29:2a -1 2029-06-27 transaction 6022 29:2a:2b 1 29:2a:2b:2c -1 2029-06-28 transaction 6023 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2029-06-29 transaction 6024 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2029-06-30 transaction 6025 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2029-07-01 transaction 6026 33 1 33:34 -1 2029-07-02 transaction 6027 33:34:35 1 33:34:35:36 -1 2029-07-03 transaction 6028 33:34:35:36:37 1 33:34:35:36:37:38 -1 2029-07-04 transaction 6029 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2029-07-05 transaction 6030 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2029-07-06 transaction 6031 3d 1 3d:3e -1 2029-07-07 transaction 6032 3d:3e:3f 1 3d:3e:3f:40 -1 2029-07-08 transaction 6033 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2029-07-09 transaction 6034 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2029-07-10 transaction 6035 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2029-07-11 transaction 6036 47 1 47:48 -1 2029-07-12 transaction 6037 47:48:49 1 47:48:49:4a -1 2029-07-13 transaction 6038 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2029-07-14 transaction 6039 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2029-07-15 transaction 6040 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2029-07-16 transaction 6041 51 1 51:52 -1 2029-07-17 transaction 6042 51:52:53 1 51:52:53:54 -1 2029-07-18 transaction 6043 51:52:53:54:55 1 51:52:53:54:55:56 -1 2029-07-19 transaction 6044 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2029-07-20 transaction 6045 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2029-07-21 transaction 6046 5b 1 5b:5c -1 2029-07-22 transaction 6047 5b:5c:5d 1 5b:5c:5d:5e -1 2029-07-23 transaction 6048 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2029-07-24 transaction 6049 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2029-07-25 transaction 6050 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2029-07-26 transaction 6051 65 1 65:66 -1 2029-07-27 transaction 6052 65:66:67 1 65:66:67:68 -1 2029-07-28 transaction 6053 65:66:67:68:69 1 65:66:67:68:69:6a -1 2029-07-29 transaction 6054 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2029-07-30 transaction 6055 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2029-07-31 transaction 6056 6f 1 6f:70 -1 2029-08-01 transaction 6057 6f:70:71 1 6f:70:71:72 -1 2029-08-02 transaction 6058 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2029-08-03 transaction 6059 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2029-08-04 transaction 6060 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2029-08-05 transaction 6061 79 1 79:7a -1 2029-08-06 transaction 6062 79:7a:7b 1 79:7a:7b:7c -1 2029-08-07 transaction 6063 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2029-08-08 transaction 6064 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2029-08-09 transaction 6065 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2029-08-10 transaction 6066 83 1 83:84 -1 2029-08-11 transaction 6067 83:84:85 1 83:84:85:86 -1 2029-08-12 transaction 6068 83:84:85:86:87 1 83:84:85:86:87:88 -1 2029-08-13 transaction 6069 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2029-08-14 transaction 6070 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2029-08-15 transaction 6071 8d 1 8d:8e -1 2029-08-16 transaction 6072 8d:8e:8f 1 8d:8e:8f:90 -1 2029-08-17 transaction 6073 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2029-08-18 transaction 6074 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2029-08-19 transaction 6075 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2029-08-20 transaction 6076 97 1 97:98 -1 2029-08-21 transaction 6077 97:98:99 1 97:98:99:9a -1 2029-08-22 transaction 6078 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2029-08-23 transaction 6079 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2029-08-24 transaction 6080 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2029-08-25 transaction 6081 a1 1 a1:a2 -1 2029-08-26 transaction 6082 a1:a2:a3 1 a1:a2:a3:a4 -1 2029-08-27 transaction 6083 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2029-08-28 transaction 6084 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2029-08-29 transaction 6085 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2029-08-30 transaction 6086 ab 1 ab:ac -1 2029-08-31 transaction 6087 ab:ac:ad 1 ab:ac:ad:ae -1 2029-09-01 transaction 6088 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2029-09-02 transaction 6089 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2029-09-03 transaction 6090 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2029-09-04 transaction 6091 b5 1 b5:b6 -1 2029-09-05 transaction 6092 b5:b6:b7 1 b5:b6:b7:b8 -1 2029-09-06 transaction 6093 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2029-09-07 transaction 6094 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2029-09-08 transaction 6095 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2029-09-09 transaction 6096 bf 1 bf:c0 -1 2029-09-10 transaction 6097 bf:c0:c1 1 bf:c0:c1:c2 -1 2029-09-11 transaction 6098 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2029-09-12 transaction 6099 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2029-09-13 transaction 6100 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2029-09-14 transaction 6101 c9 1 c9:ca -1 2029-09-15 transaction 6102 c9:ca:cb 1 c9:ca:cb:cc -1 2029-09-16 transaction 6103 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2029-09-17 transaction 6104 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2029-09-18 transaction 6105 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2029-09-19 transaction 6106 d3 1 d3:d4 -1 2029-09-20 transaction 6107 d3:d4:d5 1 d3:d4:d5:d6 -1 2029-09-21 transaction 6108 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2029-09-22 transaction 6109 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2029-09-23 transaction 6110 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2029-09-24 transaction 6111 dd 1 dd:de -1 2029-09-25 transaction 6112 dd:de:df 1 dd:de:df:e0 -1 2029-09-26 transaction 6113 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2029-09-27 transaction 6114 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2029-09-28 transaction 6115 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2029-09-29 transaction 6116 e7 1 e7:e8 -1 2029-09-30 transaction 6117 e7:e8:e9 1 e7:e8:e9:ea -1 2029-10-01 transaction 6118 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2029-10-02 transaction 6119 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2029-10-03 transaction 6120 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2029-10-04 transaction 6121 f1 1 f1:f2 -1 2029-10-05 transaction 6122 f1:f2:f3 1 f1:f2:f3:f4 -1 2029-10-06 transaction 6123 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2029-10-07 transaction 6124 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2029-10-08 transaction 6125 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2029-10-09 transaction 6126 fb 1 fb:fc -1 2029-10-10 transaction 6127 fb:fc:fd 1 fb:fc:fd:fe -1 2029-10-11 transaction 6128 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2029-10-12 transaction 6129 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2029-10-13 transaction 6130 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2029-10-14 transaction 6131 105 1 105:106 -1 2029-10-15 transaction 6132 105:106:107 1 105:106:107:108 -1 2029-10-16 transaction 6133 105:106:107:108:109 1 105:106:107:108:109:10a -1 2029-10-17 transaction 6134 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2029-10-18 transaction 6135 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2029-10-19 transaction 6136 10f 1 10f:110 -1 2029-10-20 transaction 6137 10f:110:111 1 10f:110:111:112 -1 2029-10-21 transaction 6138 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2029-10-22 transaction 6139 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2029-10-23 transaction 6140 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2029-10-24 transaction 6141 119 1 119:11a -1 2029-10-25 transaction 6142 119:11a:11b 1 119:11a:11b:11c -1 2029-10-26 transaction 6143 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2029-10-27 transaction 6144 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2029-10-28 transaction 6145 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2029-10-29 transaction 6146 123 1 123:124 -1 2029-10-30 transaction 6147 123:124:125 1 123:124:125:126 -1 2029-10-31 transaction 6148 123:124:125:126:127 1 123:124:125:126:127:128 -1 2029-11-01 transaction 6149 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2029-11-02 transaction 6150 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2029-11-03 transaction 6151 12d 1 12d:12e -1 2029-11-04 transaction 6152 12d:12e:12f 1 12d:12e:12f:130 -1 2029-11-05 transaction 6153 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2029-11-06 transaction 6154 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2029-11-07 transaction 6155 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2029-11-08 transaction 6156 137 1 137:138 -1 2029-11-09 transaction 6157 137:138:139 1 137:138:139:13a -1 2029-11-10 transaction 6158 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2029-11-11 transaction 6159 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2029-11-12 transaction 6160 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2029-11-13 transaction 6161 141 1 141:142 -1 2029-11-14 transaction 6162 141:142:143 1 141:142:143:144 -1 2029-11-15 transaction 6163 141:142:143:144:145 1 141:142:143:144:145:146 -1 2029-11-16 transaction 6164 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2029-11-17 transaction 6165 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2029-11-18 transaction 6166 14b 1 14b:14c -1 2029-11-19 transaction 6167 14b:14c:14d 1 14b:14c:14d:14e -1 2029-11-20 transaction 6168 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2029-11-21 transaction 6169 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2029-11-22 transaction 6170 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2029-11-23 transaction 6171 155 1 155:156 -1 2029-11-24 transaction 6172 155:156:157 1 155:156:157:158 -1 2029-11-25 transaction 6173 155:156:157:158:159 1 155:156:157:158:159:15a -1 2029-11-26 transaction 6174 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2029-11-27 transaction 6175 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2029-11-28 transaction 6176 15f 1 15f:160 -1 2029-11-29 transaction 6177 15f:160:161 1 15f:160:161:162 -1 2029-11-30 transaction 6178 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2029-12-01 transaction 6179 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2029-12-02 transaction 6180 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2029-12-03 transaction 6181 169 1 169:16a -1 2029-12-04 transaction 6182 169:16a:16b 1 169:16a:16b:16c -1 2029-12-05 transaction 6183 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2029-12-06 transaction 6184 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2029-12-07 transaction 6185 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2029-12-08 transaction 6186 173 1 173:174 -1 2029-12-09 transaction 6187 173:174:175 1 173:174:175:176 -1 2029-12-10 transaction 6188 173:174:175:176:177 1 173:174:175:176:177:178 -1 2029-12-11 transaction 6189 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2029-12-12 transaction 6190 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2029-12-13 transaction 6191 17d 1 17d:17e -1 2029-12-14 transaction 6192 17d:17e:17f 1 17d:17e:17f:180 -1 2029-12-15 transaction 6193 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2029-12-16 transaction 6194 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2029-12-17 transaction 6195 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2029-12-18 transaction 6196 187 1 187:188 -1 2029-12-19 transaction 6197 187:188:189 1 187:188:189:18a -1 2029-12-20 transaction 6198 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2029-12-21 transaction 6199 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2029-12-22 transaction 6200 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2029-12-23 transaction 6201 191 1 191:192 -1 2029-12-24 transaction 6202 191:192:193 1 191:192:193:194 -1 2029-12-25 transaction 6203 191:192:193:194:195 1 191:192:193:194:195:196 -1 2029-12-26 transaction 6204 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2029-12-27 transaction 6205 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2029-12-28 transaction 6206 19b 1 19b:19c -1 2029-12-29 transaction 6207 19b:19c:19d 1 19b:19c:19d:19e -1 2029-12-30 transaction 6208 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2029-12-31 transaction 6209 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2030-01-01 transaction 6210 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2030-01-02 transaction 6211 1a5 1 1a5:1a6 -1 2030-01-03 transaction 6212 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2030-01-04 transaction 6213 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2030-01-05 transaction 6214 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2030-01-06 transaction 6215 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2030-01-07 transaction 6216 1af 1 1af:1b0 -1 2030-01-08 transaction 6217 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2030-01-09 transaction 6218 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2030-01-10 transaction 6219 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2030-01-11 transaction 6220 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2030-01-12 transaction 6221 1b9 1 1b9:1ba -1 2030-01-13 transaction 6222 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2030-01-14 transaction 6223 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2030-01-15 transaction 6224 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2030-01-16 transaction 6225 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2030-01-17 transaction 6226 1c3 1 1c3:1c4 -1 2030-01-18 transaction 6227 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2030-01-19 transaction 6228 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2030-01-20 transaction 6229 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2030-01-21 transaction 6230 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2030-01-22 transaction 6231 1cd 1 1cd:1ce -1 2030-01-23 transaction 6232 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2030-01-24 transaction 6233 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2030-01-25 transaction 6234 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2030-01-26 transaction 6235 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2030-01-27 transaction 6236 1d7 1 1d7:1d8 -1 2030-01-28 transaction 6237 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2030-01-29 transaction 6238 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2030-01-30 transaction 6239 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2030-01-31 transaction 6240 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2030-02-01 transaction 6241 1e1 1 1e1:1e2 -1 2030-02-02 transaction 6242 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2030-02-03 transaction 6243 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2030-02-04 transaction 6244 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2030-02-05 transaction 6245 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2030-02-06 transaction 6246 1eb 1 1eb:1ec -1 2030-02-07 transaction 6247 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2030-02-08 transaction 6248 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2030-02-09 transaction 6249 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2030-02-10 transaction 6250 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2030-02-11 transaction 6251 1f5 1 1f5:1f6 -1 2030-02-12 transaction 6252 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2030-02-13 transaction 6253 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2030-02-14 transaction 6254 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2030-02-15 transaction 6255 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2030-02-16 transaction 6256 1ff 1 1ff:200 -1 2030-02-17 transaction 6257 1ff:200:201 1 1ff:200:201:202 -1 2030-02-18 transaction 6258 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2030-02-19 transaction 6259 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2030-02-20 transaction 6260 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2030-02-21 transaction 6261 209 1 209:20a -1 2030-02-22 transaction 6262 209:20a:20b 1 209:20a:20b:20c -1 2030-02-23 transaction 6263 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2030-02-24 transaction 6264 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2030-02-25 transaction 6265 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2030-02-26 transaction 6266 213 1 213:214 -1 2030-02-27 transaction 6267 213:214:215 1 213:214:215:216 -1 2030-02-28 transaction 6268 213:214:215:216:217 1 213:214:215:216:217:218 -1 2030-03-01 transaction 6269 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2030-03-02 transaction 6270 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2030-03-03 transaction 6271 21d 1 21d:21e -1 2030-03-04 transaction 6272 21d:21e:21f 1 21d:21e:21f:220 -1 2030-03-05 transaction 6273 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2030-03-06 transaction 6274 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2030-03-07 transaction 6275 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2030-03-08 transaction 6276 227 1 227:228 -1 2030-03-09 transaction 6277 227:228:229 1 227:228:229:22a -1 2030-03-10 transaction 6278 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2030-03-11 transaction 6279 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2030-03-12 transaction 6280 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2030-03-13 transaction 6281 231 1 231:232 -1 2030-03-14 transaction 6282 231:232:233 1 231:232:233:234 -1 2030-03-15 transaction 6283 231:232:233:234:235 1 231:232:233:234:235:236 -1 2030-03-16 transaction 6284 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2030-03-17 transaction 6285 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2030-03-18 transaction 6286 23b 1 23b:23c -1 2030-03-19 transaction 6287 23b:23c:23d 1 23b:23c:23d:23e -1 2030-03-20 transaction 6288 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2030-03-21 transaction 6289 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2030-03-22 transaction 6290 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2030-03-23 transaction 6291 245 1 245:246 -1 2030-03-24 transaction 6292 245:246:247 1 245:246:247:248 -1 2030-03-25 transaction 6293 245:246:247:248:249 1 245:246:247:248:249:24a -1 2030-03-26 transaction 6294 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2030-03-27 transaction 6295 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2030-03-28 transaction 6296 24f 1 24f:250 -1 2030-03-29 transaction 6297 24f:250:251 1 24f:250:251:252 -1 2030-03-30 transaction 6298 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2030-03-31 transaction 6299 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2030-04-01 transaction 6300 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2030-04-02 transaction 6301 259 1 259:25a -1 2030-04-03 transaction 6302 259:25a:25b 1 259:25a:25b:25c -1 2030-04-04 transaction 6303 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2030-04-05 transaction 6304 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2030-04-06 transaction 6305 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2030-04-07 transaction 6306 263 1 263:264 -1 2030-04-08 transaction 6307 263:264:265 1 263:264:265:266 -1 2030-04-09 transaction 6308 263:264:265:266:267 1 263:264:265:266:267:268 -1 2030-04-10 transaction 6309 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2030-04-11 transaction 6310 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2030-04-12 transaction 6311 26d 1 26d:26e -1 2030-04-13 transaction 6312 26d:26e:26f 1 26d:26e:26f:270 -1 2030-04-14 transaction 6313 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2030-04-15 transaction 6314 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2030-04-16 transaction 6315 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2030-04-17 transaction 6316 277 1 277:278 -1 2030-04-18 transaction 6317 277:278:279 1 277:278:279:27a -1 2030-04-19 transaction 6318 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2030-04-20 transaction 6319 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2030-04-21 transaction 6320 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2030-04-22 transaction 6321 281 1 281:282 -1 2030-04-23 transaction 6322 281:282:283 1 281:282:283:284 -1 2030-04-24 transaction 6323 281:282:283:284:285 1 281:282:283:284:285:286 -1 2030-04-25 transaction 6324 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2030-04-26 transaction 6325 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2030-04-27 transaction 6326 28b 1 28b:28c -1 2030-04-28 transaction 6327 28b:28c:28d 1 28b:28c:28d:28e -1 2030-04-29 transaction 6328 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2030-04-30 transaction 6329 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2030-05-01 transaction 6330 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2030-05-02 transaction 6331 295 1 295:296 -1 2030-05-03 transaction 6332 295:296:297 1 295:296:297:298 -1 2030-05-04 transaction 6333 295:296:297:298:299 1 295:296:297:298:299:29a -1 2030-05-05 transaction 6334 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2030-05-06 transaction 6335 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2030-05-07 transaction 6336 29f 1 29f:2a0 -1 2030-05-08 transaction 6337 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2030-05-09 transaction 6338 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2030-05-10 transaction 6339 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2030-05-11 transaction 6340 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2030-05-12 transaction 6341 2a9 1 2a9:2aa -1 2030-05-13 transaction 6342 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2030-05-14 transaction 6343 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2030-05-15 transaction 6344 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2030-05-16 transaction 6345 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2030-05-17 transaction 6346 2b3 1 2b3:2b4 -1 2030-05-18 transaction 6347 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2030-05-19 transaction 6348 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2030-05-20 transaction 6349 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2030-05-21 transaction 6350 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2030-05-22 transaction 6351 2bd 1 2bd:2be -1 2030-05-23 transaction 6352 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2030-05-24 transaction 6353 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2030-05-25 transaction 6354 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2030-05-26 transaction 6355 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2030-05-27 transaction 6356 2c7 1 2c7:2c8 -1 2030-05-28 transaction 6357 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2030-05-29 transaction 6358 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2030-05-30 transaction 6359 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2030-05-31 transaction 6360 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2030-06-01 transaction 6361 2d1 1 2d1:2d2 -1 2030-06-02 transaction 6362 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2030-06-03 transaction 6363 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2030-06-04 transaction 6364 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2030-06-05 transaction 6365 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2030-06-06 transaction 6366 2db 1 2db:2dc -1 2030-06-07 transaction 6367 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2030-06-08 transaction 6368 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2030-06-09 transaction 6369 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2030-06-10 transaction 6370 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2030-06-11 transaction 6371 2e5 1 2e5:2e6 -1 2030-06-12 transaction 6372 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2030-06-13 transaction 6373 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2030-06-14 transaction 6374 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2030-06-15 transaction 6375 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2030-06-16 transaction 6376 2ef 1 2ef:2f0 -1 2030-06-17 transaction 6377 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2030-06-18 transaction 6378 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2030-06-19 transaction 6379 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2030-06-20 transaction 6380 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2030-06-21 transaction 6381 2f9 1 2f9:2fa -1 2030-06-22 transaction 6382 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2030-06-23 transaction 6383 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2030-06-24 transaction 6384 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2030-06-25 transaction 6385 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2030-06-26 transaction 6386 303 1 303:304 -1 2030-06-27 transaction 6387 303:304:305 1 303:304:305:306 -1 2030-06-28 transaction 6388 303:304:305:306:307 1 303:304:305:306:307:308 -1 2030-06-29 transaction 6389 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2030-06-30 transaction 6390 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2030-07-01 transaction 6391 30d 1 30d:30e -1 2030-07-02 transaction 6392 30d:30e:30f 1 30d:30e:30f:310 -1 2030-07-03 transaction 6393 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2030-07-04 transaction 6394 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2030-07-05 transaction 6395 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2030-07-06 transaction 6396 317 1 317:318 -1 2030-07-07 transaction 6397 317:318:319 1 317:318:319:31a -1 2030-07-08 transaction 6398 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2030-07-09 transaction 6399 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2030-07-10 transaction 6400 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2030-07-11 transaction 6401 321 1 321:322 -1 2030-07-12 transaction 6402 321:322:323 1 321:322:323:324 -1 2030-07-13 transaction 6403 321:322:323:324:325 1 321:322:323:324:325:326 -1 2030-07-14 transaction 6404 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2030-07-15 transaction 6405 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2030-07-16 transaction 6406 32b 1 32b:32c -1 2030-07-17 transaction 6407 32b:32c:32d 1 32b:32c:32d:32e -1 2030-07-18 transaction 6408 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2030-07-19 transaction 6409 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2030-07-20 transaction 6410 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2030-07-21 transaction 6411 335 1 335:336 -1 2030-07-22 transaction 6412 335:336:337 1 335:336:337:338 -1 2030-07-23 transaction 6413 335:336:337:338:339 1 335:336:337:338:339:33a -1 2030-07-24 transaction 6414 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2030-07-25 transaction 6415 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2030-07-26 transaction 6416 33f 1 33f:340 -1 2030-07-27 transaction 6417 33f:340:341 1 33f:340:341:342 -1 2030-07-28 transaction 6418 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2030-07-29 transaction 6419 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2030-07-30 transaction 6420 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2030-07-31 transaction 6421 349 1 349:34a -1 2030-08-01 transaction 6422 349:34a:34b 1 349:34a:34b:34c -1 2030-08-02 transaction 6423 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2030-08-03 transaction 6424 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2030-08-04 transaction 6425 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2030-08-05 transaction 6426 353 1 353:354 -1 2030-08-06 transaction 6427 353:354:355 1 353:354:355:356 -1 2030-08-07 transaction 6428 353:354:355:356:357 1 353:354:355:356:357:358 -1 2030-08-08 transaction 6429 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2030-08-09 transaction 6430 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2030-08-10 transaction 6431 35d 1 35d:35e -1 2030-08-11 transaction 6432 35d:35e:35f 1 35d:35e:35f:360 -1 2030-08-12 transaction 6433 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2030-08-13 transaction 6434 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2030-08-14 transaction 6435 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2030-08-15 transaction 6436 367 1 367:368 -1 2030-08-16 transaction 6437 367:368:369 1 367:368:369:36a -1 2030-08-17 transaction 6438 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2030-08-18 transaction 6439 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2030-08-19 transaction 6440 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2030-08-20 transaction 6441 371 1 371:372 -1 2030-08-21 transaction 6442 371:372:373 1 371:372:373:374 -1 2030-08-22 transaction 6443 371:372:373:374:375 1 371:372:373:374:375:376 -1 2030-08-23 transaction 6444 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2030-08-24 transaction 6445 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2030-08-25 transaction 6446 37b 1 37b:37c -1 2030-08-26 transaction 6447 37b:37c:37d 1 37b:37c:37d:37e -1 2030-08-27 transaction 6448 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2030-08-28 transaction 6449 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2030-08-29 transaction 6450 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2030-08-30 transaction 6451 385 1 385:386 -1 2030-08-31 transaction 6452 385:386:387 1 385:386:387:388 -1 2030-09-01 transaction 6453 385:386:387:388:389 1 385:386:387:388:389:38a -1 2030-09-02 transaction 6454 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2030-09-03 transaction 6455 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2030-09-04 transaction 6456 38f 1 38f:390 -1 2030-09-05 transaction 6457 38f:390:391 1 38f:390:391:392 -1 2030-09-06 transaction 6458 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2030-09-07 transaction 6459 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2030-09-08 transaction 6460 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2030-09-09 transaction 6461 399 1 399:39a -1 2030-09-10 transaction 6462 399:39a:39b 1 399:39a:39b:39c -1 2030-09-11 transaction 6463 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2030-09-12 transaction 6464 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2030-09-13 transaction 6465 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2030-09-14 transaction 6466 3a3 1 3a3:3a4 -1 2030-09-15 transaction 6467 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2030-09-16 transaction 6468 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2030-09-17 transaction 6469 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2030-09-18 transaction 6470 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2030-09-19 transaction 6471 3ad 1 3ad:3ae -1 2030-09-20 transaction 6472 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2030-09-21 transaction 6473 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2030-09-22 transaction 6474 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2030-09-23 transaction 6475 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2030-09-24 transaction 6476 3b7 1 3b7:3b8 -1 2030-09-25 transaction 6477 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2030-09-26 transaction 6478 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2030-09-27 transaction 6479 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2030-09-28 transaction 6480 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2030-09-29 transaction 6481 3c1 1 3c1:3c2 -1 2030-09-30 transaction 6482 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2030-10-01 transaction 6483 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2030-10-02 transaction 6484 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2030-10-03 transaction 6485 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2030-10-04 transaction 6486 3cb 1 3cb:3cc -1 2030-10-05 transaction 6487 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2030-10-06 transaction 6488 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2030-10-07 transaction 6489 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2030-10-08 transaction 6490 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2030-10-09 transaction 6491 3d5 1 3d5:3d6 -1 2030-10-10 transaction 6492 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2030-10-11 transaction 6493 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2030-10-12 transaction 6494 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2030-10-13 transaction 6495 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2030-10-14 transaction 6496 3df 1 3df:3e0 -1 2030-10-15 transaction 6497 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2030-10-16 transaction 6498 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2030-10-17 transaction 6499 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2030-10-18 transaction 6500 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2030-10-19 transaction 6501 1 1 1:2 -1 2030-10-20 transaction 6502 1:2:3 1 1:2:3:4 -1 2030-10-21 transaction 6503 1:2:3:4:5 1 1:2:3:4:5:6 -1 2030-10-22 transaction 6504 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2030-10-23 transaction 6505 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2030-10-24 transaction 6506 b 1 b:c -1 2030-10-25 transaction 6507 b:c:d 1 b:c:d:e -1 2030-10-26 transaction 6508 b:c:d:e:f 1 b:c:d:e:f:10 -1 2030-10-27 transaction 6509 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2030-10-28 transaction 6510 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2030-10-29 transaction 6511 15 1 15:16 -1 2030-10-30 transaction 6512 15:16:17 1 15:16:17:18 -1 2030-10-31 transaction 6513 15:16:17:18:19 1 15:16:17:18:19:1a -1 2030-11-01 transaction 6514 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2030-11-02 transaction 6515 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2030-11-03 transaction 6516 1f 1 1f:20 -1 2030-11-04 transaction 6517 1f:20:21 1 1f:20:21:22 -1 2030-11-05 transaction 6518 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2030-11-06 transaction 6519 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2030-11-07 transaction 6520 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2030-11-08 transaction 6521 29 1 29:2a -1 2030-11-09 transaction 6522 29:2a:2b 1 29:2a:2b:2c -1 2030-11-10 transaction 6523 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2030-11-11 transaction 6524 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2030-11-12 transaction 6525 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2030-11-13 transaction 6526 33 1 33:34 -1 2030-11-14 transaction 6527 33:34:35 1 33:34:35:36 -1 2030-11-15 transaction 6528 33:34:35:36:37 1 33:34:35:36:37:38 -1 2030-11-16 transaction 6529 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2030-11-17 transaction 6530 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2030-11-18 transaction 6531 3d 1 3d:3e -1 2030-11-19 transaction 6532 3d:3e:3f 1 3d:3e:3f:40 -1 2030-11-20 transaction 6533 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2030-11-21 transaction 6534 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2030-11-22 transaction 6535 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2030-11-23 transaction 6536 47 1 47:48 -1 2030-11-24 transaction 6537 47:48:49 1 47:48:49:4a -1 2030-11-25 transaction 6538 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2030-11-26 transaction 6539 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2030-11-27 transaction 6540 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2030-11-28 transaction 6541 51 1 51:52 -1 2030-11-29 transaction 6542 51:52:53 1 51:52:53:54 -1 2030-11-30 transaction 6543 51:52:53:54:55 1 51:52:53:54:55:56 -1 2030-12-01 transaction 6544 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2030-12-02 transaction 6545 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2030-12-03 transaction 6546 5b 1 5b:5c -1 2030-12-04 transaction 6547 5b:5c:5d 1 5b:5c:5d:5e -1 2030-12-05 transaction 6548 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2030-12-06 transaction 6549 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2030-12-07 transaction 6550 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2030-12-08 transaction 6551 65 1 65:66 -1 2030-12-09 transaction 6552 65:66:67 1 65:66:67:68 -1 2030-12-10 transaction 6553 65:66:67:68:69 1 65:66:67:68:69:6a -1 2030-12-11 transaction 6554 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2030-12-12 transaction 6555 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2030-12-13 transaction 6556 6f 1 6f:70 -1 2030-12-14 transaction 6557 6f:70:71 1 6f:70:71:72 -1 2030-12-15 transaction 6558 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2030-12-16 transaction 6559 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2030-12-17 transaction 6560 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2030-12-18 transaction 6561 79 1 79:7a -1 2030-12-19 transaction 6562 79:7a:7b 1 79:7a:7b:7c -1 2030-12-20 transaction 6563 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2030-12-21 transaction 6564 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2030-12-22 transaction 6565 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2030-12-23 transaction 6566 83 1 83:84 -1 2030-12-24 transaction 6567 83:84:85 1 83:84:85:86 -1 2030-12-25 transaction 6568 83:84:85:86:87 1 83:84:85:86:87:88 -1 2030-12-26 transaction 6569 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2030-12-27 transaction 6570 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2030-12-28 transaction 6571 8d 1 8d:8e -1 2030-12-29 transaction 6572 8d:8e:8f 1 8d:8e:8f:90 -1 2030-12-30 transaction 6573 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2030-12-31 transaction 6574 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2031-01-01 transaction 6575 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2031-01-02 transaction 6576 97 1 97:98 -1 2031-01-03 transaction 6577 97:98:99 1 97:98:99:9a -1 2031-01-04 transaction 6578 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2031-01-05 transaction 6579 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2031-01-06 transaction 6580 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2031-01-07 transaction 6581 a1 1 a1:a2 -1 2031-01-08 transaction 6582 a1:a2:a3 1 a1:a2:a3:a4 -1 2031-01-09 transaction 6583 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2031-01-10 transaction 6584 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2031-01-11 transaction 6585 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2031-01-12 transaction 6586 ab 1 ab:ac -1 2031-01-13 transaction 6587 ab:ac:ad 1 ab:ac:ad:ae -1 2031-01-14 transaction 6588 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2031-01-15 transaction 6589 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2031-01-16 transaction 6590 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2031-01-17 transaction 6591 b5 1 b5:b6 -1 2031-01-18 transaction 6592 b5:b6:b7 1 b5:b6:b7:b8 -1 2031-01-19 transaction 6593 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2031-01-20 transaction 6594 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2031-01-21 transaction 6595 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2031-01-22 transaction 6596 bf 1 bf:c0 -1 2031-01-23 transaction 6597 bf:c0:c1 1 bf:c0:c1:c2 -1 2031-01-24 transaction 6598 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2031-01-25 transaction 6599 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2031-01-26 transaction 6600 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2031-01-27 transaction 6601 c9 1 c9:ca -1 2031-01-28 transaction 6602 c9:ca:cb 1 c9:ca:cb:cc -1 2031-01-29 transaction 6603 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2031-01-30 transaction 6604 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2031-01-31 transaction 6605 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2031-02-01 transaction 6606 d3 1 d3:d4 -1 2031-02-02 transaction 6607 d3:d4:d5 1 d3:d4:d5:d6 -1 2031-02-03 transaction 6608 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2031-02-04 transaction 6609 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2031-02-05 transaction 6610 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2031-02-06 transaction 6611 dd 1 dd:de -1 2031-02-07 transaction 6612 dd:de:df 1 dd:de:df:e0 -1 2031-02-08 transaction 6613 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2031-02-09 transaction 6614 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2031-02-10 transaction 6615 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2031-02-11 transaction 6616 e7 1 e7:e8 -1 2031-02-12 transaction 6617 e7:e8:e9 1 e7:e8:e9:ea -1 2031-02-13 transaction 6618 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2031-02-14 transaction 6619 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2031-02-15 transaction 6620 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2031-02-16 transaction 6621 f1 1 f1:f2 -1 2031-02-17 transaction 6622 f1:f2:f3 1 f1:f2:f3:f4 -1 2031-02-18 transaction 6623 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2031-02-19 transaction 6624 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2031-02-20 transaction 6625 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2031-02-21 transaction 6626 fb 1 fb:fc -1 2031-02-22 transaction 6627 fb:fc:fd 1 fb:fc:fd:fe -1 2031-02-23 transaction 6628 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2031-02-24 transaction 6629 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2031-02-25 transaction 6630 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2031-02-26 transaction 6631 105 1 105:106 -1 2031-02-27 transaction 6632 105:106:107 1 105:106:107:108 -1 2031-02-28 transaction 6633 105:106:107:108:109 1 105:106:107:108:109:10a -1 2031-03-01 transaction 6634 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2031-03-02 transaction 6635 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2031-03-03 transaction 6636 10f 1 10f:110 -1 2031-03-04 transaction 6637 10f:110:111 1 10f:110:111:112 -1 2031-03-05 transaction 6638 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2031-03-06 transaction 6639 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2031-03-07 transaction 6640 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2031-03-08 transaction 6641 119 1 119:11a -1 2031-03-09 transaction 6642 119:11a:11b 1 119:11a:11b:11c -1 2031-03-10 transaction 6643 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2031-03-11 transaction 6644 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2031-03-12 transaction 6645 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2031-03-13 transaction 6646 123 1 123:124 -1 2031-03-14 transaction 6647 123:124:125 1 123:124:125:126 -1 2031-03-15 transaction 6648 123:124:125:126:127 1 123:124:125:126:127:128 -1 2031-03-16 transaction 6649 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2031-03-17 transaction 6650 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2031-03-18 transaction 6651 12d 1 12d:12e -1 2031-03-19 transaction 6652 12d:12e:12f 1 12d:12e:12f:130 -1 2031-03-20 transaction 6653 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2031-03-21 transaction 6654 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2031-03-22 transaction 6655 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2031-03-23 transaction 6656 137 1 137:138 -1 2031-03-24 transaction 6657 137:138:139 1 137:138:139:13a -1 2031-03-25 transaction 6658 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2031-03-26 transaction 6659 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2031-03-27 transaction 6660 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2031-03-28 transaction 6661 141 1 141:142 -1 2031-03-29 transaction 6662 141:142:143 1 141:142:143:144 -1 2031-03-30 transaction 6663 141:142:143:144:145 1 141:142:143:144:145:146 -1 2031-03-31 transaction 6664 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2031-04-01 transaction 6665 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2031-04-02 transaction 6666 14b 1 14b:14c -1 2031-04-03 transaction 6667 14b:14c:14d 1 14b:14c:14d:14e -1 2031-04-04 transaction 6668 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2031-04-05 transaction 6669 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2031-04-06 transaction 6670 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2031-04-07 transaction 6671 155 1 155:156 -1 2031-04-08 transaction 6672 155:156:157 1 155:156:157:158 -1 2031-04-09 transaction 6673 155:156:157:158:159 1 155:156:157:158:159:15a -1 2031-04-10 transaction 6674 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2031-04-11 transaction 6675 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2031-04-12 transaction 6676 15f 1 15f:160 -1 2031-04-13 transaction 6677 15f:160:161 1 15f:160:161:162 -1 2031-04-14 transaction 6678 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2031-04-15 transaction 6679 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2031-04-16 transaction 6680 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2031-04-17 transaction 6681 169 1 169:16a -1 2031-04-18 transaction 6682 169:16a:16b 1 169:16a:16b:16c -1 2031-04-19 transaction 6683 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2031-04-20 transaction 6684 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2031-04-21 transaction 6685 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2031-04-22 transaction 6686 173 1 173:174 -1 2031-04-23 transaction 6687 173:174:175 1 173:174:175:176 -1 2031-04-24 transaction 6688 173:174:175:176:177 1 173:174:175:176:177:178 -1 2031-04-25 transaction 6689 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2031-04-26 transaction 6690 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2031-04-27 transaction 6691 17d 1 17d:17e -1 2031-04-28 transaction 6692 17d:17e:17f 1 17d:17e:17f:180 -1 2031-04-29 transaction 6693 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2031-04-30 transaction 6694 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2031-05-01 transaction 6695 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2031-05-02 transaction 6696 187 1 187:188 -1 2031-05-03 transaction 6697 187:188:189 1 187:188:189:18a -1 2031-05-04 transaction 6698 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2031-05-05 transaction 6699 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2031-05-06 transaction 6700 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2031-05-07 transaction 6701 191 1 191:192 -1 2031-05-08 transaction 6702 191:192:193 1 191:192:193:194 -1 2031-05-09 transaction 6703 191:192:193:194:195 1 191:192:193:194:195:196 -1 2031-05-10 transaction 6704 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2031-05-11 transaction 6705 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2031-05-12 transaction 6706 19b 1 19b:19c -1 2031-05-13 transaction 6707 19b:19c:19d 1 19b:19c:19d:19e -1 2031-05-14 transaction 6708 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2031-05-15 transaction 6709 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2031-05-16 transaction 6710 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2031-05-17 transaction 6711 1a5 1 1a5:1a6 -1 2031-05-18 transaction 6712 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2031-05-19 transaction 6713 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2031-05-20 transaction 6714 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2031-05-21 transaction 6715 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2031-05-22 transaction 6716 1af 1 1af:1b0 -1 2031-05-23 transaction 6717 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2031-05-24 transaction 6718 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2031-05-25 transaction 6719 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2031-05-26 transaction 6720 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2031-05-27 transaction 6721 1b9 1 1b9:1ba -1 2031-05-28 transaction 6722 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2031-05-29 transaction 6723 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2031-05-30 transaction 6724 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2031-05-31 transaction 6725 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2031-06-01 transaction 6726 1c3 1 1c3:1c4 -1 2031-06-02 transaction 6727 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2031-06-03 transaction 6728 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2031-06-04 transaction 6729 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2031-06-05 transaction 6730 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2031-06-06 transaction 6731 1cd 1 1cd:1ce -1 2031-06-07 transaction 6732 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2031-06-08 transaction 6733 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2031-06-09 transaction 6734 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2031-06-10 transaction 6735 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2031-06-11 transaction 6736 1d7 1 1d7:1d8 -1 2031-06-12 transaction 6737 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2031-06-13 transaction 6738 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2031-06-14 transaction 6739 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2031-06-15 transaction 6740 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2031-06-16 transaction 6741 1e1 1 1e1:1e2 -1 2031-06-17 transaction 6742 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2031-06-18 transaction 6743 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2031-06-19 transaction 6744 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2031-06-20 transaction 6745 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2031-06-21 transaction 6746 1eb 1 1eb:1ec -1 2031-06-22 transaction 6747 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2031-06-23 transaction 6748 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2031-06-24 transaction 6749 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2031-06-25 transaction 6750 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2031-06-26 transaction 6751 1f5 1 1f5:1f6 -1 2031-06-27 transaction 6752 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2031-06-28 transaction 6753 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2031-06-29 transaction 6754 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2031-06-30 transaction 6755 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2031-07-01 transaction 6756 1ff 1 1ff:200 -1 2031-07-02 transaction 6757 1ff:200:201 1 1ff:200:201:202 -1 2031-07-03 transaction 6758 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2031-07-04 transaction 6759 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2031-07-05 transaction 6760 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2031-07-06 transaction 6761 209 1 209:20a -1 2031-07-07 transaction 6762 209:20a:20b 1 209:20a:20b:20c -1 2031-07-08 transaction 6763 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2031-07-09 transaction 6764 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2031-07-10 transaction 6765 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2031-07-11 transaction 6766 213 1 213:214 -1 2031-07-12 transaction 6767 213:214:215 1 213:214:215:216 -1 2031-07-13 transaction 6768 213:214:215:216:217 1 213:214:215:216:217:218 -1 2031-07-14 transaction 6769 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2031-07-15 transaction 6770 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2031-07-16 transaction 6771 21d 1 21d:21e -1 2031-07-17 transaction 6772 21d:21e:21f 1 21d:21e:21f:220 -1 2031-07-18 transaction 6773 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2031-07-19 transaction 6774 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2031-07-20 transaction 6775 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2031-07-21 transaction 6776 227 1 227:228 -1 2031-07-22 transaction 6777 227:228:229 1 227:228:229:22a -1 2031-07-23 transaction 6778 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2031-07-24 transaction 6779 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2031-07-25 transaction 6780 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2031-07-26 transaction 6781 231 1 231:232 -1 2031-07-27 transaction 6782 231:232:233 1 231:232:233:234 -1 2031-07-28 transaction 6783 231:232:233:234:235 1 231:232:233:234:235:236 -1 2031-07-29 transaction 6784 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2031-07-30 transaction 6785 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2031-07-31 transaction 6786 23b 1 23b:23c -1 2031-08-01 transaction 6787 23b:23c:23d 1 23b:23c:23d:23e -1 2031-08-02 transaction 6788 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2031-08-03 transaction 6789 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2031-08-04 transaction 6790 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2031-08-05 transaction 6791 245 1 245:246 -1 2031-08-06 transaction 6792 245:246:247 1 245:246:247:248 -1 2031-08-07 transaction 6793 245:246:247:248:249 1 245:246:247:248:249:24a -1 2031-08-08 transaction 6794 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2031-08-09 transaction 6795 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2031-08-10 transaction 6796 24f 1 24f:250 -1 2031-08-11 transaction 6797 24f:250:251 1 24f:250:251:252 -1 2031-08-12 transaction 6798 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2031-08-13 transaction 6799 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2031-08-14 transaction 6800 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2031-08-15 transaction 6801 259 1 259:25a -1 2031-08-16 transaction 6802 259:25a:25b 1 259:25a:25b:25c -1 2031-08-17 transaction 6803 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2031-08-18 transaction 6804 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2031-08-19 transaction 6805 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2031-08-20 transaction 6806 263 1 263:264 -1 2031-08-21 transaction 6807 263:264:265 1 263:264:265:266 -1 2031-08-22 transaction 6808 263:264:265:266:267 1 263:264:265:266:267:268 -1 2031-08-23 transaction 6809 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2031-08-24 transaction 6810 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2031-08-25 transaction 6811 26d 1 26d:26e -1 2031-08-26 transaction 6812 26d:26e:26f 1 26d:26e:26f:270 -1 2031-08-27 transaction 6813 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2031-08-28 transaction 6814 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2031-08-29 transaction 6815 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2031-08-30 transaction 6816 277 1 277:278 -1 2031-08-31 transaction 6817 277:278:279 1 277:278:279:27a -1 2031-09-01 transaction 6818 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2031-09-02 transaction 6819 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2031-09-03 transaction 6820 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2031-09-04 transaction 6821 281 1 281:282 -1 2031-09-05 transaction 6822 281:282:283 1 281:282:283:284 -1 2031-09-06 transaction 6823 281:282:283:284:285 1 281:282:283:284:285:286 -1 2031-09-07 transaction 6824 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2031-09-08 transaction 6825 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2031-09-09 transaction 6826 28b 1 28b:28c -1 2031-09-10 transaction 6827 28b:28c:28d 1 28b:28c:28d:28e -1 2031-09-11 transaction 6828 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2031-09-12 transaction 6829 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2031-09-13 transaction 6830 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2031-09-14 transaction 6831 295 1 295:296 -1 2031-09-15 transaction 6832 295:296:297 1 295:296:297:298 -1 2031-09-16 transaction 6833 295:296:297:298:299 1 295:296:297:298:299:29a -1 2031-09-17 transaction 6834 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2031-09-18 transaction 6835 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2031-09-19 transaction 6836 29f 1 29f:2a0 -1 2031-09-20 transaction 6837 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2031-09-21 transaction 6838 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2031-09-22 transaction 6839 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2031-09-23 transaction 6840 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2031-09-24 transaction 6841 2a9 1 2a9:2aa -1 2031-09-25 transaction 6842 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2031-09-26 transaction 6843 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2031-09-27 transaction 6844 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2031-09-28 transaction 6845 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2031-09-29 transaction 6846 2b3 1 2b3:2b4 -1 2031-09-30 transaction 6847 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2031-10-01 transaction 6848 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2031-10-02 transaction 6849 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2031-10-03 transaction 6850 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2031-10-04 transaction 6851 2bd 1 2bd:2be -1 2031-10-05 transaction 6852 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2031-10-06 transaction 6853 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2031-10-07 transaction 6854 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2031-10-08 transaction 6855 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2031-10-09 transaction 6856 2c7 1 2c7:2c8 -1 2031-10-10 transaction 6857 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2031-10-11 transaction 6858 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2031-10-12 transaction 6859 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2031-10-13 transaction 6860 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2031-10-14 transaction 6861 2d1 1 2d1:2d2 -1 2031-10-15 transaction 6862 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2031-10-16 transaction 6863 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2031-10-17 transaction 6864 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2031-10-18 transaction 6865 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2031-10-19 transaction 6866 2db 1 2db:2dc -1 2031-10-20 transaction 6867 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2031-10-21 transaction 6868 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2031-10-22 transaction 6869 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2031-10-23 transaction 6870 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2031-10-24 transaction 6871 2e5 1 2e5:2e6 -1 2031-10-25 transaction 6872 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2031-10-26 transaction 6873 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2031-10-27 transaction 6874 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2031-10-28 transaction 6875 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2031-10-29 transaction 6876 2ef 1 2ef:2f0 -1 2031-10-30 transaction 6877 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2031-10-31 transaction 6878 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2031-11-01 transaction 6879 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2031-11-02 transaction 6880 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2031-11-03 transaction 6881 2f9 1 2f9:2fa -1 2031-11-04 transaction 6882 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2031-11-05 transaction 6883 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2031-11-06 transaction 6884 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2031-11-07 transaction 6885 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2031-11-08 transaction 6886 303 1 303:304 -1 2031-11-09 transaction 6887 303:304:305 1 303:304:305:306 -1 2031-11-10 transaction 6888 303:304:305:306:307 1 303:304:305:306:307:308 -1 2031-11-11 transaction 6889 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2031-11-12 transaction 6890 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2031-11-13 transaction 6891 30d 1 30d:30e -1 2031-11-14 transaction 6892 30d:30e:30f 1 30d:30e:30f:310 -1 2031-11-15 transaction 6893 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2031-11-16 transaction 6894 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2031-11-17 transaction 6895 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2031-11-18 transaction 6896 317 1 317:318 -1 2031-11-19 transaction 6897 317:318:319 1 317:318:319:31a -1 2031-11-20 transaction 6898 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2031-11-21 transaction 6899 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2031-11-22 transaction 6900 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2031-11-23 transaction 6901 321 1 321:322 -1 2031-11-24 transaction 6902 321:322:323 1 321:322:323:324 -1 2031-11-25 transaction 6903 321:322:323:324:325 1 321:322:323:324:325:326 -1 2031-11-26 transaction 6904 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2031-11-27 transaction 6905 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2031-11-28 transaction 6906 32b 1 32b:32c -1 2031-11-29 transaction 6907 32b:32c:32d 1 32b:32c:32d:32e -1 2031-11-30 transaction 6908 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2031-12-01 transaction 6909 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2031-12-02 transaction 6910 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2031-12-03 transaction 6911 335 1 335:336 -1 2031-12-04 transaction 6912 335:336:337 1 335:336:337:338 -1 2031-12-05 transaction 6913 335:336:337:338:339 1 335:336:337:338:339:33a -1 2031-12-06 transaction 6914 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2031-12-07 transaction 6915 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2031-12-08 transaction 6916 33f 1 33f:340 -1 2031-12-09 transaction 6917 33f:340:341 1 33f:340:341:342 -1 2031-12-10 transaction 6918 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2031-12-11 transaction 6919 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2031-12-12 transaction 6920 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2031-12-13 transaction 6921 349 1 349:34a -1 2031-12-14 transaction 6922 349:34a:34b 1 349:34a:34b:34c -1 2031-12-15 transaction 6923 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2031-12-16 transaction 6924 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2031-12-17 transaction 6925 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2031-12-18 transaction 6926 353 1 353:354 -1 2031-12-19 transaction 6927 353:354:355 1 353:354:355:356 -1 2031-12-20 transaction 6928 353:354:355:356:357 1 353:354:355:356:357:358 -1 2031-12-21 transaction 6929 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2031-12-22 transaction 6930 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2031-12-23 transaction 6931 35d 1 35d:35e -1 2031-12-24 transaction 6932 35d:35e:35f 1 35d:35e:35f:360 -1 2031-12-25 transaction 6933 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2031-12-26 transaction 6934 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2031-12-27 transaction 6935 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2031-12-28 transaction 6936 367 1 367:368 -1 2031-12-29 transaction 6937 367:368:369 1 367:368:369:36a -1 2031-12-30 transaction 6938 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2031-12-31 transaction 6939 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2032-01-01 transaction 6940 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2032-01-02 transaction 6941 371 1 371:372 -1 2032-01-03 transaction 6942 371:372:373 1 371:372:373:374 -1 2032-01-04 transaction 6943 371:372:373:374:375 1 371:372:373:374:375:376 -1 2032-01-05 transaction 6944 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2032-01-06 transaction 6945 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2032-01-07 transaction 6946 37b 1 37b:37c -1 2032-01-08 transaction 6947 37b:37c:37d 1 37b:37c:37d:37e -1 2032-01-09 transaction 6948 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2032-01-10 transaction 6949 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2032-01-11 transaction 6950 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2032-01-12 transaction 6951 385 1 385:386 -1 2032-01-13 transaction 6952 385:386:387 1 385:386:387:388 -1 2032-01-14 transaction 6953 385:386:387:388:389 1 385:386:387:388:389:38a -1 2032-01-15 transaction 6954 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2032-01-16 transaction 6955 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2032-01-17 transaction 6956 38f 1 38f:390 -1 2032-01-18 transaction 6957 38f:390:391 1 38f:390:391:392 -1 2032-01-19 transaction 6958 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2032-01-20 transaction 6959 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2032-01-21 transaction 6960 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2032-01-22 transaction 6961 399 1 399:39a -1 2032-01-23 transaction 6962 399:39a:39b 1 399:39a:39b:39c -1 2032-01-24 transaction 6963 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2032-01-25 transaction 6964 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2032-01-26 transaction 6965 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2032-01-27 transaction 6966 3a3 1 3a3:3a4 -1 2032-01-28 transaction 6967 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2032-01-29 transaction 6968 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2032-01-30 transaction 6969 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2032-01-31 transaction 6970 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2032-02-01 transaction 6971 3ad 1 3ad:3ae -1 2032-02-02 transaction 6972 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2032-02-03 transaction 6973 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2032-02-04 transaction 6974 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2032-02-05 transaction 6975 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2032-02-06 transaction 6976 3b7 1 3b7:3b8 -1 2032-02-07 transaction 6977 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2032-02-08 transaction 6978 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2032-02-09 transaction 6979 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2032-02-10 transaction 6980 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2032-02-11 transaction 6981 3c1 1 3c1:3c2 -1 2032-02-12 transaction 6982 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2032-02-13 transaction 6983 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2032-02-14 transaction 6984 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2032-02-15 transaction 6985 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2032-02-16 transaction 6986 3cb 1 3cb:3cc -1 2032-02-17 transaction 6987 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2032-02-18 transaction 6988 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2032-02-19 transaction 6989 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2032-02-20 transaction 6990 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2032-02-21 transaction 6991 3d5 1 3d5:3d6 -1 2032-02-22 transaction 6992 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2032-02-23 transaction 6993 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2032-02-24 transaction 6994 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2032-02-25 transaction 6995 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2032-02-26 transaction 6996 3df 1 3df:3e0 -1 2032-02-27 transaction 6997 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2032-02-28 transaction 6998 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2032-02-29 transaction 6999 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2032-03-01 transaction 7000 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2032-03-02 transaction 7001 1 1 1:2 -1 2032-03-03 transaction 7002 1:2:3 1 1:2:3:4 -1 2032-03-04 transaction 7003 1:2:3:4:5 1 1:2:3:4:5:6 -1 2032-03-05 transaction 7004 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2032-03-06 transaction 7005 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2032-03-07 transaction 7006 b 1 b:c -1 2032-03-08 transaction 7007 b:c:d 1 b:c:d:e -1 2032-03-09 transaction 7008 b:c:d:e:f 1 b:c:d:e:f:10 -1 2032-03-10 transaction 7009 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2032-03-11 transaction 7010 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2032-03-12 transaction 7011 15 1 15:16 -1 2032-03-13 transaction 7012 15:16:17 1 15:16:17:18 -1 2032-03-14 transaction 7013 15:16:17:18:19 1 15:16:17:18:19:1a -1 2032-03-15 transaction 7014 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2032-03-16 transaction 7015 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2032-03-17 transaction 7016 1f 1 1f:20 -1 2032-03-18 transaction 7017 1f:20:21 1 1f:20:21:22 -1 2032-03-19 transaction 7018 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2032-03-20 transaction 7019 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2032-03-21 transaction 7020 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2032-03-22 transaction 7021 29 1 29:2a -1 2032-03-23 transaction 7022 29:2a:2b 1 29:2a:2b:2c -1 2032-03-24 transaction 7023 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2032-03-25 transaction 7024 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2032-03-26 transaction 7025 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2032-03-27 transaction 7026 33 1 33:34 -1 2032-03-28 transaction 7027 33:34:35 1 33:34:35:36 -1 2032-03-29 transaction 7028 33:34:35:36:37 1 33:34:35:36:37:38 -1 2032-03-30 transaction 7029 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2032-03-31 transaction 7030 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2032-04-01 transaction 7031 3d 1 3d:3e -1 2032-04-02 transaction 7032 3d:3e:3f 1 3d:3e:3f:40 -1 2032-04-03 transaction 7033 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2032-04-04 transaction 7034 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2032-04-05 transaction 7035 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2032-04-06 transaction 7036 47 1 47:48 -1 2032-04-07 transaction 7037 47:48:49 1 47:48:49:4a -1 2032-04-08 transaction 7038 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2032-04-09 transaction 7039 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2032-04-10 transaction 7040 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2032-04-11 transaction 7041 51 1 51:52 -1 2032-04-12 transaction 7042 51:52:53 1 51:52:53:54 -1 2032-04-13 transaction 7043 51:52:53:54:55 1 51:52:53:54:55:56 -1 2032-04-14 transaction 7044 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2032-04-15 transaction 7045 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2032-04-16 transaction 7046 5b 1 5b:5c -1 2032-04-17 transaction 7047 5b:5c:5d 1 5b:5c:5d:5e -1 2032-04-18 transaction 7048 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2032-04-19 transaction 7049 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2032-04-20 transaction 7050 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2032-04-21 transaction 7051 65 1 65:66 -1 2032-04-22 transaction 7052 65:66:67 1 65:66:67:68 -1 2032-04-23 transaction 7053 65:66:67:68:69 1 65:66:67:68:69:6a -1 2032-04-24 transaction 7054 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2032-04-25 transaction 7055 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2032-04-26 transaction 7056 6f 1 6f:70 -1 2032-04-27 transaction 7057 6f:70:71 1 6f:70:71:72 -1 2032-04-28 transaction 7058 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2032-04-29 transaction 7059 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2032-04-30 transaction 7060 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2032-05-01 transaction 7061 79 1 79:7a -1 2032-05-02 transaction 7062 79:7a:7b 1 79:7a:7b:7c -1 2032-05-03 transaction 7063 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2032-05-04 transaction 7064 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2032-05-05 transaction 7065 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2032-05-06 transaction 7066 83 1 83:84 -1 2032-05-07 transaction 7067 83:84:85 1 83:84:85:86 -1 2032-05-08 transaction 7068 83:84:85:86:87 1 83:84:85:86:87:88 -1 2032-05-09 transaction 7069 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2032-05-10 transaction 7070 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2032-05-11 transaction 7071 8d 1 8d:8e -1 2032-05-12 transaction 7072 8d:8e:8f 1 8d:8e:8f:90 -1 2032-05-13 transaction 7073 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2032-05-14 transaction 7074 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2032-05-15 transaction 7075 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2032-05-16 transaction 7076 97 1 97:98 -1 2032-05-17 transaction 7077 97:98:99 1 97:98:99:9a -1 2032-05-18 transaction 7078 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2032-05-19 transaction 7079 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2032-05-20 transaction 7080 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2032-05-21 transaction 7081 a1 1 a1:a2 -1 2032-05-22 transaction 7082 a1:a2:a3 1 a1:a2:a3:a4 -1 2032-05-23 transaction 7083 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2032-05-24 transaction 7084 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2032-05-25 transaction 7085 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2032-05-26 transaction 7086 ab 1 ab:ac -1 2032-05-27 transaction 7087 ab:ac:ad 1 ab:ac:ad:ae -1 2032-05-28 transaction 7088 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2032-05-29 transaction 7089 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2032-05-30 transaction 7090 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2032-05-31 transaction 7091 b5 1 b5:b6 -1 2032-06-01 transaction 7092 b5:b6:b7 1 b5:b6:b7:b8 -1 2032-06-02 transaction 7093 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2032-06-03 transaction 7094 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2032-06-04 transaction 7095 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2032-06-05 transaction 7096 bf 1 bf:c0 -1 2032-06-06 transaction 7097 bf:c0:c1 1 bf:c0:c1:c2 -1 2032-06-07 transaction 7098 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2032-06-08 transaction 7099 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2032-06-09 transaction 7100 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2032-06-10 transaction 7101 c9 1 c9:ca -1 2032-06-11 transaction 7102 c9:ca:cb 1 c9:ca:cb:cc -1 2032-06-12 transaction 7103 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2032-06-13 transaction 7104 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2032-06-14 transaction 7105 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2032-06-15 transaction 7106 d3 1 d3:d4 -1 2032-06-16 transaction 7107 d3:d4:d5 1 d3:d4:d5:d6 -1 2032-06-17 transaction 7108 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2032-06-18 transaction 7109 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2032-06-19 transaction 7110 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2032-06-20 transaction 7111 dd 1 dd:de -1 2032-06-21 transaction 7112 dd:de:df 1 dd:de:df:e0 -1 2032-06-22 transaction 7113 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2032-06-23 transaction 7114 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2032-06-24 transaction 7115 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2032-06-25 transaction 7116 e7 1 e7:e8 -1 2032-06-26 transaction 7117 e7:e8:e9 1 e7:e8:e9:ea -1 2032-06-27 transaction 7118 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2032-06-28 transaction 7119 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2032-06-29 transaction 7120 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2032-06-30 transaction 7121 f1 1 f1:f2 -1 2032-07-01 transaction 7122 f1:f2:f3 1 f1:f2:f3:f4 -1 2032-07-02 transaction 7123 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2032-07-03 transaction 7124 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2032-07-04 transaction 7125 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2032-07-05 transaction 7126 fb 1 fb:fc -1 2032-07-06 transaction 7127 fb:fc:fd 1 fb:fc:fd:fe -1 2032-07-07 transaction 7128 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2032-07-08 transaction 7129 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2032-07-09 transaction 7130 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2032-07-10 transaction 7131 105 1 105:106 -1 2032-07-11 transaction 7132 105:106:107 1 105:106:107:108 -1 2032-07-12 transaction 7133 105:106:107:108:109 1 105:106:107:108:109:10a -1 2032-07-13 transaction 7134 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2032-07-14 transaction 7135 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2032-07-15 transaction 7136 10f 1 10f:110 -1 2032-07-16 transaction 7137 10f:110:111 1 10f:110:111:112 -1 2032-07-17 transaction 7138 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2032-07-18 transaction 7139 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2032-07-19 transaction 7140 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2032-07-20 transaction 7141 119 1 119:11a -1 2032-07-21 transaction 7142 119:11a:11b 1 119:11a:11b:11c -1 2032-07-22 transaction 7143 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2032-07-23 transaction 7144 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2032-07-24 transaction 7145 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2032-07-25 transaction 7146 123 1 123:124 -1 2032-07-26 transaction 7147 123:124:125 1 123:124:125:126 -1 2032-07-27 transaction 7148 123:124:125:126:127 1 123:124:125:126:127:128 -1 2032-07-28 transaction 7149 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2032-07-29 transaction 7150 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2032-07-30 transaction 7151 12d 1 12d:12e -1 2032-07-31 transaction 7152 12d:12e:12f 1 12d:12e:12f:130 -1 2032-08-01 transaction 7153 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2032-08-02 transaction 7154 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2032-08-03 transaction 7155 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2032-08-04 transaction 7156 137 1 137:138 -1 2032-08-05 transaction 7157 137:138:139 1 137:138:139:13a -1 2032-08-06 transaction 7158 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2032-08-07 transaction 7159 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2032-08-08 transaction 7160 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2032-08-09 transaction 7161 141 1 141:142 -1 2032-08-10 transaction 7162 141:142:143 1 141:142:143:144 -1 2032-08-11 transaction 7163 141:142:143:144:145 1 141:142:143:144:145:146 -1 2032-08-12 transaction 7164 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2032-08-13 transaction 7165 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2032-08-14 transaction 7166 14b 1 14b:14c -1 2032-08-15 transaction 7167 14b:14c:14d 1 14b:14c:14d:14e -1 2032-08-16 transaction 7168 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2032-08-17 transaction 7169 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2032-08-18 transaction 7170 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2032-08-19 transaction 7171 155 1 155:156 -1 2032-08-20 transaction 7172 155:156:157 1 155:156:157:158 -1 2032-08-21 transaction 7173 155:156:157:158:159 1 155:156:157:158:159:15a -1 2032-08-22 transaction 7174 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2032-08-23 transaction 7175 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2032-08-24 transaction 7176 15f 1 15f:160 -1 2032-08-25 transaction 7177 15f:160:161 1 15f:160:161:162 -1 2032-08-26 transaction 7178 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2032-08-27 transaction 7179 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2032-08-28 transaction 7180 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2032-08-29 transaction 7181 169 1 169:16a -1 2032-08-30 transaction 7182 169:16a:16b 1 169:16a:16b:16c -1 2032-08-31 transaction 7183 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2032-09-01 transaction 7184 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2032-09-02 transaction 7185 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2032-09-03 transaction 7186 173 1 173:174 -1 2032-09-04 transaction 7187 173:174:175 1 173:174:175:176 -1 2032-09-05 transaction 7188 173:174:175:176:177 1 173:174:175:176:177:178 -1 2032-09-06 transaction 7189 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2032-09-07 transaction 7190 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2032-09-08 transaction 7191 17d 1 17d:17e -1 2032-09-09 transaction 7192 17d:17e:17f 1 17d:17e:17f:180 -1 2032-09-10 transaction 7193 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2032-09-11 transaction 7194 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2032-09-12 transaction 7195 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2032-09-13 transaction 7196 187 1 187:188 -1 2032-09-14 transaction 7197 187:188:189 1 187:188:189:18a -1 2032-09-15 transaction 7198 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2032-09-16 transaction 7199 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2032-09-17 transaction 7200 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2032-09-18 transaction 7201 191 1 191:192 -1 2032-09-19 transaction 7202 191:192:193 1 191:192:193:194 -1 2032-09-20 transaction 7203 191:192:193:194:195 1 191:192:193:194:195:196 -1 2032-09-21 transaction 7204 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2032-09-22 transaction 7205 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2032-09-23 transaction 7206 19b 1 19b:19c -1 2032-09-24 transaction 7207 19b:19c:19d 1 19b:19c:19d:19e -1 2032-09-25 transaction 7208 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2032-09-26 transaction 7209 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2032-09-27 transaction 7210 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2032-09-28 transaction 7211 1a5 1 1a5:1a6 -1 2032-09-29 transaction 7212 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2032-09-30 transaction 7213 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2032-10-01 transaction 7214 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2032-10-02 transaction 7215 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2032-10-03 transaction 7216 1af 1 1af:1b0 -1 2032-10-04 transaction 7217 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2032-10-05 transaction 7218 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2032-10-06 transaction 7219 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2032-10-07 transaction 7220 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2032-10-08 transaction 7221 1b9 1 1b9:1ba -1 2032-10-09 transaction 7222 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2032-10-10 transaction 7223 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2032-10-11 transaction 7224 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2032-10-12 transaction 7225 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2032-10-13 transaction 7226 1c3 1 1c3:1c4 -1 2032-10-14 transaction 7227 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2032-10-15 transaction 7228 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2032-10-16 transaction 7229 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2032-10-17 transaction 7230 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2032-10-18 transaction 7231 1cd 1 1cd:1ce -1 2032-10-19 transaction 7232 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2032-10-20 transaction 7233 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2032-10-21 transaction 7234 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2032-10-22 transaction 7235 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2032-10-23 transaction 7236 1d7 1 1d7:1d8 -1 2032-10-24 transaction 7237 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2032-10-25 transaction 7238 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2032-10-26 transaction 7239 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2032-10-27 transaction 7240 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2032-10-28 transaction 7241 1e1 1 1e1:1e2 -1 2032-10-29 transaction 7242 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2032-10-30 transaction 7243 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2032-10-31 transaction 7244 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2032-11-01 transaction 7245 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2032-11-02 transaction 7246 1eb 1 1eb:1ec -1 2032-11-03 transaction 7247 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2032-11-04 transaction 7248 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2032-11-05 transaction 7249 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2032-11-06 transaction 7250 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2032-11-07 transaction 7251 1f5 1 1f5:1f6 -1 2032-11-08 transaction 7252 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2032-11-09 transaction 7253 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2032-11-10 transaction 7254 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2032-11-11 transaction 7255 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2032-11-12 transaction 7256 1ff 1 1ff:200 -1 2032-11-13 transaction 7257 1ff:200:201 1 1ff:200:201:202 -1 2032-11-14 transaction 7258 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2032-11-15 transaction 7259 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2032-11-16 transaction 7260 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2032-11-17 transaction 7261 209 1 209:20a -1 2032-11-18 transaction 7262 209:20a:20b 1 209:20a:20b:20c -1 2032-11-19 transaction 7263 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2032-11-20 transaction 7264 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2032-11-21 transaction 7265 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2032-11-22 transaction 7266 213 1 213:214 -1 2032-11-23 transaction 7267 213:214:215 1 213:214:215:216 -1 2032-11-24 transaction 7268 213:214:215:216:217 1 213:214:215:216:217:218 -1 2032-11-25 transaction 7269 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2032-11-26 transaction 7270 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2032-11-27 transaction 7271 21d 1 21d:21e -1 2032-11-28 transaction 7272 21d:21e:21f 1 21d:21e:21f:220 -1 2032-11-29 transaction 7273 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2032-11-30 transaction 7274 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2032-12-01 transaction 7275 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2032-12-02 transaction 7276 227 1 227:228 -1 2032-12-03 transaction 7277 227:228:229 1 227:228:229:22a -1 2032-12-04 transaction 7278 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2032-12-05 transaction 7279 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2032-12-06 transaction 7280 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2032-12-07 transaction 7281 231 1 231:232 -1 2032-12-08 transaction 7282 231:232:233 1 231:232:233:234 -1 2032-12-09 transaction 7283 231:232:233:234:235 1 231:232:233:234:235:236 -1 2032-12-10 transaction 7284 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2032-12-11 transaction 7285 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2032-12-12 transaction 7286 23b 1 23b:23c -1 2032-12-13 transaction 7287 23b:23c:23d 1 23b:23c:23d:23e -1 2032-12-14 transaction 7288 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2032-12-15 transaction 7289 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2032-12-16 transaction 7290 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2032-12-17 transaction 7291 245 1 245:246 -1 2032-12-18 transaction 7292 245:246:247 1 245:246:247:248 -1 2032-12-19 transaction 7293 245:246:247:248:249 1 245:246:247:248:249:24a -1 2032-12-20 transaction 7294 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2032-12-21 transaction 7295 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2032-12-22 transaction 7296 24f 1 24f:250 -1 2032-12-23 transaction 7297 24f:250:251 1 24f:250:251:252 -1 2032-12-24 transaction 7298 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2032-12-25 transaction 7299 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2032-12-26 transaction 7300 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2032-12-27 transaction 7301 259 1 259:25a -1 2032-12-28 transaction 7302 259:25a:25b 1 259:25a:25b:25c -1 2032-12-29 transaction 7303 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2032-12-30 transaction 7304 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2032-12-31 transaction 7305 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2033-01-01 transaction 7306 263 1 263:264 -1 2033-01-02 transaction 7307 263:264:265 1 263:264:265:266 -1 2033-01-03 transaction 7308 263:264:265:266:267 1 263:264:265:266:267:268 -1 2033-01-04 transaction 7309 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2033-01-05 transaction 7310 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2033-01-06 transaction 7311 26d 1 26d:26e -1 2033-01-07 transaction 7312 26d:26e:26f 1 26d:26e:26f:270 -1 2033-01-08 transaction 7313 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2033-01-09 transaction 7314 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2033-01-10 transaction 7315 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2033-01-11 transaction 7316 277 1 277:278 -1 2033-01-12 transaction 7317 277:278:279 1 277:278:279:27a -1 2033-01-13 transaction 7318 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2033-01-14 transaction 7319 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2033-01-15 transaction 7320 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2033-01-16 transaction 7321 281 1 281:282 -1 2033-01-17 transaction 7322 281:282:283 1 281:282:283:284 -1 2033-01-18 transaction 7323 281:282:283:284:285 1 281:282:283:284:285:286 -1 2033-01-19 transaction 7324 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2033-01-20 transaction 7325 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2033-01-21 transaction 7326 28b 1 28b:28c -1 2033-01-22 transaction 7327 28b:28c:28d 1 28b:28c:28d:28e -1 2033-01-23 transaction 7328 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2033-01-24 transaction 7329 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2033-01-25 transaction 7330 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2033-01-26 transaction 7331 295 1 295:296 -1 2033-01-27 transaction 7332 295:296:297 1 295:296:297:298 -1 2033-01-28 transaction 7333 295:296:297:298:299 1 295:296:297:298:299:29a -1 2033-01-29 transaction 7334 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2033-01-30 transaction 7335 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2033-01-31 transaction 7336 29f 1 29f:2a0 -1 2033-02-01 transaction 7337 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2033-02-02 transaction 7338 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2033-02-03 transaction 7339 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2033-02-04 transaction 7340 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2033-02-05 transaction 7341 2a9 1 2a9:2aa -1 2033-02-06 transaction 7342 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2033-02-07 transaction 7343 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2033-02-08 transaction 7344 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2033-02-09 transaction 7345 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2033-02-10 transaction 7346 2b3 1 2b3:2b4 -1 2033-02-11 transaction 7347 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2033-02-12 transaction 7348 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2033-02-13 transaction 7349 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2033-02-14 transaction 7350 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2033-02-15 transaction 7351 2bd 1 2bd:2be -1 2033-02-16 transaction 7352 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2033-02-17 transaction 7353 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2033-02-18 transaction 7354 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2033-02-19 transaction 7355 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2033-02-20 transaction 7356 2c7 1 2c7:2c8 -1 2033-02-21 transaction 7357 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2033-02-22 transaction 7358 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2033-02-23 transaction 7359 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2033-02-24 transaction 7360 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2033-02-25 transaction 7361 2d1 1 2d1:2d2 -1 2033-02-26 transaction 7362 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2033-02-27 transaction 7363 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2033-02-28 transaction 7364 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2033-03-01 transaction 7365 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2033-03-02 transaction 7366 2db 1 2db:2dc -1 2033-03-03 transaction 7367 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2033-03-04 transaction 7368 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2033-03-05 transaction 7369 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2033-03-06 transaction 7370 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2033-03-07 transaction 7371 2e5 1 2e5:2e6 -1 2033-03-08 transaction 7372 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2033-03-09 transaction 7373 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2033-03-10 transaction 7374 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2033-03-11 transaction 7375 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2033-03-12 transaction 7376 2ef 1 2ef:2f0 -1 2033-03-13 transaction 7377 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2033-03-14 transaction 7378 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2033-03-15 transaction 7379 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2033-03-16 transaction 7380 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2033-03-17 transaction 7381 2f9 1 2f9:2fa -1 2033-03-18 transaction 7382 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2033-03-19 transaction 7383 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2033-03-20 transaction 7384 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2033-03-21 transaction 7385 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2033-03-22 transaction 7386 303 1 303:304 -1 2033-03-23 transaction 7387 303:304:305 1 303:304:305:306 -1 2033-03-24 transaction 7388 303:304:305:306:307 1 303:304:305:306:307:308 -1 2033-03-25 transaction 7389 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2033-03-26 transaction 7390 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2033-03-27 transaction 7391 30d 1 30d:30e -1 2033-03-28 transaction 7392 30d:30e:30f 1 30d:30e:30f:310 -1 2033-03-29 transaction 7393 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2033-03-30 transaction 7394 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2033-03-31 transaction 7395 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2033-04-01 transaction 7396 317 1 317:318 -1 2033-04-02 transaction 7397 317:318:319 1 317:318:319:31a -1 2033-04-03 transaction 7398 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2033-04-04 transaction 7399 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2033-04-05 transaction 7400 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2033-04-06 transaction 7401 321 1 321:322 -1 2033-04-07 transaction 7402 321:322:323 1 321:322:323:324 -1 2033-04-08 transaction 7403 321:322:323:324:325 1 321:322:323:324:325:326 -1 2033-04-09 transaction 7404 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2033-04-10 transaction 7405 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2033-04-11 transaction 7406 32b 1 32b:32c -1 2033-04-12 transaction 7407 32b:32c:32d 1 32b:32c:32d:32e -1 2033-04-13 transaction 7408 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2033-04-14 transaction 7409 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2033-04-15 transaction 7410 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2033-04-16 transaction 7411 335 1 335:336 -1 2033-04-17 transaction 7412 335:336:337 1 335:336:337:338 -1 2033-04-18 transaction 7413 335:336:337:338:339 1 335:336:337:338:339:33a -1 2033-04-19 transaction 7414 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2033-04-20 transaction 7415 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2033-04-21 transaction 7416 33f 1 33f:340 -1 2033-04-22 transaction 7417 33f:340:341 1 33f:340:341:342 -1 2033-04-23 transaction 7418 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2033-04-24 transaction 7419 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2033-04-25 transaction 7420 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2033-04-26 transaction 7421 349 1 349:34a -1 2033-04-27 transaction 7422 349:34a:34b 1 349:34a:34b:34c -1 2033-04-28 transaction 7423 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2033-04-29 transaction 7424 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2033-04-30 transaction 7425 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2033-05-01 transaction 7426 353 1 353:354 -1 2033-05-02 transaction 7427 353:354:355 1 353:354:355:356 -1 2033-05-03 transaction 7428 353:354:355:356:357 1 353:354:355:356:357:358 -1 2033-05-04 transaction 7429 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2033-05-05 transaction 7430 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2033-05-06 transaction 7431 35d 1 35d:35e -1 2033-05-07 transaction 7432 35d:35e:35f 1 35d:35e:35f:360 -1 2033-05-08 transaction 7433 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2033-05-09 transaction 7434 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2033-05-10 transaction 7435 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2033-05-11 transaction 7436 367 1 367:368 -1 2033-05-12 transaction 7437 367:368:369 1 367:368:369:36a -1 2033-05-13 transaction 7438 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2033-05-14 transaction 7439 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2033-05-15 transaction 7440 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2033-05-16 transaction 7441 371 1 371:372 -1 2033-05-17 transaction 7442 371:372:373 1 371:372:373:374 -1 2033-05-18 transaction 7443 371:372:373:374:375 1 371:372:373:374:375:376 -1 2033-05-19 transaction 7444 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2033-05-20 transaction 7445 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2033-05-21 transaction 7446 37b 1 37b:37c -1 2033-05-22 transaction 7447 37b:37c:37d 1 37b:37c:37d:37e -1 2033-05-23 transaction 7448 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2033-05-24 transaction 7449 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2033-05-25 transaction 7450 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2033-05-26 transaction 7451 385 1 385:386 -1 2033-05-27 transaction 7452 385:386:387 1 385:386:387:388 -1 2033-05-28 transaction 7453 385:386:387:388:389 1 385:386:387:388:389:38a -1 2033-05-29 transaction 7454 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2033-05-30 transaction 7455 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2033-05-31 transaction 7456 38f 1 38f:390 -1 2033-06-01 transaction 7457 38f:390:391 1 38f:390:391:392 -1 2033-06-02 transaction 7458 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2033-06-03 transaction 7459 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2033-06-04 transaction 7460 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2033-06-05 transaction 7461 399 1 399:39a -1 2033-06-06 transaction 7462 399:39a:39b 1 399:39a:39b:39c -1 2033-06-07 transaction 7463 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2033-06-08 transaction 7464 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2033-06-09 transaction 7465 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2033-06-10 transaction 7466 3a3 1 3a3:3a4 -1 2033-06-11 transaction 7467 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2033-06-12 transaction 7468 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2033-06-13 transaction 7469 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2033-06-14 transaction 7470 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2033-06-15 transaction 7471 3ad 1 3ad:3ae -1 2033-06-16 transaction 7472 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2033-06-17 transaction 7473 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2033-06-18 transaction 7474 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2033-06-19 transaction 7475 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2033-06-20 transaction 7476 3b7 1 3b7:3b8 -1 2033-06-21 transaction 7477 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2033-06-22 transaction 7478 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2033-06-23 transaction 7479 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2033-06-24 transaction 7480 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2033-06-25 transaction 7481 3c1 1 3c1:3c2 -1 2033-06-26 transaction 7482 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2033-06-27 transaction 7483 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2033-06-28 transaction 7484 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2033-06-29 transaction 7485 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2033-06-30 transaction 7486 3cb 1 3cb:3cc -1 2033-07-01 transaction 7487 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2033-07-02 transaction 7488 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2033-07-03 transaction 7489 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2033-07-04 transaction 7490 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2033-07-05 transaction 7491 3d5 1 3d5:3d6 -1 2033-07-06 transaction 7492 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2033-07-07 transaction 7493 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2033-07-08 transaction 7494 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2033-07-09 transaction 7495 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2033-07-10 transaction 7496 3df 1 3df:3e0 -1 2033-07-11 transaction 7497 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2033-07-12 transaction 7498 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2033-07-13 transaction 7499 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2033-07-14 transaction 7500 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2033-07-15 transaction 7501 1 1 1:2 -1 2033-07-16 transaction 7502 1:2:3 1 1:2:3:4 -1 2033-07-17 transaction 7503 1:2:3:4:5 1 1:2:3:4:5:6 -1 2033-07-18 transaction 7504 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2033-07-19 transaction 7505 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2033-07-20 transaction 7506 b 1 b:c -1 2033-07-21 transaction 7507 b:c:d 1 b:c:d:e -1 2033-07-22 transaction 7508 b:c:d:e:f 1 b:c:d:e:f:10 -1 2033-07-23 transaction 7509 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2033-07-24 transaction 7510 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2033-07-25 transaction 7511 15 1 15:16 -1 2033-07-26 transaction 7512 15:16:17 1 15:16:17:18 -1 2033-07-27 transaction 7513 15:16:17:18:19 1 15:16:17:18:19:1a -1 2033-07-28 transaction 7514 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2033-07-29 transaction 7515 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2033-07-30 transaction 7516 1f 1 1f:20 -1 2033-07-31 transaction 7517 1f:20:21 1 1f:20:21:22 -1 2033-08-01 transaction 7518 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2033-08-02 transaction 7519 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2033-08-03 transaction 7520 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2033-08-04 transaction 7521 29 1 29:2a -1 2033-08-05 transaction 7522 29:2a:2b 1 29:2a:2b:2c -1 2033-08-06 transaction 7523 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2033-08-07 transaction 7524 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2033-08-08 transaction 7525 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2033-08-09 transaction 7526 33 1 33:34 -1 2033-08-10 transaction 7527 33:34:35 1 33:34:35:36 -1 2033-08-11 transaction 7528 33:34:35:36:37 1 33:34:35:36:37:38 -1 2033-08-12 transaction 7529 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2033-08-13 transaction 7530 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2033-08-14 transaction 7531 3d 1 3d:3e -1 2033-08-15 transaction 7532 3d:3e:3f 1 3d:3e:3f:40 -1 2033-08-16 transaction 7533 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2033-08-17 transaction 7534 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2033-08-18 transaction 7535 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2033-08-19 transaction 7536 47 1 47:48 -1 2033-08-20 transaction 7537 47:48:49 1 47:48:49:4a -1 2033-08-21 transaction 7538 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2033-08-22 transaction 7539 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2033-08-23 transaction 7540 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2033-08-24 transaction 7541 51 1 51:52 -1 2033-08-25 transaction 7542 51:52:53 1 51:52:53:54 -1 2033-08-26 transaction 7543 51:52:53:54:55 1 51:52:53:54:55:56 -1 2033-08-27 transaction 7544 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2033-08-28 transaction 7545 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2033-08-29 transaction 7546 5b 1 5b:5c -1 2033-08-30 transaction 7547 5b:5c:5d 1 5b:5c:5d:5e -1 2033-08-31 transaction 7548 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2033-09-01 transaction 7549 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2033-09-02 transaction 7550 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2033-09-03 transaction 7551 65 1 65:66 -1 2033-09-04 transaction 7552 65:66:67 1 65:66:67:68 -1 2033-09-05 transaction 7553 65:66:67:68:69 1 65:66:67:68:69:6a -1 2033-09-06 transaction 7554 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2033-09-07 transaction 7555 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2033-09-08 transaction 7556 6f 1 6f:70 -1 2033-09-09 transaction 7557 6f:70:71 1 6f:70:71:72 -1 2033-09-10 transaction 7558 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2033-09-11 transaction 7559 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2033-09-12 transaction 7560 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2033-09-13 transaction 7561 79 1 79:7a -1 2033-09-14 transaction 7562 79:7a:7b 1 79:7a:7b:7c -1 2033-09-15 transaction 7563 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2033-09-16 transaction 7564 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2033-09-17 transaction 7565 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2033-09-18 transaction 7566 83 1 83:84 -1 2033-09-19 transaction 7567 83:84:85 1 83:84:85:86 -1 2033-09-20 transaction 7568 83:84:85:86:87 1 83:84:85:86:87:88 -1 2033-09-21 transaction 7569 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2033-09-22 transaction 7570 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2033-09-23 transaction 7571 8d 1 8d:8e -1 2033-09-24 transaction 7572 8d:8e:8f 1 8d:8e:8f:90 -1 2033-09-25 transaction 7573 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2033-09-26 transaction 7574 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2033-09-27 transaction 7575 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2033-09-28 transaction 7576 97 1 97:98 -1 2033-09-29 transaction 7577 97:98:99 1 97:98:99:9a -1 2033-09-30 transaction 7578 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2033-10-01 transaction 7579 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2033-10-02 transaction 7580 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2033-10-03 transaction 7581 a1 1 a1:a2 -1 2033-10-04 transaction 7582 a1:a2:a3 1 a1:a2:a3:a4 -1 2033-10-05 transaction 7583 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2033-10-06 transaction 7584 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2033-10-07 transaction 7585 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2033-10-08 transaction 7586 ab 1 ab:ac -1 2033-10-09 transaction 7587 ab:ac:ad 1 ab:ac:ad:ae -1 2033-10-10 transaction 7588 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2033-10-11 transaction 7589 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2033-10-12 transaction 7590 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2033-10-13 transaction 7591 b5 1 b5:b6 -1 2033-10-14 transaction 7592 b5:b6:b7 1 b5:b6:b7:b8 -1 2033-10-15 transaction 7593 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2033-10-16 transaction 7594 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2033-10-17 transaction 7595 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2033-10-18 transaction 7596 bf 1 bf:c0 -1 2033-10-19 transaction 7597 bf:c0:c1 1 bf:c0:c1:c2 -1 2033-10-20 transaction 7598 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2033-10-21 transaction 7599 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2033-10-22 transaction 7600 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2033-10-23 transaction 7601 c9 1 c9:ca -1 2033-10-24 transaction 7602 c9:ca:cb 1 c9:ca:cb:cc -1 2033-10-25 transaction 7603 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2033-10-26 transaction 7604 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2033-10-27 transaction 7605 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2033-10-28 transaction 7606 d3 1 d3:d4 -1 2033-10-29 transaction 7607 d3:d4:d5 1 d3:d4:d5:d6 -1 2033-10-30 transaction 7608 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2033-10-31 transaction 7609 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2033-11-01 transaction 7610 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2033-11-02 transaction 7611 dd 1 dd:de -1 2033-11-03 transaction 7612 dd:de:df 1 dd:de:df:e0 -1 2033-11-04 transaction 7613 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2033-11-05 transaction 7614 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2033-11-06 transaction 7615 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2033-11-07 transaction 7616 e7 1 e7:e8 -1 2033-11-08 transaction 7617 e7:e8:e9 1 e7:e8:e9:ea -1 2033-11-09 transaction 7618 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2033-11-10 transaction 7619 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2033-11-11 transaction 7620 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2033-11-12 transaction 7621 f1 1 f1:f2 -1 2033-11-13 transaction 7622 f1:f2:f3 1 f1:f2:f3:f4 -1 2033-11-14 transaction 7623 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2033-11-15 transaction 7624 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2033-11-16 transaction 7625 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2033-11-17 transaction 7626 fb 1 fb:fc -1 2033-11-18 transaction 7627 fb:fc:fd 1 fb:fc:fd:fe -1 2033-11-19 transaction 7628 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2033-11-20 transaction 7629 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2033-11-21 transaction 7630 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2033-11-22 transaction 7631 105 1 105:106 -1 2033-11-23 transaction 7632 105:106:107 1 105:106:107:108 -1 2033-11-24 transaction 7633 105:106:107:108:109 1 105:106:107:108:109:10a -1 2033-11-25 transaction 7634 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2033-11-26 transaction 7635 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2033-11-27 transaction 7636 10f 1 10f:110 -1 2033-11-28 transaction 7637 10f:110:111 1 10f:110:111:112 -1 2033-11-29 transaction 7638 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2033-11-30 transaction 7639 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2033-12-01 transaction 7640 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2033-12-02 transaction 7641 119 1 119:11a -1 2033-12-03 transaction 7642 119:11a:11b 1 119:11a:11b:11c -1 2033-12-04 transaction 7643 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2033-12-05 transaction 7644 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2033-12-06 transaction 7645 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2033-12-07 transaction 7646 123 1 123:124 -1 2033-12-08 transaction 7647 123:124:125 1 123:124:125:126 -1 2033-12-09 transaction 7648 123:124:125:126:127 1 123:124:125:126:127:128 -1 2033-12-10 transaction 7649 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2033-12-11 transaction 7650 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2033-12-12 transaction 7651 12d 1 12d:12e -1 2033-12-13 transaction 7652 12d:12e:12f 1 12d:12e:12f:130 -1 2033-12-14 transaction 7653 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2033-12-15 transaction 7654 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2033-12-16 transaction 7655 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2033-12-17 transaction 7656 137 1 137:138 -1 2033-12-18 transaction 7657 137:138:139 1 137:138:139:13a -1 2033-12-19 transaction 7658 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2033-12-20 transaction 7659 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2033-12-21 transaction 7660 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2033-12-22 transaction 7661 141 1 141:142 -1 2033-12-23 transaction 7662 141:142:143 1 141:142:143:144 -1 2033-12-24 transaction 7663 141:142:143:144:145 1 141:142:143:144:145:146 -1 2033-12-25 transaction 7664 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2033-12-26 transaction 7665 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2033-12-27 transaction 7666 14b 1 14b:14c -1 2033-12-28 transaction 7667 14b:14c:14d 1 14b:14c:14d:14e -1 2033-12-29 transaction 7668 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2033-12-30 transaction 7669 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2033-12-31 transaction 7670 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2034-01-01 transaction 7671 155 1 155:156 -1 2034-01-02 transaction 7672 155:156:157 1 155:156:157:158 -1 2034-01-03 transaction 7673 155:156:157:158:159 1 155:156:157:158:159:15a -1 2034-01-04 transaction 7674 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2034-01-05 transaction 7675 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2034-01-06 transaction 7676 15f 1 15f:160 -1 2034-01-07 transaction 7677 15f:160:161 1 15f:160:161:162 -1 2034-01-08 transaction 7678 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2034-01-09 transaction 7679 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2034-01-10 transaction 7680 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2034-01-11 transaction 7681 169 1 169:16a -1 2034-01-12 transaction 7682 169:16a:16b 1 169:16a:16b:16c -1 2034-01-13 transaction 7683 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2034-01-14 transaction 7684 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2034-01-15 transaction 7685 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2034-01-16 transaction 7686 173 1 173:174 -1 2034-01-17 transaction 7687 173:174:175 1 173:174:175:176 -1 2034-01-18 transaction 7688 173:174:175:176:177 1 173:174:175:176:177:178 -1 2034-01-19 transaction 7689 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2034-01-20 transaction 7690 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2034-01-21 transaction 7691 17d 1 17d:17e -1 2034-01-22 transaction 7692 17d:17e:17f 1 17d:17e:17f:180 -1 2034-01-23 transaction 7693 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2034-01-24 transaction 7694 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2034-01-25 transaction 7695 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2034-01-26 transaction 7696 187 1 187:188 -1 2034-01-27 transaction 7697 187:188:189 1 187:188:189:18a -1 2034-01-28 transaction 7698 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2034-01-29 transaction 7699 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2034-01-30 transaction 7700 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2034-01-31 transaction 7701 191 1 191:192 -1 2034-02-01 transaction 7702 191:192:193 1 191:192:193:194 -1 2034-02-02 transaction 7703 191:192:193:194:195 1 191:192:193:194:195:196 -1 2034-02-03 transaction 7704 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2034-02-04 transaction 7705 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2034-02-05 transaction 7706 19b 1 19b:19c -1 2034-02-06 transaction 7707 19b:19c:19d 1 19b:19c:19d:19e -1 2034-02-07 transaction 7708 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2034-02-08 transaction 7709 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2034-02-09 transaction 7710 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2034-02-10 transaction 7711 1a5 1 1a5:1a6 -1 2034-02-11 transaction 7712 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2034-02-12 transaction 7713 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2034-02-13 transaction 7714 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2034-02-14 transaction 7715 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2034-02-15 transaction 7716 1af 1 1af:1b0 -1 2034-02-16 transaction 7717 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2034-02-17 transaction 7718 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2034-02-18 transaction 7719 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2034-02-19 transaction 7720 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2034-02-20 transaction 7721 1b9 1 1b9:1ba -1 2034-02-21 transaction 7722 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2034-02-22 transaction 7723 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2034-02-23 transaction 7724 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2034-02-24 transaction 7725 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2034-02-25 transaction 7726 1c3 1 1c3:1c4 -1 2034-02-26 transaction 7727 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2034-02-27 transaction 7728 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2034-02-28 transaction 7729 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2034-03-01 transaction 7730 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2034-03-02 transaction 7731 1cd 1 1cd:1ce -1 2034-03-03 transaction 7732 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2034-03-04 transaction 7733 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2034-03-05 transaction 7734 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2034-03-06 transaction 7735 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2034-03-07 transaction 7736 1d7 1 1d7:1d8 -1 2034-03-08 transaction 7737 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2034-03-09 transaction 7738 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2034-03-10 transaction 7739 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2034-03-11 transaction 7740 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2034-03-12 transaction 7741 1e1 1 1e1:1e2 -1 2034-03-13 transaction 7742 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2034-03-14 transaction 7743 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2034-03-15 transaction 7744 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2034-03-16 transaction 7745 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2034-03-17 transaction 7746 1eb 1 1eb:1ec -1 2034-03-18 transaction 7747 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2034-03-19 transaction 7748 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2034-03-20 transaction 7749 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2034-03-21 transaction 7750 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2034-03-22 transaction 7751 1f5 1 1f5:1f6 -1 2034-03-23 transaction 7752 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2034-03-24 transaction 7753 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2034-03-25 transaction 7754 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2034-03-26 transaction 7755 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2034-03-27 transaction 7756 1ff 1 1ff:200 -1 2034-03-28 transaction 7757 1ff:200:201 1 1ff:200:201:202 -1 2034-03-29 transaction 7758 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2034-03-30 transaction 7759 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2034-03-31 transaction 7760 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2034-04-01 transaction 7761 209 1 209:20a -1 2034-04-02 transaction 7762 209:20a:20b 1 209:20a:20b:20c -1 2034-04-03 transaction 7763 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2034-04-04 transaction 7764 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2034-04-05 transaction 7765 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2034-04-06 transaction 7766 213 1 213:214 -1 2034-04-07 transaction 7767 213:214:215 1 213:214:215:216 -1 2034-04-08 transaction 7768 213:214:215:216:217 1 213:214:215:216:217:218 -1 2034-04-09 transaction 7769 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2034-04-10 transaction 7770 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2034-04-11 transaction 7771 21d 1 21d:21e -1 2034-04-12 transaction 7772 21d:21e:21f 1 21d:21e:21f:220 -1 2034-04-13 transaction 7773 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2034-04-14 transaction 7774 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2034-04-15 transaction 7775 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2034-04-16 transaction 7776 227 1 227:228 -1 2034-04-17 transaction 7777 227:228:229 1 227:228:229:22a -1 2034-04-18 transaction 7778 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2034-04-19 transaction 7779 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2034-04-20 transaction 7780 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2034-04-21 transaction 7781 231 1 231:232 -1 2034-04-22 transaction 7782 231:232:233 1 231:232:233:234 -1 2034-04-23 transaction 7783 231:232:233:234:235 1 231:232:233:234:235:236 -1 2034-04-24 transaction 7784 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2034-04-25 transaction 7785 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2034-04-26 transaction 7786 23b 1 23b:23c -1 2034-04-27 transaction 7787 23b:23c:23d 1 23b:23c:23d:23e -1 2034-04-28 transaction 7788 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2034-04-29 transaction 7789 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2034-04-30 transaction 7790 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2034-05-01 transaction 7791 245 1 245:246 -1 2034-05-02 transaction 7792 245:246:247 1 245:246:247:248 -1 2034-05-03 transaction 7793 245:246:247:248:249 1 245:246:247:248:249:24a -1 2034-05-04 transaction 7794 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2034-05-05 transaction 7795 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2034-05-06 transaction 7796 24f 1 24f:250 -1 2034-05-07 transaction 7797 24f:250:251 1 24f:250:251:252 -1 2034-05-08 transaction 7798 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2034-05-09 transaction 7799 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2034-05-10 transaction 7800 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2034-05-11 transaction 7801 259 1 259:25a -1 2034-05-12 transaction 7802 259:25a:25b 1 259:25a:25b:25c -1 2034-05-13 transaction 7803 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2034-05-14 transaction 7804 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2034-05-15 transaction 7805 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2034-05-16 transaction 7806 263 1 263:264 -1 2034-05-17 transaction 7807 263:264:265 1 263:264:265:266 -1 2034-05-18 transaction 7808 263:264:265:266:267 1 263:264:265:266:267:268 -1 2034-05-19 transaction 7809 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2034-05-20 transaction 7810 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2034-05-21 transaction 7811 26d 1 26d:26e -1 2034-05-22 transaction 7812 26d:26e:26f 1 26d:26e:26f:270 -1 2034-05-23 transaction 7813 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2034-05-24 transaction 7814 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2034-05-25 transaction 7815 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2034-05-26 transaction 7816 277 1 277:278 -1 2034-05-27 transaction 7817 277:278:279 1 277:278:279:27a -1 2034-05-28 transaction 7818 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2034-05-29 transaction 7819 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2034-05-30 transaction 7820 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2034-05-31 transaction 7821 281 1 281:282 -1 2034-06-01 transaction 7822 281:282:283 1 281:282:283:284 -1 2034-06-02 transaction 7823 281:282:283:284:285 1 281:282:283:284:285:286 -1 2034-06-03 transaction 7824 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2034-06-04 transaction 7825 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2034-06-05 transaction 7826 28b 1 28b:28c -1 2034-06-06 transaction 7827 28b:28c:28d 1 28b:28c:28d:28e -1 2034-06-07 transaction 7828 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2034-06-08 transaction 7829 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2034-06-09 transaction 7830 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2034-06-10 transaction 7831 295 1 295:296 -1 2034-06-11 transaction 7832 295:296:297 1 295:296:297:298 -1 2034-06-12 transaction 7833 295:296:297:298:299 1 295:296:297:298:299:29a -1 2034-06-13 transaction 7834 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2034-06-14 transaction 7835 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2034-06-15 transaction 7836 29f 1 29f:2a0 -1 2034-06-16 transaction 7837 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2034-06-17 transaction 7838 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2034-06-18 transaction 7839 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2034-06-19 transaction 7840 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2034-06-20 transaction 7841 2a9 1 2a9:2aa -1 2034-06-21 transaction 7842 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2034-06-22 transaction 7843 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2034-06-23 transaction 7844 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2034-06-24 transaction 7845 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2034-06-25 transaction 7846 2b3 1 2b3:2b4 -1 2034-06-26 transaction 7847 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2034-06-27 transaction 7848 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2034-06-28 transaction 7849 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2034-06-29 transaction 7850 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2034-06-30 transaction 7851 2bd 1 2bd:2be -1 2034-07-01 transaction 7852 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2034-07-02 transaction 7853 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2034-07-03 transaction 7854 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2034-07-04 transaction 7855 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2034-07-05 transaction 7856 2c7 1 2c7:2c8 -1 2034-07-06 transaction 7857 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2034-07-07 transaction 7858 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2034-07-08 transaction 7859 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2034-07-09 transaction 7860 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2034-07-10 transaction 7861 2d1 1 2d1:2d2 -1 2034-07-11 transaction 7862 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2034-07-12 transaction 7863 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2034-07-13 transaction 7864 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2034-07-14 transaction 7865 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2034-07-15 transaction 7866 2db 1 2db:2dc -1 2034-07-16 transaction 7867 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2034-07-17 transaction 7868 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2034-07-18 transaction 7869 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2034-07-19 transaction 7870 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2034-07-20 transaction 7871 2e5 1 2e5:2e6 -1 2034-07-21 transaction 7872 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2034-07-22 transaction 7873 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2034-07-23 transaction 7874 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2034-07-24 transaction 7875 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2034-07-25 transaction 7876 2ef 1 2ef:2f0 -1 2034-07-26 transaction 7877 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2034-07-27 transaction 7878 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2034-07-28 transaction 7879 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2034-07-29 transaction 7880 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2034-07-30 transaction 7881 2f9 1 2f9:2fa -1 2034-07-31 transaction 7882 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2034-08-01 transaction 7883 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2034-08-02 transaction 7884 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2034-08-03 transaction 7885 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2034-08-04 transaction 7886 303 1 303:304 -1 2034-08-05 transaction 7887 303:304:305 1 303:304:305:306 -1 2034-08-06 transaction 7888 303:304:305:306:307 1 303:304:305:306:307:308 -1 2034-08-07 transaction 7889 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2034-08-08 transaction 7890 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2034-08-09 transaction 7891 30d 1 30d:30e -1 2034-08-10 transaction 7892 30d:30e:30f 1 30d:30e:30f:310 -1 2034-08-11 transaction 7893 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2034-08-12 transaction 7894 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2034-08-13 transaction 7895 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2034-08-14 transaction 7896 317 1 317:318 -1 2034-08-15 transaction 7897 317:318:319 1 317:318:319:31a -1 2034-08-16 transaction 7898 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2034-08-17 transaction 7899 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2034-08-18 transaction 7900 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2034-08-19 transaction 7901 321 1 321:322 -1 2034-08-20 transaction 7902 321:322:323 1 321:322:323:324 -1 2034-08-21 transaction 7903 321:322:323:324:325 1 321:322:323:324:325:326 -1 2034-08-22 transaction 7904 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2034-08-23 transaction 7905 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2034-08-24 transaction 7906 32b 1 32b:32c -1 2034-08-25 transaction 7907 32b:32c:32d 1 32b:32c:32d:32e -1 2034-08-26 transaction 7908 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2034-08-27 transaction 7909 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2034-08-28 transaction 7910 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2034-08-29 transaction 7911 335 1 335:336 -1 2034-08-30 transaction 7912 335:336:337 1 335:336:337:338 -1 2034-08-31 transaction 7913 335:336:337:338:339 1 335:336:337:338:339:33a -1 2034-09-01 transaction 7914 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2034-09-02 transaction 7915 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2034-09-03 transaction 7916 33f 1 33f:340 -1 2034-09-04 transaction 7917 33f:340:341 1 33f:340:341:342 -1 2034-09-05 transaction 7918 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2034-09-06 transaction 7919 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2034-09-07 transaction 7920 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2034-09-08 transaction 7921 349 1 349:34a -1 2034-09-09 transaction 7922 349:34a:34b 1 349:34a:34b:34c -1 2034-09-10 transaction 7923 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2034-09-11 transaction 7924 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2034-09-12 transaction 7925 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2034-09-13 transaction 7926 353 1 353:354 -1 2034-09-14 transaction 7927 353:354:355 1 353:354:355:356 -1 2034-09-15 transaction 7928 353:354:355:356:357 1 353:354:355:356:357:358 -1 2034-09-16 transaction 7929 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2034-09-17 transaction 7930 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2034-09-18 transaction 7931 35d 1 35d:35e -1 2034-09-19 transaction 7932 35d:35e:35f 1 35d:35e:35f:360 -1 2034-09-20 transaction 7933 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2034-09-21 transaction 7934 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2034-09-22 transaction 7935 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2034-09-23 transaction 7936 367 1 367:368 -1 2034-09-24 transaction 7937 367:368:369 1 367:368:369:36a -1 2034-09-25 transaction 7938 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2034-09-26 transaction 7939 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2034-09-27 transaction 7940 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2034-09-28 transaction 7941 371 1 371:372 -1 2034-09-29 transaction 7942 371:372:373 1 371:372:373:374 -1 2034-09-30 transaction 7943 371:372:373:374:375 1 371:372:373:374:375:376 -1 2034-10-01 transaction 7944 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2034-10-02 transaction 7945 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2034-10-03 transaction 7946 37b 1 37b:37c -1 2034-10-04 transaction 7947 37b:37c:37d 1 37b:37c:37d:37e -1 2034-10-05 transaction 7948 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2034-10-06 transaction 7949 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2034-10-07 transaction 7950 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2034-10-08 transaction 7951 385 1 385:386 -1 2034-10-09 transaction 7952 385:386:387 1 385:386:387:388 -1 2034-10-10 transaction 7953 385:386:387:388:389 1 385:386:387:388:389:38a -1 2034-10-11 transaction 7954 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2034-10-12 transaction 7955 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2034-10-13 transaction 7956 38f 1 38f:390 -1 2034-10-14 transaction 7957 38f:390:391 1 38f:390:391:392 -1 2034-10-15 transaction 7958 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2034-10-16 transaction 7959 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2034-10-17 transaction 7960 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2034-10-18 transaction 7961 399 1 399:39a -1 2034-10-19 transaction 7962 399:39a:39b 1 399:39a:39b:39c -1 2034-10-20 transaction 7963 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2034-10-21 transaction 7964 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2034-10-22 transaction 7965 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2034-10-23 transaction 7966 3a3 1 3a3:3a4 -1 2034-10-24 transaction 7967 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2034-10-25 transaction 7968 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2034-10-26 transaction 7969 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2034-10-27 transaction 7970 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2034-10-28 transaction 7971 3ad 1 3ad:3ae -1 2034-10-29 transaction 7972 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2034-10-30 transaction 7973 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2034-10-31 transaction 7974 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2034-11-01 transaction 7975 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2034-11-02 transaction 7976 3b7 1 3b7:3b8 -1 2034-11-03 transaction 7977 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2034-11-04 transaction 7978 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2034-11-05 transaction 7979 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2034-11-06 transaction 7980 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2034-11-07 transaction 7981 3c1 1 3c1:3c2 -1 2034-11-08 transaction 7982 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2034-11-09 transaction 7983 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2034-11-10 transaction 7984 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2034-11-11 transaction 7985 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2034-11-12 transaction 7986 3cb 1 3cb:3cc -1 2034-11-13 transaction 7987 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2034-11-14 transaction 7988 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2034-11-15 transaction 7989 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2034-11-16 transaction 7990 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2034-11-17 transaction 7991 3d5 1 3d5:3d6 -1 2034-11-18 transaction 7992 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2034-11-19 transaction 7993 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2034-11-20 transaction 7994 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2034-11-21 transaction 7995 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2034-11-22 transaction 7996 3df 1 3df:3e0 -1 2034-11-23 transaction 7997 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2034-11-24 transaction 7998 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2034-11-25 transaction 7999 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2034-11-26 transaction 8000 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2034-11-27 transaction 8001 1 1 1:2 -1 2034-11-28 transaction 8002 1:2:3 1 1:2:3:4 -1 2034-11-29 transaction 8003 1:2:3:4:5 1 1:2:3:4:5:6 -1 2034-11-30 transaction 8004 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2034-12-01 transaction 8005 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2034-12-02 transaction 8006 b 1 b:c -1 2034-12-03 transaction 8007 b:c:d 1 b:c:d:e -1 2034-12-04 transaction 8008 b:c:d:e:f 1 b:c:d:e:f:10 -1 2034-12-05 transaction 8009 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2034-12-06 transaction 8010 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2034-12-07 transaction 8011 15 1 15:16 -1 2034-12-08 transaction 8012 15:16:17 1 15:16:17:18 -1 2034-12-09 transaction 8013 15:16:17:18:19 1 15:16:17:18:19:1a -1 2034-12-10 transaction 8014 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2034-12-11 transaction 8015 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2034-12-12 transaction 8016 1f 1 1f:20 -1 2034-12-13 transaction 8017 1f:20:21 1 1f:20:21:22 -1 2034-12-14 transaction 8018 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2034-12-15 transaction 8019 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2034-12-16 transaction 8020 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2034-12-17 transaction 8021 29 1 29:2a -1 2034-12-18 transaction 8022 29:2a:2b 1 29:2a:2b:2c -1 2034-12-19 transaction 8023 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2034-12-20 transaction 8024 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2034-12-21 transaction 8025 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2034-12-22 transaction 8026 33 1 33:34 -1 2034-12-23 transaction 8027 33:34:35 1 33:34:35:36 -1 2034-12-24 transaction 8028 33:34:35:36:37 1 33:34:35:36:37:38 -1 2034-12-25 transaction 8029 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2034-12-26 transaction 8030 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2034-12-27 transaction 8031 3d 1 3d:3e -1 2034-12-28 transaction 8032 3d:3e:3f 1 3d:3e:3f:40 -1 2034-12-29 transaction 8033 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2034-12-30 transaction 8034 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2034-12-31 transaction 8035 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2035-01-01 transaction 8036 47 1 47:48 -1 2035-01-02 transaction 8037 47:48:49 1 47:48:49:4a -1 2035-01-03 transaction 8038 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2035-01-04 transaction 8039 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2035-01-05 transaction 8040 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2035-01-06 transaction 8041 51 1 51:52 -1 2035-01-07 transaction 8042 51:52:53 1 51:52:53:54 -1 2035-01-08 transaction 8043 51:52:53:54:55 1 51:52:53:54:55:56 -1 2035-01-09 transaction 8044 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2035-01-10 transaction 8045 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2035-01-11 transaction 8046 5b 1 5b:5c -1 2035-01-12 transaction 8047 5b:5c:5d 1 5b:5c:5d:5e -1 2035-01-13 transaction 8048 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2035-01-14 transaction 8049 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2035-01-15 transaction 8050 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2035-01-16 transaction 8051 65 1 65:66 -1 2035-01-17 transaction 8052 65:66:67 1 65:66:67:68 -1 2035-01-18 transaction 8053 65:66:67:68:69 1 65:66:67:68:69:6a -1 2035-01-19 transaction 8054 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2035-01-20 transaction 8055 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2035-01-21 transaction 8056 6f 1 6f:70 -1 2035-01-22 transaction 8057 6f:70:71 1 6f:70:71:72 -1 2035-01-23 transaction 8058 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2035-01-24 transaction 8059 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2035-01-25 transaction 8060 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2035-01-26 transaction 8061 79 1 79:7a -1 2035-01-27 transaction 8062 79:7a:7b 1 79:7a:7b:7c -1 2035-01-28 transaction 8063 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2035-01-29 transaction 8064 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2035-01-30 transaction 8065 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2035-01-31 transaction 8066 83 1 83:84 -1 2035-02-01 transaction 8067 83:84:85 1 83:84:85:86 -1 2035-02-02 transaction 8068 83:84:85:86:87 1 83:84:85:86:87:88 -1 2035-02-03 transaction 8069 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2035-02-04 transaction 8070 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2035-02-05 transaction 8071 8d 1 8d:8e -1 2035-02-06 transaction 8072 8d:8e:8f 1 8d:8e:8f:90 -1 2035-02-07 transaction 8073 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2035-02-08 transaction 8074 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2035-02-09 transaction 8075 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2035-02-10 transaction 8076 97 1 97:98 -1 2035-02-11 transaction 8077 97:98:99 1 97:98:99:9a -1 2035-02-12 transaction 8078 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2035-02-13 transaction 8079 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2035-02-14 transaction 8080 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2035-02-15 transaction 8081 a1 1 a1:a2 -1 2035-02-16 transaction 8082 a1:a2:a3 1 a1:a2:a3:a4 -1 2035-02-17 transaction 8083 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2035-02-18 transaction 8084 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2035-02-19 transaction 8085 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2035-02-20 transaction 8086 ab 1 ab:ac -1 2035-02-21 transaction 8087 ab:ac:ad 1 ab:ac:ad:ae -1 2035-02-22 transaction 8088 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2035-02-23 transaction 8089 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2035-02-24 transaction 8090 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2035-02-25 transaction 8091 b5 1 b5:b6 -1 2035-02-26 transaction 8092 b5:b6:b7 1 b5:b6:b7:b8 -1 2035-02-27 transaction 8093 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2035-02-28 transaction 8094 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2035-03-01 transaction 8095 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2035-03-02 transaction 8096 bf 1 bf:c0 -1 2035-03-03 transaction 8097 bf:c0:c1 1 bf:c0:c1:c2 -1 2035-03-04 transaction 8098 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2035-03-05 transaction 8099 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2035-03-06 transaction 8100 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2035-03-07 transaction 8101 c9 1 c9:ca -1 2035-03-08 transaction 8102 c9:ca:cb 1 c9:ca:cb:cc -1 2035-03-09 transaction 8103 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2035-03-10 transaction 8104 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2035-03-11 transaction 8105 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2035-03-12 transaction 8106 d3 1 d3:d4 -1 2035-03-13 transaction 8107 d3:d4:d5 1 d3:d4:d5:d6 -1 2035-03-14 transaction 8108 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2035-03-15 transaction 8109 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2035-03-16 transaction 8110 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2035-03-17 transaction 8111 dd 1 dd:de -1 2035-03-18 transaction 8112 dd:de:df 1 dd:de:df:e0 -1 2035-03-19 transaction 8113 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2035-03-20 transaction 8114 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2035-03-21 transaction 8115 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2035-03-22 transaction 8116 e7 1 e7:e8 -1 2035-03-23 transaction 8117 e7:e8:e9 1 e7:e8:e9:ea -1 2035-03-24 transaction 8118 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2035-03-25 transaction 8119 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2035-03-26 transaction 8120 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2035-03-27 transaction 8121 f1 1 f1:f2 -1 2035-03-28 transaction 8122 f1:f2:f3 1 f1:f2:f3:f4 -1 2035-03-29 transaction 8123 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2035-03-30 transaction 8124 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2035-03-31 transaction 8125 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2035-04-01 transaction 8126 fb 1 fb:fc -1 2035-04-02 transaction 8127 fb:fc:fd 1 fb:fc:fd:fe -1 2035-04-03 transaction 8128 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2035-04-04 transaction 8129 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2035-04-05 transaction 8130 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2035-04-06 transaction 8131 105 1 105:106 -1 2035-04-07 transaction 8132 105:106:107 1 105:106:107:108 -1 2035-04-08 transaction 8133 105:106:107:108:109 1 105:106:107:108:109:10a -1 2035-04-09 transaction 8134 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2035-04-10 transaction 8135 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2035-04-11 transaction 8136 10f 1 10f:110 -1 2035-04-12 transaction 8137 10f:110:111 1 10f:110:111:112 -1 2035-04-13 transaction 8138 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2035-04-14 transaction 8139 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2035-04-15 transaction 8140 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2035-04-16 transaction 8141 119 1 119:11a -1 2035-04-17 transaction 8142 119:11a:11b 1 119:11a:11b:11c -1 2035-04-18 transaction 8143 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2035-04-19 transaction 8144 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2035-04-20 transaction 8145 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2035-04-21 transaction 8146 123 1 123:124 -1 2035-04-22 transaction 8147 123:124:125 1 123:124:125:126 -1 2035-04-23 transaction 8148 123:124:125:126:127 1 123:124:125:126:127:128 -1 2035-04-24 transaction 8149 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2035-04-25 transaction 8150 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2035-04-26 transaction 8151 12d 1 12d:12e -1 2035-04-27 transaction 8152 12d:12e:12f 1 12d:12e:12f:130 -1 2035-04-28 transaction 8153 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2035-04-29 transaction 8154 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2035-04-30 transaction 8155 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2035-05-01 transaction 8156 137 1 137:138 -1 2035-05-02 transaction 8157 137:138:139 1 137:138:139:13a -1 2035-05-03 transaction 8158 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2035-05-04 transaction 8159 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2035-05-05 transaction 8160 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2035-05-06 transaction 8161 141 1 141:142 -1 2035-05-07 transaction 8162 141:142:143 1 141:142:143:144 -1 2035-05-08 transaction 8163 141:142:143:144:145 1 141:142:143:144:145:146 -1 2035-05-09 transaction 8164 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2035-05-10 transaction 8165 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2035-05-11 transaction 8166 14b 1 14b:14c -1 2035-05-12 transaction 8167 14b:14c:14d 1 14b:14c:14d:14e -1 2035-05-13 transaction 8168 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2035-05-14 transaction 8169 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2035-05-15 transaction 8170 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2035-05-16 transaction 8171 155 1 155:156 -1 2035-05-17 transaction 8172 155:156:157 1 155:156:157:158 -1 2035-05-18 transaction 8173 155:156:157:158:159 1 155:156:157:158:159:15a -1 2035-05-19 transaction 8174 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2035-05-20 transaction 8175 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2035-05-21 transaction 8176 15f 1 15f:160 -1 2035-05-22 transaction 8177 15f:160:161 1 15f:160:161:162 -1 2035-05-23 transaction 8178 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2035-05-24 transaction 8179 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2035-05-25 transaction 8180 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2035-05-26 transaction 8181 169 1 169:16a -1 2035-05-27 transaction 8182 169:16a:16b 1 169:16a:16b:16c -1 2035-05-28 transaction 8183 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2035-05-29 transaction 8184 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2035-05-30 transaction 8185 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2035-05-31 transaction 8186 173 1 173:174 -1 2035-06-01 transaction 8187 173:174:175 1 173:174:175:176 -1 2035-06-02 transaction 8188 173:174:175:176:177 1 173:174:175:176:177:178 -1 2035-06-03 transaction 8189 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2035-06-04 transaction 8190 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2035-06-05 transaction 8191 17d 1 17d:17e -1 2035-06-06 transaction 8192 17d:17e:17f 1 17d:17e:17f:180 -1 2035-06-07 transaction 8193 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2035-06-08 transaction 8194 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2035-06-09 transaction 8195 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2035-06-10 transaction 8196 187 1 187:188 -1 2035-06-11 transaction 8197 187:188:189 1 187:188:189:18a -1 2035-06-12 transaction 8198 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2035-06-13 transaction 8199 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2035-06-14 transaction 8200 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2035-06-15 transaction 8201 191 1 191:192 -1 2035-06-16 transaction 8202 191:192:193 1 191:192:193:194 -1 2035-06-17 transaction 8203 191:192:193:194:195 1 191:192:193:194:195:196 -1 2035-06-18 transaction 8204 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2035-06-19 transaction 8205 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2035-06-20 transaction 8206 19b 1 19b:19c -1 2035-06-21 transaction 8207 19b:19c:19d 1 19b:19c:19d:19e -1 2035-06-22 transaction 8208 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2035-06-23 transaction 8209 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2035-06-24 transaction 8210 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2035-06-25 transaction 8211 1a5 1 1a5:1a6 -1 2035-06-26 transaction 8212 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2035-06-27 transaction 8213 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2035-06-28 transaction 8214 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2035-06-29 transaction 8215 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2035-06-30 transaction 8216 1af 1 1af:1b0 -1 2035-07-01 transaction 8217 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2035-07-02 transaction 8218 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2035-07-03 transaction 8219 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2035-07-04 transaction 8220 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2035-07-05 transaction 8221 1b9 1 1b9:1ba -1 2035-07-06 transaction 8222 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2035-07-07 transaction 8223 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2035-07-08 transaction 8224 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2035-07-09 transaction 8225 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2035-07-10 transaction 8226 1c3 1 1c3:1c4 -1 2035-07-11 transaction 8227 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2035-07-12 transaction 8228 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2035-07-13 transaction 8229 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2035-07-14 transaction 8230 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2035-07-15 transaction 8231 1cd 1 1cd:1ce -1 2035-07-16 transaction 8232 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2035-07-17 transaction 8233 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2035-07-18 transaction 8234 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2035-07-19 transaction 8235 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2035-07-20 transaction 8236 1d7 1 1d7:1d8 -1 2035-07-21 transaction 8237 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2035-07-22 transaction 8238 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2035-07-23 transaction 8239 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2035-07-24 transaction 8240 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2035-07-25 transaction 8241 1e1 1 1e1:1e2 -1 2035-07-26 transaction 8242 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2035-07-27 transaction 8243 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2035-07-28 transaction 8244 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2035-07-29 transaction 8245 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2035-07-30 transaction 8246 1eb 1 1eb:1ec -1 2035-07-31 transaction 8247 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2035-08-01 transaction 8248 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2035-08-02 transaction 8249 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2035-08-03 transaction 8250 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2035-08-04 transaction 8251 1f5 1 1f5:1f6 -1 2035-08-05 transaction 8252 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2035-08-06 transaction 8253 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2035-08-07 transaction 8254 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2035-08-08 transaction 8255 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2035-08-09 transaction 8256 1ff 1 1ff:200 -1 2035-08-10 transaction 8257 1ff:200:201 1 1ff:200:201:202 -1 2035-08-11 transaction 8258 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2035-08-12 transaction 8259 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2035-08-13 transaction 8260 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2035-08-14 transaction 8261 209 1 209:20a -1 2035-08-15 transaction 8262 209:20a:20b 1 209:20a:20b:20c -1 2035-08-16 transaction 8263 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2035-08-17 transaction 8264 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2035-08-18 transaction 8265 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2035-08-19 transaction 8266 213 1 213:214 -1 2035-08-20 transaction 8267 213:214:215 1 213:214:215:216 -1 2035-08-21 transaction 8268 213:214:215:216:217 1 213:214:215:216:217:218 -1 2035-08-22 transaction 8269 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2035-08-23 transaction 8270 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2035-08-24 transaction 8271 21d 1 21d:21e -1 2035-08-25 transaction 8272 21d:21e:21f 1 21d:21e:21f:220 -1 2035-08-26 transaction 8273 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2035-08-27 transaction 8274 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2035-08-28 transaction 8275 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2035-08-29 transaction 8276 227 1 227:228 -1 2035-08-30 transaction 8277 227:228:229 1 227:228:229:22a -1 2035-08-31 transaction 8278 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2035-09-01 transaction 8279 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2035-09-02 transaction 8280 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2035-09-03 transaction 8281 231 1 231:232 -1 2035-09-04 transaction 8282 231:232:233 1 231:232:233:234 -1 2035-09-05 transaction 8283 231:232:233:234:235 1 231:232:233:234:235:236 -1 2035-09-06 transaction 8284 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2035-09-07 transaction 8285 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2035-09-08 transaction 8286 23b 1 23b:23c -1 2035-09-09 transaction 8287 23b:23c:23d 1 23b:23c:23d:23e -1 2035-09-10 transaction 8288 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2035-09-11 transaction 8289 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2035-09-12 transaction 8290 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2035-09-13 transaction 8291 245 1 245:246 -1 2035-09-14 transaction 8292 245:246:247 1 245:246:247:248 -1 2035-09-15 transaction 8293 245:246:247:248:249 1 245:246:247:248:249:24a -1 2035-09-16 transaction 8294 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2035-09-17 transaction 8295 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2035-09-18 transaction 8296 24f 1 24f:250 -1 2035-09-19 transaction 8297 24f:250:251 1 24f:250:251:252 -1 2035-09-20 transaction 8298 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2035-09-21 transaction 8299 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2035-09-22 transaction 8300 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2035-09-23 transaction 8301 259 1 259:25a -1 2035-09-24 transaction 8302 259:25a:25b 1 259:25a:25b:25c -1 2035-09-25 transaction 8303 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2035-09-26 transaction 8304 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2035-09-27 transaction 8305 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2035-09-28 transaction 8306 263 1 263:264 -1 2035-09-29 transaction 8307 263:264:265 1 263:264:265:266 -1 2035-09-30 transaction 8308 263:264:265:266:267 1 263:264:265:266:267:268 -1 2035-10-01 transaction 8309 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2035-10-02 transaction 8310 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2035-10-03 transaction 8311 26d 1 26d:26e -1 2035-10-04 transaction 8312 26d:26e:26f 1 26d:26e:26f:270 -1 2035-10-05 transaction 8313 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2035-10-06 transaction 8314 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2035-10-07 transaction 8315 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2035-10-08 transaction 8316 277 1 277:278 -1 2035-10-09 transaction 8317 277:278:279 1 277:278:279:27a -1 2035-10-10 transaction 8318 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2035-10-11 transaction 8319 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2035-10-12 transaction 8320 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2035-10-13 transaction 8321 281 1 281:282 -1 2035-10-14 transaction 8322 281:282:283 1 281:282:283:284 -1 2035-10-15 transaction 8323 281:282:283:284:285 1 281:282:283:284:285:286 -1 2035-10-16 transaction 8324 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2035-10-17 transaction 8325 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2035-10-18 transaction 8326 28b 1 28b:28c -1 2035-10-19 transaction 8327 28b:28c:28d 1 28b:28c:28d:28e -1 2035-10-20 transaction 8328 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2035-10-21 transaction 8329 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2035-10-22 transaction 8330 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2035-10-23 transaction 8331 295 1 295:296 -1 2035-10-24 transaction 8332 295:296:297 1 295:296:297:298 -1 2035-10-25 transaction 8333 295:296:297:298:299 1 295:296:297:298:299:29a -1 2035-10-26 transaction 8334 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2035-10-27 transaction 8335 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2035-10-28 transaction 8336 29f 1 29f:2a0 -1 2035-10-29 transaction 8337 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2035-10-30 transaction 8338 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2035-10-31 transaction 8339 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2035-11-01 transaction 8340 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2035-11-02 transaction 8341 2a9 1 2a9:2aa -1 2035-11-03 transaction 8342 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2035-11-04 transaction 8343 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2035-11-05 transaction 8344 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2035-11-06 transaction 8345 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2035-11-07 transaction 8346 2b3 1 2b3:2b4 -1 2035-11-08 transaction 8347 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2035-11-09 transaction 8348 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2035-11-10 transaction 8349 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2035-11-11 transaction 8350 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2035-11-12 transaction 8351 2bd 1 2bd:2be -1 2035-11-13 transaction 8352 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2035-11-14 transaction 8353 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2035-11-15 transaction 8354 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2035-11-16 transaction 8355 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2035-11-17 transaction 8356 2c7 1 2c7:2c8 -1 2035-11-18 transaction 8357 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2035-11-19 transaction 8358 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2035-11-20 transaction 8359 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2035-11-21 transaction 8360 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2035-11-22 transaction 8361 2d1 1 2d1:2d2 -1 2035-11-23 transaction 8362 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2035-11-24 transaction 8363 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2035-11-25 transaction 8364 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2035-11-26 transaction 8365 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2035-11-27 transaction 8366 2db 1 2db:2dc -1 2035-11-28 transaction 8367 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2035-11-29 transaction 8368 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2035-11-30 transaction 8369 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2035-12-01 transaction 8370 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2035-12-02 transaction 8371 2e5 1 2e5:2e6 -1 2035-12-03 transaction 8372 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2035-12-04 transaction 8373 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2035-12-05 transaction 8374 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2035-12-06 transaction 8375 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2035-12-07 transaction 8376 2ef 1 2ef:2f0 -1 2035-12-08 transaction 8377 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2035-12-09 transaction 8378 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2035-12-10 transaction 8379 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2035-12-11 transaction 8380 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2035-12-12 transaction 8381 2f9 1 2f9:2fa -1 2035-12-13 transaction 8382 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2035-12-14 transaction 8383 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2035-12-15 transaction 8384 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2035-12-16 transaction 8385 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2035-12-17 transaction 8386 303 1 303:304 -1 2035-12-18 transaction 8387 303:304:305 1 303:304:305:306 -1 2035-12-19 transaction 8388 303:304:305:306:307 1 303:304:305:306:307:308 -1 2035-12-20 transaction 8389 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2035-12-21 transaction 8390 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2035-12-22 transaction 8391 30d 1 30d:30e -1 2035-12-23 transaction 8392 30d:30e:30f 1 30d:30e:30f:310 -1 2035-12-24 transaction 8393 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2035-12-25 transaction 8394 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2035-12-26 transaction 8395 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2035-12-27 transaction 8396 317 1 317:318 -1 2035-12-28 transaction 8397 317:318:319 1 317:318:319:31a -1 2035-12-29 transaction 8398 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2035-12-30 transaction 8399 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2035-12-31 transaction 8400 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2036-01-01 transaction 8401 321 1 321:322 -1 2036-01-02 transaction 8402 321:322:323 1 321:322:323:324 -1 2036-01-03 transaction 8403 321:322:323:324:325 1 321:322:323:324:325:326 -1 2036-01-04 transaction 8404 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2036-01-05 transaction 8405 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2036-01-06 transaction 8406 32b 1 32b:32c -1 2036-01-07 transaction 8407 32b:32c:32d 1 32b:32c:32d:32e -1 2036-01-08 transaction 8408 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2036-01-09 transaction 8409 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2036-01-10 transaction 8410 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2036-01-11 transaction 8411 335 1 335:336 -1 2036-01-12 transaction 8412 335:336:337 1 335:336:337:338 -1 2036-01-13 transaction 8413 335:336:337:338:339 1 335:336:337:338:339:33a -1 2036-01-14 transaction 8414 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2036-01-15 transaction 8415 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2036-01-16 transaction 8416 33f 1 33f:340 -1 2036-01-17 transaction 8417 33f:340:341 1 33f:340:341:342 -1 2036-01-18 transaction 8418 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2036-01-19 transaction 8419 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2036-01-20 transaction 8420 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2036-01-21 transaction 8421 349 1 349:34a -1 2036-01-22 transaction 8422 349:34a:34b 1 349:34a:34b:34c -1 2036-01-23 transaction 8423 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2036-01-24 transaction 8424 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2036-01-25 transaction 8425 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2036-01-26 transaction 8426 353 1 353:354 -1 2036-01-27 transaction 8427 353:354:355 1 353:354:355:356 -1 2036-01-28 transaction 8428 353:354:355:356:357 1 353:354:355:356:357:358 -1 2036-01-29 transaction 8429 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2036-01-30 transaction 8430 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2036-01-31 transaction 8431 35d 1 35d:35e -1 2036-02-01 transaction 8432 35d:35e:35f 1 35d:35e:35f:360 -1 2036-02-02 transaction 8433 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2036-02-03 transaction 8434 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2036-02-04 transaction 8435 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2036-02-05 transaction 8436 367 1 367:368 -1 2036-02-06 transaction 8437 367:368:369 1 367:368:369:36a -1 2036-02-07 transaction 8438 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2036-02-08 transaction 8439 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2036-02-09 transaction 8440 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2036-02-10 transaction 8441 371 1 371:372 -1 2036-02-11 transaction 8442 371:372:373 1 371:372:373:374 -1 2036-02-12 transaction 8443 371:372:373:374:375 1 371:372:373:374:375:376 -1 2036-02-13 transaction 8444 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2036-02-14 transaction 8445 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2036-02-15 transaction 8446 37b 1 37b:37c -1 2036-02-16 transaction 8447 37b:37c:37d 1 37b:37c:37d:37e -1 2036-02-17 transaction 8448 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2036-02-18 transaction 8449 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2036-02-19 transaction 8450 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2036-02-20 transaction 8451 385 1 385:386 -1 2036-02-21 transaction 8452 385:386:387 1 385:386:387:388 -1 2036-02-22 transaction 8453 385:386:387:388:389 1 385:386:387:388:389:38a -1 2036-02-23 transaction 8454 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2036-02-24 transaction 8455 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2036-02-25 transaction 8456 38f 1 38f:390 -1 2036-02-26 transaction 8457 38f:390:391 1 38f:390:391:392 -1 2036-02-27 transaction 8458 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2036-02-28 transaction 8459 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2036-02-29 transaction 8460 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2036-03-01 transaction 8461 399 1 399:39a -1 2036-03-02 transaction 8462 399:39a:39b 1 399:39a:39b:39c -1 2036-03-03 transaction 8463 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2036-03-04 transaction 8464 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2036-03-05 transaction 8465 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2036-03-06 transaction 8466 3a3 1 3a3:3a4 -1 2036-03-07 transaction 8467 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2036-03-08 transaction 8468 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2036-03-09 transaction 8469 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2036-03-10 transaction 8470 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2036-03-11 transaction 8471 3ad 1 3ad:3ae -1 2036-03-12 transaction 8472 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2036-03-13 transaction 8473 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2036-03-14 transaction 8474 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2036-03-15 transaction 8475 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2036-03-16 transaction 8476 3b7 1 3b7:3b8 -1 2036-03-17 transaction 8477 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2036-03-18 transaction 8478 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2036-03-19 transaction 8479 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2036-03-20 transaction 8480 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2036-03-21 transaction 8481 3c1 1 3c1:3c2 -1 2036-03-22 transaction 8482 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2036-03-23 transaction 8483 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2036-03-24 transaction 8484 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2036-03-25 transaction 8485 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2036-03-26 transaction 8486 3cb 1 3cb:3cc -1 2036-03-27 transaction 8487 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2036-03-28 transaction 8488 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2036-03-29 transaction 8489 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2036-03-30 transaction 8490 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2036-03-31 transaction 8491 3d5 1 3d5:3d6 -1 2036-04-01 transaction 8492 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2036-04-02 transaction 8493 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2036-04-03 transaction 8494 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2036-04-04 transaction 8495 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2036-04-05 transaction 8496 3df 1 3df:3e0 -1 2036-04-06 transaction 8497 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2036-04-07 transaction 8498 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2036-04-08 transaction 8499 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2036-04-09 transaction 8500 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2036-04-10 transaction 8501 1 1 1:2 -1 2036-04-11 transaction 8502 1:2:3 1 1:2:3:4 -1 2036-04-12 transaction 8503 1:2:3:4:5 1 1:2:3:4:5:6 -1 2036-04-13 transaction 8504 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2036-04-14 transaction 8505 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2036-04-15 transaction 8506 b 1 b:c -1 2036-04-16 transaction 8507 b:c:d 1 b:c:d:e -1 2036-04-17 transaction 8508 b:c:d:e:f 1 b:c:d:e:f:10 -1 2036-04-18 transaction 8509 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2036-04-19 transaction 8510 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2036-04-20 transaction 8511 15 1 15:16 -1 2036-04-21 transaction 8512 15:16:17 1 15:16:17:18 -1 2036-04-22 transaction 8513 15:16:17:18:19 1 15:16:17:18:19:1a -1 2036-04-23 transaction 8514 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2036-04-24 transaction 8515 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2036-04-25 transaction 8516 1f 1 1f:20 -1 2036-04-26 transaction 8517 1f:20:21 1 1f:20:21:22 -1 2036-04-27 transaction 8518 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2036-04-28 transaction 8519 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2036-04-29 transaction 8520 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2036-04-30 transaction 8521 29 1 29:2a -1 2036-05-01 transaction 8522 29:2a:2b 1 29:2a:2b:2c -1 2036-05-02 transaction 8523 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2036-05-03 transaction 8524 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2036-05-04 transaction 8525 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2036-05-05 transaction 8526 33 1 33:34 -1 2036-05-06 transaction 8527 33:34:35 1 33:34:35:36 -1 2036-05-07 transaction 8528 33:34:35:36:37 1 33:34:35:36:37:38 -1 2036-05-08 transaction 8529 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2036-05-09 transaction 8530 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2036-05-10 transaction 8531 3d 1 3d:3e -1 2036-05-11 transaction 8532 3d:3e:3f 1 3d:3e:3f:40 -1 2036-05-12 transaction 8533 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2036-05-13 transaction 8534 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2036-05-14 transaction 8535 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2036-05-15 transaction 8536 47 1 47:48 -1 2036-05-16 transaction 8537 47:48:49 1 47:48:49:4a -1 2036-05-17 transaction 8538 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2036-05-18 transaction 8539 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2036-05-19 transaction 8540 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2036-05-20 transaction 8541 51 1 51:52 -1 2036-05-21 transaction 8542 51:52:53 1 51:52:53:54 -1 2036-05-22 transaction 8543 51:52:53:54:55 1 51:52:53:54:55:56 -1 2036-05-23 transaction 8544 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2036-05-24 transaction 8545 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2036-05-25 transaction 8546 5b 1 5b:5c -1 2036-05-26 transaction 8547 5b:5c:5d 1 5b:5c:5d:5e -1 2036-05-27 transaction 8548 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2036-05-28 transaction 8549 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2036-05-29 transaction 8550 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2036-05-30 transaction 8551 65 1 65:66 -1 2036-05-31 transaction 8552 65:66:67 1 65:66:67:68 -1 2036-06-01 transaction 8553 65:66:67:68:69 1 65:66:67:68:69:6a -1 2036-06-02 transaction 8554 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2036-06-03 transaction 8555 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2036-06-04 transaction 8556 6f 1 6f:70 -1 2036-06-05 transaction 8557 6f:70:71 1 6f:70:71:72 -1 2036-06-06 transaction 8558 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2036-06-07 transaction 8559 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2036-06-08 transaction 8560 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2036-06-09 transaction 8561 79 1 79:7a -1 2036-06-10 transaction 8562 79:7a:7b 1 79:7a:7b:7c -1 2036-06-11 transaction 8563 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2036-06-12 transaction 8564 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2036-06-13 transaction 8565 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2036-06-14 transaction 8566 83 1 83:84 -1 2036-06-15 transaction 8567 83:84:85 1 83:84:85:86 -1 2036-06-16 transaction 8568 83:84:85:86:87 1 83:84:85:86:87:88 -1 2036-06-17 transaction 8569 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2036-06-18 transaction 8570 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2036-06-19 transaction 8571 8d 1 8d:8e -1 2036-06-20 transaction 8572 8d:8e:8f 1 8d:8e:8f:90 -1 2036-06-21 transaction 8573 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2036-06-22 transaction 8574 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2036-06-23 transaction 8575 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2036-06-24 transaction 8576 97 1 97:98 -1 2036-06-25 transaction 8577 97:98:99 1 97:98:99:9a -1 2036-06-26 transaction 8578 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2036-06-27 transaction 8579 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2036-06-28 transaction 8580 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2036-06-29 transaction 8581 a1 1 a1:a2 -1 2036-06-30 transaction 8582 a1:a2:a3 1 a1:a2:a3:a4 -1 2036-07-01 transaction 8583 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2036-07-02 transaction 8584 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2036-07-03 transaction 8585 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2036-07-04 transaction 8586 ab 1 ab:ac -1 2036-07-05 transaction 8587 ab:ac:ad 1 ab:ac:ad:ae -1 2036-07-06 transaction 8588 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2036-07-07 transaction 8589 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2036-07-08 transaction 8590 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2036-07-09 transaction 8591 b5 1 b5:b6 -1 2036-07-10 transaction 8592 b5:b6:b7 1 b5:b6:b7:b8 -1 2036-07-11 transaction 8593 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2036-07-12 transaction 8594 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2036-07-13 transaction 8595 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2036-07-14 transaction 8596 bf 1 bf:c0 -1 2036-07-15 transaction 8597 bf:c0:c1 1 bf:c0:c1:c2 -1 2036-07-16 transaction 8598 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2036-07-17 transaction 8599 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2036-07-18 transaction 8600 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2036-07-19 transaction 8601 c9 1 c9:ca -1 2036-07-20 transaction 8602 c9:ca:cb 1 c9:ca:cb:cc -1 2036-07-21 transaction 8603 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2036-07-22 transaction 8604 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2036-07-23 transaction 8605 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2036-07-24 transaction 8606 d3 1 d3:d4 -1 2036-07-25 transaction 8607 d3:d4:d5 1 d3:d4:d5:d6 -1 2036-07-26 transaction 8608 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2036-07-27 transaction 8609 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2036-07-28 transaction 8610 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2036-07-29 transaction 8611 dd 1 dd:de -1 2036-07-30 transaction 8612 dd:de:df 1 dd:de:df:e0 -1 2036-07-31 transaction 8613 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2036-08-01 transaction 8614 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2036-08-02 transaction 8615 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2036-08-03 transaction 8616 e7 1 e7:e8 -1 2036-08-04 transaction 8617 e7:e8:e9 1 e7:e8:e9:ea -1 2036-08-05 transaction 8618 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2036-08-06 transaction 8619 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2036-08-07 transaction 8620 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2036-08-08 transaction 8621 f1 1 f1:f2 -1 2036-08-09 transaction 8622 f1:f2:f3 1 f1:f2:f3:f4 -1 2036-08-10 transaction 8623 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2036-08-11 transaction 8624 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2036-08-12 transaction 8625 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2036-08-13 transaction 8626 fb 1 fb:fc -1 2036-08-14 transaction 8627 fb:fc:fd 1 fb:fc:fd:fe -1 2036-08-15 transaction 8628 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2036-08-16 transaction 8629 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2036-08-17 transaction 8630 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2036-08-18 transaction 8631 105 1 105:106 -1 2036-08-19 transaction 8632 105:106:107 1 105:106:107:108 -1 2036-08-20 transaction 8633 105:106:107:108:109 1 105:106:107:108:109:10a -1 2036-08-21 transaction 8634 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2036-08-22 transaction 8635 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2036-08-23 transaction 8636 10f 1 10f:110 -1 2036-08-24 transaction 8637 10f:110:111 1 10f:110:111:112 -1 2036-08-25 transaction 8638 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2036-08-26 transaction 8639 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2036-08-27 transaction 8640 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2036-08-28 transaction 8641 119 1 119:11a -1 2036-08-29 transaction 8642 119:11a:11b 1 119:11a:11b:11c -1 2036-08-30 transaction 8643 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2036-08-31 transaction 8644 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2036-09-01 transaction 8645 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2036-09-02 transaction 8646 123 1 123:124 -1 2036-09-03 transaction 8647 123:124:125 1 123:124:125:126 -1 2036-09-04 transaction 8648 123:124:125:126:127 1 123:124:125:126:127:128 -1 2036-09-05 transaction 8649 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2036-09-06 transaction 8650 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2036-09-07 transaction 8651 12d 1 12d:12e -1 2036-09-08 transaction 8652 12d:12e:12f 1 12d:12e:12f:130 -1 2036-09-09 transaction 8653 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2036-09-10 transaction 8654 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2036-09-11 transaction 8655 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2036-09-12 transaction 8656 137 1 137:138 -1 2036-09-13 transaction 8657 137:138:139 1 137:138:139:13a -1 2036-09-14 transaction 8658 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2036-09-15 transaction 8659 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2036-09-16 transaction 8660 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2036-09-17 transaction 8661 141 1 141:142 -1 2036-09-18 transaction 8662 141:142:143 1 141:142:143:144 -1 2036-09-19 transaction 8663 141:142:143:144:145 1 141:142:143:144:145:146 -1 2036-09-20 transaction 8664 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2036-09-21 transaction 8665 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2036-09-22 transaction 8666 14b 1 14b:14c -1 2036-09-23 transaction 8667 14b:14c:14d 1 14b:14c:14d:14e -1 2036-09-24 transaction 8668 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2036-09-25 transaction 8669 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2036-09-26 transaction 8670 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2036-09-27 transaction 8671 155 1 155:156 -1 2036-09-28 transaction 8672 155:156:157 1 155:156:157:158 -1 2036-09-29 transaction 8673 155:156:157:158:159 1 155:156:157:158:159:15a -1 2036-09-30 transaction 8674 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2036-10-01 transaction 8675 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2036-10-02 transaction 8676 15f 1 15f:160 -1 2036-10-03 transaction 8677 15f:160:161 1 15f:160:161:162 -1 2036-10-04 transaction 8678 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2036-10-05 transaction 8679 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2036-10-06 transaction 8680 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2036-10-07 transaction 8681 169 1 169:16a -1 2036-10-08 transaction 8682 169:16a:16b 1 169:16a:16b:16c -1 2036-10-09 transaction 8683 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2036-10-10 transaction 8684 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2036-10-11 transaction 8685 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2036-10-12 transaction 8686 173 1 173:174 -1 2036-10-13 transaction 8687 173:174:175 1 173:174:175:176 -1 2036-10-14 transaction 8688 173:174:175:176:177 1 173:174:175:176:177:178 -1 2036-10-15 transaction 8689 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2036-10-16 transaction 8690 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2036-10-17 transaction 8691 17d 1 17d:17e -1 2036-10-18 transaction 8692 17d:17e:17f 1 17d:17e:17f:180 -1 2036-10-19 transaction 8693 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2036-10-20 transaction 8694 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2036-10-21 transaction 8695 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2036-10-22 transaction 8696 187 1 187:188 -1 2036-10-23 transaction 8697 187:188:189 1 187:188:189:18a -1 2036-10-24 transaction 8698 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2036-10-25 transaction 8699 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2036-10-26 transaction 8700 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2036-10-27 transaction 8701 191 1 191:192 -1 2036-10-28 transaction 8702 191:192:193 1 191:192:193:194 -1 2036-10-29 transaction 8703 191:192:193:194:195 1 191:192:193:194:195:196 -1 2036-10-30 transaction 8704 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2036-10-31 transaction 8705 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2036-11-01 transaction 8706 19b 1 19b:19c -1 2036-11-02 transaction 8707 19b:19c:19d 1 19b:19c:19d:19e -1 2036-11-03 transaction 8708 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2036-11-04 transaction 8709 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2036-11-05 transaction 8710 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2036-11-06 transaction 8711 1a5 1 1a5:1a6 -1 2036-11-07 transaction 8712 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2036-11-08 transaction 8713 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2036-11-09 transaction 8714 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2036-11-10 transaction 8715 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2036-11-11 transaction 8716 1af 1 1af:1b0 -1 2036-11-12 transaction 8717 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2036-11-13 transaction 8718 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2036-11-14 transaction 8719 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2036-11-15 transaction 8720 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2036-11-16 transaction 8721 1b9 1 1b9:1ba -1 2036-11-17 transaction 8722 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2036-11-18 transaction 8723 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2036-11-19 transaction 8724 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2036-11-20 transaction 8725 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2036-11-21 transaction 8726 1c3 1 1c3:1c4 -1 2036-11-22 transaction 8727 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2036-11-23 transaction 8728 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2036-11-24 transaction 8729 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2036-11-25 transaction 8730 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2036-11-26 transaction 8731 1cd 1 1cd:1ce -1 2036-11-27 transaction 8732 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2036-11-28 transaction 8733 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2036-11-29 transaction 8734 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2036-11-30 transaction 8735 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2036-12-01 transaction 8736 1d7 1 1d7:1d8 -1 2036-12-02 transaction 8737 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2036-12-03 transaction 8738 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2036-12-04 transaction 8739 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2036-12-05 transaction 8740 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2036-12-06 transaction 8741 1e1 1 1e1:1e2 -1 2036-12-07 transaction 8742 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2036-12-08 transaction 8743 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2036-12-09 transaction 8744 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2036-12-10 transaction 8745 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2036-12-11 transaction 8746 1eb 1 1eb:1ec -1 2036-12-12 transaction 8747 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2036-12-13 transaction 8748 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2036-12-14 transaction 8749 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2036-12-15 transaction 8750 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2036-12-16 transaction 8751 1f5 1 1f5:1f6 -1 2036-12-17 transaction 8752 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2036-12-18 transaction 8753 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2036-12-19 transaction 8754 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2036-12-20 transaction 8755 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2036-12-21 transaction 8756 1ff 1 1ff:200 -1 2036-12-22 transaction 8757 1ff:200:201 1 1ff:200:201:202 -1 2036-12-23 transaction 8758 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2036-12-24 transaction 8759 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2036-12-25 transaction 8760 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2036-12-26 transaction 8761 209 1 209:20a -1 2036-12-27 transaction 8762 209:20a:20b 1 209:20a:20b:20c -1 2036-12-28 transaction 8763 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2036-12-29 transaction 8764 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2036-12-30 transaction 8765 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2036-12-31 transaction 8766 213 1 213:214 -1 2037-01-01 transaction 8767 213:214:215 1 213:214:215:216 -1 2037-01-02 transaction 8768 213:214:215:216:217 1 213:214:215:216:217:218 -1 2037-01-03 transaction 8769 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2037-01-04 transaction 8770 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2037-01-05 transaction 8771 21d 1 21d:21e -1 2037-01-06 transaction 8772 21d:21e:21f 1 21d:21e:21f:220 -1 2037-01-07 transaction 8773 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2037-01-08 transaction 8774 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2037-01-09 transaction 8775 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2037-01-10 transaction 8776 227 1 227:228 -1 2037-01-11 transaction 8777 227:228:229 1 227:228:229:22a -1 2037-01-12 transaction 8778 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2037-01-13 transaction 8779 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2037-01-14 transaction 8780 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2037-01-15 transaction 8781 231 1 231:232 -1 2037-01-16 transaction 8782 231:232:233 1 231:232:233:234 -1 2037-01-17 transaction 8783 231:232:233:234:235 1 231:232:233:234:235:236 -1 2037-01-18 transaction 8784 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2037-01-19 transaction 8785 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2037-01-20 transaction 8786 23b 1 23b:23c -1 2037-01-21 transaction 8787 23b:23c:23d 1 23b:23c:23d:23e -1 2037-01-22 transaction 8788 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2037-01-23 transaction 8789 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2037-01-24 transaction 8790 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2037-01-25 transaction 8791 245 1 245:246 -1 2037-01-26 transaction 8792 245:246:247 1 245:246:247:248 -1 2037-01-27 transaction 8793 245:246:247:248:249 1 245:246:247:248:249:24a -1 2037-01-28 transaction 8794 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2037-01-29 transaction 8795 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2037-01-30 transaction 8796 24f 1 24f:250 -1 2037-01-31 transaction 8797 24f:250:251 1 24f:250:251:252 -1 2037-02-01 transaction 8798 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2037-02-02 transaction 8799 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2037-02-03 transaction 8800 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2037-02-04 transaction 8801 259 1 259:25a -1 2037-02-05 transaction 8802 259:25a:25b 1 259:25a:25b:25c -1 2037-02-06 transaction 8803 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2037-02-07 transaction 8804 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2037-02-08 transaction 8805 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2037-02-09 transaction 8806 263 1 263:264 -1 2037-02-10 transaction 8807 263:264:265 1 263:264:265:266 -1 2037-02-11 transaction 8808 263:264:265:266:267 1 263:264:265:266:267:268 -1 2037-02-12 transaction 8809 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2037-02-13 transaction 8810 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2037-02-14 transaction 8811 26d 1 26d:26e -1 2037-02-15 transaction 8812 26d:26e:26f 1 26d:26e:26f:270 -1 2037-02-16 transaction 8813 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2037-02-17 transaction 8814 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2037-02-18 transaction 8815 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2037-02-19 transaction 8816 277 1 277:278 -1 2037-02-20 transaction 8817 277:278:279 1 277:278:279:27a -1 2037-02-21 transaction 8818 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2037-02-22 transaction 8819 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2037-02-23 transaction 8820 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2037-02-24 transaction 8821 281 1 281:282 -1 2037-02-25 transaction 8822 281:282:283 1 281:282:283:284 -1 2037-02-26 transaction 8823 281:282:283:284:285 1 281:282:283:284:285:286 -1 2037-02-27 transaction 8824 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2037-02-28 transaction 8825 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2037-03-01 transaction 8826 28b 1 28b:28c -1 2037-03-02 transaction 8827 28b:28c:28d 1 28b:28c:28d:28e -1 2037-03-03 transaction 8828 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2037-03-04 transaction 8829 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2037-03-05 transaction 8830 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2037-03-06 transaction 8831 295 1 295:296 -1 2037-03-07 transaction 8832 295:296:297 1 295:296:297:298 -1 2037-03-08 transaction 8833 295:296:297:298:299 1 295:296:297:298:299:29a -1 2037-03-09 transaction 8834 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2037-03-10 transaction 8835 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2037-03-11 transaction 8836 29f 1 29f:2a0 -1 2037-03-12 transaction 8837 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2037-03-13 transaction 8838 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2037-03-14 transaction 8839 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2037-03-15 transaction 8840 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2037-03-16 transaction 8841 2a9 1 2a9:2aa -1 2037-03-17 transaction 8842 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2037-03-18 transaction 8843 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2037-03-19 transaction 8844 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2037-03-20 transaction 8845 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2037-03-21 transaction 8846 2b3 1 2b3:2b4 -1 2037-03-22 transaction 8847 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2037-03-23 transaction 8848 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2037-03-24 transaction 8849 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2037-03-25 transaction 8850 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2037-03-26 transaction 8851 2bd 1 2bd:2be -1 2037-03-27 transaction 8852 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2037-03-28 transaction 8853 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2037-03-29 transaction 8854 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2037-03-30 transaction 8855 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2037-03-31 transaction 8856 2c7 1 2c7:2c8 -1 2037-04-01 transaction 8857 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2037-04-02 transaction 8858 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2037-04-03 transaction 8859 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2037-04-04 transaction 8860 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2037-04-05 transaction 8861 2d1 1 2d1:2d2 -1 2037-04-06 transaction 8862 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2037-04-07 transaction 8863 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2037-04-08 transaction 8864 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2037-04-09 transaction 8865 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2037-04-10 transaction 8866 2db 1 2db:2dc -1 2037-04-11 transaction 8867 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2037-04-12 transaction 8868 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2037-04-13 transaction 8869 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2037-04-14 transaction 8870 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2037-04-15 transaction 8871 2e5 1 2e5:2e6 -1 2037-04-16 transaction 8872 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2037-04-17 transaction 8873 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2037-04-18 transaction 8874 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2037-04-19 transaction 8875 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2037-04-20 transaction 8876 2ef 1 2ef:2f0 -1 2037-04-21 transaction 8877 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2037-04-22 transaction 8878 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2037-04-23 transaction 8879 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2037-04-24 transaction 8880 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2037-04-25 transaction 8881 2f9 1 2f9:2fa -1 2037-04-26 transaction 8882 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2037-04-27 transaction 8883 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2037-04-28 transaction 8884 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2037-04-29 transaction 8885 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2037-04-30 transaction 8886 303 1 303:304 -1 2037-05-01 transaction 8887 303:304:305 1 303:304:305:306 -1 2037-05-02 transaction 8888 303:304:305:306:307 1 303:304:305:306:307:308 -1 2037-05-03 transaction 8889 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2037-05-04 transaction 8890 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2037-05-05 transaction 8891 30d 1 30d:30e -1 2037-05-06 transaction 8892 30d:30e:30f 1 30d:30e:30f:310 -1 2037-05-07 transaction 8893 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2037-05-08 transaction 8894 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2037-05-09 transaction 8895 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2037-05-10 transaction 8896 317 1 317:318 -1 2037-05-11 transaction 8897 317:318:319 1 317:318:319:31a -1 2037-05-12 transaction 8898 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2037-05-13 transaction 8899 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2037-05-14 transaction 8900 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2037-05-15 transaction 8901 321 1 321:322 -1 2037-05-16 transaction 8902 321:322:323 1 321:322:323:324 -1 2037-05-17 transaction 8903 321:322:323:324:325 1 321:322:323:324:325:326 -1 2037-05-18 transaction 8904 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2037-05-19 transaction 8905 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2037-05-20 transaction 8906 32b 1 32b:32c -1 2037-05-21 transaction 8907 32b:32c:32d 1 32b:32c:32d:32e -1 2037-05-22 transaction 8908 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2037-05-23 transaction 8909 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2037-05-24 transaction 8910 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2037-05-25 transaction 8911 335 1 335:336 -1 2037-05-26 transaction 8912 335:336:337 1 335:336:337:338 -1 2037-05-27 transaction 8913 335:336:337:338:339 1 335:336:337:338:339:33a -1 2037-05-28 transaction 8914 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2037-05-29 transaction 8915 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2037-05-30 transaction 8916 33f 1 33f:340 -1 2037-05-31 transaction 8917 33f:340:341 1 33f:340:341:342 -1 2037-06-01 transaction 8918 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2037-06-02 transaction 8919 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2037-06-03 transaction 8920 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2037-06-04 transaction 8921 349 1 349:34a -1 2037-06-05 transaction 8922 349:34a:34b 1 349:34a:34b:34c -1 2037-06-06 transaction 8923 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2037-06-07 transaction 8924 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2037-06-08 transaction 8925 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2037-06-09 transaction 8926 353 1 353:354 -1 2037-06-10 transaction 8927 353:354:355 1 353:354:355:356 -1 2037-06-11 transaction 8928 353:354:355:356:357 1 353:354:355:356:357:358 -1 2037-06-12 transaction 8929 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2037-06-13 transaction 8930 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2037-06-14 transaction 8931 35d 1 35d:35e -1 2037-06-15 transaction 8932 35d:35e:35f 1 35d:35e:35f:360 -1 2037-06-16 transaction 8933 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2037-06-17 transaction 8934 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2037-06-18 transaction 8935 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2037-06-19 transaction 8936 367 1 367:368 -1 2037-06-20 transaction 8937 367:368:369 1 367:368:369:36a -1 2037-06-21 transaction 8938 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2037-06-22 transaction 8939 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2037-06-23 transaction 8940 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2037-06-24 transaction 8941 371 1 371:372 -1 2037-06-25 transaction 8942 371:372:373 1 371:372:373:374 -1 2037-06-26 transaction 8943 371:372:373:374:375 1 371:372:373:374:375:376 -1 2037-06-27 transaction 8944 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2037-06-28 transaction 8945 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2037-06-29 transaction 8946 37b 1 37b:37c -1 2037-06-30 transaction 8947 37b:37c:37d 1 37b:37c:37d:37e -1 2037-07-01 transaction 8948 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2037-07-02 transaction 8949 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2037-07-03 transaction 8950 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2037-07-04 transaction 8951 385 1 385:386 -1 2037-07-05 transaction 8952 385:386:387 1 385:386:387:388 -1 2037-07-06 transaction 8953 385:386:387:388:389 1 385:386:387:388:389:38a -1 2037-07-07 transaction 8954 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2037-07-08 transaction 8955 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2037-07-09 transaction 8956 38f 1 38f:390 -1 2037-07-10 transaction 8957 38f:390:391 1 38f:390:391:392 -1 2037-07-11 transaction 8958 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2037-07-12 transaction 8959 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2037-07-13 transaction 8960 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2037-07-14 transaction 8961 399 1 399:39a -1 2037-07-15 transaction 8962 399:39a:39b 1 399:39a:39b:39c -1 2037-07-16 transaction 8963 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2037-07-17 transaction 8964 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2037-07-18 transaction 8965 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2037-07-19 transaction 8966 3a3 1 3a3:3a4 -1 2037-07-20 transaction 8967 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2037-07-21 transaction 8968 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2037-07-22 transaction 8969 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2037-07-23 transaction 8970 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2037-07-24 transaction 8971 3ad 1 3ad:3ae -1 2037-07-25 transaction 8972 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2037-07-26 transaction 8973 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2037-07-27 transaction 8974 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2037-07-28 transaction 8975 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2037-07-29 transaction 8976 3b7 1 3b7:3b8 -1 2037-07-30 transaction 8977 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2037-07-31 transaction 8978 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2037-08-01 transaction 8979 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2037-08-02 transaction 8980 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2037-08-03 transaction 8981 3c1 1 3c1:3c2 -1 2037-08-04 transaction 8982 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2037-08-05 transaction 8983 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2037-08-06 transaction 8984 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2037-08-07 transaction 8985 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2037-08-08 transaction 8986 3cb 1 3cb:3cc -1 2037-08-09 transaction 8987 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2037-08-10 transaction 8988 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2037-08-11 transaction 8989 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2037-08-12 transaction 8990 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2037-08-13 transaction 8991 3d5 1 3d5:3d6 -1 2037-08-14 transaction 8992 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2037-08-15 transaction 8993 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2037-08-16 transaction 8994 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2037-08-17 transaction 8995 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2037-08-18 transaction 8996 3df 1 3df:3e0 -1 2037-08-19 transaction 8997 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2037-08-20 transaction 8998 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2037-08-21 transaction 8999 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2037-08-22 transaction 9000 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2037-08-23 transaction 9001 1 1 1:2 -1 2037-08-24 transaction 9002 1:2:3 1 1:2:3:4 -1 2037-08-25 transaction 9003 1:2:3:4:5 1 1:2:3:4:5:6 -1 2037-08-26 transaction 9004 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2037-08-27 transaction 9005 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2037-08-28 transaction 9006 b 1 b:c -1 2037-08-29 transaction 9007 b:c:d 1 b:c:d:e -1 2037-08-30 transaction 9008 b:c:d:e:f 1 b:c:d:e:f:10 -1 2037-08-31 transaction 9009 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2037-09-01 transaction 9010 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2037-09-02 transaction 9011 15 1 15:16 -1 2037-09-03 transaction 9012 15:16:17 1 15:16:17:18 -1 2037-09-04 transaction 9013 15:16:17:18:19 1 15:16:17:18:19:1a -1 2037-09-05 transaction 9014 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2037-09-06 transaction 9015 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2037-09-07 transaction 9016 1f 1 1f:20 -1 2037-09-08 transaction 9017 1f:20:21 1 1f:20:21:22 -1 2037-09-09 transaction 9018 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2037-09-10 transaction 9019 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2037-09-11 transaction 9020 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2037-09-12 transaction 9021 29 1 29:2a -1 2037-09-13 transaction 9022 29:2a:2b 1 29:2a:2b:2c -1 2037-09-14 transaction 9023 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2037-09-15 transaction 9024 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2037-09-16 transaction 9025 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2037-09-17 transaction 9026 33 1 33:34 -1 2037-09-18 transaction 9027 33:34:35 1 33:34:35:36 -1 2037-09-19 transaction 9028 33:34:35:36:37 1 33:34:35:36:37:38 -1 2037-09-20 transaction 9029 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2037-09-21 transaction 9030 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2037-09-22 transaction 9031 3d 1 3d:3e -1 2037-09-23 transaction 9032 3d:3e:3f 1 3d:3e:3f:40 -1 2037-09-24 transaction 9033 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2037-09-25 transaction 9034 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2037-09-26 transaction 9035 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2037-09-27 transaction 9036 47 1 47:48 -1 2037-09-28 transaction 9037 47:48:49 1 47:48:49:4a -1 2037-09-29 transaction 9038 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2037-09-30 transaction 9039 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2037-10-01 transaction 9040 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2037-10-02 transaction 9041 51 1 51:52 -1 2037-10-03 transaction 9042 51:52:53 1 51:52:53:54 -1 2037-10-04 transaction 9043 51:52:53:54:55 1 51:52:53:54:55:56 -1 2037-10-05 transaction 9044 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2037-10-06 transaction 9045 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2037-10-07 transaction 9046 5b 1 5b:5c -1 2037-10-08 transaction 9047 5b:5c:5d 1 5b:5c:5d:5e -1 2037-10-09 transaction 9048 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2037-10-10 transaction 9049 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2037-10-11 transaction 9050 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2037-10-12 transaction 9051 65 1 65:66 -1 2037-10-13 transaction 9052 65:66:67 1 65:66:67:68 -1 2037-10-14 transaction 9053 65:66:67:68:69 1 65:66:67:68:69:6a -1 2037-10-15 transaction 9054 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2037-10-16 transaction 9055 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2037-10-17 transaction 9056 6f 1 6f:70 -1 2037-10-18 transaction 9057 6f:70:71 1 6f:70:71:72 -1 2037-10-19 transaction 9058 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2037-10-20 transaction 9059 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2037-10-21 transaction 9060 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2037-10-22 transaction 9061 79 1 79:7a -1 2037-10-23 transaction 9062 79:7a:7b 1 79:7a:7b:7c -1 2037-10-24 transaction 9063 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2037-10-25 transaction 9064 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2037-10-26 transaction 9065 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2037-10-27 transaction 9066 83 1 83:84 -1 2037-10-28 transaction 9067 83:84:85 1 83:84:85:86 -1 2037-10-29 transaction 9068 83:84:85:86:87 1 83:84:85:86:87:88 -1 2037-10-30 transaction 9069 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2037-10-31 transaction 9070 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2037-11-01 transaction 9071 8d 1 8d:8e -1 2037-11-02 transaction 9072 8d:8e:8f 1 8d:8e:8f:90 -1 2037-11-03 transaction 9073 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2037-11-04 transaction 9074 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2037-11-05 transaction 9075 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2037-11-06 transaction 9076 97 1 97:98 -1 2037-11-07 transaction 9077 97:98:99 1 97:98:99:9a -1 2037-11-08 transaction 9078 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2037-11-09 transaction 9079 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2037-11-10 transaction 9080 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2037-11-11 transaction 9081 a1 1 a1:a2 -1 2037-11-12 transaction 9082 a1:a2:a3 1 a1:a2:a3:a4 -1 2037-11-13 transaction 9083 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2037-11-14 transaction 9084 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2037-11-15 transaction 9085 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2037-11-16 transaction 9086 ab 1 ab:ac -1 2037-11-17 transaction 9087 ab:ac:ad 1 ab:ac:ad:ae -1 2037-11-18 transaction 9088 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2037-11-19 transaction 9089 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2037-11-20 transaction 9090 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2037-11-21 transaction 9091 b5 1 b5:b6 -1 2037-11-22 transaction 9092 b5:b6:b7 1 b5:b6:b7:b8 -1 2037-11-23 transaction 9093 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2037-11-24 transaction 9094 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2037-11-25 transaction 9095 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2037-11-26 transaction 9096 bf 1 bf:c0 -1 2037-11-27 transaction 9097 bf:c0:c1 1 bf:c0:c1:c2 -1 2037-11-28 transaction 9098 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2037-11-29 transaction 9099 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2037-11-30 transaction 9100 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2037-12-01 transaction 9101 c9 1 c9:ca -1 2037-12-02 transaction 9102 c9:ca:cb 1 c9:ca:cb:cc -1 2037-12-03 transaction 9103 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2037-12-04 transaction 9104 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2037-12-05 transaction 9105 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2037-12-06 transaction 9106 d3 1 d3:d4 -1 2037-12-07 transaction 9107 d3:d4:d5 1 d3:d4:d5:d6 -1 2037-12-08 transaction 9108 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2037-12-09 transaction 9109 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2037-12-10 transaction 9110 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2037-12-11 transaction 9111 dd 1 dd:de -1 2037-12-12 transaction 9112 dd:de:df 1 dd:de:df:e0 -1 2037-12-13 transaction 9113 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2037-12-14 transaction 9114 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2037-12-15 transaction 9115 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2037-12-16 transaction 9116 e7 1 e7:e8 -1 2037-12-17 transaction 9117 e7:e8:e9 1 e7:e8:e9:ea -1 2037-12-18 transaction 9118 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2037-12-19 transaction 9119 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2037-12-20 transaction 9120 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2037-12-21 transaction 9121 f1 1 f1:f2 -1 2037-12-22 transaction 9122 f1:f2:f3 1 f1:f2:f3:f4 -1 2037-12-23 transaction 9123 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2037-12-24 transaction 9124 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2037-12-25 transaction 9125 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2037-12-26 transaction 9126 fb 1 fb:fc -1 2037-12-27 transaction 9127 fb:fc:fd 1 fb:fc:fd:fe -1 2037-12-28 transaction 9128 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2037-12-29 transaction 9129 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2037-12-30 transaction 9130 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2037-12-31 transaction 9131 105 1 105:106 -1 2038-01-01 transaction 9132 105:106:107 1 105:106:107:108 -1 2038-01-02 transaction 9133 105:106:107:108:109 1 105:106:107:108:109:10a -1 2038-01-03 transaction 9134 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2038-01-04 transaction 9135 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2038-01-05 transaction 9136 10f 1 10f:110 -1 2038-01-06 transaction 9137 10f:110:111 1 10f:110:111:112 -1 2038-01-07 transaction 9138 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2038-01-08 transaction 9139 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2038-01-09 transaction 9140 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2038-01-10 transaction 9141 119 1 119:11a -1 2038-01-11 transaction 9142 119:11a:11b 1 119:11a:11b:11c -1 2038-01-12 transaction 9143 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2038-01-13 transaction 9144 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2038-01-14 transaction 9145 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2038-01-15 transaction 9146 123 1 123:124 -1 2038-01-16 transaction 9147 123:124:125 1 123:124:125:126 -1 2038-01-17 transaction 9148 123:124:125:126:127 1 123:124:125:126:127:128 -1 2038-01-18 transaction 9149 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2038-01-19 transaction 9150 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2038-01-20 transaction 9151 12d 1 12d:12e -1 2038-01-21 transaction 9152 12d:12e:12f 1 12d:12e:12f:130 -1 2038-01-22 transaction 9153 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2038-01-23 transaction 9154 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2038-01-24 transaction 9155 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2038-01-25 transaction 9156 137 1 137:138 -1 2038-01-26 transaction 9157 137:138:139 1 137:138:139:13a -1 2038-01-27 transaction 9158 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2038-01-28 transaction 9159 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2038-01-29 transaction 9160 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2038-01-30 transaction 9161 141 1 141:142 -1 2038-01-31 transaction 9162 141:142:143 1 141:142:143:144 -1 2038-02-01 transaction 9163 141:142:143:144:145 1 141:142:143:144:145:146 -1 2038-02-02 transaction 9164 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2038-02-03 transaction 9165 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2038-02-04 transaction 9166 14b 1 14b:14c -1 2038-02-05 transaction 9167 14b:14c:14d 1 14b:14c:14d:14e -1 2038-02-06 transaction 9168 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2038-02-07 transaction 9169 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2038-02-08 transaction 9170 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2038-02-09 transaction 9171 155 1 155:156 -1 2038-02-10 transaction 9172 155:156:157 1 155:156:157:158 -1 2038-02-11 transaction 9173 155:156:157:158:159 1 155:156:157:158:159:15a -1 2038-02-12 transaction 9174 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2038-02-13 transaction 9175 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2038-02-14 transaction 9176 15f 1 15f:160 -1 2038-02-15 transaction 9177 15f:160:161 1 15f:160:161:162 -1 2038-02-16 transaction 9178 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2038-02-17 transaction 9179 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2038-02-18 transaction 9180 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2038-02-19 transaction 9181 169 1 169:16a -1 2038-02-20 transaction 9182 169:16a:16b 1 169:16a:16b:16c -1 2038-02-21 transaction 9183 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2038-02-22 transaction 9184 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2038-02-23 transaction 9185 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2038-02-24 transaction 9186 173 1 173:174 -1 2038-02-25 transaction 9187 173:174:175 1 173:174:175:176 -1 2038-02-26 transaction 9188 173:174:175:176:177 1 173:174:175:176:177:178 -1 2038-02-27 transaction 9189 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2038-02-28 transaction 9190 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2038-03-01 transaction 9191 17d 1 17d:17e -1 2038-03-02 transaction 9192 17d:17e:17f 1 17d:17e:17f:180 -1 2038-03-03 transaction 9193 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2038-03-04 transaction 9194 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2038-03-05 transaction 9195 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2038-03-06 transaction 9196 187 1 187:188 -1 2038-03-07 transaction 9197 187:188:189 1 187:188:189:18a -1 2038-03-08 transaction 9198 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2038-03-09 transaction 9199 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2038-03-10 transaction 9200 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2038-03-11 transaction 9201 191 1 191:192 -1 2038-03-12 transaction 9202 191:192:193 1 191:192:193:194 -1 2038-03-13 transaction 9203 191:192:193:194:195 1 191:192:193:194:195:196 -1 2038-03-14 transaction 9204 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2038-03-15 transaction 9205 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2038-03-16 transaction 9206 19b 1 19b:19c -1 2038-03-17 transaction 9207 19b:19c:19d 1 19b:19c:19d:19e -1 2038-03-18 transaction 9208 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2038-03-19 transaction 9209 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2038-03-20 transaction 9210 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2038-03-21 transaction 9211 1a5 1 1a5:1a6 -1 2038-03-22 transaction 9212 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2038-03-23 transaction 9213 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2038-03-24 transaction 9214 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2038-03-25 transaction 9215 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2038-03-26 transaction 9216 1af 1 1af:1b0 -1 2038-03-27 transaction 9217 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2038-03-28 transaction 9218 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2038-03-29 transaction 9219 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2038-03-30 transaction 9220 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2038-03-31 transaction 9221 1b9 1 1b9:1ba -1 2038-04-01 transaction 9222 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2038-04-02 transaction 9223 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2038-04-03 transaction 9224 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2038-04-04 transaction 9225 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2038-04-05 transaction 9226 1c3 1 1c3:1c4 -1 2038-04-06 transaction 9227 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2038-04-07 transaction 9228 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2038-04-08 transaction 9229 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2038-04-09 transaction 9230 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2038-04-10 transaction 9231 1cd 1 1cd:1ce -1 2038-04-11 transaction 9232 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2038-04-12 transaction 9233 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2038-04-13 transaction 9234 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2038-04-14 transaction 9235 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2038-04-15 transaction 9236 1d7 1 1d7:1d8 -1 2038-04-16 transaction 9237 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2038-04-17 transaction 9238 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2038-04-18 transaction 9239 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2038-04-19 transaction 9240 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2038-04-20 transaction 9241 1e1 1 1e1:1e2 -1 2038-04-21 transaction 9242 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2038-04-22 transaction 9243 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2038-04-23 transaction 9244 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2038-04-24 transaction 9245 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2038-04-25 transaction 9246 1eb 1 1eb:1ec -1 2038-04-26 transaction 9247 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2038-04-27 transaction 9248 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2038-04-28 transaction 9249 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2038-04-29 transaction 9250 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2038-04-30 transaction 9251 1f5 1 1f5:1f6 -1 2038-05-01 transaction 9252 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2038-05-02 transaction 9253 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2038-05-03 transaction 9254 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2038-05-04 transaction 9255 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2038-05-05 transaction 9256 1ff 1 1ff:200 -1 2038-05-06 transaction 9257 1ff:200:201 1 1ff:200:201:202 -1 2038-05-07 transaction 9258 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2038-05-08 transaction 9259 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2038-05-09 transaction 9260 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2038-05-10 transaction 9261 209 1 209:20a -1 2038-05-11 transaction 9262 209:20a:20b 1 209:20a:20b:20c -1 2038-05-12 transaction 9263 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2038-05-13 transaction 9264 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2038-05-14 transaction 9265 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2038-05-15 transaction 9266 213 1 213:214 -1 2038-05-16 transaction 9267 213:214:215 1 213:214:215:216 -1 2038-05-17 transaction 9268 213:214:215:216:217 1 213:214:215:216:217:218 -1 2038-05-18 transaction 9269 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2038-05-19 transaction 9270 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2038-05-20 transaction 9271 21d 1 21d:21e -1 2038-05-21 transaction 9272 21d:21e:21f 1 21d:21e:21f:220 -1 2038-05-22 transaction 9273 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2038-05-23 transaction 9274 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2038-05-24 transaction 9275 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2038-05-25 transaction 9276 227 1 227:228 -1 2038-05-26 transaction 9277 227:228:229 1 227:228:229:22a -1 2038-05-27 transaction 9278 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2038-05-28 transaction 9279 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2038-05-29 transaction 9280 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2038-05-30 transaction 9281 231 1 231:232 -1 2038-05-31 transaction 9282 231:232:233 1 231:232:233:234 -1 2038-06-01 transaction 9283 231:232:233:234:235 1 231:232:233:234:235:236 -1 2038-06-02 transaction 9284 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2038-06-03 transaction 9285 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2038-06-04 transaction 9286 23b 1 23b:23c -1 2038-06-05 transaction 9287 23b:23c:23d 1 23b:23c:23d:23e -1 2038-06-06 transaction 9288 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2038-06-07 transaction 9289 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2038-06-08 transaction 9290 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2038-06-09 transaction 9291 245 1 245:246 -1 2038-06-10 transaction 9292 245:246:247 1 245:246:247:248 -1 2038-06-11 transaction 9293 245:246:247:248:249 1 245:246:247:248:249:24a -1 2038-06-12 transaction 9294 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2038-06-13 transaction 9295 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2038-06-14 transaction 9296 24f 1 24f:250 -1 2038-06-15 transaction 9297 24f:250:251 1 24f:250:251:252 -1 2038-06-16 transaction 9298 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2038-06-17 transaction 9299 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2038-06-18 transaction 9300 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2038-06-19 transaction 9301 259 1 259:25a -1 2038-06-20 transaction 9302 259:25a:25b 1 259:25a:25b:25c -1 2038-06-21 transaction 9303 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2038-06-22 transaction 9304 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2038-06-23 transaction 9305 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2038-06-24 transaction 9306 263 1 263:264 -1 2038-06-25 transaction 9307 263:264:265 1 263:264:265:266 -1 2038-06-26 transaction 9308 263:264:265:266:267 1 263:264:265:266:267:268 -1 2038-06-27 transaction 9309 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2038-06-28 transaction 9310 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2038-06-29 transaction 9311 26d 1 26d:26e -1 2038-06-30 transaction 9312 26d:26e:26f 1 26d:26e:26f:270 -1 2038-07-01 transaction 9313 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2038-07-02 transaction 9314 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2038-07-03 transaction 9315 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2038-07-04 transaction 9316 277 1 277:278 -1 2038-07-05 transaction 9317 277:278:279 1 277:278:279:27a -1 2038-07-06 transaction 9318 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2038-07-07 transaction 9319 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2038-07-08 transaction 9320 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2038-07-09 transaction 9321 281 1 281:282 -1 2038-07-10 transaction 9322 281:282:283 1 281:282:283:284 -1 2038-07-11 transaction 9323 281:282:283:284:285 1 281:282:283:284:285:286 -1 2038-07-12 transaction 9324 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2038-07-13 transaction 9325 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2038-07-14 transaction 9326 28b 1 28b:28c -1 2038-07-15 transaction 9327 28b:28c:28d 1 28b:28c:28d:28e -1 2038-07-16 transaction 9328 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2038-07-17 transaction 9329 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2038-07-18 transaction 9330 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2038-07-19 transaction 9331 295 1 295:296 -1 2038-07-20 transaction 9332 295:296:297 1 295:296:297:298 -1 2038-07-21 transaction 9333 295:296:297:298:299 1 295:296:297:298:299:29a -1 2038-07-22 transaction 9334 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2038-07-23 transaction 9335 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2038-07-24 transaction 9336 29f 1 29f:2a0 -1 2038-07-25 transaction 9337 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2038-07-26 transaction 9338 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2038-07-27 transaction 9339 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2038-07-28 transaction 9340 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2038-07-29 transaction 9341 2a9 1 2a9:2aa -1 2038-07-30 transaction 9342 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2038-07-31 transaction 9343 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2038-08-01 transaction 9344 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2038-08-02 transaction 9345 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2038-08-03 transaction 9346 2b3 1 2b3:2b4 -1 2038-08-04 transaction 9347 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2038-08-05 transaction 9348 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2038-08-06 transaction 9349 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2038-08-07 transaction 9350 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2038-08-08 transaction 9351 2bd 1 2bd:2be -1 2038-08-09 transaction 9352 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2038-08-10 transaction 9353 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2038-08-11 transaction 9354 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2038-08-12 transaction 9355 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2038-08-13 transaction 9356 2c7 1 2c7:2c8 -1 2038-08-14 transaction 9357 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2038-08-15 transaction 9358 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2038-08-16 transaction 9359 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2038-08-17 transaction 9360 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2038-08-18 transaction 9361 2d1 1 2d1:2d2 -1 2038-08-19 transaction 9362 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2038-08-20 transaction 9363 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2038-08-21 transaction 9364 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2038-08-22 transaction 9365 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2038-08-23 transaction 9366 2db 1 2db:2dc -1 2038-08-24 transaction 9367 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2038-08-25 transaction 9368 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2038-08-26 transaction 9369 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2038-08-27 transaction 9370 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2038-08-28 transaction 9371 2e5 1 2e5:2e6 -1 2038-08-29 transaction 9372 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2038-08-30 transaction 9373 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2038-08-31 transaction 9374 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2038-09-01 transaction 9375 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2038-09-02 transaction 9376 2ef 1 2ef:2f0 -1 2038-09-03 transaction 9377 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2038-09-04 transaction 9378 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2038-09-05 transaction 9379 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2038-09-06 transaction 9380 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2038-09-07 transaction 9381 2f9 1 2f9:2fa -1 2038-09-08 transaction 9382 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2038-09-09 transaction 9383 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2038-09-10 transaction 9384 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2038-09-11 transaction 9385 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2038-09-12 transaction 9386 303 1 303:304 -1 2038-09-13 transaction 9387 303:304:305 1 303:304:305:306 -1 2038-09-14 transaction 9388 303:304:305:306:307 1 303:304:305:306:307:308 -1 2038-09-15 transaction 9389 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2038-09-16 transaction 9390 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2038-09-17 transaction 9391 30d 1 30d:30e -1 2038-09-18 transaction 9392 30d:30e:30f 1 30d:30e:30f:310 -1 2038-09-19 transaction 9393 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2038-09-20 transaction 9394 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2038-09-21 transaction 9395 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2038-09-22 transaction 9396 317 1 317:318 -1 2038-09-23 transaction 9397 317:318:319 1 317:318:319:31a -1 2038-09-24 transaction 9398 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2038-09-25 transaction 9399 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2038-09-26 transaction 9400 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2038-09-27 transaction 9401 321 1 321:322 -1 2038-09-28 transaction 9402 321:322:323 1 321:322:323:324 -1 2038-09-29 transaction 9403 321:322:323:324:325 1 321:322:323:324:325:326 -1 2038-09-30 transaction 9404 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2038-10-01 transaction 9405 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2038-10-02 transaction 9406 32b 1 32b:32c -1 2038-10-03 transaction 9407 32b:32c:32d 1 32b:32c:32d:32e -1 2038-10-04 transaction 9408 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2038-10-05 transaction 9409 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2038-10-06 transaction 9410 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2038-10-07 transaction 9411 335 1 335:336 -1 2038-10-08 transaction 9412 335:336:337 1 335:336:337:338 -1 2038-10-09 transaction 9413 335:336:337:338:339 1 335:336:337:338:339:33a -1 2038-10-10 transaction 9414 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2038-10-11 transaction 9415 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2038-10-12 transaction 9416 33f 1 33f:340 -1 2038-10-13 transaction 9417 33f:340:341 1 33f:340:341:342 -1 2038-10-14 transaction 9418 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2038-10-15 transaction 9419 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2038-10-16 transaction 9420 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2038-10-17 transaction 9421 349 1 349:34a -1 2038-10-18 transaction 9422 349:34a:34b 1 349:34a:34b:34c -1 2038-10-19 transaction 9423 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2038-10-20 transaction 9424 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2038-10-21 transaction 9425 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2038-10-22 transaction 9426 353 1 353:354 -1 2038-10-23 transaction 9427 353:354:355 1 353:354:355:356 -1 2038-10-24 transaction 9428 353:354:355:356:357 1 353:354:355:356:357:358 -1 2038-10-25 transaction 9429 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2038-10-26 transaction 9430 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2038-10-27 transaction 9431 35d 1 35d:35e -1 2038-10-28 transaction 9432 35d:35e:35f 1 35d:35e:35f:360 -1 2038-10-29 transaction 9433 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2038-10-30 transaction 9434 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2038-10-31 transaction 9435 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2038-11-01 transaction 9436 367 1 367:368 -1 2038-11-02 transaction 9437 367:368:369 1 367:368:369:36a -1 2038-11-03 transaction 9438 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2038-11-04 transaction 9439 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2038-11-05 transaction 9440 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2038-11-06 transaction 9441 371 1 371:372 -1 2038-11-07 transaction 9442 371:372:373 1 371:372:373:374 -1 2038-11-08 transaction 9443 371:372:373:374:375 1 371:372:373:374:375:376 -1 2038-11-09 transaction 9444 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2038-11-10 transaction 9445 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2038-11-11 transaction 9446 37b 1 37b:37c -1 2038-11-12 transaction 9447 37b:37c:37d 1 37b:37c:37d:37e -1 2038-11-13 transaction 9448 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2038-11-14 transaction 9449 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2038-11-15 transaction 9450 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2038-11-16 transaction 9451 385 1 385:386 -1 2038-11-17 transaction 9452 385:386:387 1 385:386:387:388 -1 2038-11-18 transaction 9453 385:386:387:388:389 1 385:386:387:388:389:38a -1 2038-11-19 transaction 9454 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2038-11-20 transaction 9455 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2038-11-21 transaction 9456 38f 1 38f:390 -1 2038-11-22 transaction 9457 38f:390:391 1 38f:390:391:392 -1 2038-11-23 transaction 9458 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2038-11-24 transaction 9459 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2038-11-25 transaction 9460 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2038-11-26 transaction 9461 399 1 399:39a -1 2038-11-27 transaction 9462 399:39a:39b 1 399:39a:39b:39c -1 2038-11-28 transaction 9463 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2038-11-29 transaction 9464 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2038-11-30 transaction 9465 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2038-12-01 transaction 9466 3a3 1 3a3:3a4 -1 2038-12-02 transaction 9467 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2038-12-03 transaction 9468 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2038-12-04 transaction 9469 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2038-12-05 transaction 9470 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2038-12-06 transaction 9471 3ad 1 3ad:3ae -1 2038-12-07 transaction 9472 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2038-12-08 transaction 9473 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2038-12-09 transaction 9474 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2038-12-10 transaction 9475 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2038-12-11 transaction 9476 3b7 1 3b7:3b8 -1 2038-12-12 transaction 9477 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2038-12-13 transaction 9478 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2038-12-14 transaction 9479 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2038-12-15 transaction 9480 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2038-12-16 transaction 9481 3c1 1 3c1:3c2 -1 2038-12-17 transaction 9482 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2038-12-18 transaction 9483 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2038-12-19 transaction 9484 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2038-12-20 transaction 9485 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2038-12-21 transaction 9486 3cb 1 3cb:3cc -1 2038-12-22 transaction 9487 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2038-12-23 transaction 9488 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2038-12-24 transaction 9489 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2038-12-25 transaction 9490 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2038-12-26 transaction 9491 3d5 1 3d5:3d6 -1 2038-12-27 transaction 9492 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2038-12-28 transaction 9493 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2038-12-29 transaction 9494 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2038-12-30 transaction 9495 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2038-12-31 transaction 9496 3df 1 3df:3e0 -1 2039-01-01 transaction 9497 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2039-01-02 transaction 9498 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2039-01-03 transaction 9499 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2039-01-04 transaction 9500 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 2039-01-05 transaction 9501 1 1 1:2 -1 2039-01-06 transaction 9502 1:2:3 1 1:2:3:4 -1 2039-01-07 transaction 9503 1:2:3:4:5 1 1:2:3:4:5:6 -1 2039-01-08 transaction 9504 1:2:3:4:5:6:7 1 1:2:3:4:5:6:7:8 -1 2039-01-09 transaction 9505 1:2:3:4:5:6:7:8:9 1 1:2:3:4:5:6:7:8:9:a -1 2039-01-10 transaction 9506 b 1 b:c -1 2039-01-11 transaction 9507 b:c:d 1 b:c:d:e -1 2039-01-12 transaction 9508 b:c:d:e:f 1 b:c:d:e:f:10 -1 2039-01-13 transaction 9509 b:c:d:e:f:10:11 1 b:c:d:e:f:10:11:12 -1 2039-01-14 transaction 9510 b:c:d:e:f:10:11:12:13 1 b:c:d:e:f:10:11:12:13:14 -1 2039-01-15 transaction 9511 15 1 15:16 -1 2039-01-16 transaction 9512 15:16:17 1 15:16:17:18 -1 2039-01-17 transaction 9513 15:16:17:18:19 1 15:16:17:18:19:1a -1 2039-01-18 transaction 9514 15:16:17:18:19:1a:1b 1 15:16:17:18:19:1a:1b:1c -1 2039-01-19 transaction 9515 15:16:17:18:19:1a:1b:1c:1d 1 15:16:17:18:19:1a:1b:1c:1d:1e -1 2039-01-20 transaction 9516 1f 1 1f:20 -1 2039-01-21 transaction 9517 1f:20:21 1 1f:20:21:22 -1 2039-01-22 transaction 9518 1f:20:21:22:23 1 1f:20:21:22:23:24 -1 2039-01-23 transaction 9519 1f:20:21:22:23:24:25 1 1f:20:21:22:23:24:25:26 -1 2039-01-24 transaction 9520 1f:20:21:22:23:24:25:26:27 1 1f:20:21:22:23:24:25:26:27:28 -1 2039-01-25 transaction 9521 29 1 29:2a -1 2039-01-26 transaction 9522 29:2a:2b 1 29:2a:2b:2c -1 2039-01-27 transaction 9523 29:2a:2b:2c:2d 1 29:2a:2b:2c:2d:2e -1 2039-01-28 transaction 9524 29:2a:2b:2c:2d:2e:2f 1 29:2a:2b:2c:2d:2e:2f:30 -1 2039-01-29 transaction 9525 29:2a:2b:2c:2d:2e:2f:30:31 1 29:2a:2b:2c:2d:2e:2f:30:31:32 -1 2039-01-30 transaction 9526 33 1 33:34 -1 2039-01-31 transaction 9527 33:34:35 1 33:34:35:36 -1 2039-02-01 transaction 9528 33:34:35:36:37 1 33:34:35:36:37:38 -1 2039-02-02 transaction 9529 33:34:35:36:37:38:39 1 33:34:35:36:37:38:39:3a -1 2039-02-03 transaction 9530 33:34:35:36:37:38:39:3a:3b 1 33:34:35:36:37:38:39:3a:3b:3c -1 2039-02-04 transaction 9531 3d 1 3d:3e -1 2039-02-05 transaction 9532 3d:3e:3f 1 3d:3e:3f:40 -1 2039-02-06 transaction 9533 3d:3e:3f:40:41 1 3d:3e:3f:40:41:42 -1 2039-02-07 transaction 9534 3d:3e:3f:40:41:42:43 1 3d:3e:3f:40:41:42:43:44 -1 2039-02-08 transaction 9535 3d:3e:3f:40:41:42:43:44:45 1 3d:3e:3f:40:41:42:43:44:45:46 -1 2039-02-09 transaction 9536 47 1 47:48 -1 2039-02-10 transaction 9537 47:48:49 1 47:48:49:4a -1 2039-02-11 transaction 9538 47:48:49:4a:4b 1 47:48:49:4a:4b:4c -1 2039-02-12 transaction 9539 47:48:49:4a:4b:4c:4d 1 47:48:49:4a:4b:4c:4d:4e -1 2039-02-13 transaction 9540 47:48:49:4a:4b:4c:4d:4e:4f 1 47:48:49:4a:4b:4c:4d:4e:4f:50 -1 2039-02-14 transaction 9541 51 1 51:52 -1 2039-02-15 transaction 9542 51:52:53 1 51:52:53:54 -1 2039-02-16 transaction 9543 51:52:53:54:55 1 51:52:53:54:55:56 -1 2039-02-17 transaction 9544 51:52:53:54:55:56:57 1 51:52:53:54:55:56:57:58 -1 2039-02-18 transaction 9545 51:52:53:54:55:56:57:58:59 1 51:52:53:54:55:56:57:58:59:5a -1 2039-02-19 transaction 9546 5b 1 5b:5c -1 2039-02-20 transaction 9547 5b:5c:5d 1 5b:5c:5d:5e -1 2039-02-21 transaction 9548 5b:5c:5d:5e:5f 1 5b:5c:5d:5e:5f:60 -1 2039-02-22 transaction 9549 5b:5c:5d:5e:5f:60:61 1 5b:5c:5d:5e:5f:60:61:62 -1 2039-02-23 transaction 9550 5b:5c:5d:5e:5f:60:61:62:63 1 5b:5c:5d:5e:5f:60:61:62:63:64 -1 2039-02-24 transaction 9551 65 1 65:66 -1 2039-02-25 transaction 9552 65:66:67 1 65:66:67:68 -1 2039-02-26 transaction 9553 65:66:67:68:69 1 65:66:67:68:69:6a -1 2039-02-27 transaction 9554 65:66:67:68:69:6a:6b 1 65:66:67:68:69:6a:6b:6c -1 2039-02-28 transaction 9555 65:66:67:68:69:6a:6b:6c:6d 1 65:66:67:68:69:6a:6b:6c:6d:6e -1 2039-03-01 transaction 9556 6f 1 6f:70 -1 2039-03-02 transaction 9557 6f:70:71 1 6f:70:71:72 -1 2039-03-03 transaction 9558 6f:70:71:72:73 1 6f:70:71:72:73:74 -1 2039-03-04 transaction 9559 6f:70:71:72:73:74:75 1 6f:70:71:72:73:74:75:76 -1 2039-03-05 transaction 9560 6f:70:71:72:73:74:75:76:77 1 6f:70:71:72:73:74:75:76:77:78 -1 2039-03-06 transaction 9561 79 1 79:7a -1 2039-03-07 transaction 9562 79:7a:7b 1 79:7a:7b:7c -1 2039-03-08 transaction 9563 79:7a:7b:7c:7d 1 79:7a:7b:7c:7d:7e -1 2039-03-09 transaction 9564 79:7a:7b:7c:7d:7e:7f 1 79:7a:7b:7c:7d:7e:7f:80 -1 2039-03-10 transaction 9565 79:7a:7b:7c:7d:7e:7f:80:81 1 79:7a:7b:7c:7d:7e:7f:80:81:82 -1 2039-03-11 transaction 9566 83 1 83:84 -1 2039-03-12 transaction 9567 83:84:85 1 83:84:85:86 -1 2039-03-13 transaction 9568 83:84:85:86:87 1 83:84:85:86:87:88 -1 2039-03-14 transaction 9569 83:84:85:86:87:88:89 1 83:84:85:86:87:88:89:8a -1 2039-03-15 transaction 9570 83:84:85:86:87:88:89:8a:8b 1 83:84:85:86:87:88:89:8a:8b:8c -1 2039-03-16 transaction 9571 8d 1 8d:8e -1 2039-03-17 transaction 9572 8d:8e:8f 1 8d:8e:8f:90 -1 2039-03-18 transaction 9573 8d:8e:8f:90:91 1 8d:8e:8f:90:91:92 -1 2039-03-19 transaction 9574 8d:8e:8f:90:91:92:93 1 8d:8e:8f:90:91:92:93:94 -1 2039-03-20 transaction 9575 8d:8e:8f:90:91:92:93:94:95 1 8d:8e:8f:90:91:92:93:94:95:96 -1 2039-03-21 transaction 9576 97 1 97:98 -1 2039-03-22 transaction 9577 97:98:99 1 97:98:99:9a -1 2039-03-23 transaction 9578 97:98:99:9a:9b 1 97:98:99:9a:9b:9c -1 2039-03-24 transaction 9579 97:98:99:9a:9b:9c:9d 1 97:98:99:9a:9b:9c:9d:9e -1 2039-03-25 transaction 9580 97:98:99:9a:9b:9c:9d:9e:9f 1 97:98:99:9a:9b:9c:9d:9e:9f:a0 -1 2039-03-26 transaction 9581 a1 1 a1:a2 -1 2039-03-27 transaction 9582 a1:a2:a3 1 a1:a2:a3:a4 -1 2039-03-28 transaction 9583 a1:a2:a3:a4:a5 1 a1:a2:a3:a4:a5:a6 -1 2039-03-29 transaction 9584 a1:a2:a3:a4:a5:a6:a7 1 a1:a2:a3:a4:a5:a6:a7:a8 -1 2039-03-30 transaction 9585 a1:a2:a3:a4:a5:a6:a7:a8:a9 1 a1:a2:a3:a4:a5:a6:a7:a8:a9:aa -1 2039-03-31 transaction 9586 ab 1 ab:ac -1 2039-04-01 transaction 9587 ab:ac:ad 1 ab:ac:ad:ae -1 2039-04-02 transaction 9588 ab:ac:ad:ae:af 1 ab:ac:ad:ae:af:b0 -1 2039-04-03 transaction 9589 ab:ac:ad:ae:af:b0:b1 1 ab:ac:ad:ae:af:b0:b1:b2 -1 2039-04-04 transaction 9590 ab:ac:ad:ae:af:b0:b1:b2:b3 1 ab:ac:ad:ae:af:b0:b1:b2:b3:b4 -1 2039-04-05 transaction 9591 b5 1 b5:b6 -1 2039-04-06 transaction 9592 b5:b6:b7 1 b5:b6:b7:b8 -1 2039-04-07 transaction 9593 b5:b6:b7:b8:b9 1 b5:b6:b7:b8:b9:ba -1 2039-04-08 transaction 9594 b5:b6:b7:b8:b9:ba:bb 1 b5:b6:b7:b8:b9:ba:bb:bc -1 2039-04-09 transaction 9595 b5:b6:b7:b8:b9:ba:bb:bc:bd 1 b5:b6:b7:b8:b9:ba:bb:bc:bd:be -1 2039-04-10 transaction 9596 bf 1 bf:c0 -1 2039-04-11 transaction 9597 bf:c0:c1 1 bf:c0:c1:c2 -1 2039-04-12 transaction 9598 bf:c0:c1:c2:c3 1 bf:c0:c1:c2:c3:c4 -1 2039-04-13 transaction 9599 bf:c0:c1:c2:c3:c4:c5 1 bf:c0:c1:c2:c3:c4:c5:c6 -1 2039-04-14 transaction 9600 bf:c0:c1:c2:c3:c4:c5:c6:c7 1 bf:c0:c1:c2:c3:c4:c5:c6:c7:c8 -1 2039-04-15 transaction 9601 c9 1 c9:ca -1 2039-04-16 transaction 9602 c9:ca:cb 1 c9:ca:cb:cc -1 2039-04-17 transaction 9603 c9:ca:cb:cc:cd 1 c9:ca:cb:cc:cd:ce -1 2039-04-18 transaction 9604 c9:ca:cb:cc:cd:ce:cf 1 c9:ca:cb:cc:cd:ce:cf:d0 -1 2039-04-19 transaction 9605 c9:ca:cb:cc:cd:ce:cf:d0:d1 1 c9:ca:cb:cc:cd:ce:cf:d0:d1:d2 -1 2039-04-20 transaction 9606 d3 1 d3:d4 -1 2039-04-21 transaction 9607 d3:d4:d5 1 d3:d4:d5:d6 -1 2039-04-22 transaction 9608 d3:d4:d5:d6:d7 1 d3:d4:d5:d6:d7:d8 -1 2039-04-23 transaction 9609 d3:d4:d5:d6:d7:d8:d9 1 d3:d4:d5:d6:d7:d8:d9:da -1 2039-04-24 transaction 9610 d3:d4:d5:d6:d7:d8:d9:da:db 1 d3:d4:d5:d6:d7:d8:d9:da:db:dc -1 2039-04-25 transaction 9611 dd 1 dd:de -1 2039-04-26 transaction 9612 dd:de:df 1 dd:de:df:e0 -1 2039-04-27 transaction 9613 dd:de:df:e0:e1 1 dd:de:df:e0:e1:e2 -1 2039-04-28 transaction 9614 dd:de:df:e0:e1:e2:e3 1 dd:de:df:e0:e1:e2:e3:e4 -1 2039-04-29 transaction 9615 dd:de:df:e0:e1:e2:e3:e4:e5 1 dd:de:df:e0:e1:e2:e3:e4:e5:e6 -1 2039-04-30 transaction 9616 e7 1 e7:e8 -1 2039-05-01 transaction 9617 e7:e8:e9 1 e7:e8:e9:ea -1 2039-05-02 transaction 9618 e7:e8:e9:ea:eb 1 e7:e8:e9:ea:eb:ec -1 2039-05-03 transaction 9619 e7:e8:e9:ea:eb:ec:ed 1 e7:e8:e9:ea:eb:ec:ed:ee -1 2039-05-04 transaction 9620 e7:e8:e9:ea:eb:ec:ed:ee:ef 1 e7:e8:e9:ea:eb:ec:ed:ee:ef:f0 -1 2039-05-05 transaction 9621 f1 1 f1:f2 -1 2039-05-06 transaction 9622 f1:f2:f3 1 f1:f2:f3:f4 -1 2039-05-07 transaction 9623 f1:f2:f3:f4:f5 1 f1:f2:f3:f4:f5:f6 -1 2039-05-08 transaction 9624 f1:f2:f3:f4:f5:f6:f7 1 f1:f2:f3:f4:f5:f6:f7:f8 -1 2039-05-09 transaction 9625 f1:f2:f3:f4:f5:f6:f7:f8:f9 1 f1:f2:f3:f4:f5:f6:f7:f8:f9:fa -1 2039-05-10 transaction 9626 fb 1 fb:fc -1 2039-05-11 transaction 9627 fb:fc:fd 1 fb:fc:fd:fe -1 2039-05-12 transaction 9628 fb:fc:fd:fe:ff 1 fb:fc:fd:fe:ff:100 -1 2039-05-13 transaction 9629 fb:fc:fd:fe:ff:100:101 1 fb:fc:fd:fe:ff:100:101:102 -1 2039-05-14 transaction 9630 fb:fc:fd:fe:ff:100:101:102:103 1 fb:fc:fd:fe:ff:100:101:102:103:104 -1 2039-05-15 transaction 9631 105 1 105:106 -1 2039-05-16 transaction 9632 105:106:107 1 105:106:107:108 -1 2039-05-17 transaction 9633 105:106:107:108:109 1 105:106:107:108:109:10a -1 2039-05-18 transaction 9634 105:106:107:108:109:10a:10b 1 105:106:107:108:109:10a:10b:10c -1 2039-05-19 transaction 9635 105:106:107:108:109:10a:10b:10c:10d 1 105:106:107:108:109:10a:10b:10c:10d:10e -1 2039-05-20 transaction 9636 10f 1 10f:110 -1 2039-05-21 transaction 9637 10f:110:111 1 10f:110:111:112 -1 2039-05-22 transaction 9638 10f:110:111:112:113 1 10f:110:111:112:113:114 -1 2039-05-23 transaction 9639 10f:110:111:112:113:114:115 1 10f:110:111:112:113:114:115:116 -1 2039-05-24 transaction 9640 10f:110:111:112:113:114:115:116:117 1 10f:110:111:112:113:114:115:116:117:118 -1 2039-05-25 transaction 9641 119 1 119:11a -1 2039-05-26 transaction 9642 119:11a:11b 1 119:11a:11b:11c -1 2039-05-27 transaction 9643 119:11a:11b:11c:11d 1 119:11a:11b:11c:11d:11e -1 2039-05-28 transaction 9644 119:11a:11b:11c:11d:11e:11f 1 119:11a:11b:11c:11d:11e:11f:120 -1 2039-05-29 transaction 9645 119:11a:11b:11c:11d:11e:11f:120:121 1 119:11a:11b:11c:11d:11e:11f:120:121:122 -1 2039-05-30 transaction 9646 123 1 123:124 -1 2039-05-31 transaction 9647 123:124:125 1 123:124:125:126 -1 2039-06-01 transaction 9648 123:124:125:126:127 1 123:124:125:126:127:128 -1 2039-06-02 transaction 9649 123:124:125:126:127:128:129 1 123:124:125:126:127:128:129:12a -1 2039-06-03 transaction 9650 123:124:125:126:127:128:129:12a:12b 1 123:124:125:126:127:128:129:12a:12b:12c -1 2039-06-04 transaction 9651 12d 1 12d:12e -1 2039-06-05 transaction 9652 12d:12e:12f 1 12d:12e:12f:130 -1 2039-06-06 transaction 9653 12d:12e:12f:130:131 1 12d:12e:12f:130:131:132 -1 2039-06-07 transaction 9654 12d:12e:12f:130:131:132:133 1 12d:12e:12f:130:131:132:133:134 -1 2039-06-08 transaction 9655 12d:12e:12f:130:131:132:133:134:135 1 12d:12e:12f:130:131:132:133:134:135:136 -1 2039-06-09 transaction 9656 137 1 137:138 -1 2039-06-10 transaction 9657 137:138:139 1 137:138:139:13a -1 2039-06-11 transaction 9658 137:138:139:13a:13b 1 137:138:139:13a:13b:13c -1 2039-06-12 transaction 9659 137:138:139:13a:13b:13c:13d 1 137:138:139:13a:13b:13c:13d:13e -1 2039-06-13 transaction 9660 137:138:139:13a:13b:13c:13d:13e:13f 1 137:138:139:13a:13b:13c:13d:13e:13f:140 -1 2039-06-14 transaction 9661 141 1 141:142 -1 2039-06-15 transaction 9662 141:142:143 1 141:142:143:144 -1 2039-06-16 transaction 9663 141:142:143:144:145 1 141:142:143:144:145:146 -1 2039-06-17 transaction 9664 141:142:143:144:145:146:147 1 141:142:143:144:145:146:147:148 -1 2039-06-18 transaction 9665 141:142:143:144:145:146:147:148:149 1 141:142:143:144:145:146:147:148:149:14a -1 2039-06-19 transaction 9666 14b 1 14b:14c -1 2039-06-20 transaction 9667 14b:14c:14d 1 14b:14c:14d:14e -1 2039-06-21 transaction 9668 14b:14c:14d:14e:14f 1 14b:14c:14d:14e:14f:150 -1 2039-06-22 transaction 9669 14b:14c:14d:14e:14f:150:151 1 14b:14c:14d:14e:14f:150:151:152 -1 2039-06-23 transaction 9670 14b:14c:14d:14e:14f:150:151:152:153 1 14b:14c:14d:14e:14f:150:151:152:153:154 -1 2039-06-24 transaction 9671 155 1 155:156 -1 2039-06-25 transaction 9672 155:156:157 1 155:156:157:158 -1 2039-06-26 transaction 9673 155:156:157:158:159 1 155:156:157:158:159:15a -1 2039-06-27 transaction 9674 155:156:157:158:159:15a:15b 1 155:156:157:158:159:15a:15b:15c -1 2039-06-28 transaction 9675 155:156:157:158:159:15a:15b:15c:15d 1 155:156:157:158:159:15a:15b:15c:15d:15e -1 2039-06-29 transaction 9676 15f 1 15f:160 -1 2039-06-30 transaction 9677 15f:160:161 1 15f:160:161:162 -1 2039-07-01 transaction 9678 15f:160:161:162:163 1 15f:160:161:162:163:164 -1 2039-07-02 transaction 9679 15f:160:161:162:163:164:165 1 15f:160:161:162:163:164:165:166 -1 2039-07-03 transaction 9680 15f:160:161:162:163:164:165:166:167 1 15f:160:161:162:163:164:165:166:167:168 -1 2039-07-04 transaction 9681 169 1 169:16a -1 2039-07-05 transaction 9682 169:16a:16b 1 169:16a:16b:16c -1 2039-07-06 transaction 9683 169:16a:16b:16c:16d 1 169:16a:16b:16c:16d:16e -1 2039-07-07 transaction 9684 169:16a:16b:16c:16d:16e:16f 1 169:16a:16b:16c:16d:16e:16f:170 -1 2039-07-08 transaction 9685 169:16a:16b:16c:16d:16e:16f:170:171 1 169:16a:16b:16c:16d:16e:16f:170:171:172 -1 2039-07-09 transaction 9686 173 1 173:174 -1 2039-07-10 transaction 9687 173:174:175 1 173:174:175:176 -1 2039-07-11 transaction 9688 173:174:175:176:177 1 173:174:175:176:177:178 -1 2039-07-12 transaction 9689 173:174:175:176:177:178:179 1 173:174:175:176:177:178:179:17a -1 2039-07-13 transaction 9690 173:174:175:176:177:178:179:17a:17b 1 173:174:175:176:177:178:179:17a:17b:17c -1 2039-07-14 transaction 9691 17d 1 17d:17e -1 2039-07-15 transaction 9692 17d:17e:17f 1 17d:17e:17f:180 -1 2039-07-16 transaction 9693 17d:17e:17f:180:181 1 17d:17e:17f:180:181:182 -1 2039-07-17 transaction 9694 17d:17e:17f:180:181:182:183 1 17d:17e:17f:180:181:182:183:184 -1 2039-07-18 transaction 9695 17d:17e:17f:180:181:182:183:184:185 1 17d:17e:17f:180:181:182:183:184:185:186 -1 2039-07-19 transaction 9696 187 1 187:188 -1 2039-07-20 transaction 9697 187:188:189 1 187:188:189:18a -1 2039-07-21 transaction 9698 187:188:189:18a:18b 1 187:188:189:18a:18b:18c -1 2039-07-22 transaction 9699 187:188:189:18a:18b:18c:18d 1 187:188:189:18a:18b:18c:18d:18e -1 2039-07-23 transaction 9700 187:188:189:18a:18b:18c:18d:18e:18f 1 187:188:189:18a:18b:18c:18d:18e:18f:190 -1 2039-07-24 transaction 9701 191 1 191:192 -1 2039-07-25 transaction 9702 191:192:193 1 191:192:193:194 -1 2039-07-26 transaction 9703 191:192:193:194:195 1 191:192:193:194:195:196 -1 2039-07-27 transaction 9704 191:192:193:194:195:196:197 1 191:192:193:194:195:196:197:198 -1 2039-07-28 transaction 9705 191:192:193:194:195:196:197:198:199 1 191:192:193:194:195:196:197:198:199:19a -1 2039-07-29 transaction 9706 19b 1 19b:19c -1 2039-07-30 transaction 9707 19b:19c:19d 1 19b:19c:19d:19e -1 2039-07-31 transaction 9708 19b:19c:19d:19e:19f 1 19b:19c:19d:19e:19f:1a0 -1 2039-08-01 transaction 9709 19b:19c:19d:19e:19f:1a0:1a1 1 19b:19c:19d:19e:19f:1a0:1a1:1a2 -1 2039-08-02 transaction 9710 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3 1 19b:19c:19d:19e:19f:1a0:1a1:1a2:1a3:1a4 -1 2039-08-03 transaction 9711 1a5 1 1a5:1a6 -1 2039-08-04 transaction 9712 1a5:1a6:1a7 1 1a5:1a6:1a7:1a8 -1 2039-08-05 transaction 9713 1a5:1a6:1a7:1a8:1a9 1 1a5:1a6:1a7:1a8:1a9:1aa -1 2039-08-06 transaction 9714 1a5:1a6:1a7:1a8:1a9:1aa:1ab 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac -1 2039-08-07 transaction 9715 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad 1 1a5:1a6:1a7:1a8:1a9:1aa:1ab:1ac:1ad:1ae -1 2039-08-08 transaction 9716 1af 1 1af:1b0 -1 2039-08-09 transaction 9717 1af:1b0:1b1 1 1af:1b0:1b1:1b2 -1 2039-08-10 transaction 9718 1af:1b0:1b1:1b2:1b3 1 1af:1b0:1b1:1b2:1b3:1b4 -1 2039-08-11 transaction 9719 1af:1b0:1b1:1b2:1b3:1b4:1b5 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6 -1 2039-08-12 transaction 9720 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7 1 1af:1b0:1b1:1b2:1b3:1b4:1b5:1b6:1b7:1b8 -1 2039-08-13 transaction 9721 1b9 1 1b9:1ba -1 2039-08-14 transaction 9722 1b9:1ba:1bb 1 1b9:1ba:1bb:1bc -1 2039-08-15 transaction 9723 1b9:1ba:1bb:1bc:1bd 1 1b9:1ba:1bb:1bc:1bd:1be -1 2039-08-16 transaction 9724 1b9:1ba:1bb:1bc:1bd:1be:1bf 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0 -1 2039-08-17 transaction 9725 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1 1 1b9:1ba:1bb:1bc:1bd:1be:1bf:1c0:1c1:1c2 -1 2039-08-18 transaction 9726 1c3 1 1c3:1c4 -1 2039-08-19 transaction 9727 1c3:1c4:1c5 1 1c3:1c4:1c5:1c6 -1 2039-08-20 transaction 9728 1c3:1c4:1c5:1c6:1c7 1 1c3:1c4:1c5:1c6:1c7:1c8 -1 2039-08-21 transaction 9729 1c3:1c4:1c5:1c6:1c7:1c8:1c9 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca -1 2039-08-22 transaction 9730 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb 1 1c3:1c4:1c5:1c6:1c7:1c8:1c9:1ca:1cb:1cc -1 2039-08-23 transaction 9731 1cd 1 1cd:1ce -1 2039-08-24 transaction 9732 1cd:1ce:1cf 1 1cd:1ce:1cf:1d0 -1 2039-08-25 transaction 9733 1cd:1ce:1cf:1d0:1d1 1 1cd:1ce:1cf:1d0:1d1:1d2 -1 2039-08-26 transaction 9734 1cd:1ce:1cf:1d0:1d1:1d2:1d3 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4 -1 2039-08-27 transaction 9735 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5 1 1cd:1ce:1cf:1d0:1d1:1d2:1d3:1d4:1d5:1d6 -1 2039-08-28 transaction 9736 1d7 1 1d7:1d8 -1 2039-08-29 transaction 9737 1d7:1d8:1d9 1 1d7:1d8:1d9:1da -1 2039-08-30 transaction 9738 1d7:1d8:1d9:1da:1db 1 1d7:1d8:1d9:1da:1db:1dc -1 2039-08-31 transaction 9739 1d7:1d8:1d9:1da:1db:1dc:1dd 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de -1 2039-09-01 transaction 9740 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df 1 1d7:1d8:1d9:1da:1db:1dc:1dd:1de:1df:1e0 -1 2039-09-02 transaction 9741 1e1 1 1e1:1e2 -1 2039-09-03 transaction 9742 1e1:1e2:1e3 1 1e1:1e2:1e3:1e4 -1 2039-09-04 transaction 9743 1e1:1e2:1e3:1e4:1e5 1 1e1:1e2:1e3:1e4:1e5:1e6 -1 2039-09-05 transaction 9744 1e1:1e2:1e3:1e4:1e5:1e6:1e7 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8 -1 2039-09-06 transaction 9745 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9 1 1e1:1e2:1e3:1e4:1e5:1e6:1e7:1e8:1e9:1ea -1 2039-09-07 transaction 9746 1eb 1 1eb:1ec -1 2039-09-08 transaction 9747 1eb:1ec:1ed 1 1eb:1ec:1ed:1ee -1 2039-09-09 transaction 9748 1eb:1ec:1ed:1ee:1ef 1 1eb:1ec:1ed:1ee:1ef:1f0 -1 2039-09-10 transaction 9749 1eb:1ec:1ed:1ee:1ef:1f0:1f1 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2 -1 2039-09-11 transaction 9750 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3 1 1eb:1ec:1ed:1ee:1ef:1f0:1f1:1f2:1f3:1f4 -1 2039-09-12 transaction 9751 1f5 1 1f5:1f6 -1 2039-09-13 transaction 9752 1f5:1f6:1f7 1 1f5:1f6:1f7:1f8 -1 2039-09-14 transaction 9753 1f5:1f6:1f7:1f8:1f9 1 1f5:1f6:1f7:1f8:1f9:1fa -1 2039-09-15 transaction 9754 1f5:1f6:1f7:1f8:1f9:1fa:1fb 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc -1 2039-09-16 transaction 9755 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd 1 1f5:1f6:1f7:1f8:1f9:1fa:1fb:1fc:1fd:1fe -1 2039-09-17 transaction 9756 1ff 1 1ff:200 -1 2039-09-18 transaction 9757 1ff:200:201 1 1ff:200:201:202 -1 2039-09-19 transaction 9758 1ff:200:201:202:203 1 1ff:200:201:202:203:204 -1 2039-09-20 transaction 9759 1ff:200:201:202:203:204:205 1 1ff:200:201:202:203:204:205:206 -1 2039-09-21 transaction 9760 1ff:200:201:202:203:204:205:206:207 1 1ff:200:201:202:203:204:205:206:207:208 -1 2039-09-22 transaction 9761 209 1 209:20a -1 2039-09-23 transaction 9762 209:20a:20b 1 209:20a:20b:20c -1 2039-09-24 transaction 9763 209:20a:20b:20c:20d 1 209:20a:20b:20c:20d:20e -1 2039-09-25 transaction 9764 209:20a:20b:20c:20d:20e:20f 1 209:20a:20b:20c:20d:20e:20f:210 -1 2039-09-26 transaction 9765 209:20a:20b:20c:20d:20e:20f:210:211 1 209:20a:20b:20c:20d:20e:20f:210:211:212 -1 2039-09-27 transaction 9766 213 1 213:214 -1 2039-09-28 transaction 9767 213:214:215 1 213:214:215:216 -1 2039-09-29 transaction 9768 213:214:215:216:217 1 213:214:215:216:217:218 -1 2039-09-30 transaction 9769 213:214:215:216:217:218:219 1 213:214:215:216:217:218:219:21a -1 2039-10-01 transaction 9770 213:214:215:216:217:218:219:21a:21b 1 213:214:215:216:217:218:219:21a:21b:21c -1 2039-10-02 transaction 9771 21d 1 21d:21e -1 2039-10-03 transaction 9772 21d:21e:21f 1 21d:21e:21f:220 -1 2039-10-04 transaction 9773 21d:21e:21f:220:221 1 21d:21e:21f:220:221:222 -1 2039-10-05 transaction 9774 21d:21e:21f:220:221:222:223 1 21d:21e:21f:220:221:222:223:224 -1 2039-10-06 transaction 9775 21d:21e:21f:220:221:222:223:224:225 1 21d:21e:21f:220:221:222:223:224:225:226 -1 2039-10-07 transaction 9776 227 1 227:228 -1 2039-10-08 transaction 9777 227:228:229 1 227:228:229:22a -1 2039-10-09 transaction 9778 227:228:229:22a:22b 1 227:228:229:22a:22b:22c -1 2039-10-10 transaction 9779 227:228:229:22a:22b:22c:22d 1 227:228:229:22a:22b:22c:22d:22e -1 2039-10-11 transaction 9780 227:228:229:22a:22b:22c:22d:22e:22f 1 227:228:229:22a:22b:22c:22d:22e:22f:230 -1 2039-10-12 transaction 9781 231 1 231:232 -1 2039-10-13 transaction 9782 231:232:233 1 231:232:233:234 -1 2039-10-14 transaction 9783 231:232:233:234:235 1 231:232:233:234:235:236 -1 2039-10-15 transaction 9784 231:232:233:234:235:236:237 1 231:232:233:234:235:236:237:238 -1 2039-10-16 transaction 9785 231:232:233:234:235:236:237:238:239 1 231:232:233:234:235:236:237:238:239:23a -1 2039-10-17 transaction 9786 23b 1 23b:23c -1 2039-10-18 transaction 9787 23b:23c:23d 1 23b:23c:23d:23e -1 2039-10-19 transaction 9788 23b:23c:23d:23e:23f 1 23b:23c:23d:23e:23f:240 -1 2039-10-20 transaction 9789 23b:23c:23d:23e:23f:240:241 1 23b:23c:23d:23e:23f:240:241:242 -1 2039-10-21 transaction 9790 23b:23c:23d:23e:23f:240:241:242:243 1 23b:23c:23d:23e:23f:240:241:242:243:244 -1 2039-10-22 transaction 9791 245 1 245:246 -1 2039-10-23 transaction 9792 245:246:247 1 245:246:247:248 -1 2039-10-24 transaction 9793 245:246:247:248:249 1 245:246:247:248:249:24a -1 2039-10-25 transaction 9794 245:246:247:248:249:24a:24b 1 245:246:247:248:249:24a:24b:24c -1 2039-10-26 transaction 9795 245:246:247:248:249:24a:24b:24c:24d 1 245:246:247:248:249:24a:24b:24c:24d:24e -1 2039-10-27 transaction 9796 24f 1 24f:250 -1 2039-10-28 transaction 9797 24f:250:251 1 24f:250:251:252 -1 2039-10-29 transaction 9798 24f:250:251:252:253 1 24f:250:251:252:253:254 -1 2039-10-30 transaction 9799 24f:250:251:252:253:254:255 1 24f:250:251:252:253:254:255:256 -1 2039-10-31 transaction 9800 24f:250:251:252:253:254:255:256:257 1 24f:250:251:252:253:254:255:256:257:258 -1 2039-11-01 transaction 9801 259 1 259:25a -1 2039-11-02 transaction 9802 259:25a:25b 1 259:25a:25b:25c -1 2039-11-03 transaction 9803 259:25a:25b:25c:25d 1 259:25a:25b:25c:25d:25e -1 2039-11-04 transaction 9804 259:25a:25b:25c:25d:25e:25f 1 259:25a:25b:25c:25d:25e:25f:260 -1 2039-11-05 transaction 9805 259:25a:25b:25c:25d:25e:25f:260:261 1 259:25a:25b:25c:25d:25e:25f:260:261:262 -1 2039-11-06 transaction 9806 263 1 263:264 -1 2039-11-07 transaction 9807 263:264:265 1 263:264:265:266 -1 2039-11-08 transaction 9808 263:264:265:266:267 1 263:264:265:266:267:268 -1 2039-11-09 transaction 9809 263:264:265:266:267:268:269 1 263:264:265:266:267:268:269:26a -1 2039-11-10 transaction 9810 263:264:265:266:267:268:269:26a:26b 1 263:264:265:266:267:268:269:26a:26b:26c -1 2039-11-11 transaction 9811 26d 1 26d:26e -1 2039-11-12 transaction 9812 26d:26e:26f 1 26d:26e:26f:270 -1 2039-11-13 transaction 9813 26d:26e:26f:270:271 1 26d:26e:26f:270:271:272 -1 2039-11-14 transaction 9814 26d:26e:26f:270:271:272:273 1 26d:26e:26f:270:271:272:273:274 -1 2039-11-15 transaction 9815 26d:26e:26f:270:271:272:273:274:275 1 26d:26e:26f:270:271:272:273:274:275:276 -1 2039-11-16 transaction 9816 277 1 277:278 -1 2039-11-17 transaction 9817 277:278:279 1 277:278:279:27a -1 2039-11-18 transaction 9818 277:278:279:27a:27b 1 277:278:279:27a:27b:27c -1 2039-11-19 transaction 9819 277:278:279:27a:27b:27c:27d 1 277:278:279:27a:27b:27c:27d:27e -1 2039-11-20 transaction 9820 277:278:279:27a:27b:27c:27d:27e:27f 1 277:278:279:27a:27b:27c:27d:27e:27f:280 -1 2039-11-21 transaction 9821 281 1 281:282 -1 2039-11-22 transaction 9822 281:282:283 1 281:282:283:284 -1 2039-11-23 transaction 9823 281:282:283:284:285 1 281:282:283:284:285:286 -1 2039-11-24 transaction 9824 281:282:283:284:285:286:287 1 281:282:283:284:285:286:287:288 -1 2039-11-25 transaction 9825 281:282:283:284:285:286:287:288:289 1 281:282:283:284:285:286:287:288:289:28a -1 2039-11-26 transaction 9826 28b 1 28b:28c -1 2039-11-27 transaction 9827 28b:28c:28d 1 28b:28c:28d:28e -1 2039-11-28 transaction 9828 28b:28c:28d:28e:28f 1 28b:28c:28d:28e:28f:290 -1 2039-11-29 transaction 9829 28b:28c:28d:28e:28f:290:291 1 28b:28c:28d:28e:28f:290:291:292 -1 2039-11-30 transaction 9830 28b:28c:28d:28e:28f:290:291:292:293 1 28b:28c:28d:28e:28f:290:291:292:293:294 -1 2039-12-01 transaction 9831 295 1 295:296 -1 2039-12-02 transaction 9832 295:296:297 1 295:296:297:298 -1 2039-12-03 transaction 9833 295:296:297:298:299 1 295:296:297:298:299:29a -1 2039-12-04 transaction 9834 295:296:297:298:299:29a:29b 1 295:296:297:298:299:29a:29b:29c -1 2039-12-05 transaction 9835 295:296:297:298:299:29a:29b:29c:29d 1 295:296:297:298:299:29a:29b:29c:29d:29e -1 2039-12-06 transaction 9836 29f 1 29f:2a0 -1 2039-12-07 transaction 9837 29f:2a0:2a1 1 29f:2a0:2a1:2a2 -1 2039-12-08 transaction 9838 29f:2a0:2a1:2a2:2a3 1 29f:2a0:2a1:2a2:2a3:2a4 -1 2039-12-09 transaction 9839 29f:2a0:2a1:2a2:2a3:2a4:2a5 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6 -1 2039-12-10 transaction 9840 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7 1 29f:2a0:2a1:2a2:2a3:2a4:2a5:2a6:2a7:2a8 -1 2039-12-11 transaction 9841 2a9 1 2a9:2aa -1 2039-12-12 transaction 9842 2a9:2aa:2ab 1 2a9:2aa:2ab:2ac -1 2039-12-13 transaction 9843 2a9:2aa:2ab:2ac:2ad 1 2a9:2aa:2ab:2ac:2ad:2ae -1 2039-12-14 transaction 9844 2a9:2aa:2ab:2ac:2ad:2ae:2af 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0 -1 2039-12-15 transaction 9845 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1 1 2a9:2aa:2ab:2ac:2ad:2ae:2af:2b0:2b1:2b2 -1 2039-12-16 transaction 9846 2b3 1 2b3:2b4 -1 2039-12-17 transaction 9847 2b3:2b4:2b5 1 2b3:2b4:2b5:2b6 -1 2039-12-18 transaction 9848 2b3:2b4:2b5:2b6:2b7 1 2b3:2b4:2b5:2b6:2b7:2b8 -1 2039-12-19 transaction 9849 2b3:2b4:2b5:2b6:2b7:2b8:2b9 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba -1 2039-12-20 transaction 9850 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb 1 2b3:2b4:2b5:2b6:2b7:2b8:2b9:2ba:2bb:2bc -1 2039-12-21 transaction 9851 2bd 1 2bd:2be -1 2039-12-22 transaction 9852 2bd:2be:2bf 1 2bd:2be:2bf:2c0 -1 2039-12-23 transaction 9853 2bd:2be:2bf:2c0:2c1 1 2bd:2be:2bf:2c0:2c1:2c2 -1 2039-12-24 transaction 9854 2bd:2be:2bf:2c0:2c1:2c2:2c3 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4 -1 2039-12-25 transaction 9855 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5 1 2bd:2be:2bf:2c0:2c1:2c2:2c3:2c4:2c5:2c6 -1 2039-12-26 transaction 9856 2c7 1 2c7:2c8 -1 2039-12-27 transaction 9857 2c7:2c8:2c9 1 2c7:2c8:2c9:2ca -1 2039-12-28 transaction 9858 2c7:2c8:2c9:2ca:2cb 1 2c7:2c8:2c9:2ca:2cb:2cc -1 2039-12-29 transaction 9859 2c7:2c8:2c9:2ca:2cb:2cc:2cd 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce -1 2039-12-30 transaction 9860 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf 1 2c7:2c8:2c9:2ca:2cb:2cc:2cd:2ce:2cf:2d0 -1 2039-12-31 transaction 9861 2d1 1 2d1:2d2 -1 2040-01-01 transaction 9862 2d1:2d2:2d3 1 2d1:2d2:2d3:2d4 -1 2040-01-02 transaction 9863 2d1:2d2:2d3:2d4:2d5 1 2d1:2d2:2d3:2d4:2d5:2d6 -1 2040-01-03 transaction 9864 2d1:2d2:2d3:2d4:2d5:2d6:2d7 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8 -1 2040-01-04 transaction 9865 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9 1 2d1:2d2:2d3:2d4:2d5:2d6:2d7:2d8:2d9:2da -1 2040-01-05 transaction 9866 2db 1 2db:2dc -1 2040-01-06 transaction 9867 2db:2dc:2dd 1 2db:2dc:2dd:2de -1 2040-01-07 transaction 9868 2db:2dc:2dd:2de:2df 1 2db:2dc:2dd:2de:2df:2e0 -1 2040-01-08 transaction 9869 2db:2dc:2dd:2de:2df:2e0:2e1 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2 -1 2040-01-09 transaction 9870 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3 1 2db:2dc:2dd:2de:2df:2e0:2e1:2e2:2e3:2e4 -1 2040-01-10 transaction 9871 2e5 1 2e5:2e6 -1 2040-01-11 transaction 9872 2e5:2e6:2e7 1 2e5:2e6:2e7:2e8 -1 2040-01-12 transaction 9873 2e5:2e6:2e7:2e8:2e9 1 2e5:2e6:2e7:2e8:2e9:2ea -1 2040-01-13 transaction 9874 2e5:2e6:2e7:2e8:2e9:2ea:2eb 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec -1 2040-01-14 transaction 9875 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed 1 2e5:2e6:2e7:2e8:2e9:2ea:2eb:2ec:2ed:2ee -1 2040-01-15 transaction 9876 2ef 1 2ef:2f0 -1 2040-01-16 transaction 9877 2ef:2f0:2f1 1 2ef:2f0:2f1:2f2 -1 2040-01-17 transaction 9878 2ef:2f0:2f1:2f2:2f3 1 2ef:2f0:2f1:2f2:2f3:2f4 -1 2040-01-18 transaction 9879 2ef:2f0:2f1:2f2:2f3:2f4:2f5 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6 -1 2040-01-19 transaction 9880 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7 1 2ef:2f0:2f1:2f2:2f3:2f4:2f5:2f6:2f7:2f8 -1 2040-01-20 transaction 9881 2f9 1 2f9:2fa -1 2040-01-21 transaction 9882 2f9:2fa:2fb 1 2f9:2fa:2fb:2fc -1 2040-01-22 transaction 9883 2f9:2fa:2fb:2fc:2fd 1 2f9:2fa:2fb:2fc:2fd:2fe -1 2040-01-23 transaction 9884 2f9:2fa:2fb:2fc:2fd:2fe:2ff 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300 -1 2040-01-24 transaction 9885 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301 1 2f9:2fa:2fb:2fc:2fd:2fe:2ff:300:301:302 -1 2040-01-25 transaction 9886 303 1 303:304 -1 2040-01-26 transaction 9887 303:304:305 1 303:304:305:306 -1 2040-01-27 transaction 9888 303:304:305:306:307 1 303:304:305:306:307:308 -1 2040-01-28 transaction 9889 303:304:305:306:307:308:309 1 303:304:305:306:307:308:309:30a -1 2040-01-29 transaction 9890 303:304:305:306:307:308:309:30a:30b 1 303:304:305:306:307:308:309:30a:30b:30c -1 2040-01-30 transaction 9891 30d 1 30d:30e -1 2040-01-31 transaction 9892 30d:30e:30f 1 30d:30e:30f:310 -1 2040-02-01 transaction 9893 30d:30e:30f:310:311 1 30d:30e:30f:310:311:312 -1 2040-02-02 transaction 9894 30d:30e:30f:310:311:312:313 1 30d:30e:30f:310:311:312:313:314 -1 2040-02-03 transaction 9895 30d:30e:30f:310:311:312:313:314:315 1 30d:30e:30f:310:311:312:313:314:315:316 -1 2040-02-04 transaction 9896 317 1 317:318 -1 2040-02-05 transaction 9897 317:318:319 1 317:318:319:31a -1 2040-02-06 transaction 9898 317:318:319:31a:31b 1 317:318:319:31a:31b:31c -1 2040-02-07 transaction 9899 317:318:319:31a:31b:31c:31d 1 317:318:319:31a:31b:31c:31d:31e -1 2040-02-08 transaction 9900 317:318:319:31a:31b:31c:31d:31e:31f 1 317:318:319:31a:31b:31c:31d:31e:31f:320 -1 2040-02-09 transaction 9901 321 1 321:322 -1 2040-02-10 transaction 9902 321:322:323 1 321:322:323:324 -1 2040-02-11 transaction 9903 321:322:323:324:325 1 321:322:323:324:325:326 -1 2040-02-12 transaction 9904 321:322:323:324:325:326:327 1 321:322:323:324:325:326:327:328 -1 2040-02-13 transaction 9905 321:322:323:324:325:326:327:328:329 1 321:322:323:324:325:326:327:328:329:32a -1 2040-02-14 transaction 9906 32b 1 32b:32c -1 2040-02-15 transaction 9907 32b:32c:32d 1 32b:32c:32d:32e -1 2040-02-16 transaction 9908 32b:32c:32d:32e:32f 1 32b:32c:32d:32e:32f:330 -1 2040-02-17 transaction 9909 32b:32c:32d:32e:32f:330:331 1 32b:32c:32d:32e:32f:330:331:332 -1 2040-02-18 transaction 9910 32b:32c:32d:32e:32f:330:331:332:333 1 32b:32c:32d:32e:32f:330:331:332:333:334 -1 2040-02-19 transaction 9911 335 1 335:336 -1 2040-02-20 transaction 9912 335:336:337 1 335:336:337:338 -1 2040-02-21 transaction 9913 335:336:337:338:339 1 335:336:337:338:339:33a -1 2040-02-22 transaction 9914 335:336:337:338:339:33a:33b 1 335:336:337:338:339:33a:33b:33c -1 2040-02-23 transaction 9915 335:336:337:338:339:33a:33b:33c:33d 1 335:336:337:338:339:33a:33b:33c:33d:33e -1 2040-02-24 transaction 9916 33f 1 33f:340 -1 2040-02-25 transaction 9917 33f:340:341 1 33f:340:341:342 -1 2040-02-26 transaction 9918 33f:340:341:342:343 1 33f:340:341:342:343:344 -1 2040-02-27 transaction 9919 33f:340:341:342:343:344:345 1 33f:340:341:342:343:344:345:346 -1 2040-02-28 transaction 9920 33f:340:341:342:343:344:345:346:347 1 33f:340:341:342:343:344:345:346:347:348 -1 2040-02-29 transaction 9921 349 1 349:34a -1 2040-03-01 transaction 9922 349:34a:34b 1 349:34a:34b:34c -1 2040-03-02 transaction 9923 349:34a:34b:34c:34d 1 349:34a:34b:34c:34d:34e -1 2040-03-03 transaction 9924 349:34a:34b:34c:34d:34e:34f 1 349:34a:34b:34c:34d:34e:34f:350 -1 2040-03-04 transaction 9925 349:34a:34b:34c:34d:34e:34f:350:351 1 349:34a:34b:34c:34d:34e:34f:350:351:352 -1 2040-03-05 transaction 9926 353 1 353:354 -1 2040-03-06 transaction 9927 353:354:355 1 353:354:355:356 -1 2040-03-07 transaction 9928 353:354:355:356:357 1 353:354:355:356:357:358 -1 2040-03-08 transaction 9929 353:354:355:356:357:358:359 1 353:354:355:356:357:358:359:35a -1 2040-03-09 transaction 9930 353:354:355:356:357:358:359:35a:35b 1 353:354:355:356:357:358:359:35a:35b:35c -1 2040-03-10 transaction 9931 35d 1 35d:35e -1 2040-03-11 transaction 9932 35d:35e:35f 1 35d:35e:35f:360 -1 2040-03-12 transaction 9933 35d:35e:35f:360:361 1 35d:35e:35f:360:361:362 -1 2040-03-13 transaction 9934 35d:35e:35f:360:361:362:363 1 35d:35e:35f:360:361:362:363:364 -1 2040-03-14 transaction 9935 35d:35e:35f:360:361:362:363:364:365 1 35d:35e:35f:360:361:362:363:364:365:366 -1 2040-03-15 transaction 9936 367 1 367:368 -1 2040-03-16 transaction 9937 367:368:369 1 367:368:369:36a -1 2040-03-17 transaction 9938 367:368:369:36a:36b 1 367:368:369:36a:36b:36c -1 2040-03-18 transaction 9939 367:368:369:36a:36b:36c:36d 1 367:368:369:36a:36b:36c:36d:36e -1 2040-03-19 transaction 9940 367:368:369:36a:36b:36c:36d:36e:36f 1 367:368:369:36a:36b:36c:36d:36e:36f:370 -1 2040-03-20 transaction 9941 371 1 371:372 -1 2040-03-21 transaction 9942 371:372:373 1 371:372:373:374 -1 2040-03-22 transaction 9943 371:372:373:374:375 1 371:372:373:374:375:376 -1 2040-03-23 transaction 9944 371:372:373:374:375:376:377 1 371:372:373:374:375:376:377:378 -1 2040-03-24 transaction 9945 371:372:373:374:375:376:377:378:379 1 371:372:373:374:375:376:377:378:379:37a -1 2040-03-25 transaction 9946 37b 1 37b:37c -1 2040-03-26 transaction 9947 37b:37c:37d 1 37b:37c:37d:37e -1 2040-03-27 transaction 9948 37b:37c:37d:37e:37f 1 37b:37c:37d:37e:37f:380 -1 2040-03-28 transaction 9949 37b:37c:37d:37e:37f:380:381 1 37b:37c:37d:37e:37f:380:381:382 -1 2040-03-29 transaction 9950 37b:37c:37d:37e:37f:380:381:382:383 1 37b:37c:37d:37e:37f:380:381:382:383:384 -1 2040-03-30 transaction 9951 385 1 385:386 -1 2040-03-31 transaction 9952 385:386:387 1 385:386:387:388 -1 2040-04-01 transaction 9953 385:386:387:388:389 1 385:386:387:388:389:38a -1 2040-04-02 transaction 9954 385:386:387:388:389:38a:38b 1 385:386:387:388:389:38a:38b:38c -1 2040-04-03 transaction 9955 385:386:387:388:389:38a:38b:38c:38d 1 385:386:387:388:389:38a:38b:38c:38d:38e -1 2040-04-04 transaction 9956 38f 1 38f:390 -1 2040-04-05 transaction 9957 38f:390:391 1 38f:390:391:392 -1 2040-04-06 transaction 9958 38f:390:391:392:393 1 38f:390:391:392:393:394 -1 2040-04-07 transaction 9959 38f:390:391:392:393:394:395 1 38f:390:391:392:393:394:395:396 -1 2040-04-08 transaction 9960 38f:390:391:392:393:394:395:396:397 1 38f:390:391:392:393:394:395:396:397:398 -1 2040-04-09 transaction 9961 399 1 399:39a -1 2040-04-10 transaction 9962 399:39a:39b 1 399:39a:39b:39c -1 2040-04-11 transaction 9963 399:39a:39b:39c:39d 1 399:39a:39b:39c:39d:39e -1 2040-04-12 transaction 9964 399:39a:39b:39c:39d:39e:39f 1 399:39a:39b:39c:39d:39e:39f:3a0 -1 2040-04-13 transaction 9965 399:39a:39b:39c:39d:39e:39f:3a0:3a1 1 399:39a:39b:39c:39d:39e:39f:3a0:3a1:3a2 -1 2040-04-14 transaction 9966 3a3 1 3a3:3a4 -1 2040-04-15 transaction 9967 3a3:3a4:3a5 1 3a3:3a4:3a5:3a6 -1 2040-04-16 transaction 9968 3a3:3a4:3a5:3a6:3a7 1 3a3:3a4:3a5:3a6:3a7:3a8 -1 2040-04-17 transaction 9969 3a3:3a4:3a5:3a6:3a7:3a8:3a9 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa -1 2040-04-18 transaction 9970 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab 1 3a3:3a4:3a5:3a6:3a7:3a8:3a9:3aa:3ab:3ac -1 2040-04-19 transaction 9971 3ad 1 3ad:3ae -1 2040-04-20 transaction 9972 3ad:3ae:3af 1 3ad:3ae:3af:3b0 -1 2040-04-21 transaction 9973 3ad:3ae:3af:3b0:3b1 1 3ad:3ae:3af:3b0:3b1:3b2 -1 2040-04-22 transaction 9974 3ad:3ae:3af:3b0:3b1:3b2:3b3 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4 -1 2040-04-23 transaction 9975 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5 1 3ad:3ae:3af:3b0:3b1:3b2:3b3:3b4:3b5:3b6 -1 2040-04-24 transaction 9976 3b7 1 3b7:3b8 -1 2040-04-25 transaction 9977 3b7:3b8:3b9 1 3b7:3b8:3b9:3ba -1 2040-04-26 transaction 9978 3b7:3b8:3b9:3ba:3bb 1 3b7:3b8:3b9:3ba:3bb:3bc -1 2040-04-27 transaction 9979 3b7:3b8:3b9:3ba:3bb:3bc:3bd 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be -1 2040-04-28 transaction 9980 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf 1 3b7:3b8:3b9:3ba:3bb:3bc:3bd:3be:3bf:3c0 -1 2040-04-29 transaction 9981 3c1 1 3c1:3c2 -1 2040-04-30 transaction 9982 3c1:3c2:3c3 1 3c1:3c2:3c3:3c4 -1 2040-05-01 transaction 9983 3c1:3c2:3c3:3c4:3c5 1 3c1:3c2:3c3:3c4:3c5:3c6 -1 2040-05-02 transaction 9984 3c1:3c2:3c3:3c4:3c5:3c6:3c7 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8 -1 2040-05-03 transaction 9985 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9 1 3c1:3c2:3c3:3c4:3c5:3c6:3c7:3c8:3c9:3ca -1 2040-05-04 transaction 9986 3cb 1 3cb:3cc -1 2040-05-05 transaction 9987 3cb:3cc:3cd 1 3cb:3cc:3cd:3ce -1 2040-05-06 transaction 9988 3cb:3cc:3cd:3ce:3cf 1 3cb:3cc:3cd:3ce:3cf:3d0 -1 2040-05-07 transaction 9989 3cb:3cc:3cd:3ce:3cf:3d0:3d1 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2 -1 2040-05-08 transaction 9990 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3 1 3cb:3cc:3cd:3ce:3cf:3d0:3d1:3d2:3d3:3d4 -1 2040-05-09 transaction 9991 3d5 1 3d5:3d6 -1 2040-05-10 transaction 9992 3d5:3d6:3d7 1 3d5:3d6:3d7:3d8 -1 2040-05-11 transaction 9993 3d5:3d6:3d7:3d8:3d9 1 3d5:3d6:3d7:3d8:3d9:3da -1 2040-05-12 transaction 9994 3d5:3d6:3d7:3d8:3d9:3da:3db 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc -1 2040-05-13 transaction 9995 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd 1 3d5:3d6:3d7:3d8:3d9:3da:3db:3dc:3dd:3de -1 2040-05-14 transaction 9996 3df 1 3df:3e0 -1 2040-05-15 transaction 9997 3df:3e0:3e1 1 3df:3e0:3e1:3e2 -1 2040-05-16 transaction 9998 3df:3e0:3e1:3e2:3e3 1 3df:3e0:3e1:3e2:3e3:3e4 -1 2040-05-17 transaction 9999 3df:3e0:3e1:3e2:3e3:3e4:3e5 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6 -1 2040-05-18 transaction 10000 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7 1 3df:3e0:3e1:3e2:3e3:3e4:3e5:3e6:3e7:3e8 -1 hledger-1.32.3/hledger.10000644000000000000000000132632014555433336013116 0ustar0000000000000000.\"t .TH "HLEDGER" "1" "January 2024" "hledger-1.32.3 " "hledger User Manuals" .SH NAME hledger \- robust, friendly plain text accounting (CLI version) .SH SYNOPSIS \f[CR]hledger\f[R] .PD 0 .P .PD \f[CR]hledger COMMAND [OPTS] [ARGS]\f[R] .PD 0 .P .PD \f[CR]hledger ADDONCMD \-\- [OPTS] [ARGS]\f[R] .SH DESCRIPTION hledger is a robust, user\-friendly, cross\-platform set of programs for tracking money, time, or any other commodity, using double\-entry accounting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). .PP This manual is for hledger\[aq]s command line interface, version 1.32.3. It also describes the common options, file formats and concepts used by all hledger programs. It might accidentally teach you some bookkeeping/accounting as well! You don\[aq]t need to know everything in here to use hledger productively, but when you have a question about functionality, this doc should answer it. It is detailed, so do skip ahead or skim when needed. You can read it on hledger.org, or as an info manual or man page on your system. You can also get it from hledger itself with .PD 0 .P .PD \f[CR]hledger \-\-man\f[R], \f[CR]hledger \-\-info\f[R] or \f[CR]hledger help [TOPIC]\f[R]. .PP The main function of the hledger CLI is to read plain text files describing financial transactions, crunch the numbers, and print a useful report on the terminal (or save it as HTML, CSV, JSON or SQL). Many reports are available, as subcommands. hledger will also detect other \f[CR]hledger\-*\f[R] executables as extra subcommands. .PP hledger usually reads from (and appends to) a journal file specified by the \f[CR]LEDGER_FILE\f[R] environment variable (defaulting to \f[CR]$HOME/.hledger.journal\f[R]); or you can specify files with \f[CR]\-f\f[R] options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. .PP Here is a small journal file describing one transaction: .IP .EX 2015\-10\-16 bought food expenses:food $10 assets:cash .EE .PP Transactions are dated movements of money (etc.) between two or more \f[I]accounts\f[R]: bank accounts, your wallet, revenue/expense categories, people, etc. You can choose any account names you wish, using \f[CR]:\f[R] to indicate subaccounts. There must be at least two spaces between account name and amount. Positive amounts are inflow to that account (\f[I]debit\f[R]), negatives are outflow from it (\f[I]credit\f[R]). (Some reports show revenue, liability and equity account balances as negative numbers as a result; this is normal.) .PP hledger\[cq]s add command can help you add transactions, or you can install other data entry UIs like hledger\-web or hledger\-iadd. For more extensive/efficient changes, use a text editor: Emacs + ledger\-mode, VIM + vim\-ledger, or VS Code + hledger\-vscode are some good choices (see https://hledger.org/editors.html). .PP To get started, run \f[CR]hledger add\f[R] and follow the prompts, or save some entries like the above in \f[CR]$HOME/.hledger.journal\f[R], then try commands like: .PD 0 .P .PD \f[CR]hledger print \-x\f[R] .PD 0 .P .PD \f[CR]hledger aregister assets\f[R] .PD 0 .P .PD \f[CR]hledger balance\f[R] .PD 0 .P .PD \f[CR]hledger balancesheet\f[R] .PD 0 .P .PD \f[CR]hledger incomestatement\f[R]. .PD 0 .P .PD Run \f[CR]hledger\f[R] to list the commands. See also the \[dq]Starting a journal file\[dq] and \[dq]Setting opening balances\[dq] sections in PART 5: COMMON TASKS. .SH PART 1: USER INTERFACE .SH Input hledger reads one or more data files, each time you run it. You can specify a file with \f[CR]\-f\f[R], like so .IP .EX $ hledger \-f FILE print .EE .PP Files are most often in hledger\[aq]s journal format, with the \f[CR].journal\f[R] file extension (\f[CR].hledger\f[R] or \f[CR].j\f[R] also work); these files describe transactions, like an accounting general journal. .PP When no file is specified, hledger looks for \f[CR].hledger.journal\f[R] in your home directory. .PP But most people prefer to keep financial files in a dedicated folder, perhaps with version control. Also, starting a new journal file each year is common (it\[aq]s not required, but helps keep things fast and organised). So we usually configure a different journal file, by setting the \f[CR]LEDGER_FILE\f[R] environment variable, to something like \f[CR]\[ti]/finance/2023.journal\f[R]. For more about how to do that on your system, see Common tasks > Setting LEDGER_FILE. .SS Data formats Usually the data file is in hledger\[aq]s journal format, but it can be in any of the supported file formats, which currently are: .PP .TS tab(@); lw(12.3n) lw(30.0n) lw(27.7n). T{ Reader: T}@T{ Reads: T}@T{ Used for file extensions: T} _ T{ \f[CR]journal\f[R] T}@T{ hledger journal files and some Ledger journals, for transactions T}@T{ \f[CR].journal\f[R] \f[CR].j\f[R] \f[CR].hledger\f[R] \f[CR].ledger\f[R] T} T{ \f[CR]timeclock\f[R] T}@T{ timeclock files, for precise time logging T}@T{ \f[CR].timeclock\f[R] T} T{ \f[CR]timedot\f[R] T}@T{ timedot files, for approximate time logging T}@T{ \f[CR].timedot\f[R] T} T{ \f[CR]csv\f[R] T}@T{ CSV/SSV/TSV/character\-separated values, for data import T}@T{ \f[CR].csv\f[R] \f[CR].ssv\f[R] \f[CR].tsv\f[R] \f[CR].csv.rules\f[R] \f[CR].ssv.rules\f[R] \f[CR].tsv.rules\f[R] T} .TE .PP These formats are described in more detail below. .PP hledger detects the format automatically based on the file extensions shown above. If it can\[aq]t recognise the file extension, it assumes \f[CR]journal\f[R] format. So for non\-journal files, it\[aq]s important to use a recognised file extension, so as to either read successfully or to show relevant error messages. .PP You can also force a specific reader/format by prefixing the file path with the format and a colon. Eg, to read a .dat file as csv format: .IP .EX $ hledger \-f csv:/some/csv\-file.dat stats .EE .SS Standard input The file name \f[CR]\-\f[R] means standard input: .IP .EX $ cat FILE | hledger \-f\- print .EE .PP If reading non\-journal data in this way, you\[aq]ll need to add a file format prefix, like: .IP .EX $ echo \[aq]i 2009/13/1 08:00:00\[aq] | hledger print \-f timeclock:\- .EE .SS Multiple files You can specify multiple \f[CR]\-f\f[R] options, to read multiple files as one big journal. When doing this, note that certain features (described below) will be affected: .IP \[bu] 2 Balance assertions will not see the effect of transactions in previous files. (Usually this doesn\[aq]t matter as each file will set the corresponding opening balances.) .IP \[bu] 2 Some directives will not affect previous or subsequent files. .PP If needed, you can work around these by using a single parent file which includes the others, or concatenating the files into one, eg: \f[CR]cat a.journal b.journal | hledger \-f\- CMD\f[R]. .SS Strict mode hledger checks input files for valid data. By default, the most important errors are detected, while still accepting easy journal files without a lot of declarations: .IP \[bu] 2 Are the input files parseable, with valid syntax ? .IP \[bu] 2 Are all transactions balanced ? .IP \[bu] 2 Do all balance assertions pass ? .PP With the \f[CR]\-s\f[R]/\f[CR]\-\-strict\f[R] flag, additional checks are performed: .IP \[bu] 2 Are all accounts posted to, declared with an \f[CR]account\f[R] directive ? (Account error checking) .IP \[bu] 2 Are all commodities declared with a \f[CR]commodity\f[R] directive ? (Commodity error checking) .IP \[bu] 2 Are all commodity conversions declared explicitly ? .PP You can use the check command to run individual checks \-\- the ones listed above and some more. .SH Commands hledger provides various subcommands for getting things done. Most of these commands do not change the journal file; they just read it and output a report. A few commands assist with adding data and file management. .PP To show the commands list, run \f[CR]hledger\f[R] with no arguments. The commands are described in detail in PART 4: COMMANDS, below. .PP To use a particular command, run \f[CR]hledger CMD [CMDOPTS] [CMDARGS]\f[R], .IP \[bu] 2 CMD is the full command name, or its standard abbreviation shown in the commands list, or any unambiguous prefix of the name. .IP \[bu] 2 CMDOPTS are command\-specific options, if any. Command\-specific options must be written after the command name. Eg: \f[CR]hledger print \-x\f[R]. .IP \[bu] 2 CMDARGS are additional arguments to the command, if any. Most hledger commands accept arguments representing a query, to limit the data in some way. Eg: \f[CR]hledger reg assets:checking\f[R]. .PP To list a command\[aq]s options, arguments, and documentation in the terminal, run \f[CR]hledger CMD \-h\f[R]. Eg: \f[CR]hledger bal \-h\f[R]. .SS Add\-on commands In addition to the built\-in commands, you can install \f[I]add\-on commands\f[R]: programs or scripts named \[dq]hledger\-SOMETHING\[dq], which will also appear in hledger\[aq]s commands list. If you used the hledger\-install script, you will have several add\-ons installed already. Some more can be found in hledger\[aq]s bin/ directory, documented at https://hledger.org/scripts.html. .PP More precisely, add\-on commands are programs or scripts in your shell\[aq]s PATH, whose name starts with \[dq]hledger\-\[dq] and ends with no extension or a recognised extension (\[dq].bat\[dq], \[dq].com\[dq], \[dq].exe\[dq], \[dq].hs\[dq], \[dq].js\[dq], \[dq].lhs\[dq], \[dq].lua\[dq], \[dq].php\[dq], \[dq].pl\[dq], \[dq].py\[dq], \[dq].rb\[dq], \[dq].rkt\[dq], or \[dq].sh\[dq]), and (on unix and mac) which has executable permission for the current user. .PP You can run add\-on commands using hledger, much like built\-in commands: \f[CR]hledger ADDONCMD [\-\- ADDONCMDOPTS] [ADDONCMDARGS]\f[R]. But note the double hyphen argument, required before add\-on\-specific options. Eg: \f[CR]hledger ui \-\- \-\-watch\f[R] or \f[CR]hledger web \-\- \-\-serve\f[R]. If this causes difficulty, you can always run the add\-on directly, without using \f[CR]hledger\f[R]: \f[CR]hledger\-ui \-\-watch\f[R] or \f[CR]hledger\-web \-\-serve\f[R]. .SH Options Run \f[CR]hledger \-h\f[R] to see general command line help, and general options which are common to most hledger commands. These options can be written anywhere on the command line. They can be grouped into help, input, and reporting options: .SS General help options .TP \f[CR]\-h \-\-help\f[R] show general or COMMAND help .TP \f[CR]\-\-man\f[R] show general or COMMAND user manual with man .TP \f[CR]\-\-info\f[R] show general or COMMAND user manual with info .TP \f[CR]\-\-version\f[R] show general or ADDONCMD version .TP \f[CR]\-\-debug[=N]\f[R] show debug output (levels 1\-9, default: 1) .SS General input options .TP \f[CR]\-f FILE \-\-file=FILE\f[R] use a different input file. For stdin, use \- (default: \f[CR]$LEDGER_FILE\f[R] or \f[CR]$HOME/.hledger.journal\f[R]) .TP \f[CR]\-\-rules\-file=RULESFILE\f[R] Conversion rules file to use when reading CSV (default: FILE.rules) .TP \f[CR]\-\-separator=CHAR\f[R] Field separator to expect when reading CSV (default: \[aq],\[aq]) .TP \f[CR]\-\-alias=OLD=NEW\f[R] rename accounts named OLD to NEW .TP \f[CR]\-\-pivot FIELDNAME\f[R] use some other field or tag for the account name .TP \f[CR]\-I \-\-ignore\-assertions\f[R] disable balance assertion checks (note: does not disable balance assignments) .TP \f[CR]\-s \-\-strict\f[R] do extra error checking (check that all posted accounts are declared) .SS General reporting options .TP \f[CR]\-b \-\-begin=DATE\f[R] include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) .TP \f[CR]\-e \-\-end=DATE\f[R] include postings/txns before this date (will be adjusted to following subperiod end when using a report interval) .TP \f[CR]\-D \-\-daily\f[R] multiperiod/multicolumn report by day .TP \f[CR]\-W \-\-weekly\f[R] multiperiod/multicolumn report by week .TP \f[CR]\-M \-\-monthly\f[R] multiperiod/multicolumn report by month .TP \f[CR]\-Q \-\-quarterly\f[R] multiperiod/multicolumn report by quarter .TP \f[CR]\-Y \-\-yearly\f[R] multiperiod/multicolumn report by year .TP \f[CR]\-p \-\-period=PERIODEXP\f[R] set start date, end date, and/or reporting interval all at once using period expressions syntax .TP \f[CR]\-\-date2\f[R] match the secondary date instead (see command help for other effects) .TP \f[CR]\-\-today=DATE\f[R] override today\[aq]s date (affects relative smart dates, for tests/examples) .TP \f[CR]\-U \-\-unmarked\f[R] include only unmarked postings/txns (can combine with \-P or \-C) .TP \f[CR]\-P \-\-pending\f[R] include only pending postings/txns .TP \f[CR]\-C \-\-cleared\f[R] include only cleared postings/txns .TP \f[CR]\-R \-\-real\f[R] include only non\-virtual postings .TP \f[CR]\-NUM \-\-depth=NUM\f[R] hide/aggregate accounts or postings more than NUM levels deep .TP \f[CR]\-E \-\-empty\f[R] show items with zero amount, normally hidden (and vice\-versa in hledger\-ui/hledger\-web) .TP \f[CR]\-B \-\-cost\f[R] convert amounts to their cost/selling amount at transaction time .TP \f[CR]\-V \-\-market\f[R] convert amounts to their market value in default valuation commodities .TP \f[CR]\-X \-\-exchange=COMM\f[R] convert amounts to their market value in commodity COMM .TP \f[CR]\-\-value\f[R] convert amounts to cost or market value, more flexibly than \-B/\-V/\-X .TP \f[CR]\-\-infer\-equity\f[R] infer conversion equity postings from costs .TP \f[CR]\-\-infer\-costs\f[R] infer costs from conversion equity postings .TP \f[CR]\-\-infer\-market\-prices\f[R] use costs as additional market prices, as if they were P directives .TP \f[CR]\-\-forecast\f[R] generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger\-ui make future\-dated transactions visible. .TP \f[CR]\-\-auto\f[R] generate extra postings by applying auto posting rules to all txns (not just forecast txns) .TP \f[CR]\-\-verbose\-tags\f[R] add visible tags indicating transactions or postings which have been generated/modified .TP \f[CR]\-\-commodity\-style\f[R] Override the commodity style in the output for the specified commodity. For example \[aq]EUR1.000,00\[aq]. .TP \f[CR]\-\-color=WHEN (or \-\-colour=WHEN)\f[R] Should color\-supporting commands use ANSI color codes in text output. \[aq]auto\[aq] (default): whenever stdout seems to be a color\-supporting terminal. \[aq]always\[aq] or \[aq]yes\[aq]: always, useful eg when piping output into \[aq]less \-R\[aq]. \[aq]never\[aq] or \[aq]no\[aq]: never. A NO_COLOR environment variable overrides this. .TP \f[CR]\-\-pretty[=WHEN]\f[R] Show prettier output, e.g. using unicode box\-drawing characters. Accepts \[aq]yes\[aq] (the default) or \[aq]no\[aq] (\[aq]y\[aq], \[aq]n\[aq], \[aq]always\[aq], \[aq]never\[aq] also work). If you provide an argument you must use \[aq]=\[aq], e.g. \[aq]\-\-pretty=yes\[aq]. .PP When a reporting option appears more than once in the command line, the last one takes precedence. .PP Some reporting options can also be written as query arguments. .SH Command line tips Here are some details useful to know about for hledger command lines (and elsewhere). Feel free to skip this section until you need it. .SS Option repetition If options are repeated in a command line, hledger will generally use the last (right\-most) occurence. .SS Special characters .SS Single escaping (shell metacharacters) In shell command lines, characters significant to your shell \- such as spaces, \f[CR]<\f[R], \f[CR]>\f[R], \f[CR](\f[R], \f[CR])\f[R], \f[CR]|\f[R], \f[CR]$\f[R] and \f[CR]\[rs]\f[R] \- should be \[dq]shell\-escaped\[dq] if you want hledger to see them. This is done by enclosing them in single or double quotes, or by writing a backslash before them. Eg to match an account name containing a space: .IP .EX $ hledger register \[aq]credit card\[aq] .EE .PP or: .IP .EX $ hledger register credit\[rs] card .EE .PP Windows users should keep in mind that \f[CR]cmd\f[R] treats single quote as a regular character, so you should be using double quotes exclusively. PowerShell treats both single and double quotes as quotes. .SS Double escaping (regular expression metacharacters) Characters significant in regular expressions (described below) \- such as \f[CR].\f[R], \f[CR]\[ha]\f[R], \f[CR]$\f[R], \f[CR][\f[R], \f[CR]]\f[R], \f[CR](\f[R], \f[CR])\f[R], \f[CR]|\f[R], and \f[CR]\[rs]\f[R] \- may need to be \[dq]regex\-escaped\[dq] if you don\[aq]t want them to be interpreted by hledger\[aq]s regular expression engine. This is done by writing backslashes before them, but since backslash is typically also a shell metacharacter, both shell\-escaping and regex\-escaping will be needed. Eg to match a literal \f[CR]$\f[R] sign while using the bash shell: .IP .EX $ hledger balance cur:\[aq]\[rs]$\[aq] .EE .PP or: .IP .EX $ hledger balance cur:\[rs]\[rs]$ .EE .SS Triple escaping (for add\-on commands) When you use hledger to run an external add\-on command (described below), one level of shell\-escaping is lost from any options or arguments intended for by the add\-on command, so those need an extra level of shell\-escaping. Eg to match a literal \f[CR]$\f[R] sign while using the bash shell and running an add\-on command (\f[CR]ui\f[R]): .IP .EX $ hledger ui cur:\[aq]\[rs]\[rs]$\[aq] .EE .PP or: .IP .EX $ hledger ui cur:\[rs]\[rs]\[rs]\[rs]$ .EE .PP If you wondered why \f[I]four\f[R] backslashes, perhaps this helps: .PP .TS tab(@); l l. T{ unescaped: T}@T{ \f[CR]$\f[R] T} T{ escaped: T}@T{ \f[CR]\[rs]$\f[R] T} T{ double\-escaped: T}@T{ \f[CR]\[rs]\[rs]$\f[R] T} T{ triple\-escaped: T}@T{ \f[CR]\[rs]\[rs]\[rs]\[rs]$\f[R] T} .TE .PP Or, you can avoid the extra escaping by running the add\-on executable directly: .IP .EX $ hledger\-ui cur:\[rs]\[rs]$ .EE .SS Less escaping Options and arguments are sometimes used in places other than the shell command line, where shell\-escaping is not needed, so there you should use one less level of escaping. Those places include: .IP \[bu] 2 an \[at]argumentfile .IP \[bu] 2 hledger\-ui\[aq]s filter field .IP \[bu] 2 hledger\-web\[aq]s search form .IP \[bu] 2 GHCI\[aq]s prompt (used by developers). .SS Unicode characters hledger is expected to handle non\-ascii characters correctly: .IP \[bu] 2 they should be parsed correctly in input files and on the command line, by all hledger tools (add, iadd, hledger\-web\[aq]s search/add/edit forms, etc.) .IP \[bu] 2 they should be displayed correctly by all hledger tools, and on\-screen alignment should be preserved. .PP This requires a well\-configured environment. Here are some tips: .IP \[bu] 2 A system locale must be configured, and it must be one that can decode the characters being used. In bash, you can set a locale like this: \f[CR]export LANG=en_US.UTF\-8\f[R]. There are some more details in Troubleshooting. This step is essential \- without it, hledger will quit on encountering a non\-ascii character (as with all GHC\-compiled programs). .IP \[bu] 2 your terminal software (eg Terminal.app, iTerm, CMD.exe, xterm..) must support unicode .IP \[bu] 2 the terminal must be using a font which includes the required unicode glyphs .IP \[bu] 2 the terminal should be configured to display wide characters as double width (for report alignment) .IP \[bu] 2 on Windows, for best results you should run hledger in the same kind of environment in which it was built. Eg hledger built in the standard CMD.EXE environment (like the binaries on our download page) might show display problems when run in a cygwin or msys terminal, and vice versa. (See eg #961). .SS Regular expressions A regular expression (regexp) is a small piece of text where certain characters (like \f[CR].\f[R], \f[CR]\[ha]\f[R], \f[CR]$\f[R], \f[CR]+\f[R], \f[CR]*\f[R], \f[CR]()\f[R], \f[CR]|\f[R], \f[CR][]\f[R], \f[CR]\[rs]\f[R]) have special meanings, forming a tiny language for matching text precisely \- very useful in hledger and elsewhere. To learn all about them, visit regular\-expressions.info. .PP hledger supports regexps whenever you are entering a pattern to match something, eg in query arguments, account aliases, CSV if rules, hledger\-web\[aq]s search form, hledger\-ui\[aq]s \f[CR]/\f[R] search, etc. You may need to wrap them in quotes, especially at the command line (see Special characters above). Here are some examples: .PP Account name queries (quoted for command line use): .IP .EX Regular expression: Matches: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- bank assets:bank, assets:bank:savings, expenses:art:banksy, ... :bank assets:bank:savings, expenses:art:banksy :bank: assets:bank:savings \[aq]\[ha]bank\[aq] none of those ( \[ha] matches beginning of text ) \[aq]bank$\[aq] assets:bank ( $ matches end of text ) \[aq]big \[rs]$ bank\[aq] big $ bank ( \[rs] disables following character\[aq]s special meaning ) \[aq]\[rs]bbank\[rs]b\[aq] assets:bank, assets:bank:savings ( \[rs]b matches word boundaries ) \[aq](sav|check)ing\[aq] saving or checking ( (|) matches either alternative ) \[aq]saving|checking\[aq] saving or checking ( outer parentheses are not needed ) \[aq]savings?\[aq] saving or savings ( ? matches 0 or 1 of the preceding thing ) \[aq]my +bank\[aq] my bank, my bank, ... ( + matches 1 or more of the preceding thing ) \[aq]my *bank\[aq] mybank, my bank, my bank, ... ( * matches 0 or more of the preceding thing ) \[aq]b.nk\[aq] bank, bonk, b nk, ... ( . matches any character ) .EE .PP Some other queries: .IP .EX desc:\[aq]amazon|amzn|audible\[aq] Amazon transactions cur:EUR amounts with commodity symbol containing EUR cur:\[aq]\[rs]$\[aq] amounts with commodity symbol containing $ cur:\[aq]\[ha]\[rs]$$\[aq] only $ amounts, not eg AU$ or CA$ cur:....? amounts with 4\-or\-more\-character symbols tag:.=202[1\-3] things with any tag whose value contains 2021, 2022 or 2023 .EE .PP Account name aliases: accept \f[CR].\f[R] instead of \f[CR]:\f[R] as account separator: .IP .EX alias /\[rs]./=: replaces all periods in account names with colons .EE .PP Show multiple top\-level accounts combined as one: .IP .EX \-\-alias=\[aq]/\[ha][\[ha]:]+/=combined\[aq] ( [\[ha]:] matches any character other than : ) .EE .PP Show accounts with the second\-level part removed: .IP .EX \-\-alias \[aq]/\[ha]([\[ha]:]+):[\[ha]:]+/ = \[rs]1\[aq] match a top\-level account and a second\-level account and replace those with just the top\-level account ( \[rs]1 in the replacement text means \[dq]whatever was matched by the first parenthesised part of the regexp\[dq] .EE .PP CSV rules: match CSV records containing dining\-related MCC codes: .IP .EX if \[rs]?MCC581[124] .EE .PP Match CSV records with a specific amount around the end/start of month: .IP .EX if %amount \[rs]b3\[rs].99 & %date (29|30|31|01|02|03)$ .EE .SS hledger\[aq]s regular expressions hledger\[aq]s regular expressions come from the regex\-tdfa library. If they\[aq]re not doing what you expect, it\[aq]s important to know exactly what they support: .IP "1." 3 they are case insensitive .IP "2." 3 they are infix matching (they do not need to match the entire thing being matched) .IP "3." 3 they are POSIX ERE (extended regular expressions) .IP "4." 3 they also support GNU word boundaries (\f[CR]\[rs]b\f[R], \f[CR]\[rs]B\f[R], \f[CR]\[rs]<\f[R], \f[CR]\[rs]>\f[R]) .IP "5." 3 backreferences are supported when doing text replacement in account aliases or CSV rules, where backreferences can be used in the replacement string to reference capturing groups in the search regexp. Otherwise, if you write \f[CR]\[rs]1\f[R], it will match the digit \f[CR]1\f[R]. .IP "6." 3 they do not support mode modifiers (\f[CR](?s)\f[R]), character classes (\f[CR]\[rs]w\f[R], \f[CR]\[rs]d\f[R]), or anything else not mentioned above. .PP Some things to note: .IP \[bu] 2 In the \f[CR]alias\f[R] directive and \f[CR]\-\-alias\f[R] option, regular expressions must be enclosed in forward slashes (\f[CR]/REGEX/\f[R]). Elsewhere in hledger, these are not required. .IP \[bu] 2 In queries, to match a regular expression metacharacter like \f[CR]$\f[R] as a literal character, prepend a backslash. Eg to search for amounts with the dollar sign in hledger\-web, write \f[CR]cur:\[rs]$\f[R]. .IP \[bu] 2 On the command line, some metacharacters like \f[CR]$\f[R] have a special meaning to the shell and so must be escaped at least once more. See Special characters. .SS Argument files You can save a set of command line options and arguments in a file, and then reuse them by writing \f[CR]\[at]FILENAME\f[R] as a command line argument. Eg: \f[CR]hledger bal \[at]foo.args\f[R]. .PP Inside the argument file, each line should contain just one option or argument. Don\[aq]t use spaces except inside quotes (or you\[aq]ll see a confusing error); write \f[CR]=\f[R] (or nothing) between a flag and its argument. For the special characters mentioned above, use one less level of quoting than you would at the command prompt. .SH Output .SS Output destination hledger commands send their output to the terminal by default. You can of course redirect this, eg into a file, using standard shell syntax: .IP .EX $ hledger print > foo.txt .EE .PP Some commands (print, register, stats, the balance commands) also provide the \f[CR]\-o/\-\-output\-file\f[R] option, which does the same thing without needing the shell. Eg: .IP .EX $ hledger print \-o foo.txt $ hledger print \-o \- # write to stdout (the default) .EE .SS Output format Some commands offer other kinds of output, not just text on the terminal. Here are those commands and the formats currently supported: .PP .TS tab(@); lw(16.1n) lw(14.5n) lw(14.5n) lw(16.1n) lw(4.8n) lw(4.0n). T{ \- T}@T{ txt T}@T{ csv/tsv T}@T{ html T}@T{ json T}@T{ sql T} _ T{ aregister T}@T{ Y T}@T{ Y T}@T{ Y T}@T{ Y T}@T{ T} T{ balance T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1,2\f[R] T}@T{ Y T}@T{ T} T{ balancesheet T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y T}@T{ T} T{ balancesheetequity T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y T}@T{ T} T{ cashflow T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y T}@T{ T} T{ incomestatement T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y T}@T{ T} T{ print T}@T{ Y T}@T{ Y T}@T{ T}@T{ Y T}@T{ Y T} T{ register T}@T{ Y T}@T{ Y T}@T{ T}@T{ Y T}@T{ T} .TE .IP \[bu] 2 \f[I]1 Also affected by the balance commands\[aq] \f[CI]\-\-layout\f[I] option.\f[R] .IP \[bu] 2 \f[I]2 \f[CI]balance\f[I] does not support html output without a report interval or with \f[CI]\-\-budget\f[I].\f[R] .PP The output format is selected by the \f[CR]\-O/\-\-output\-format=FMT\f[R] option: .IP .EX $ hledger print \-O csv # print CSV on stdout .EE .PP or by the filename extension of an output file specified with the \f[CR]\-o/\-\-output\-file=FILE.FMT\f[R] option: .IP .EX $ hledger balancesheet \-o foo.csv # write CSV to foo.csv .EE .PP The \f[CR]\-O\f[R] option can be combined with \f[CR]\-o\f[R] to override the file extension, if needed: .IP .EX $ hledger balancesheet \-o foo.txt \-O csv # write CSV to foo.txt .EE .PP Some notes about the various output formats: .SS CSV output .IP \[bu] 2 In CSV output, digit group marks (such as thousands separators) are disabled automatically. .SS HTML output .IP \[bu] 2 HTML output can be styled by an optional \f[CR]hledger.css\f[R] file in the same directory. .SS JSON output .IP \[bu] 2 This is not yet much used; real\-world feedback is welcome. .IP \[bu] 2 Our JSON is rather large and verbose, since it is a faithful representation of hledger\[aq]s internal data types. To understand the JSON, read the Haskell type definitions, which are mostly in https://github.com/simonmichael/hledger/blob/master/hledger\-lib/Hledger/Data/Types.hs. .IP \[bu] 2 hledger represents quantities as Decimal values storing up to 255 significant digits, eg for repeating decimals. Such numbers can arise in practice (from automatically\-calculated transaction prices), and would break most JSON consumers. So in JSON, we show quantities as simple Numbers with at most 10 decimal places. We don\[aq]t limit the number of integer digits, but that part is under your control. We hope this approach will not cause problems in practice; if you find otherwise, please let us know. (Cf #1195) .SS SQL output .IP \[bu] 2 This is not yet much used; real\-world feedback is welcome. .IP \[bu] 2 SQL output is expected to work at least with SQLite, MySQL and Postgres. .IP \[bu] 2 For SQLite, it will be more useful if you modify the generated \f[CR]id\f[R] field to be a PRIMARY KEY. Eg: .RS 2 .IP .EX $ hledger print \-O sql | sed \[aq]s/id serial/id INTEGER PRIMARY KEY AUTOINCREMENT NOT NULL/g\[aq] | ... .EE .RE .IP \[bu] 2 SQL output is structured with the expectations that statements will be executed in the empty database. If you already have tables created via SQL output of hledger, you would probably want to either clear tables of existing data (via \f[CR]delete\f[R] or \f[CR]truncate\f[R] SQL statements) or drop tables completely as otherwise your postings will be duped. .SS Commodity styles When displaying amounts, hledger infers a standard display style for each commodity/currency, as described below in Commodity display style. .PP If needed, this can be overridden by a \f[CR]\-c/\-\-commodity\-style\f[R] option (except for cost amounts and amounts displayed by the \f[CR]print\f[R] command, which are always displayed with all decimal digits). For example, the following will force dollar amounts to be displayed as shown: .IP .EX $ hledger print \-c \[aq]$1.000,0\[aq] .EE .PP This option can repeated to set the display style for multiple commodities/currencies. Its argument is as described in the commodity directive. .SS Colour In terminal output, some commands can produce colour when the terminal supports it: .IP \[bu] 2 if the \f[CR]\-\-color/\-\-colour\f[R] option is given a value of \f[CR]yes\f[R] or \f[CR]always\f[R] (or \f[CR]no\f[R] or \f[CR]never\f[R]), colour will (or will not) be used; .IP \[bu] 2 otherwise, if the \f[CR]NO_COLOR\f[R] environment variable is set, colour will not be used; .IP \[bu] 2 otherwise, colour will be used if the output (terminal or file) supports it. .SS Box\-drawing In terminal output, you can enable unicode box\-drawing characters to render prettier tables: .IP \[bu] 2 if the \f[CR]\-\-pretty\f[R] option is given a value of \f[CR]yes\f[R] or \f[CR]always\f[R] (or \f[CR]no\f[R] or \f[CR]never\f[R]), unicode characters will (or will not) be used; .IP \[bu] 2 otherwise, unicode characters will not be used. .SS Paging When showing long output in the terminal, hledger will try to use the pager specified by the \f[CR]PAGER\f[R] environment variable, or \f[CR]less\f[R], or \f[CR]more\f[R]. (A pager is a helper program that shows one page at a time rather than scrolling everything off screen). Currently it does this only for help output, not for reports; specifically, .IP \[bu] 2 when listing commands, with \f[CR]hledger\f[R] .IP \[bu] 2 when showing help with \f[CR]hledger [CMD] \-\-help\f[R], .IP \[bu] 2 when viewing manuals with \f[CR]hledger help\f[R] or \f[CR]hledger \-\-man\f[R]. .PP Note the pager is expected to handle ANSI codes, which hledger uses eg for bold emphasis. For the common pager \f[CR]less\f[R] (and its \f[CR]more\f[R] compatibility mode), we add \f[CR]R\f[R] to the \f[CR]LESS\f[R] and \f[CR]MORE\f[R] environment variables to make this work. If you use a different pager, you might need to configure it similarly, to avoid seeing junk on screen (let us know). Otherwise, you can set the \f[CR]NO_COLOR\f[R] environment variable to 1 to disable all ANSI output (see Colour). .SS Debug output We intend hledger to be relatively easy to troubleshoot, introspect and develop. You can add \f[CR]\-\-debug[=N]\f[R] to any hledger command line to see additional debug output. N ranges from 1 (least output, the default) to 9 (maximum output). Typically you would start with 1 and increase until you are seeing enough. Debug output goes to stderr, and is not affected by \f[CR]\-o/\-\-output\-file\f[R] (unless you redirect stderr to stdout, eg: \f[CR]2>&1\f[R]). It will be interleaved with normal output, which can help reveal when parts of the code are evaluated. To capture debug output in a log file instead, you can usually redirect stderr, eg: .IP .EX hledger bal \-\-debug=3 2>hledger.log .EE .SH Environment These environment variables affect hledger: .PP \f[B]COLUMNS\f[R] This is normally set by your terminal; some hledger commands (\f[CR]register\f[R]) will format their output to this width. If not set, they will try to use the available terminal width. .PP \f[B]LEDGER_FILE\f[R] The main journal file to use when not specified with \f[CR]\-f/\-\-file\f[R]. Default: \f[CR]$HOME/.hledger.journal\f[R]. .PP \f[B]NO_COLOR\f[R] If this environment variable is set (with any value), hledger will not use ANSI color codes in terminal output, unless overridden by an explicit \f[CR]\-\-color/\-\-colour\f[R] option. .SH PART 2: DATA FORMATS .SH Journal hledger\[aq]s default file format, representing a General Journal. Here\[aq]s a cheatsheet/mini\-tutorial, or you can skip ahead to About journal format. .SS Journal cheatsheet .IP .EX # Here is the main syntax of hledger\[aq]s journal format # (omitting extra Ledger compatibility syntax). # hledger journals contain comments, directives, and transactions, in any order: ############################################################################### # 1. Comment lines are for notes or temporarily disabling things. # They begin with #, ;, or a line containing the word \[dq]comment\[dq]. # hash comment line ; semicolon comment line comment These lines are commented. end comment # Some but not all hledger entries can have same\-line comments attached to them, # from ; (semicolon) to end of line. ############################################################################### # 2. Directives modify parsing or reports in some way. # They begin with a word or letter (or symbol). account actifs ; type:A, declare an account that is an Asset. 2+ spaces before ;. account passifs ; type:L, declare an account that is a Liability, and so on.. (ALERX) alias chkg = assets:checking commodity $0.00 decimal\-mark . include /dev/null payee Whole Foods P 2022\-01\-01 AAAA $1.40 \[ti] monthly budget goals ; <\- 2+ spaces between period expression and description expenses:food $400 expenses:home $1000 budgeted ############################################################################### # 3. Transactions are what it\[aq]s all about; they are dated events, # usually describing movements of money. # They begin with a date. # DATE DESCRIPTION ; This is a transaction comment. # ACCOUNT NAME 1 AMOUNT1 ; <\- posting 1. This is a posting comment. # ACCOUNT NAME 2 AMOUNT2 ; <\- posting 2. Postings must be indented. # ; \[ha]\[ha] At least 2 spaces between account and amount. # ... ; Any number of postings is allowed. The amounts must balance (sum to 0). 2022\-01\-01 opening balances are declared this way assets:checking $1000 ; Account names can be anything. lower case is easy to type. assets:savings $1000 ; assets, liabilities, equity, revenues, expenses are common. assets:cash:wallet $100 ; : indicates subaccounts. liabilities:credit card $\-200 ; liabilities, equity, revenues balances are usually negative. equity ; One amount can be left blank; $\-1900 is inferred here. 2022\-04\-15 * (#12345) pay taxes ; There can be a ! or * after the date meaning \[dq]pending\[dq] or \[dq]cleared\[dq]. ; There can be a transaction code (text in parentheses) after the date/status. ; Amounts\[aq] sign represents direction of flow, or credit/debit: assets:checking $\-500 ; minus means removed from this account (credit) expenses:tax:us:2021 $500 ; plus means added to this account (debit) ; revenue/expense categories are also \[dq]accounts\[dq] 2022\-01\-01 ; The description is optional. ; Any currency/commodity symbols are allowed, on either side. assets:cash:wallet GBP \-10 expenses:clothing GBP 10 assets:gringotts \-10 gold assets:pouch 10 gold revenues:gifts \-2 \[dq]Liquorice Wands\[dq] ; Complex symbols assets:bag 2 \[dq]Liquorice Wands\[dq] ; must be double\-quoted. 2022\-01\-01 Cost in another commodity can be noted with \[at] or \[at]\[at] assets:investments 2.0 AAAA \[at] $1.50 ; \[at] means per\-unit cost assets:investments 3.0 AAAA \[at]\[at] $4 ; \[at]\[at] means total cost assets:checking $\-7.00 2022\-01\-02 assert balances ; Balances can be asserted for extra error checking, in any transaction. assets:investments 0 AAAA = 5.0 AAAA assets:pouch 0 gold = 10 gold assets:savings $0 = $1000 1999\-12\-31 Ordering transactions by date is recommended but not required. ; Postings are not required. 2022.01.01 These date 2022/1/1 formats are 12/31 also allowed (but consistent YYYY\-MM\-DD is recommended). .EE .SS About journal format hledger\[aq]s usual data source is a plain text file containing journal entries in hledger journal format. This file represents a standard accounting general journal. I use file names ending in \f[CR].journal\f[R], but that\[aq]s not required. The journal file contains a number of transaction entries, each describing a transfer of money (or any commodity) between two or more named accounts, in a simple format readable by both hledger and humans. .PP hledger\[aq]s journal format is compatible with most of Ledger\[aq]s journal format, but not all of it. The differences and interoperation tips are described at hledger and Ledger. With some care, and by avoiding incompatible features, you can keep your hledger journal readable by Ledger and vice versa. This can useful eg for comparing the behaviour of one app against the other. .PP You can use hledger without learning any more about this file; just use the add or web or import commands to create and update it. .PP Many users, though, edit the journal file with a text editor, and track changes with a version control system such as git. Editor addons such as ledger\-mode or hledger\-mode for Emacs, vim\-ledger for Vim, and hledger\-vscode for Visual Studio Code, make this easier, adding colour, formatting, tab completion, and useful commands. See Editor configuration at hledger.org for the full list. .PP Here\[aq]s a description of each part of the file format (and hledger\[aq]s data model). .PP A hledger journal file can contain three kinds of thing: file comments, transactions, and/or directives (counting periodic transaction rules and auto posting rules as directives). .SS Comments Lines in the journal will be ignored if they begin with a hash (\f[CR]#\f[R]) or a semicolon (\f[CR];\f[R]). (See also Other syntax.) hledger will also ignore regions beginning with a \f[CR]comment\f[R] line and ending with an \f[CR]end comment\f[R] line (or file end). Here\[aq]s a suggestion for choosing between them: .IP \[bu] 2 \f[CR]#\f[R] for top\-level notes .IP \[bu] 2 \f[CR];\f[R] for commenting out things temporarily .IP \[bu] 2 \f[CR]comment\f[R] for quickly commenting large regions (remember it\[aq]s there, or you might get confused) .PP Eg: .IP .EX # a comment line ; another commentline comment A multi\-line comment block, continuing until \[dq]end comment\[dq] directive or the end of the current file. end comment .EE .PP Some hledger entries can have same\-line comments attached to them, from ; (semicolon) to end of line. See Transaction comments, Posting comments, and Account comments below. .SS Transactions Transactions are the main unit of information in a journal file. They represent events, typically a movement of some quantity of commodities between two or more named accounts. .PP Each transaction is recorded as a journal entry, beginning with a simple date in column 0. This can be followed by any of the following optional fields, separated by spaces: .IP \[bu] 2 a status character (empty, \f[CR]!\f[R], or \f[CR]*\f[R]) .IP \[bu] 2 a code (any short number or text, enclosed in parentheses) .IP \[bu] 2 a description (any remaining text until end of line or a semicolon) .IP \[bu] 2 a comment (any remaining text following a semicolon until end of line, and any following indented lines beginning with a semicolon) .IP \[bu] 2 0 or more indented \f[I]posting\f[R] lines, describing what was transferred and the accounts involved (indented comment lines are also allowed, but not blank lines or non\-indented lines). .PP Here\[aq]s a simple journal file containing one transaction: .IP .EX 2008/01/01 income assets:bank:checking $1 income:salary $\-1 .EE .SS Dates .SS Simple dates Dates in the journal file use \f[I]simple dates\f[R] format: \f[CR]YYYY\-MM\-DD\f[R] or \f[CR]YYYY/MM/DD\f[R] or \f[CR]YYYY.MM.DD\f[R], with leading zeros optional. The year may be omitted, in which case it will be inferred from the context: the current transaction, the default year set with a \f[CR]Y\f[R] directive, or the current date when the command is run. Some examples: \f[CR]2010\-01\-31\f[R], \f[CR]2010/01/31\f[R], \f[CR]2010.1.31\f[R], \f[CR]1/31\f[R]. .PP (The UI also accepts simple dates, as well as the more flexible smart dates documented in the hledger manual.) .SS Posting dates You can give individual postings a different date from their parent transaction, by adding a posting comment containing a tag (see below) like \f[CR]date:DATE\f[R]. This is probably the best way to control posting dates precisely. Eg in this example the expense should appear in May reports, and the deduction from checking should be reported on 6/1 for easy bank reconciliation: .IP .EX 2015/5/30 expenses:food $10 ; food purchased on saturday 5/30 assets:checking ; bank cleared it on monday, date:6/1 .EE .IP .EX $ hledger \-f t.j register food 2015\-05\-30 expenses:food $10 $10 .EE .IP .EX $ hledger \-f t.j register checking 2015\-06\-01 assets:checking $\-10 $\-10 .EE .PP DATE should be a simple date; if the year is not specified it will use the year of the transaction\[aq]s date. .PD 0 .P .PD The \f[CR]date:\f[R] tag must have a valid simple date value if it is present, eg a \f[CR]date:\f[R] tag with no value is not allowed. .SS Status Transactions, or individual postings within a transaction, can have a status mark, which is a single character before the transaction description or posting account name, separated from it by a space, indicating one of three statuses: .PP .TS tab(@); l l. T{ mark \ T}@T{ status T} _ T{ \ T}@T{ unmarked T} T{ \f[CR]!\f[R] T}@T{ pending T} T{ \f[CR]*\f[R] T}@T{ cleared T} .TE .PP When reporting, you can filter by status with the \f[CR]\-U/\-\-unmarked\f[R], \f[CR]\-P/\-\-pending\f[R], and \f[CR]\-C/\-\-cleared\f[R] flags; or the \f[CR]status:\f[R], \f[CR]status:!\f[R], and \f[CR]status:*\f[R] queries; or the U, P, C keys in hledger\-ui. .PP Note, in Ledger and in older versions of hledger, the \[dq]unmarked\[dq] state is called \[dq]uncleared\[dq]. As of hledger 1.3 we have renamed it to unmarked for clarity. .PP To replicate Ledger and old hledger\[aq]s behaviour of also matching pending, combine \-U and \-P. .PP Status marks are optional, but can be helpful eg for reconciling with real\-world accounts. Some editor modes provide highlighting and shortcuts for working with status. Eg in Emacs ledger\-mode, you can toggle transaction status with C\-c C\-e, or posting status with C\-c C\-c. .PP What \[dq]uncleared\[dq], \[dq]pending\[dq], and \[dq]cleared\[dq] actually mean is up to you. Here\[aq]s one suggestion: .PP .TS tab(@); lw(9.7n) lw(60.3n). T{ status T}@T{ meaning T} _ T{ uncleared T}@T{ recorded but not yet reconciled; needs review T} T{ pending T}@T{ tentatively reconciled (if needed, eg during a big reconciliation) T} T{ cleared T}@T{ complete, reconciled as far as possible, and considered correct T} .TE .PP With this scheme, you would use \f[CR]\-PC\f[R] to see the current balance at your bank, \f[CR]\-U\f[R] to see things which will probably hit your bank soon (like uncashed checks), and no flags to see the most up\-to\-date state of your finances. .SS Code After the status mark, but before the description, you can optionally write a transaction \[dq]code\[dq], enclosed in parentheses. This is a good place to record a check number, or some other important transaction id or reference number. .SS Description A transaction\[aq]s description is the rest of the line following the date and status mark (or until a comment begins). Sometimes called the \[dq]narration\[dq] in traditional bookkeeping, it can be used for whatever you wish, or left blank. Transaction descriptions can be queried, unlike comments. .SS Payee and note You can optionally include a \f[CR]|\f[R] (pipe) character in descriptions to subdivide the description into separate fields for payee/payer name on the left (up to the first \f[CR]|\f[R]) and an additional note field on the right (after the first \f[CR]|\f[R]). This may be worthwhile if you need to do more precise querying and pivoting by payee or by note. .SS Transaction comments Text following \f[CR];\f[R], after a transaction description, and/or on indented lines immediately below it, form comments for that transaction. They are reproduced by \f[CR]print\f[R] but otherwise ignored, except they may contain tags, which are not ignored. .IP .EX 2012\-01\-01 something ; a transaction comment ; a second line of transaction comment expenses 1 assets .EE .SS Postings A posting is an addition of some amount to, or removal of some amount from, an account. Each posting line begins with at least one space or tab (2 or 4 spaces is common), followed by: .IP \[bu] 2 (optional) a status character (empty, \f[CR]!\f[R], or \f[CR]*\f[R]), followed by a space .IP \[bu] 2 (required) an account name (any text, optionally containing \f[B]single spaces\f[R], until end of line or a double space) .IP \[bu] 2 (optional) \f[B]two or more spaces\f[R] or tabs followed by an amount. .PP Positive amounts are being added to the account, negative amounts are being removed. .PP The amounts within a transaction must always sum up to zero. As a convenience, one amount may be left blank; it will be inferred so as to balance the transaction. .PP Be sure to note the unusual two\-space delimiter between account name and amount. This makes it easy to write account names containing spaces. But if you accidentally leave only one space (or tab) before the amount, the amount will be considered part of the account name. .SS Account names Accounts are the main way of categorising things in hledger. As in Double Entry Bookkeeping, they can represent real world accounts (such as a bank account), or more abstract categories such as \[dq]money borrowed from Frank\[dq] or \[dq]money spent on electricity\[dq]. .PP You can use any account names you like, but we usually start with the traditional accounting categories, which in english are \f[CR]assets\f[R], \f[CR]liabilities\f[R], \f[CR]equity\f[R], \f[CR]revenues\f[R], \f[CR]expenses\f[R]. (You might see these referred to as A, L, E, R, X for short.) .PP For more precise reporting, we usually divide the top level accounts into more detailed subaccounts, by writing a full colon between account name parts. For example, from the account names \f[CR]assets:bank:checking\f[R] and \f[CR]expenses:food\f[R], hledger will infer this hierarchy of five accounts: .IP .EX assets assets:bank assets:bank:checking expenses expenses:food .EE .PP Shown as an outline, the hierarchical tree structure is more clear: .IP .EX assets bank checking expenses food .EE .PP hledger reports can summarise the account tree to any depth, so you can go as deep as you like with subcategories, but keeping your account names relatively simple may be best when starting out. .PP Account names may be capitalised or not; they may contain letters, numbers, symbols, or single spaces. Note, when an account name and an amount are written on the same line, they must be separated by \f[B]two or more spaces\f[R] (or tabs). .PP Parentheses or brackets enclosing the full account name indicate virtual postings, described below. Parentheses or brackets internal to the account name have no special meaning. .PP Account names can be altered temporarily or permanently by account aliases. .SS Amounts After the account name, there is usually an amount. (Important: between account name and amount, there must be \f[B]two or more spaces\f[R].) .PP hledger\[aq]s amount format is flexible, supporting several international formats. Here are some examples. Amounts have a number (the \[dq]quantity\[dq]): .IP .EX 1 .EE .PP \&..and usually a currency symbol or commodity name (more on this below), to the left or right of the quantity, with or without a separating space: .IP .EX $1 4000 AAPL 3 \[dq]green apples\[dq] .EE .PP Amounts can be preceded by a minus sign (or a plus sign, though plus is the default), The sign can be written before or after a left\-side commodity symbol: .IP .EX \-$1 $\-1 .EE .PP One or more spaces between the sign and the number are acceptable when parsing (but they won\[aq]t be displayed in output): .IP .EX + $1 $\- 1 .EE .PP Scientific E notation is allowed: .IP .EX 1E\-6 EUR 1E3 .EE .SS Decimal marks, digit group marks A \f[I]decimal mark\f[R] can be written as a period or a comma: .IP .EX 1.23 1,23 .EE .PP In the integer part of the quantity (left of the decimal mark), groups of digits can optionally be separated by a \f[I]digit group mark\f[R] \- a space, comma, or period (different from the decimal mark): .IP .EX $1,000,000.00 EUR 2.000.000,00 INR 9,99,99,999.00 1 000 000.9455 .EE .PP hledger is not biased towards period or comma decimal marks, so a number containing just one period or comma, like \f[CR]1,000\f[R] or \f[CR]1.000\f[R], is ambiguous. In such cases hledger assumes it is a decimal mark, parsing both of these as 1. .PP To disambiguate these and ensure accurate number parsing, especially if you use digit group marks, we recommend declaring the decimal mark. You can declare it for each file with \f[CR]decimal\-mark\f[R] directives, or for each commodity with \f[CR]commodity\f[R] directives (described below). .SS Commodity Amounts in hledger have both a \[dq]quantity\[dq], which is a signed decimal number, and a \[dq]commodity\[dq], which is a currency symbol, stock ticker, or any word or phrase describing something you are tracking. .PP If the commodity name contains non\-letters (spaces, numbers, or punctuation), you must always write it inside double quotes (\f[CR]\[dq]green apples\[dq]\f[R], \f[CR]\[dq]ABC123\[dq]\f[R]). .PP If you write just a bare number, that too will have a commodity, with name \f[CR]\[dq]\[dq]\f[R]; we call that the \[dq]no\-symbol commodity\[dq]. .PP Actually, hledger combines these single\-commodity amounts into more powerful multi\-commodity amounts, which are what it works with most of the time. A multi\-commodity amount could be, eg: \f[CR]1 USD, 2 EUR, 3.456 TSLA\f[R]. In practice, you will only see multi\-commodity amounts in hledger\[aq]s output; you can\[aq]t write them directly in the journal file. .PP (If you are writing scripts or working with hledger\[aq]s internals, these are the \f[CR]Amount\f[R] and \f[CR]MixedAmount\f[R] types.) .SS Directives influencing number parsing and display You can add \f[CR]decimal\-mark\f[R] and \f[CR]commodity\f[R] directives to the journal, to declare and control these things more explicitly and precisely. These are described below, but here\[aq]s a quick example: .IP .EX # the decimal mark character used by all amounts in this file (all commodities) decimal\-mark . # display styles for the $, EUR, INR and no\-symbol commodities: commodity $1,000.00 commodity EUR 1.000,00 commodity INR 9,99,99,999.00 commodity 1 000 000.9455 .EE .PP .SS Commodity display style For the amounts in each commodity, hledger chooses a consistent display style (symbol placement, decimal mark and digit group marks, number of decimal digits) to use in most reports. This is inferred as follows: .PP First, if there\[aq]s a \f[CR]D\f[R] directive declaring a default commodity, that commodity symbol and amount format is applied to all no\-symbol amounts in the journal. .PP Then each commodity\[aq]s display style is determined from its \f[CR]commodity\f[R] directive. We recommend always declaring commodities with \f[CR]commodity\f[R] directives, since they help ensure consistent display styles and precisions, and bring other benefits such as error checking for commodity symbols. .PP But if a \f[CR]commodity\f[R] directive is not present, hledger infers a commodity\[aq]s display styles from its amounts as they are written in the journal (excluding cost amounts and amounts in periodic transaction rules or auto posting rules). It uses .IP \[bu] 2 the symbol placement and decimal mark of the first amount seen .IP \[bu] 2 the digit group marks of the first amount with digit group marks .IP \[bu] 2 and the maximum number of decimal digits seen across all amounts. .PP And as fallback if no applicable amounts are found, it would use a default style, like \f[CR]$1000.00\f[R] (symbol on the left with no space, period as decimal mark, and two decimal digits). .PP Finally, commodity styles can be overridden by the \f[CR]\-c/\-\-commodity\-style\f[R] command line option. .SS Rounding Amounts are stored internally as decimal numbers with up to 255 decimal places. They are displayed with their original journal precisions by print and print\-like reports, and rounded to their display precision (the number of decimal digits specified by the commodity display style) by other reports. When rounding, hledger uses banker\[aq]s rounding (it rounds to the nearest even digit). So eg 0.5 displayed with zero decimal digits appears as \[dq]0\[dq]. .PP .SS Costs After a posting amount, you can note its cost (when buying) or selling price (when selling) in another commodity, by writing either \f[CR]\[at] UNITPRICE\f[R] or \f[CR]\[at]\[at] TOTALPRICE\f[R] after it. This indicates a conversion transaction, where one commodity is exchanged for another. .PP (You might also see this called \[dq]transaction price\[dq] in hledger docs, discussions, or code; that term was directionally neutral and reminded that it is a price specific to a transaction, but we now just call it \[dq]cost\[dq], with the understanding that the transaction could be a purchase or a sale.) .PP Costs are usually written explicitly with \f[CR]\[at]\f[R] or \f[CR]\[at]\[at]\f[R], but can also be inferred automatically for simple multi\-commodity transactions. Note, if costs are inferred, the order of postings is significant; the first posting will have a cost attached, in the commodity of the second. .PP As an example, here are several ways to record purchases of a foreign currency in hledger, using the cost notation either explicitly or implicitly: .IP "1." 3 Write the price per unit, as \f[CR]\[at] UNITPRICE\f[R] after the amount: .RS 4 .IP .EX 2009/1/1 assets:euros €100 \[at] $1.35 ; one hundred euros purchased at $1.35 each assets:dollars ; balancing amount is \-$135.00 .EE .RE .IP "2." 3 Write the total price, as \f[CR]\[at]\[at] TOTALPRICE\f[R] after the amount: .RS 4 .IP .EX 2009/1/1 assets:euros €100 \[at]\[at] $135 ; one hundred euros purchased at $135 for the lot assets:dollars .EE .RE .IP "3." 3 Specify amounts for all postings, using exactly two commodities, and let hledger infer the price that balances the transaction. Note the effect of posting order: the price is added to first posting, making it \f[CR]€100 \[at]\[at] $135\f[R], as in example 2: .RS 4 .IP .EX 2009/1/1 assets:euros €100 ; one hundred euros purchased assets:dollars $\-135 ; for $135 .EE .RE .PP Amounts can be converted to cost at report time using the \f[CR]\-B/\-\-cost\f[R] flag; this is discussed more in the Cost reporting section. .PP Note that the cost normally should be a positive amount, though it\[aq]s not required to be. This can be a little confusing, see discussion at \-\-infer\-market\-prices: market prices from transactions. .SS Other cost/lot notations A slight digression for Ledger and Beancount users. Ledger has a number of cost/lot\-related notations: .IP \[bu] 2 \f[CR]\[at] UNITCOST\f[R] and \f[CR]\[at]\[at] TOTALCOST\f[R] .RS 2 .IP \[bu] 2 expresses a conversion rate, as in hledger .IP \[bu] 2 when buying, also creates a lot than can be selected at selling time .RE .IP \[bu] 2 \f[CR](\[at]) UNITCOST\f[R] and \f[CR](\[at]\[at]) TOTALCOST\f[R] (virtual cost) .RS 2 .IP \[bu] 2 like the above, but also means \[dq]this cost was exceptional, don\[aq]t use it when inferring market prices\[dq]. .RE .PP Currently, hledger treats the above like \f[CR]\[at]\f[R] and \f[CR]\[at]\[at]\f[R]; the parentheses are ignored. .IP \[bu] 2 \f[CR]{=FIXEDUNITCOST}\f[R] and \f[CR]{{=FIXEDTOTALCOST}}\f[R] (fixed price) .RS 2 .IP \[bu] 2 when buying, means \[dq]this cost is also the fixed price, don\[aq]t let it fluctuate in value reports\[dq] .RE .IP \[bu] 2 \f[CR]{UNITCOST}\f[R] and \f[CR]{{TOTALCOST}}\f[R] (lot price) .RS 2 .IP \[bu] 2 can be used identically to \f[CR]\[at] UNITCOST\f[R] and \f[CR]\[at]\[at] TOTALCOST\f[R], also creates a lot .IP \[bu] 2 when selling, combined with \f[CR]\[at] ...\f[R], specifies an investment lot by its cost basis; does not check if that lot is present .RE .IP \[bu] 2 and related: \f[CR][YYYY/MM/DD]\f[R] (lot date) .RS 2 .IP \[bu] 2 when buying, attaches this acquisition date to the lot .IP \[bu] 2 when selling, selects a lot by its acquisition date .RE .IP \[bu] 2 \f[CR](SOME TEXT)\f[R] (lot note) .RS 2 .IP \[bu] 2 when buying, attaches this note to the lot .IP \[bu] 2 when selling, selects a lot by its note .RE .PP Currently, hledger accepts any or all of the above in any order after the posting amount, but ignores them. (This can break transaction balancing.) .PP For Beancount users, the notation and behaviour is different: .IP \[bu] 2 \f[CR]\[at] UNITCOST\f[R] and \f[CR]\[at]\[at] TOTALCOST\f[R] .RS 2 .IP \[bu] 2 expresses a cost without creating a lot, as in hledger .IP \[bu] 2 when buying (augmenting) or selling (reducing) a lot, combined with \f[CR]{...}\f[R]: documents the cost/selling price (not used for transaction balancing) .RE .IP \[bu] 2 \f[CR]{UNITCOST}\f[R] and \f[CR]{{TOTALCOST}}\f[R] .RS 2 .IP \[bu] 2 when buying (augmenting), expresses the cost for transaction balancing, and also creates a lot with this cost basis attached .IP \[bu] 2 when selling (reducing), .RS 2 .IP \[bu] 2 selects a lot by its cost basis .IP \[bu] 2 raises an error if that lot is not present or can not be selected unambiguously (depending on booking method configured) .IP \[bu] 2 expresses the selling price for transaction balancing .RE .RE .PP Currently, hledger accepts the \f[CR]{UNITCOST}\f[R]/\f[CR]{{TOTALCOST}}\f[R] notation but ignores it. .IP \[bu] 2 variations: \f[CR]{}\f[R], \f[CR]{YYYY\-MM\-DD}\f[R], \f[CR]{\[dq]LABEL\[dq]}\f[R], \f[CR]{UNITCOST, \[dq]LABEL\[dq]}\f[R], \f[CR]{UNITCOST, YYYY\-MM\-DD, \[dq]LABEL\[dq]}\f[R] etc. .PP Currently, hledger rejects these. .SS Balance assertions hledger supports Ledger\-style balance assertions in journal files. These look like, for example, \f[CR]= EXPECTEDBALANCE\f[R] following a posting\[aq]s amount. Eg here we assert the expected dollar balance in accounts a and b after each posting: .IP .EX 2013/1/1 a $1 =$1 b =$\-1 2013/1/2 a $1 =$2 b $\-1 =$\-2 .EE .PP After reading a journal file, hledger will check all balance assertions and report an error if any of them fail. Balance assertions can protect you from, eg, inadvertently disrupting reconciled balances while cleaning up old entries. You can disable them temporarily with the \f[CR]\-I/\-\-ignore\-assertions\f[R] flag, which can be useful for troubleshooting or for reading Ledger files. (Note: this flag currently does not disable balance assignments, described below). .SS Assertions and ordering hledger sorts an account\[aq]s postings and assertions first by date and then (for postings on the same day) by parse order. Note this is different from Ledger, which sorts assertions only by parse order. (Also, Ledger assertions do not see the accumulated effect of repeated postings to the same account within a transaction.) .PP So, hledger balance assertions keep working if you reorder differently\-dated transactions within the journal. But if you reorder same\-dated transactions or postings, assertions might break and require updating. This order dependence does bring an advantage: precise control over the order of postings and assertions within a day, so you can assert intra\-day balances. .SS Assertions and multiple included files Multiple files included with the \f[CR]include\f[R] directive are processed as if concatenated into one file, preserving their order and the posting order within each file. It means that balance assertions in later files will see balance from earlier files. .PP And if you have multiple postings to an account on the same day, split across multiple files, and you want to assert the account\[aq]s balance on that day, you\[aq]ll need to put the assertion in the right file \- the last one in the sequence, probably. .SS Assertions and multiple \-f files Unlike \f[CR]include\f[R], when multiple files are specified on the command line with multiple \f[CR]\-f/\-\-file\f[R] options, balance assertions will not see balance from earlier files. This can be useful when you do not want problems in earlier files to disrupt valid assertions in later files. .PP If you do want assertions to see balance from earlier files, use \f[CR]include\f[R], or concatenate the files temporarily. .SS Assertions and commodities The asserted balance must be a simple single\-commodity amount, and in fact the assertion checks only this commodity\[aq]s balance within the (possibly multi\-commodity) account balance. This is how assertions work in Ledger also. We could call this a \[dq]partial\[dq] balance assertion. .PP To assert the balance of more than one commodity in an account, you can write multiple postings, each asserting one commodity\[aq]s balance. .PP You can make a stronger \[dq]total\[dq] balance assertion by writing a double equals sign (\f[CR]== EXPECTEDBALANCE\f[R]). This asserts that there are no other commodities in the account besides the asserted one (or at least, that their balance is 0). .IP .EX 2013/1/1 a $1 a 1€ b $\-1 c \-1€ 2013/1/2 ; These assertions succeed a 0 = $1 a 0 = 1€ b 0 == $\-1 c 0 == \-1€ 2013/1/3 ; This assertion fails as \[aq]a\[aq] also contains 1€ a 0 == $1 .EE .PP It\[aq]s not yet possible to make a complete assertion about a balance that has multiple commodities. One workaround is to isolate each commodity into its own subaccount: .IP .EX 2013/1/1 a:usd $1 a:euro 1€ b 2013/1/2 a 0 == 0 a:usd 0 == $1 a:euro 0 == 1€ .EE .SS Assertions and costs Balance assertions ignore costs, and should normally be written without one: .IP .EX 2019/1/1 (a) $1 \[at] €1 = $1 .EE .PP We do allow costs to be written in balance assertion amounts, however, and print shows them, but they don\[aq]t affect whether the assertion passes or fails. This is for backward compatibility (hledger\[aq]s close command used to generate balance assertions with costs), and because balance \f[I]assignments\f[R] do use costs (see below). .SS Assertions and subaccounts The balance assertions above (\f[CR]=\f[R] and \f[CR]==\f[R]) do not count the balance from subaccounts; they check the account\[aq]s exclusive balance only. You can assert the balance including subaccounts by writing \f[CR]=*\f[R] or \f[CR]==*\f[R], eg: .IP .EX 2019/1/1 equity:opening balances checking:a 5 checking:b 5 checking 1 ==* 11 .EE .SS Assertions and virtual postings Balance assertions always consider both real and virtual postings; they are not affected by the \f[CR]\-\-real/\-R\f[R] flag or \f[CR]real:\f[R] query. .SS Assertions and auto postings Balance assertions \f[I]are\f[R] affected by the \f[CR]\-\-auto\f[R] flag, which generates auto postings, which can alter account balances. Because auto postings are optional in hledger, accounts affected by them effectively have two balances. But balance assertions can only test one or the other of these. So to avoid making fragile assertions, either: .IP \[bu] 2 assert the balance calculated with \f[CR]\-\-auto\f[R], and always use \f[CR]\-\-auto\f[R] with that file .IP \[bu] 2 or assert the balance calculated without \f[CR]\-\-auto\f[R], and never use \f[CR]\-\-auto\f[R] with that file .IP \[bu] 2 or avoid balance assertions on accounts affected by auto postings (or avoid auto postings entirely). .SS Assertions and precision Balance assertions compare the exactly calculated amounts, which are not always what is shown by reports. Eg a commodity directive may limit the display precision, but this will not affect balance assertions. Balance assertion failure messages show exact amounts. .SS Posting comments Text following \f[CR];\f[R], at the end of a posting line, and/or on indented lines immediately below it, form comments for that posting. They are reproduced by \f[CR]print\f[R] but otherwise ignored, except they may contain tags, which are not ignored. .IP .EX 2012\-01\-01 expenses 1 ; a comment for posting 1 assets ; a comment for posting 2 ; a second comment line for posting 2 .EE .SS Tags Tags are a way to add extra labels or labelled data to transactions, postings, or accounts, which you can then search or pivot on. .PP They are written as a word (optionally hyphenated) immediately followed by a full colon, in a transaction or posting or account directive\[aq]s comment. (This is an exception to the usual rule that things in comments are ignored.) Eg, here four different tags are recorded: one on the checking account, two on the transaction, and one on the expenses posting: .IP .EX account assets:checking ; accounttag: 2017/1/16 bought groceries ; transactiontag\-1: ; transactiontag\-2: assets:checking $\-1 expenses:food $1 ; postingtag: .EE .PP Postings also inherit tags from their transaction and their account. And transactions also acquire tags from their postings (and postings\[aq] accounts). So in the example above, the expenses posting effectively has all four tags (by inheriting from account and transaction), and the transaction also has all four tags (by acquiring from the expenses posting). .PP You can list tag names with \f[CR]hledger tags [NAMEREGEX]\f[R], or match by tag name with a \f[CR]tag:NAMEREGEX\f[R] query. .SS Tag values Tags can have a value, which is any text after the colon up until a comma or end of line (with surrounding whitespace removed). Note this means that hledger tag values can not contain commas. Eg in the following posting, the three tags\[aq] values are \[dq]value 1\[dq], \[dq]value 2\[dq], and \[dq]\[dq] (empty) respectively: .IP .EX expenses:food $10 ; foo, tag1: value 1 , tag2:value 2, bar tag3: , baz .EE .PP Note that tags can be repeated, and are additive rather than overriding: when the same tag name is seen again with a new value, the new name:value pair is added to the tags. (It is not possible to override a tag\[aq]s value or remove a tag.) .PP You can list a tag\[aq]s values with \f[CR]hledger tags TAGNAME \-\-values\f[R], or match by tag value with a \f[CR]tag:NAMEREGEX=VALUEREGEX\f[R] query. .SS Directives Besides transactions, there is something else you can put in a \f[CR]journal\f[R] file: directives. These are declarations, beginning with a keyword, that modify hledger\[aq]s behaviour. Some directives can have more specific subdirectives, indented below them. hledger\[aq]s directives are similar to Ledger\[aq]s in many cases, but there are also many differences. Directives are not required, but can be useful. Here are the main directives: .PP .TS tab(@); lw(39.7n) lw(30.3n). T{ purpose T}@T{ directive T} _ T{ \f[B]READING DATA:\f[R] T}@T{ T} T{ Rewrite account names T}@T{ \f[CR]alias\f[R] T} T{ Comment out sections of the file T}@T{ \f[CR]comment\f[R] T} T{ Declare file\[aq]s decimal mark, to help parse amounts accurately T}@T{ \f[CR]decimal\-mark\f[R] T} T{ Include other data files T}@T{ \f[CR]include\f[R] T} T{ \f[B]GENERATING DATA:\f[R] T}@T{ T} T{ Generate recurring transactions or budget goals T}@T{ \f[CR]\[ti]\f[R] T} T{ Generate extra postings on existing transactions T}@T{ \f[CR]=\f[R] T} T{ \f[B]CHECKING FOR ERRORS:\f[R] T}@T{ T} T{ Define valid entities to provide more error checking T}@T{ \f[CR]account\f[R], \f[CR]commodity\f[R], \f[CR]payee\f[R], \f[CR]tag\f[R] T} T{ \f[B]REPORTING:\f[R] T}@T{ T} T{ Declare accounts\[aq] type and display order T}@T{ \f[CR]account\f[R] T} T{ Declare commodity display styles T}@T{ \f[CR]commodity\f[R] T} T{ Declare market prices T}@T{ \f[CR]P\f[R] T} .TE .SS Directives and multiple files Directives vary in their scope, ie which journal entries and which input files they affect. Most often, a directive will affect the following entries and included files if any, until the end of the current file \- and no further. You might find this inconvenient! For example, \f[CR]alias\f[R] directives do not affect parent or sibling files. But there are usually workarounds; for example, put \f[CR]alias\f[R] directives in your top\-most file, before including other files. .PP The restriction, though it may be annoying at first, is in a good cause; it allows reports to be stable and deterministic, independent of the order of input. Without it, reports could show different numbers depending on the order of \-f options, or the positions of include directives in your files. .SS Directive effects Here are all hledger\[aq]s directives, with their effects and scope summarised \- nine main directives, plus four others which we consider non\-essential: .PP .TS tab(@); lw(3.5n) lw(64.1n) lw(2.4n). T{ directive T}@T{ what it does T}@T{ ends at file end? T} _ T{ \f[B]\f[CB]account\f[B]\f[R] T}@T{ Declares an account, for checking all entries in all files; and its display order and type. Subdirectives: any text, ignored. T}@T{ N T} T{ \f[B]\f[CB]alias\f[B]\f[R] T}@T{ Rewrites account names, in following entries until end of current file or \f[CR]end aliases\f[R]. Command line equivalent: \f[CR]\-\-alias\f[R] T}@T{ Y T} T{ \f[B]\f[CB]comment\f[B]\f[R] T}@T{ Ignores part of the journal file, until end of current file or \f[CR]end comment\f[R]. T}@T{ Y T} T{ \f[B]\f[CB]commodity\f[B]\f[R] T}@T{ Declares up to four things: 1. a commodity symbol, for checking all amounts in all files 2. the decimal mark for parsing amounts of this commodity, in the following entries until end of current file (if there is no \f[CR]decimal\-mark\f[R] directive) 3. and the display style for amounts of this commodity 4. which is also the precision to use for balanced\-transaction checking in this commodity. Takes precedence over \f[CR]D\f[R]. Subdirectives: \f[CR]format\f[R] (Ledger\-compatible syntax). Command line equivalent: \f[CR]\-c/\-\-commodity\-style\f[R] T}@T{ N,Y,N,N T} T{ \f[B]\f[CB]decimal\-mark\f[B]\f[R] T}@T{ Declares the decimal mark, for parsing amounts of all commodities in following entries until next \f[CR]decimal\-mark\f[R] or end of current file. Included files can override. Takes precedence over \f[CR]commodity\f[R] and \f[CR]D\f[R]. T}@T{ Y T} T{ \f[B]\f[CB]include\f[B]\f[R] T}@T{ Includes entries and directives from another file, as if they were written inline. Command line alternative: multiple \f[CR]\-f/\-\-file\f[R] T}@T{ N T} T{ \f[B]\f[CB]payee\f[B]\f[R] T}@T{ Declares a payee name, for checking all entries in all files. T}@T{ N T} T{ \f[B]\f[CB]P\f[B]\f[R] T}@T{ Declares the market price of a commodity on some date, for value reports. T}@T{ N T} T{ \f[B]\f[CB]\[ti]\f[B]\f[R] (tilde) T}@T{ Declares a periodic transaction rule that generates future transactions with \f[CR]\-\-forecast\f[R] and budget goals with \f[CR]balance \-\-budget\f[R]. T}@T{ N T} T{ Other syntax: T}@T{ T}@T{ T} T{ \f[B]\f[CB]apply account\f[B]\f[R] T}@T{ Prepends a common parent account to all account names, in following entries until end of current file or \f[CR]end apply account\f[R]. T}@T{ Y T} T{ \f[B]\f[CB]D\f[B]\f[R] T}@T{ Sets a default commodity to use for no\-symbol amounts;and, if there is no \f[CR]commodity\f[R] directive for this commodity: its decimal mark, balancing precision, and display style, as above. T}@T{ Y,Y,N,N T} T{ \f[B]\f[CB]Y\f[B]\f[R] T}@T{ Sets a default year to use for any yearless dates, in following entries until end of current file. T}@T{ Y T} T{ \f[B]\f[CB]=\f[B]\f[R] (equals) T}@T{ Declares an auto posting rule that generates extra postings on matched transactions with \f[CR]\-\-auto\f[R], in current, parent, and child files (but not sibling files, see #1212). T}@T{ partly T} T{ \f[B]Other Ledger directives\f[R] T}@T{ Other directives from Ledger\[aq]s file format are accepted but ignored. T}@T{ T} .TE .SS \f[CR]account\f[R] directive \f[CR]account\f[R] directives can be used to declare accounts (ie, the places that amounts are transferred from and to). Though not required, these declarations can provide several benefits: .IP \[bu] 2 They can document your intended chart of accounts, providing a reference. .IP \[bu] 2 In strict mode, they restrict which accounts may be posted to by transactions, which helps detect typos. .IP \[bu] 2 They control account display order in reports, allowing non\-alphabetic sorting (eg Revenues to appear above Expenses). .IP \[bu] 2 They help with account name completion (in hledger add, hledger\-web, hledger\-iadd, ledger\-mode, etc.) .IP \[bu] 2 They can store additional account information as comments, or as tags which can be used to filter or pivot reports. .IP \[bu] 2 They can help hledger know your accounts\[aq] types (asset, liability, equity, revenue, expense), affecting reports like balancesheet and incomestatement. .PP They are written as the word \f[CR]account\f[R] followed by a hledger\-style account name, eg: .IP .EX account assets:bank:checking .EE .PP Note, however, that accounts declared in account directives are not allowed to have surrounding brackets and parentheses, unlike accounts used in postings. So the following journal will not parse: .IP .EX account (assets:bank:checking) .EE .SS Account comments Text following \f[B]two or more spaces\f[R] and \f[CR];\f[R] at the end of an account directive line, and/or following \f[CR];\f[R] on indented lines immediately below it, form comments for that account. They are ignored except they may contain tags, which are not ignored. .PP The two\-space requirement for same\-line account comments is because \f[CR];\f[R] is allowed in account names. .IP .EX account assets:bank:checking ; same\-line comment, at least 2 spaces before the semicolon ; next\-line comment ; some tags \- type:A, acctnum:12345 .EE .SS Account subdirectives Ledger\-style indented subdirectives are also accepted, but currently ignored: .IP .EX account assets:bank:checking format subdirective is ignored .EE .SS Account error checking By default, accounts need not be declared; they come into existence when a posting references them. This is convenient, but it means hledger can\[aq]t warn you when you mis\-spell an account name in the journal. Usually you\[aq]ll find that error later, as an extra account in balance reports, or an incorrect balance when reconciling. .PP In strict mode, enabled with the \f[CR]\-s\f[R]/\f[CR]\-\-strict\f[R] flag, hledger will report an error if any transaction uses an account name that has not been declared by an account directive. Some notes: .IP \[bu] 2 The declaration is case\-sensitive; transactions must use the correct account name capitalisation. .IP \[bu] 2 The account directive\[aq]s scope is \[dq]whole file and below\[dq] (see directives). This means it affects all of the current file, and any files it includes, but not parent or sibling files. The position of account directives within the file does not matter, though it\[aq]s usual to put them at the top. .IP \[bu] 2 Accounts can only be declared in \f[CR]journal\f[R] files, but will affect included files of all types. .IP \[bu] 2 It\[aq]s currently not possible to declare \[dq]all possible subaccounts\[dq] with a wildcard; every account posted to must be declared. .SS Account display order The order in which account directives are written influences the order in which accounts appear in reports, hledger\-ui, hledger\-web etc. By default accounts appear in alphabetical order, but if you add these account directives to the journal file: .IP .EX account assets account liabilities account equity account revenues account expenses .EE .PP those accounts will be displayed in declaration order: .IP .EX $ hledger accounts \-1 assets liabilities equity revenues expenses .EE .PP Any undeclared accounts are displayed last, in alphabetical order. .PP Sorting is done at each level of the account tree, within each group of sibling accounts under the same parent. And currently, this directive: .IP .EX account other:zoo .EE .PP would influence the position of \f[CR]zoo\f[R] among \f[CR]other\f[R]\[aq]s subaccounts, but not the position of \f[CR]other\f[R] among the top\-level accounts. This means: .IP \[bu] 2 you will sometimes declare parent accounts (eg \f[CR]account other\f[R] above) that you don\[aq]t intend to post to, just to customize their display order .IP \[bu] 2 sibling accounts stay together (you couldn\[aq]t display \f[CR]x:y\f[R] in between \f[CR]a:b\f[R] and \f[CR]a:c\f[R]). .SS Account types hledger knows that accounts come in several types: assets, liabilities, expenses and so on. This enables easy reports like balancesheet and incomestatement, and filtering by account type with the \f[CR]type:\f[R] query. .PP As a convenience, hledger will detect these account types automatically if you are using common english\-language top\-level account names (described below). But generally we recommend you declare types explicitly, by adding a \f[CR]type:\f[R] tag to your top\-level account directives. Subaccounts will inherit the type of their parent. The tag\[aq]s value should be one of the five main account types: .IP \[bu] 2 \f[CR]A\f[R] or \f[CR]Asset\f[R] (things you own) .IP \[bu] 2 \f[CR]L\f[R] or \f[CR]Liability\f[R] (things you owe) .IP \[bu] 2 \f[CR]E\f[R] or \f[CR]Equity\f[R] (investment/ownership; balanced counterpart of assets & liabilities) .IP \[bu] 2 \f[CR]R\f[R] or \f[CR]Revenue\f[R] (what you received money from, AKA income; technically part of Equity) .IP \[bu] 2 \f[CR]X\f[R] or \f[CR]Expense\f[R] (what you spend money on; technically part of Equity) .PP or, it can be (these are used less often): .IP \[bu] 2 \f[CR]C\f[R] or \f[CR]Cash\f[R] (a subtype of Asset, indicating liquid assets for the cashflow report) .IP \[bu] 2 \f[CR]V\f[R] or \f[CR]Conversion\f[R] (a subtype of Equity, for conversions (see Cost reporting).) .PP Here is a typical set of account type declarations: .IP .EX account assets ; type: A account liabilities ; type: L account equity ; type: E account revenues ; type: R account expenses ; type: X account assets:bank ; type: C account assets:cash ; type: C account equity:conversion ; type: V .EE .PP Here are some tips for working with account types. .IP \[bu] 2 The rules for inferring types from account names are as follows. These are just a convenience that sometimes help new users get going; if they don\[aq]t work for you, just ignore them and declare your account types. See also Regular expressions. .RS 2 .IP .EX If account\[aq]s name contains this (CI) regular expression: | its type is: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-|\-\-\-\-\-\-\-\-\-\-\-\-\- \[ha]assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|current)(:|$) | Cash \[ha]assets?(:|$) | Asset \[ha](debts?|liabilit(y|ies))(:|$) | Liability \[ha]equity:(trad(e|ing)|conversion)s?(:|$) | Conversion \[ha]equity(:|$) | Equity \[ha](income|revenue)s?(:|$) | Revenue \[ha]expenses?(:|$) | Expense .EE .RE .IP \[bu] 2 If you declare any account types, it\[aq]s a good idea to declare an account for all of the account types, because a mixture of declared and name\-inferred types can disrupt certain reports. .IP \[bu] 2 Certain uses of account aliases can disrupt account types. See Rewriting accounts > Aliases and account types. .IP \[bu] 2 As mentioned above, subaccounts will inherit a type from their parent account. More precisely, an account\[aq]s type is decided by the first of these that exists: .RS 2 .IP "1." 3 A \f[CR]type:\f[R] declaration for this account. .IP "2." 3 A \f[CR]type:\f[R] declaration in the parent accounts above it, preferring the nearest. .IP "3." 3 An account type inferred from this account\[aq]s name. .IP "4." 3 An account type inferred from a parent account\[aq]s name, preferring the nearest parent. .IP "5." 3 Otherwise, it will have no type. .RE .IP \[bu] 2 For troubleshooting, you can list accounts and their types with: .RS 2 .IP .EX $ hledger accounts \-\-types [ACCTPAT] [\-DEPTH] [type:TYPECODES] .EE .RE .SS \f[CR]alias\f[R] directive You can define account alias rules which rewrite your account names, or parts of them, before generating reports. This can be useful for: .IP \[bu] 2 expanding shorthand account names to their full form, allowing easier data entry and a less verbose journal .IP \[bu] 2 adapting old journals to your current chart of accounts .IP \[bu] 2 experimenting with new account organisations, like a new hierarchy .IP \[bu] 2 combining two accounts into one, eg to see their sum or difference on one line .IP \[bu] 2 customising reports .PP Account aliases also rewrite account names in account directives. They do not affect account names being entered via hledger add or hledger\-web. .PP Account aliases are very powerful. They are generally easy to use correctly, but you can also generate invalid account names with them; more on this below. .PP See also Rewrite account names. .SS Basic aliases To set an account alias, use the \f[CR]alias\f[R] directive in your journal file. This affects all subsequent journal entries in the current file or its included files (but note: not sibling or parent files). The spaces around the = are optional: .IP .EX alias OLD = NEW .EE .PP Or, you can use the \f[CR]\-\-alias \[aq]OLD=NEW\[aq]\f[R] option on the command line. This affects all entries. It\[aq]s useful for trying out aliases interactively. .PP OLD and NEW are case sensitive full account names. hledger will replace any occurrence of the old account name with the new one. Subaccounts are also affected. Eg: .IP .EX alias checking = assets:bank:wells fargo:checking ; rewrites \[dq]checking\[dq] to \[dq]assets:bank:wells fargo:checking\[dq], or \[dq]checking:a\[dq] to \[dq]assets:bank:wells fargo:checking:a\[dq] .EE .SS Regex aliases There is also a more powerful variant that uses a regular expression, indicated by wrapping the pattern in forward slashes. (This is the only place where hledger requires forward slashes around a regular expression.) .PP Eg: .IP .EX alias /REGEX/ = REPLACEMENT .EE .PP or: .IP .EX $ hledger \-\-alias \[aq]/REGEX/=REPLACEMENT\[aq] ... .EE .PP Any part of an account name matched by REGEX will be replaced by REPLACEMENT. REGEX is case\-insensitive as usual. .PP If you need to match a forward slash, escape it with a backslash, eg \f[CR]/\[rs]/=:\f[R]. .PP If REGEX contains parenthesised match groups, these can be referenced by the usual backslash and number in REPLACEMENT: .IP .EX alias /\[ha](.+):bank:([\[ha]:]+):(.*)/ = \[rs]1:\[rs]2 \[rs]3 ; rewrites \[dq]assets:bank:wells fargo:checking\[dq] to \[dq]assets:wells fargo checking\[dq] .EE .PP REPLACEMENT continues to the end of line (or on command line, to end of option argument), so it can contain trailing whitespace. .SS Combining aliases You can define as many aliases as you like, using journal directives and/or command line options. .PP Recursive aliases \- where an account name is rewritten by one alias, then by another alias, and so on \- are allowed. Each alias sees the effect of previously applied aliases. .PP In such cases it can be important to understand which aliases will be applied and in which order. For (each account name in) each journal entry, we apply: .IP "1." 3 \f[CR]alias\f[R] directives preceding the journal entry, most recently parsed first (ie, reading upward from the journal entry, bottom to top) .IP "2." 3 \f[CR]\-\-alias\f[R] options, in the order they appeared on the command line (left to right). .PP In other words, for (an account name in) a given journal entry: .IP \[bu] 2 the nearest alias declaration before/above the entry is applied first .IP \[bu] 2 the next alias before/above that will be be applied next, and so on .IP \[bu] 2 aliases defined after/below the entry do not affect it. .PP This gives nearby aliases precedence over distant ones, and helps provide semantic stability \- aliases will keep working the same way independent of which files are being read and in which order. .PP In case of trouble, adding \f[CR]\-\-debug=6\f[R] to the command line will show which aliases are being applied when. .SS Aliases and multiple files As explained at Directives and multiple files, \f[CR]alias\f[R] directives do not affect parent or sibling files. Eg in this command, .IP .EX hledger \-f a.aliases \-f b.journal .EE .PP account aliases defined in a.aliases will not affect b.journal. Including the aliases doesn\[aq]t work either: .IP .EX include a.aliases 2023\-01\-01 ; not affected by a.aliases foo 1 bar .EE .PP This means that account aliases should usually be declared at the start of your top\-most file, like this: .IP .EX alias foo=Foo alias bar=Bar 2023\-01\-01 ; affected by aliases above foo 1 bar include c.journal ; also affected .EE .SS \f[CR]end aliases\f[R] directive You can clear (forget) all currently defined aliases (seen in the journal so far, or defined on the command line) with this directive: .IP .EX end aliases .EE .SS Aliases can generate bad account names Be aware that account aliases can produce malformed account names, which could cause confusing reports or invalid \f[CR]print\f[R] output. For example, you could erase all account names: .IP .EX 2021\-01\-01 a:aa 1 b .EE .IP .EX $ hledger print \-\-alias \[aq]/.*/=\[aq] 2021\-01\-01 1 .EE .PP The above \f[CR]print\f[R] output is not a valid journal. Or you could insert an illegal double space, causing \f[CR]print\f[R] output that would give a different journal when reparsed: .IP .EX 2021\-01\-01 old 1 other .EE .IP .EX $ hledger print \-\-alias old=\[dq]new USD\[dq] | hledger \-f\- print 2021\-01\-01 new USD 1 other .EE .SS Aliases and account types If an account with a type declaration (see Declaring accounts > Account types) is renamed by an alias, normally the account type remains in effect. .PP However, renaming in a way that reshapes the account tree (eg renaming parent accounts but not their children, or vice versa) could prevent child accounts from inheriting the account type of their parents. .PP Secondly, if an account\[aq]s type is being inferred from its name, renaming it by an alias could prevent or alter that. .PP If you are using account aliases and the \f[CR]type:\f[R] query is not matching accounts as you expect, try troubleshooting with the accounts command, eg something like: .IP .EX $ hledger accounts \-\-alias assets=bassetts type:a .EE .SS \f[CR]commodity\f[R] directive The \f[CR]commodity\f[R] directive performs several functions: .IP "1." 3 It declares which commodity symbols may be used in the journal, enabling useful error checking with strict mode or the check command. (See Commodity error checking below.) .IP "2." 3 It declares the precision with which this commodity\[aq]s amounts should be compared when checking for balanced transactions. .IP "3." 3 It declares how this commodity\[aq]s amounts should be displayed, eg their symbol placement, digit group mark if any, digit group sizes, decimal mark (period or comma), and the number of decimal places. (See Commodity display style above.) .IP "4." 3 It sets which decimal mark (period or comma) to expect when parsing subsequent amounts in this commodity (if there is no \f[CR]decimal\-mark\f[R] directive in effect. See Decimal marks, digit group marks above. For related dev discussion, see #793.) .PP Declaring commodities solves several common parsing/display problems, so we recommend it. Generally you should put \f[CR]commodity\f[R] directives at the top of your journal file (because function 4 is position\-sensitive). .SS Commodity directive syntax A commodity directive is normally the word \f[CR]commodity\f[R] followed by a sample amount (and optionally a comment). Only the amount\[aq]s symbol and format is significant. Eg: .IP .EX commodity $1000.00 commodity 1.000,00 EUR commodity 1 000 000.0000 ; the no\-symbol commodity .EE .PP Commodities do not have tags (tags in the comment will be ignored). .PP A commodity directive\[aq]s sample amount must always include a period or comma decimal mark (this rule helps disambiguate decimal marks and digit group marks). If you don\[aq]t want to show any decimal digits, write the decimal mark at the end: .IP .EX commodity 1000. AAAA ; show AAAA with no decimals .EE .PP Commodity symbols containing spaces, numbers, or punctuation must be enclosed in double quotes, as usual: .IP .EX commodity 1.0000 \[dq]AAAA 2023\[dq] .EE .PP Commodity directives normally include a sample amount, but can declare only a symbol (ie, just function 1 above): .IP .EX commodity $ commodity INR commodity \[dq]AAAA 2023\[dq] commodity \[dq]\[dq] ; the no\-symbol commodity .EE .PP Commodity directives may also be written with an indented \f[CR]format\f[R] subdirective, as in Ledger. The symbol is repeated and must be the same in both places. Other subdirectives are currently ignored: .IP .EX ; display indian rupees with currency name on the left, ; thousands, lakhs and crores comma\-separated, ; period as decimal point, and two decimal places. commodity INR format INR 1,00,00,000.00 an unsupported subdirective ; ignored by hledger .EE .SS Commodity error checking In strict mode (\f[CR]\-s\f[R]/\f[CR]\-\-strict\f[R]) (or when you run \f[CR]hledger check commodities\f[R]), hledger will report an error if an undeclared commodity symbol is used. (With one exception: zero amounts are always allowed to have no commodity symbol.) It works like account error checking (described above). .SS \f[CR]decimal\-mark\f[R] directive You can use a \f[CR]decimal\-mark\f[R] directive \- usually one per file, at the top of the file \- to declare which character represents a decimal mark when parsing amounts in this file. It can look like .IP .EX decimal\-mark . .EE .PP or .IP .EX decimal\-mark , .EE .PP This prevents any ambiguity when parsing numbers in the file, so we recommend it, especially if the file contains digit group marks (eg thousands separators). .SS \f[CR]include\f[R] directive You can pull in the content of additional files by writing an include directive, like this: .IP .EX include FILEPATH .EE .PP Only journal files can include, and only journal, timeclock or timedot files can be included (not CSV files, currently). .PP If the file path does not begin with a slash, it is relative to the current file\[aq]s folder. .PP A tilde means home directory, eg: \f[CR]include \[ti]/main.journal\f[R]. .PP The path may contain glob patterns to match multiple files, eg: \f[CR]include *.journal\f[R]. .PP There is limited support for recursive wildcards: \f[CR]**/\f[R] (the slash is required) matches 0 or more subdirectories. It\[aq]s not super convenient since you have to avoid include cycles and including directories, but this can be done, eg: \f[CR]include */**/*.journal\f[R]. .PP The path may also be prefixed to force a specific file format, overriding the file extension (as described in Data formats): \f[CR]include timedot:\[ti]/notes/2023*.md\f[R]. .SS \f[CR]P\f[R] directive The \f[CR]P\f[R] directive declares a market price, which is a conversion rate between two commodities on a certain date. This allows value reports to convert amounts of one commodity to their value in another, on or after that date. These prices are often obtained from a stock exchange, cryptocurrency exchange, the or foreign exchange market. .PP The format is: .IP .EX P DATE COMMODITY1SYMBOL COMMODITY2AMOUNT .EE .PP DATE is a simple date, COMMODITY1SYMBOL is the symbol of the commodity being priced, and COMMODITY2AMOUNT is the amount (symbol and quantity) of commodity 2 that one unit of commodity 1 is worth on this date. Examples: .IP .EX # one euro was worth $1.35 from 2009\-01\-01 onward: P 2009\-01\-01 € $1.35 # and $1.40 from 2010\-01\-01 onward: P 2010\-01\-01 € $1.40 .EE .PP The \f[CR]\-V\f[R], \f[CR]\-X\f[R] and \f[CR]\-\-value\f[R] flags use these market prices to show amount values in another commodity. See Value reporting. .PP .SS \f[CR]payee\f[R] directive \f[CR]payee PAYEE NAME\f[R] .PP This directive can be used to declare a limited set of payees which may appear in transaction descriptions. The \[dq]payees\[dq] check will report an error if any transaction refers to a payee that has not been declared. Eg: .IP .EX payee Whole Foods ; a comment .EE .PP Payees do not have tags (tags in the comment will be ignored). .PP To declare the empty payee name, use \f[CR]\[dq]\[dq]\f[R]. .IP .EX payee \[dq]\[dq] .EE .PP Ledger\-style indented subdirectives, if any, are currently ignored. .SS \f[CR]tag\f[R] directive \f[CR]tag TAGNAME\f[R] .PP This directive can be used to declare a limited set of tag names allowed in tags. TAGNAME should be a valid tag name (no spaces). Eg: .IP .EX tag item\-id .EE .PP Any indented subdirectives are currently ignored. .PP The \[dq]tags\[dq] check will report an error if any undeclared tag name is used. It is quite easy to accidentally create a tag through normal use of colons in comments(#comments]; if you want to prevent this, you can declare and check your tags . .SS Periodic transactions The \f[CR]\[ti]\f[R] directive declares a \[dq]periodic rule\[dq] which generates temporary extra transactions, usually recurring at some interval, when hledger is run with the \f[CR]\-\-forecast\f[R] flag. These \[dq]forecast transactions\[dq] are useful for forecasting future activity. They exist only for the duration of the report, and only when \f[CR]\-\-forecast\f[R] is used; they are not saved in the journal file by hledger. .PP Periodic rules also have a second use: with the \f[CR]\-\-budget\f[R] flag they set budget goals for budgeting. .PP Periodic rules can be a little tricky, so before you use them, read this whole section, or at least the following tips: .IP "1." 3 Two spaces accidentally added or omitted will cause you trouble \- read about this below. .IP "2." 3 For troubleshooting, show the generated transactions with \f[CR]hledger print \-\-forecast tag:generated\f[R] or \f[CR]hledger register \-\-forecast tag:generated\f[R]. .IP "3." 3 Forecasted transactions will begin only after the last non\-forecasted transaction\[aq]s date. .IP "4." 3 Forecasted transactions will end 6 months from today, by default. See below for the exact start/end rules. .IP "5." 3 period expressions can be tricky. Their documentation needs improvement, but is worth studying. .IP "6." 3 Some period expressions with a repeating interval must begin on a natural boundary of that interval. Eg in \f[CR]weekly from DATE\f[R], DATE must be a monday. \f[CR]\[ti] weekly from 2019/10/1\f[R] (a tuesday) will give an error. .IP "7." 3 Other period expressions with an interval are automatically expanded to cover a whole number of that interval. (This is done to improve reports, but it also affects periodic transactions. Yes, it\[aq]s a bit inconsistent with the above.) Eg: \f[CR]\[ti] every 10th day of month from 2023/01\f[R], which is equivalent to \f[CR]\[ti] every 10th day of month from 2023/01/01\f[R], will be adjusted to start on 2019/12/10. .SS Periodic rule syntax A periodic transaction rule looks like a normal journal entry, with the date replaced by a tilde (\f[CR]\[ti]\f[R]) followed by a period expression (mnemonic: \f[CR]\[ti]\f[R] looks like a recurring sine wave.): .IP .EX # every first of month \[ti] monthly expenses:rent $2000 assets:bank:checking # every 15th of month in 2023\[aq]s first quarter: \[ti] monthly from 2023\-04\-15 to 2023\-06\-16 expenses:utilities $400 assets:bank:checking .EE .PP The period expression is the same syntax used for specifying multi\-period reports, just interpreted differently; there, it specifies report periods; here it specifies recurrence dates (the periods\[aq] start dates). .SS Periodic rules and relative dates Partial or relative dates (like \f[CR]12/31\f[R], \f[CR]25\f[R], \f[CR]tomorrow\f[R], \f[CR]last week\f[R], \f[CR]next quarter\f[R]) are usually not recommended in periodic rules, since the results will change as time passes. If used, they will be interpreted relative to, in order of preference: .IP "1." 3 the first day of the default year specified by a recent \f[CR]Y\f[R] directive .IP "2." 3 or the date specified with \f[CR]\-\-today\f[R] .IP "3." 3 or the date on which you are running the report. .PP They will not be affected at all by report period or forecast period dates. .SS Two spaces between period expression and description! If the period expression is followed by a transaction description, these must be separated by \f[B]two or more spaces\f[R]. This helps hledger know where the period expression ends, so that descriptions can not accidentally alter their meaning, as in this example: .IP .EX ; 2 or more spaces needed here, so the period is not understood as \[dq]every 2 months in 2023\[dq] ; || ; vv \[ti] every 2 months in 2023, we will review assets:bank:checking $1500 income:acme inc .EE .PP So, .IP \[bu] 2 Do write two spaces between your period expression and your transaction description, if any. .IP \[bu] 2 Don\[aq]t accidentally write two spaces in the middle of your period expression. .SS Auto postings The \f[CR]=\f[R] directive declares an \[dq]auto posting rule\[dq] which generates temporary extra postings on existing transactions, when hledger is run with the \f[CR]\-\-auto\f[R] flag. (Remember, postings are the account name & amount lines.) The rule contains a query and one or more posting templates. Wherever the query matches an existing posting, the new posting(s) will be generated and added below that one. Optionally the generated amount(s) can depend on the matched posting\[aq]s amount. .PP These auto postings can be useful for, eg, adding tax postings with a standard percentage. They exist only for the duration of the report, and only when \f[CR]\-\-auto\f[R] is used; they are not saved in the journal file by hledger. .PP Note that depending fully on generated data such as this has some drawbacks \- it\[aq]s less portable, less future\-proof, less auditable by others, and less robust (eg your balance assertions will depend on whether you use or don\[aq]t use \f[CR]\-\-auto\f[R]). An alternative is to use auto postings in \[dq]one time\[dq] fashion \- use them to help build a complex journal entry, view it with \f[CR]hledger print \-\-auto\f[R], and then copy that output into the journal file to make it permanent. .PP Here\[aq]s the journal file syntax. An auto posting rule looks a bit like a transaction: .IP .EX = QUERY ACCOUNT AMOUNT ... ACCOUNT [AMOUNT] .EE .PP except the first line is an equals sign (mnemonic: \f[CR]=\f[R] suggests matching), followed by a query (which matches existing postings), and each \[dq]posting\[dq] line describes a posting to be generated, and the posting amounts can be: .IP \[bu] 2 a normal amount with a commodity symbol, eg \f[CR]$2\f[R]. This will be used as\-is. .IP \[bu] 2 a number, eg \f[CR]2\f[R]. The commodity symbol (if any) from the matched posting will be added to this. .IP \[bu] 2 a numeric multiplier, eg \f[CR]*2\f[R] (a star followed by a number N). The matched posting\[aq]s amount (and total price, if any) will be multiplied by N. .IP \[bu] 2 a multiplier with a commodity symbol, eg \f[CR]*$2\f[R] (a star, number N, and symbol S). The matched posting\[aq]s amount will be multiplied by N, and its commodity symbol will be replaced with S. .PP Any query term containing spaces must be enclosed in single or double quotes, as on the command line. Eg, note the quotes around the second query term below: .IP .EX = expenses:groceries \[aq]expenses:dining out\[aq] (budget:funds:dining out) *\-1 .EE .PP Some examples: .IP .EX ; every time I buy food, schedule a dollar donation = expenses:food (liabilities:charity) $\-1 ; when I buy a gift, also deduct that amount from a budget envelope subaccount = expenses:gifts assets:checking:gifts *\-1 assets:checking *1 2017/12/1 expenses:food $10 assets:checking 2017/12/14 expenses:gifts $20 assets:checking .EE .IP .EX $ hledger print \-\-auto 2017\-12\-01 expenses:food $10 assets:checking (liabilities:charity) $\-1 2017\-12\-14 expenses:gifts $20 assets:checking assets:checking:gifts \-$20 assets:checking $20 .EE .SS Auto postings and multiple files An auto posting rule can affect any transaction in the current file, or in any parent file or child file. Note, currently it will not affect sibling files (when multiple \f[CR]\-f\f[R]/\f[CR]\-\-file\f[R] are used \- see #1212). .SS Auto postings and dates A posting date (or secondary date) in the matched posting, or (taking precedence) a posting date in the auto posting rule itself, will also be used in the generated posting. .SS Auto postings and transaction balancing / inferred amounts / balance assertions Currently, auto postings are added: .IP \[bu] 2 after missing amounts are inferred, and transactions are checked for balancedness, .IP \[bu] 2 but before balance assertions are checked. .PP Note this means that journal entries must be balanced both before and after auto postings are added. This changed in hledger 1.12+; see #893 for background. .PP This also means that you cannot have more than one auto\-posting with a missing amount applied to a given transaction, as it will be unable to infer amounts. .SS Auto posting tags Automated postings will have some extra tags: .IP \[bu] 2 \f[CR]generated\-posting:= QUERY\f[R] \- shows this was generated by an auto posting rule, and the query .IP \[bu] 2 \f[CR]_generated\-posting:= QUERY\f[R] \- a hidden tag, which does not appear in hledger\[aq]s output. This can be used to match postings generated \[dq]just now\[dq], rather than generated in the past and saved to the journal. .PP Also, any transaction that has been changed by auto posting rules will have these tags added: .IP \[bu] 2 \f[CR]modified:\f[R] \- this transaction was modified .IP \[bu] 2 \f[CR]_modified:\f[R] \- a hidden tag not appearing in the comment; this transaction was modified \[dq]just now\[dq]. .SS Auto postings on forecast transactions only Tip: you can can make auto postings that will apply to forecast transactions but not recorded transactions, by adding \f[CR]tag:_generated\-transaction\f[R] to their QUERY. This can be useful when generating new journal entries to be saved in the journal. .SS Other syntax hledger journal format supports quite a few other features, mainly to make interoperating with or converting from Ledger easier. Note some of the features below are powerful and can be useful in special cases, but in general, features in this section are considered less important or even not recommended for most users. Downsides are mentioned to help you decide if you want to use them. .SS Balance assignments Ledger\-style balance assignments are also supported. These are like balance assertions, but with no posting amount on the left side of the equals sign; instead it is calculated automatically so as to satisfy the assertion. This can be a convenience during data entry, eg when setting opening balances: .IP .EX ; starting a new journal, set asset account balances 2016/1/1 opening balances assets:checking = $409.32 assets:savings = $735.24 assets:cash = $42 equity:opening balances .EE .PP or when adjusting a balance to reality: .IP .EX ; no cash left; update balance, record any untracked spending as a generic expense 2016/1/15 assets:cash = $0 expenses:misc .EE .PP The calculated amount depends on the account\[aq]s balance in the commodity at that point (which depends on the previously\-dated postings of the commodity to that account since the last balance assertion or assignment). .PP Downsides: using balance assignments makes your journal less explicit; to know the exact amount posted, you have to run hledger or do the calculations yourself, instead of just reading it. Also balance assignments\[aq] forcing of balances can hide errors. These things make your financial data less portable, less future\-proof, and less trustworthy in an audit. .SS Balance assignments and prices A cost in a balance assignment will cause the calculated amount to have that price attached: .IP .EX 2019/1/1 (a) = $1 \[at] €2 .EE .IP .EX $ hledger print \-\-explicit 2019\-01\-01 (a) $1 \[at] €2 = $1 \[at] €2 .EE .SS Balance assignments and multiple files Balance assignments handle multiple files like balance assertions. They see balance from other files previously included from the current file, but not from previous sibling or parent files. .SS Bracketed posting dates For setting posting dates and secondary posting dates, Ledger\[aq]s bracketed date syntax is also supported: \f[CR][DATE]\f[R], \f[CR][DATE=DATE2]\f[R] or \f[CR][=DATE2]\f[R] in posting comments. hledger will attempt to parse any square\-bracketed sequence of the \f[CR]0123456789/\-.=\f[R] characters in this way. With this syntax, DATE infers its year from the transaction and DATE2 infers its year from DATE. .PP Downsides: another syntax to learn, redundant with hledger\[aq]s \f[CR]date:\f[R]/\f[CR]date2:\f[R] tags, and confusingly similar to Ledger\[aq]s lot date syntax. .SS \f[CR]D\f[R] directive \f[CR]D AMOUNT\f[R] .PP This directive sets a default commodity, to be used for any subsequent commodityless amounts (ie, plain numbers) seen while parsing the journal. This effect lasts until the next \f[CR]D\f[R] directive, or the end of the journal. .PP For compatibility/historical reasons, \f[CR]D\f[R] also acts like a \f[CR]commodity\f[R] directive (setting the commodity\[aq]s decimal mark for parsing and display style for output). So its argument is not just a commodity symbol, but a full amount demonstrating the style. The amount must include a decimal mark (either period or comma). Eg: .IP .EX ; commodity\-less amounts should be treated as dollars ; (and displayed with the dollar sign on the left, thousands separators and two decimal places) D $1,000.00 1/1 a 5 ; <\- commodity\-less amount, parsed as $5 and displayed as $5.00 b .EE .PP Interactions with other directives: .PP For setting a commodity\[aq]s display style, a \f[CR]commodity\f[R] directive has highest priority, then a \f[CR]D\f[R] directive. .PP For detecting a commodity\[aq]s decimal mark during parsing, \f[CR]decimal\-mark\f[R] has highest priority, then \f[CR]commodity\f[R], then \f[CR]D\f[R]. .PP For checking commodity symbols with the check command, a \f[CR]commodity\f[R] directive is required (\f[CR]hledger check commodities\f[R] ignores \f[CR]D\f[R] directives). .PP Downsides: omitting commodity symbols makes your financial data less explicit, less portable, and less trustworthy in an audit. It is usually an unsustainable shortcut; sooner or later you will want to track multiple commodities. D is overloaded with functions redundant with \f[CR]commodity\f[R] and \f[CR]decimal\-mark\f[R]. And it works differently from Ledger\[aq]s \f[CR]D\f[R]. .SS \f[CR]apply account\f[R] directive This directive sets a default parent account, which will be prepended to all accounts in following entries, until an \f[CR]end apply account\f[R] directive or end of current file. Eg: .IP .EX apply account home 2010/1/1 food $10 cash end apply account .EE .PP is equivalent to: .IP .EX 2010/01/01 home:food $10 home:cash $\-10 .EE .PP \f[CR]account\f[R] directives are also affected, and so is any \f[CR]include\f[R]d content. .PP Account names entered via hledger add or hledger\-web are not affected. .PP Account aliases, if any, are applied after the parent account is prepended. .PP Downsides: this can make your financial data less explicit, less portable, and less trustworthy in an audit. .SS \f[CR]Y\f[R] directive \f[CR]Y YEAR\f[R] .PP or (deprecated backward\-compatible forms): .PP \f[CR]year YEAR\f[R] \f[CR]apply year YEAR\f[R] .PP The space is optional. This sets a default year to be used for subsequent dates which don\[aq]t specify a year. Eg: .IP .EX Y2009 ; set default year to 2009 12/15 ; equivalent to 2009/12/15 expenses 1 assets year 2010 ; change default year to 2010 2009/1/30 ; specifies the year, not affected expenses 1 assets 1/31 ; equivalent to 2010/1/31 expenses 1 assets .EE .PP Downsides: omitting the year (from primary transaction dates, at least) makes your financial data less explicit, less portable, and less trustworthy in an audit. Such dates can get separated from their corresponding Y directive, eg when evaluating a region of the journal in your editor. A missing Y directive makes reports dependent on today\[aq]s date. .SS Secondary dates A secondary date is written after the primary date, following an equals sign. If the year is omitted, the primary date\[aq]s year is assumed. When running reports, the primary (left) date is used by default, but with the \f[CR]\-\-date2\f[R] flag (or \f[CR]\-\-aux\-date\f[R] or \f[CR]\-\-effective\f[R]), the secondary (right) date will be used instead. .PP The meaning of secondary dates is up to you, but it\[aq]s best to follow a consistent rule. Eg \[dq]primary = the bank\[aq]s clearing date, secondary = date the transaction was initiated, if different\[dq]. .PP Downsides: makes your financial data more complicated, less portable, and less trustworthy in an audit. Keeping the meaning of the two dates consistent requires discipline, and you have to remember which reporting mode is appropriate for a given report. Posting dates are simpler and better. .SS Star comments Lines beginning with \f[CR]*\f[R] (star/asterisk) are also comment lines. This feature allows Emacs users to insert org headings in their journal, allowing them to fold/unfold/navigate it like an outline when viewed with org mode. .PP Downsides: another, unconventional comment syntax to learn. Decreases your journal\[aq]s portability. And switching to Emacs org mode just for folding/unfolding meant losing the benefits of ledger mode; nowadays you can add outshine mode to ledger mode to get folding without losing ledger mode\[aq]s features. .SS Valuation expressions Ledger allows a valuation function or value to be written in double parentheses after an amount. hledger ignores these. .SS Virtual postings A posting with parentheses around the account name (\f[CR](some:account)\f[R]) is called a \f[I]unbalanced virtual posting\f[R]. Such postings do not participate in transaction balancing. (And if you write them without an amount, a zero amount is always inferred.) These can occasionally be convenient for special circumstances, but they violate double entry bookkeeping and make your data less portable across applications, so many people avoid using them at all. .PP A posting with brackets around the account name (\f[CR][some:account]\f[R]) is called a \f[I]balanced virtual posting\f[R]. The balanced virtual postings in a transaction must add up to zero, just like ordinary postings, but separately from them. These are not part of double entry bookkeeping either, but they are at least balanced. An example: .IP .EX 2022\-01\-01 buy food with cash, update budget envelope subaccounts, & something else assets:cash $\-10 ; <\- these balance each other expenses:food $7 ; <\- expenses:food $3 ; <\- [assets:checking:budget:food] $\-10 ; <\- and these balance each other [assets:checking:available] $10 ; <\- (something:else) $5 ; <\- this is not required to balance .EE .PP Ordinary postings, whose account names are neither parenthesised nor bracketed, are called \f[I]real postings\f[R]. You can exclude virtual postings from reports with the \f[CR]\-R/\-\-real\f[R] flag or a \f[CR]real:1\f[R] query. .SS Other Ledger directives These other Ledger directives are currently accepted but ignored. This allows hledger to read more Ledger files, but be aware that hledger\[aq]s reports may differ from Ledger\[aq]s if you use these. .IP .EX apply fixed COMM AMT apply tag TAG assert EXPR bucket / A ACCT capture ACCT REGEX check EXPR define VAR=EXPR end apply fixed end apply tag end apply year end tag eval / expr EXPR python PYTHONCODE tag NAME value EXPR \-\-command\-line\-flags .EE .PP See also https://hledger.org/ledger.html for a detailed hledger/Ledger syntax comparison. .PP .SH CSV hledger can read CSV files (Character Separated Value \- usually comma, semicolon, or tab) containing dated records, automatically converting each record into a transaction. .PP (To learn about \f[I]writing\f[R] CSV, see CSV output.) .PP For best error messages when reading CSV/TSV/SSV files, make sure they have a corresponding \f[CR].csv\f[R], \f[CR].tsv\f[R] or \f[CR].ssv\f[R] file extension or use a hledger file prefix (see File Extension below). .PP Each CSV file must be described by a corresponding \f[I]rules file\f[R]. .PD 0 .P .PD This contains rules describing the CSV data (header line, fields layout, date format etc.), how to construct hledger transactions from it, and how to categorise transactions based on description or other attributes. .PP By default hledger looks for a rules file named like the CSV file with an extra \f[CR].rules\f[R] extension, in the same directory. Eg when asked to read \f[CR]foo/FILE.csv\f[R], hledger looks for \f[CR]foo/FILE.csv.rules\f[R]. You can specify a different rules file with the \f[CR]\-\-rules\-file\f[R] option. If no rules file is found, hledger will create a sample rules file, which you\[aq]ll need to adjust. .PP At minimum, the rules file must identify the date and amount fields, and often it also specifies the date format and how many header lines there are. Here\[aq]s a simple CSV file and a rules file for it: .IP .EX Date, Description, Id, Amount 12/11/2019, Foo, 123, 10.23 .EE .IP .EX # basic.csv.rules skip 1 fields date, description, , amount date\-format %d/%m/%Y .EE .IP .EX $ hledger print \-f basic.csv 2019\-11\-12 Foo expenses:unknown 10.23 income:unknown \-10.23 .EE .PP There\[aq]s an introductory Importing CSV data tutorial on hledger.org, and more CSV rules examples below, and a larger collection at https://github.com/simonmichael/hledger/tree/master/examples/csv. .SS CSV rules cheatsheet The following kinds of rule can appear in the rules file, in any order. (Blank lines and lines beginning with \f[CR]#\f[R] or \f[CR];\f[R] or \f[CR]*\f[R] are ignored.) .PP .TS tab(@); lw(23.7n) lw(46.3n). T{ \f[B]\f[CB]source\f[B]\f[R] T}@T{ optionally declare which file to read data from T} T{ \f[B]\f[CB]separator\f[B]\f[R] T}@T{ declare the field separator, instead of relying on file extension T} T{ \f[B]\f[CB]skip\f[B]\f[R] T}@T{ skip one or more header lines at start of file T} T{ \f[B]\f[CB]date\-format\f[B]\f[R] T}@T{ declare how to parse CSV dates/date\-times T} T{ \f[B]\f[CB]timezone\f[B]\f[R] T}@T{ declare the time zone of ambiguous CSV date\-times T} T{ \f[B]\f[CB]newest\-first\f[B]\f[R] T}@T{ improve txn order when: there are multiple records, newest first, all with the same date T} T{ \f[B]\f[CB]intra\-day\-reversed\f[B]\f[R] T}@T{ improve txn order when: same\-day txns are in opposite order to the overall file T} T{ \f[B]\f[CB]decimal\-mark\f[B]\f[R] T}@T{ declare the decimal mark used in CSV amounts, when ambiguous T} T{ \f[B]\f[CB]fields\f[B] list\f[R] T}@T{ name CSV fields for easy reference, and optionally assign their values to hledger fields T} T{ \f[B]Field assignment\f[R] T}@T{ assign a CSV value or interpolated text value to a hledger field T} T{ \f[B]\f[CB]if\f[B] block\f[R] T}@T{ conditionally assign values to hledger fields, or \f[CR]skip\f[R] a record or \f[CR]end\f[R] (skip rest of file) T} T{ \f[B]\f[CB]if\f[B] table\f[R] T}@T{ conditionally assign values to hledger fields, using compact syntax T} T{ \f[B]\f[CB]balance\-type\f[B]\f[R] T}@T{ select which type of balance assertions/assignments to generate T} T{ \f[B]\f[CB]include\f[B]\f[R] T}@T{ inline another CSV rules file T} .TE .PP Working with CSV tips can be found below, including How CSV rules are evaluated. .SS \f[CR]source\f[R] If you tell hledger to read a csv file with \f[CR]\-f foo.csv\f[R], it will look for rules in \f[CR]foo.csv.rules\f[R]. Or, you can tell it to read the rules file, with \f[CR]\-f foo.csv.rules\f[R], and it will look for data in \f[CR]foo.csv\f[R] (since 1.30). .PP These are mostly equivalent, but the second method provides some extra features. For one, the data file can be missing, without causing an error; it is just considered empty. And, you can specify a different data file by adding a \[dq]source\[dq] rule: .IP .EX source ./Checking1.csv .EE .PP If you specify just a file name with no path, hledger will look for it in your system\[aq]s downloads directory (\f[CR]\[ti]/Downloads\f[R], currently): .IP .EX source Checking1.csv .EE .PP And if you specify a glob pattern, hledger will read the most recent of the matched files (useful with repeated downloads): .IP .EX source Checking1*.csv .EE .PP See also \[dq]Working with CSV > Reading files specified by rule\[dq]. .SS \f[CR]separator\f[R] You can use the \f[CR]separator\f[R] rule to read other kinds of character\-separated data. The argument is any single separator character, or the words \f[CR]tab\f[R] or \f[CR]space\f[R] (case insensitive). Eg, for comma\-separated values (CSV): .IP .EX separator , .EE .PP or for semicolon\-separated values (SSV): .IP .EX separator ; .EE .PP or for tab\-separated values (TSV): .IP .EX separator TAB .EE .PP If the input file has a \f[CR].csv\f[R], \f[CR].ssv\f[R] or \f[CR].tsv\f[R] file extension (or a \f[CR]csv:\f[R], \f[CR]ssv:\f[R], \f[CR]tsv:\f[R] prefix), the appropriate separator will be inferred automatically, and you won\[aq]t need this rule. .SS \f[CR]skip\f[R] .IP .EX skip N .EE .PP The word \f[CR]skip\f[R] followed by a number (or no number, meaning 1) tells hledger to ignore this many non\-empty lines at the start of the input data. You\[aq]ll need this whenever your CSV data contains header lines. Note, empty and blank lines are skipped automatically, so you don\[aq]t need to count those. .PP \f[CR]skip\f[R] has a second meaning: it can be used inside if blocks (described below), to skip one or more records whenever the condition is true. Records skipped in this way are ignored, except they are still required to be valid CSV. .SS \f[CR]date\-format\f[R] .IP .EX date\-format DATEFMT .EE .PP This is a helper for the \f[CR]date\f[R] (and \f[CR]date2\f[R]) fields. If your CSV dates are not formatted like \f[CR]YYYY\-MM\-DD\f[R], \f[CR]YYYY/MM/DD\f[R] or \f[CR]YYYY.MM.DD\f[R], you\[aq]ll need to add a date\-format rule describing them with a strptime\-style date parsing pattern \- see https://hackage.haskell.org/package/time/docs/Data\-Time\-Format.html#v:formatTime. The pattern must parse the CSV date value completely. Some examples: .IP .EX # MM/DD/YY date\-format %m/%d/%y .EE .IP .EX # D/M/YYYY # The \- makes leading zeros optional. date\-format %\-d/%\-m/%Y .EE .IP .EX # YYYY\-Mmm\-DD date\-format %Y\-%h\-%d .EE .IP .EX # M/D/YYYY HH:MM AM some other junk # Note the time and junk must be fully parsed, though only the date is used. date\-format %\-m/%\-d/%Y %l:%M %p some other junk .EE .SS \f[CR]timezone\f[R] .IP .EX timezone TIMEZONE .EE .PP When CSV contains date\-times that are implicitly in some time zone other than yours, but containing no explicit time zone information, you can use this rule to declare the CSV\[aq]s native time zone, which helps prevent off\-by\-one dates. .PP When the CSV date\-times do contain time zone information, you don\[aq]t need this rule; instead, use \f[CR]%Z\f[R] in \f[CR]date\-format\f[R] (or \f[CR]%z\f[R], \f[CR]%EZ\f[R], \f[CR]%Ez\f[R]; see the formatTime link above). .PP In either of these cases, hledger will do a time\-zone\-aware conversion, localising the CSV date\-times to your current system time zone. If you prefer to localise to some other time zone, eg for reproducibility, you can (on unix at least) set the output timezone with the TZ environment variable, eg: .IP .EX $ TZ=\-1000 hledger print \-f foo.csv # or TZ=\-1000 hledger import foo.csv .EE .PP \f[CR]timezone\f[R] currently does not understand timezone names, except \[dq]UTC\[dq], \[dq]GMT\[dq], \[dq]EST\[dq], \[dq]EDT\[dq], \[dq]CST\[dq], \[dq]CDT\[dq], \[dq]MST\[dq], \[dq]MDT\[dq], \[dq]PST\[dq], or \[dq]PDT\[dq]. For others, use numeric format: +HHMM or \-HHMM. .SS \f[CR]newest\-first\f[R] hledger tries to ensure that the generated transactions will be ordered chronologically, including same\-day transactions. Usually it can auto\-detect how the CSV records are ordered. But if it encounters CSV where all records are on the same date, it assumes that the records are oldest first. If in fact the CSV\[aq]s records are normally newest first, like: .IP .EX 2022\-10\-01, txn 3... 2022\-10\-01, txn 2... 2022\-10\-01, txn 1... .EE .PP you can add the \f[CR]newest\-first\f[R] rule to help hledger generate the transactions in correct order. .IP .EX # same\-day CSV records are newest first newest\-first .EE .SS \f[CR]intra\-day\-reversed\f[R] If CSV records within a single day are ordered opposite to the overall record order, you can add the \f[CR]intra\-day\-reversed\f[R] rule to improve the order of journal entries. Eg, here the overall record order is newest first, but same\-day records are oldest first: .IP .EX 2022\-10\-02, txn 3... 2022\-10\-02, txn 4... 2022\-10\-01, txn 1... 2022\-10\-01, txn 2... .EE .IP .EX # transactions within each day are reversed with respect to the overall date order intra\-day\-reversed .EE .SS \f[CR]decimal\-mark\f[R] .IP .EX decimal\-mark . .EE .PP or: .IP .EX decimal\-mark , .EE .PP hledger automatically accepts either period or comma as a decimal mark when parsing numbers (cf Amounts). However if any numbers in the CSV contain digit group marks, such as thousand\-separating commas, you should declare the decimal mark explicitly with this rule, to avoid misparsed numbers. .SS \f[CR]fields\f[R] list .IP .EX fields FIELDNAME1, FIELDNAME2, ... .EE .PP A fields list (the word \f[CR]fields\f[R] followed by comma\-separated field names) is optional, but convenient. It does two things: .IP "1." 3 It names the CSV field in each column. This can be convenient if you are referencing them in other rules, so you can say \f[CR]%SomeField\f[R] instead of remembering \f[CR]%13\f[R]. .IP "2." 3 Whenever you use one of the special hledger field names (described below), it assigns the CSV value in this position to that hledger field. This is the quickest way to populate hledger\[aq]s fields and build a transaction. .PP Here\[aq]s an example that says \[dq]use the 1st, 2nd and 4th fields as the transaction\[aq]s date, description and amount; name the last two fields for later reference; and ignore the others\[dq]: .IP .EX fields date, description, , amount, , , somefield, anotherfield .EE .PP In a fields list, the separator is always comma; it is unrelated to the CSV file\[aq]s separator. Also: .IP \[bu] 2 There must be least two items in the list (at least one comma). .IP \[bu] 2 Field names may not contain spaces. Spaces before/after field names are optional. .IP \[bu] 2 Field names may contain \f[CR]_\f[R] (underscore) or \f[CR]\-\f[R] (hyphen). .IP \[bu] 2 Fields you don\[aq]t care about can be given a dummy name or an empty name. .PP If the CSV contains column headings, it\[aq]s convenient to use these for your field names, suitably modified (eg lower\-cased with spaces replaced by underscores). .PP Sometimes you may want to alter a CSV field name to avoid assigning to a hledger field with the same name. Eg you could call the CSV\[aq]s \[dq]balance\[dq] field \f[CR]balance_\f[R] to avoid directly setting hledger\[aq]s \f[CR]balance\f[R] field (and generating a balance assertion). .SS Field assignment .IP .EX HLEDGERFIELD FIELDVALUE .EE .PP Field assignments are the more flexible way to assign CSV values to hledger fields. They can be used instead of or in addition to a fields list (see above). .PP To assign a value to a hledger field, write the field name (any of the standard hledger field/pseudo\-field names, defined below), a space, followed by a text value on the same line. This text value may interpolate CSV fields, referenced either by their 1\-based position in the CSV record (\f[CR]%N\f[R]) or by the name they were given in the fields list (\f[CR]%CSVFIELD\f[R]), and regular expression match groups (\f[CR]\[rs]N\f[R]). .PP Some examples: .IP .EX # set the amount to the 4th CSV field, with \[dq] USD\[dq] appended amount %4 USD # combine three fields to make a comment, containing note: and date: tags comment note: %somefield \- %anotherfield, date: %1 .EE .PP Tips: .IP \[bu] 2 Interpolation strips outer whitespace (so a CSV value like \f[CR]\[dq] 1 \[dq]\f[R] becomes \f[CR]1\f[R] when interpolated) (#1051). .IP \[bu] 2 Interpolations always refer to a CSV field \- you can\[aq]t interpolate a hledger field. (See Referencing other fields below). .SS Field names Note the two kinds of field names mentioned here, and used only in hledger CSV rules files: .IP "1." 3 \f[B]CSV field names\f[R] (\f[CR]CSVFIELD\f[R] in these docs): you can optionally name the CSV columns for easy reference (since hledger doesn\[aq]t yet automatically recognise column headings in a CSV file), by writing arbitrary names in a \f[CR]fields\f[R] list, eg: .RS 4 .IP .EX fields When, What, Some_Id, Net, Total, Foo, Bar .EE .RE .IP "2." 3 Special \f[B]hledger field names\f[R] (\f[CR]HLEDGERFIELD\f[R] in these docs): you must set at least some of these to generate the hledger transaction from a CSV record, by writing them as the left hand side of a field assignment, eg: .RS 4 .IP .EX date %When code %Some_Id description %What comment %Foo %Bar amount1 $ %Total .EE .PP or directly in a \f[CR]fields\f[R] list: .IP .EX fields date, description, code, , amount1, Foo, Bar currency $ comment %Foo %Bar .EE .RE .PP Here are all the special hledger field names available, and what happens when you assign values to them: .SS date field Assigning to \f[CR]date\f[R] sets the transaction date. .SS date2 field \f[CR]date2\f[R] sets the transaction\[aq]s secondary date, if any. .SS status field \f[CR]status\f[R] sets the transaction\[aq]s status, if any. .SS code field \f[CR]code\f[R] sets the transaction\[aq]s code, if any. .SS description field \f[CR]description\f[R] sets the transaction\[aq]s description, if any. .SS comment field \f[CR]comment\f[R] sets the transaction\[aq]s comment, if any. .PP \f[CR]commentN\f[R], where N is a number, sets the Nth posting\[aq]s comment. .PP You can assign multi\-line comments by writing literal \f[CR]\[rs]n\f[R] in the code. A comment starting with \f[CR]\[rs]n\f[R] will begin on a new line. .PP Comments can contain tags, as usual. .SS account field Assigning to \f[CR]accountN\f[R], where N is 1 to 99, sets the account name of the Nth posting, and causes that posting to be generated. .PP Most often there are two postings, so you\[aq]ll want to set \f[CR]account1\f[R] and \f[CR]account2\f[R]. Typically \f[CR]account1\f[R] is associated with the CSV file, and is set once with a top\-level assignment, while \f[CR]account2\f[R] is set based on each transaction\[aq]s description, in conditional rules. .PP If a posting\[aq]s account name is left unset but its amount is set (see below), a default account name will be chosen (like \[dq]expenses:unknown\[dq] or \[dq]income:unknown\[dq]). .SS amount field There are several ways to set posting amounts from CSV, useful in different situations. .IP "1." 3 \f[B]\f[CB]amount\f[B]\f[R] is the oldest and simplest. Assigning to this sets the amount of the first and second postings. In the second posting, the amount will be negated; also, if it has a cost attached, it will be converted to cost. .IP "2." 3 \f[B]\f[CB]amount\-in\f[B]\f[R] and \f[B]\f[CB]amount\-out\f[B]\f[R] work exactly like the above, but should be used when the CSV has two amount fields (such as \[dq]Debit\[dq] and \[dq]Credit\[dq], or \[dq]Inflow\[dq] and \[dq]Outflow\[dq]). Whichever field has a non\-zero value will be used as the amount of the first and second postings. Here are some tips to avoid confusion: .RS 4 .IP \[bu] 2 It\[aq]s not \[dq]amount\-in for posting 1 and amount\-out for posting 2\[dq], it is \[dq]extract a single amount from the amount\-in or amount\-out field, and use that for posting 1 and (negated) for posting 2\[dq]. .IP \[bu] 2 Don\[aq]t use both \f[CR]amount\f[R] and \f[CR]amount\-in\f[R]/\f[CR]amount\-out\f[R] in the same rules file; choose based on whether the amount is in a single CSV field or spread across two fields. .IP \[bu] 2 In each record, at most one of the two CSV fields should contain a non\-zero amount; the other field must contain a zero or nothing. .IP \[bu] 2 hledger assumes both CSV fields contain unsigned numbers, and it automatically negates the amount\-out values. .IP \[bu] 2 If the data doesn\[aq]t fit these requirements, you\[aq]ll probably need an if rule (see below). .RE .IP "3." 3 \f[B]\f[CB]amountN\f[B]\f[R] (where N is a number from 1 to 99) sets the amount of only a single posting: the Nth posting in the transaction. You\[aq]ll usually need at least two such assignments to make a balanced transaction. You can also generate more than two postings, to represent more complex transactions. The posting numbers don\[aq]t have to be consecutive; with if rules, higher posting numbers can be useful to ensure a certain order of postings. .IP "4." 3 \f[B]\f[CB]amountN\-in\f[B]\f[R] and \f[B]\f[CB]amountN\-out\f[B]\f[R] work exactly like the above, but should be used when the CSV has two amount fields. This is analogous to \f[CR]amount\-in\f[R] and \f[CR]amount\-out\f[R], and those tips also apply here. .IP "5." 3 Remember that a \f[CR]fields\f[R] list can also do assignments. So in a fields list if you name a CSV field \[dq]amount\[dq], that counts as assigning to \f[CR]amount\f[R]. (If you don\[aq]t want that, call it something else in the fields list, like \[dq]amount_\[dq].) .IP "6." 3 The above don\[aq]t handle every situation; if you need more flexibility, use an \f[CR]if\f[R] rule to set amounts conditionally. See \[dq]Working with CSV > Setting amounts\[dq] below for more on this and on amount\-setting generally. .SS currency field \f[CR]currency\f[R] sets a currency symbol, to be prepended to all postings\[aq] amounts. You can use this if the CSV amounts do not have a currency symbol, eg if it is in a separate column. .PP \f[CR]currencyN\f[R] prepends a currency symbol to just the Nth posting\[aq]s amount. .SS balance field \f[CR]balanceN\f[R] sets a balance assertion amount (or if the posting amount is left empty, a balance assignment) on posting N. .PP \f[CR]balance\f[R] is a compatibility spelling for hledger <1.17; it is equivalent to \f[CR]balance1\f[R]. .PP You can adjust the type of assertion/assignment with the \f[CR]balance\-type\f[R] rule (see below). .PP See Tips below for more about setting amounts and currency. .SS \f[CR]if\f[R] block Rules can be applied conditionally, depending on patterns in the CSV data. This allows flexibility; in particular, it is how you can categorise transactions, selecting an appropriate account name based on their description (for example). There are two ways to write conditional rules: \[dq]if blocks\[dq], described here, and \[dq]if tables\[dq], described below. .PP An if block is the word \f[CR]if\f[R] and one or more \[dq]matcher\[dq] expressions (can be a word or phrase), one per line, starting either on the same or next line; followed by one or more indented rules. Eg, .IP .EX if MATCHER RULE .EE .PP or .IP .EX if MATCHER MATCHER MATCHER RULE RULE .EE .PP If any of the matchers succeeds, all of the indented rules will be applied. They are usually field assignments, but the following special rules may also be used within an if block: .IP \[bu] 2 \f[CR]skip\f[R] \- skips the matched CSV record (generating no transaction from it) .IP \[bu] 2 \f[CR]end\f[R] \- skips the rest of the current CSV file. .PP Some examples: .IP .EX # if the record contains \[dq]groceries\[dq], set account2 to \[dq]expenses:groceries\[dq] if groceries account2 expenses:groceries .EE .IP .EX # if the record contains any of these phrases, set account2 and a transaction comment as shown if monthly service fee atm transaction fee banking thru software account2 expenses:business:banking comment XXX deductible ? check it .EE .IP .EX # if an empty record is seen (assuming five fields), ignore the rest of the CSV file if ,,,, end .EE .SS Matchers There are two kinds: .IP "1." 3 A record matcher is a word or single\-line text fragment or regular expression (\f[CR]REGEX\f[R]), which hledger will try to match case\-insensitively anywhere within the CSV record. .PD 0 .P .PD Eg: \f[CR]whole foods\f[R] .IP "2." 3 A field matcher is preceded with a percent sign and CSV field name (\f[CR]%CSVFIELD REGEX\f[R]). hledger will try to match these just within the named CSV field. .PD 0 .P .PD Eg: \f[CR]%date 2023\f[R] .PP The regular expression is (as usual in hledger) a POSIX extended regular expression, that also supports GNU word boundaries (\f[CR]\[rs]b\f[R], \f[CR]\[rs]B\f[R], \f[CR]\[rs]<\f[R], \f[CR]\[rs]>\f[R]), and nothing else. If you have trouble, see \[dq]Regular expressions\[dq] in the hledger manual (https://hledger.org/hledger.html#regular\-expressions). .SS What matchers match With record matchers, it\[aq]s important to know that the record matched is not the original CSV record, but a modified one: separators will be converted to commas, and enclosing double quotes (but not enclosing whitespace) are removed. So for example, when reading an SSV file, if the original record was: .IP .EX 2023\-01\-01; \[dq]Acme, Inc.\[dq]; 1,000 .EE .PP the regex would see, and try to match, this modified record text: .IP .EX 2023\-01\-01,Acme, Inc., 1,000 .EE .SS Combining matchers When an if block has multiple matchers, they are combined as follows: .IP \[bu] 2 By default they are OR\[aq]d (any one of them can match) .IP \[bu] 2 When a matcher is preceded by ampersand (\f[CR]&\f[R]) it will be AND\[aq]ed with the previous matcher (both of them must match) .IP \[bu] 2 When a matcher is preceded by an exclamation mark (\f[CR]!\f[R]), the matcher is negated (it may not match). .PP Currently there is a limitation: you can\[aq]t use both \f[CR]&\f[R] and \f[CR]!\f[R] on the same line (you can\[aq]t AND a negated matcher). .SS Match groups Matchers can define match groups: parenthesised portions of the regular expression which are available for reference in field assignments. Groups are enclosed in regular parentheses (\f[CR](\f[R] and \f[CR])\f[R]) and can be nested. Each group is available in field assignments using the token \f[CR]\[rs]N\f[R], where N is an index into the match groups for this conditional block (e.g. \f[CR]\[rs]1\f[R], \f[CR]\[rs]2\f[R], etc.). .PP Example: Warp credit card payment postings to the beginning of the billing period (Month start), to match how they are presented in statements, using posting dates: .IP .EX if %date (....\-..)\-.. comment2 date:\[rs]1\-01 .EE .PP Another example: Read the expense account from the CSV field, but throw away a prefix: .IP .EX if %account1 liabilities:family:(expenses:.*) account1 \[rs]1 .EE .SS \f[CR]if\f[R] table \[dq]if tables\[dq] are an alternative to if blocks; they can express many matchers and field assignments in a more compact tabular format, like this: .IP .EX if,HLEDGERFIELD1,HLEDGERFIELD2,... MATCHERA,VALUE1,VALUE2,... MATCHERB,VALUE1,VALUE2,... MATCHERC,VALUE1,VALUE2,... .EE .PP The first character after \f[CR]if\f[R] is taken to be this if table\[aq]s field separator. It is unrelated to the separator used in the CSV file. It should be a non\-alphanumeric character like \f[CR],\f[R] or \f[CR]|\f[R] that does not appear anywhere else in the table (it should not be used in field names or matchers or values, and it cannot be escaped with a backslash). .PP Each line must contain the same number of separators; empty values are allowed. Whitespace can be used in the matcher lines for readability (but not in the if line, currently). The table must be terminated by an empty line (or end of file). .PP An if table like the above is interpreted as follows: try all of the matchers; whenever a matcher succeeds, assign all of the values on that line to the corresponding hledger fields; later lines can overrider earlier ones. It is equivalent to this sequence of if blocks: .IP .EX if MATCHERA HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERB HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERC HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... .EE .PP Example: .IP .EX if,account2,comment atm transaction fee,expenses:business:banking,deductible? check it %description groceries,expenses:groceries, 2023/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call\-out .EE .SS \f[CR]balance\-type\f[R] Balance assertions generated by assigning to balanceN are of the simple \f[CR]=\f[R] type by default, which is a single\-commodity, subaccount\-excluding assertion. You may find the subaccount\-including variants more useful, eg if you have created some virtual subaccounts of checking to help with budgeting. You can select a different type of assertion with the \f[CR]balance\-type\f[R] rule: .IP .EX # balance assertions will consider all commodities and all subaccounts balance\-type ==* .EE .PP Here are the balance assertion types for quick reference: .IP .EX = single commodity, exclude subaccounts =* single commodity, include subaccounts == multi commodity, exclude subaccounts ==* multi commodity, include subaccounts .EE .SS \f[CR]include\f[R] .IP .EX include RULESFILE .EE .PP This includes the contents of another CSV rules file at this point. \f[CR]RULESFILE\f[R] is an absolute file path or a path relative to the current file\[aq]s directory. This can be useful for sharing common rules between several rules files, eg: .IP .EX # someaccount.csv.rules ## someaccount\-specific rules fields date,description,amount account1 assets:someaccount account2 expenses:misc ## common rules include categorisation.rules .EE .SS Working with CSV Some tips: .SS Rapid feedback It\[aq]s a good idea to get rapid feedback while creating/troubleshooting CSV rules. Here\[aq]s a good way, using entr from eradman.com/entrproject: .IP .EX $ ls foo.csv* | entr bash \-c \[aq]echo \-\-\-\-; hledger \-f foo.csv print desc:SOMEDESC\[aq] .EE .PP A desc: query (eg) is used to select just one, or a few, transactions of interest. \[dq]bash \-c\[dq] is used to run multiple commands, so we can echo a separator each time the command re\-runs, making it easier to read the output. .SS Valid CSV Note that hledger will only accept valid CSV conforming to RFC 4180, and equivalent SSV and TSV formats (like RFC 4180 but with semicolon or tab as separators). This means, eg: .IP \[bu] 2 Values may be enclosed in double quotes, or not. Enclosing in single quotes is not allowed. (Eg \f[CR]\[aq]A\[aq],\[aq]B\[aq]\f[R] is rejected.) .IP \[bu] 2 When values are enclosed in double quotes, spaces outside the quotes are not allowed. (Eg \f[CR]\[dq]A\[dq], \[dq]B\[dq]\f[R] is rejected.) .IP \[bu] 2 When values are not enclosed in quotes, they may not contain double quotes. (Eg \f[CR]A\[dq]A, B\f[R] is rejected.) .PP If your CSV/SSV/TSV is not valid in this sense, you\[aq]ll need to transform it before reading with hledger. Try using sed, or a more permissive CSV parser like python\[aq]s csv lib. .SS File Extension To help hledger choose the CSV file reader and show the right error messages (and choose the right field separator character by default), it\[aq]s best if CSV/SSV/TSV files are named with a \f[CR].csv\f[R], \f[CR].ssv\f[R] or \f[CR].tsv\f[R] filename extension. (More about this at Data formats.) .PP When reading files with the \[dq]wrong\[dq] extension, you can ensure the CSV reader (and the default field separator) by prefixing the file path with \f[CR]csv:\f[R], \f[CR]ssv:\f[R] or \f[CR]tsv:\f[R]: Eg: .IP .EX $ hledger \-f ssv:foo.dat print .EE .PP You can also override the default field separator with a separator rule if needed. .SS Reading CSV from standard input You\[aq]ll need the file format prefix when reading CSV from stdin also, since hledger assumes journal format by default. Eg: .IP .EX $ cat foo.dat | hledger \-f ssv:\- print .EE .SS Reading multiple CSV files If you use multiple \f[CR]\-f\f[R] options to read multiple CSV files at once, hledger will look for a correspondingly\-named rules file for each CSV file. But if you use the \f[CR]\-\-rules\-file\f[R] option, that rules file will be used for all the CSV files. .SS Reading files specified by rule Instead of specifying a CSV file in the command line, you can specify a rules file, as in \f[CR]hledger \-f foo.csv.rules CMD\f[R]. By default this will read data from foo.csv in the same directory, but you can add a source rule to specify a different data file, perhaps located in your web browser\[aq]s download directory. .PP This feature was added in hledger 1.30, so you won\[aq]t see it in most CSV rules examples. But it helps remove some of the busywork of managing CSV downloads. Most of your financial institutions\[aq]s default CSV filenames are different and can be recognised by a glob pattern. So you can put a rule like \f[CR]source Checking1*.csv\f[R] in foo\-checking.csv.rules, and then periodically follow a workflow like: .IP "1." 3 Download CSV from Foo\[aq]s website, using your browser\[aq]s defaults .IP "2." 3 Run \f[CR]hledger import foo\-checking.csv.rules\f[R] to import any new transactions .PP After import, you can: discard the CSV, or leave it where it is for a while, or move it into your archives, as you prefer. If you do nothing, next time your browser will save something like Checking1\-2.csv, and hledger will use that because of the \f[CR]*\f[R] wild card and because it is the most recent. .SS Valid transactions After reading a CSV file, hledger post\-processes and validates the generated journal entries as it would for a journal file \- balancing them, applying balance assignments, and canonicalising amount styles. Any errors at this stage will be reported in the usual way, displaying the problem entry. .PP There is one exception: balance assertions, if you have generated them, will not be checked, since normally these will work only when the CSV data is part of the main journal. If you do need to check balance assertions generated from CSV right away, pipe into another hledger: .IP .EX $ hledger \-f file.csv print | hledger \-f\- print .EE .SS Deduplicating, importing When you download a CSV file periodically, eg to get your latest bank transactions, the new file may overlap with the old one, containing some of the same records. .PP The import command will (a) detect the new transactions, and (b) append just those transactions to your main journal. It is idempotent, so you don\[aq]t have to remember how many times you ran it or with which version of the CSV. (It keeps state in a hidden \f[CR].latest.FILE.csv\f[R] file.) This is the easiest way to import CSV data. Eg: .IP .EX # download the latest CSV files, then run this command. # Note, no \-f flags needed here. $ hledger import *.csv [\-\-dry] .EE .PP This method works for most CSV files. (Where records have a stable chronological order, and new records appear only at the new end.) .PP A number of other tools and workflows, hledger\-specific and otherwise, exist for converting, deduplicating, classifying and managing CSV data. See: .IP \[bu] 2 https://hledger.org/cookbook.html#setups\-and\-workflows .IP \[bu] 2 https://plaintextaccounting.org \-> data import/conversion .SS Setting amounts Continuing from amount field above, here are more tips for amount\-setting: .IP "1." 3 \f[B]If the amount is in a single CSV field:\f[R] .PD 0 .P .PD .RS 4 .IP "a." 3 \f[B]If its sign indicates direction of flow:\f[R] .PD 0 .P .PD Assign it to \f[CR]amountN\f[R], to set the Nth posting\[aq]s amount. N is usually 1 or 2 but can go up to 99. .IP "b." 3 \f[B]If another field indicates direction of flow:\f[R] .PD 0 .P .PD Use one or more conditional rules to set the appropriate amount sign. Eg: .IP .EX # assume a withdrawal unless Type contains \[dq]deposit\[dq]: amount1 \-%Amount if %Type deposit amount1 %Amount .EE .RE .IP "2." 3 \f[B]If the amount is in two CSV fields (such as Debit and Credit, or In and Out):\f[R] .PD 0 .P .PD .RS 4 .IP "a." 3 \f[B]If both fields are unsigned:\f[R] .PD 0 .P .PD Assign one field to \f[CR]amountN\-in\f[R] and the other to \f[CR]amountN\-out\f[R]. hledger will automatically negate the \[dq]out\[dq] field, and will use whichever field value is non\-zero as posting N\[aq]s amount. .IP "b." 3 \f[B]If either field is signed:\f[R] .PD 0 .P .PD You will probably need to override hledger\[aq]s sign for one or the other field, as in the following example: .IP .EX # Negate the \-out value, but only if it is not empty: fields date, description, amount1\-in, amount1\-out if %amount1\-out [1\-9] amount1\-out \-%amount1\-out .EE .IP "c." 3 \f[B]If both fields can contain a non\-zero value (or both can be empty):\f[R] .PD 0 .P .PD The \-in/\-out rules normally choose the value which is non\-zero/non\-empty. Some value pairs can be ambiguous, such as \f[CR]1\f[R] and \f[CR]none\f[R]. For such cases, use conditional rules to help select the amount. Eg, to handle the above you could select the value containing non\-zero digits: .IP .EX fields date, description, in, out if %in [1\-9] amount1 %in if %out [1\-9] amount1 %out .EE .RE .IP "3." 3 \f[B]If you want posting 2\[aq]s amount converted to cost:\f[R] .PD 0 .P .PD Use the unnumbered \f[CR]amount\f[R] (or \f[CR]amount\-in\f[R] and \f[CR]amount\-out\f[R]) syntax. .IP "4." 3 \f[B]If the CSV has only balance amounts, not transaction amounts:\f[R] .PD 0 .P .PD Assign to \f[CR]balanceN\f[R], to set a balance assignment on the Nth posting, causing the posting\[aq]s amount to be calculated automatically. \f[CR]balance\f[R] with no number is equivalent to \f[CR]balance1\f[R]. In this situation hledger is more likely to guess the wrong default account name, so you may need to set that explicitly. .SS Amount signs There is some special handling making it easier to parse and to reverse amount signs. (This only works for whole amounts, not for cost amounts such as COST in \f[CR]amount1 AMT \[at] COST\f[R]): .IP \[bu] 2 \f[B]If an amount value begins with a plus sign:\f[R] .PD 0 .P .PD that will be removed: \f[CR]+AMT\f[R] becomes \f[CR]AMT\f[R] .IP \[bu] 2 \f[B]If an amount value is parenthesised:\f[R] .PD 0 .P .PD it will be de\-parenthesised and sign\-flipped: \f[CR](AMT)\f[R] becomes \f[CR]\-AMT\f[R] .IP \[bu] 2 \f[B]If an amount value has two minus signs (or two sets of parentheses, or a minus sign and parentheses):\f[R] .PD 0 .P .PD they cancel out and will be removed: \f[CR]\-\-AMT\f[R] or \f[CR]\-(AMT)\f[R] becomes \f[CR]AMT\f[R] .IP \[bu] 2 \f[B]If an amount value contains just a sign (or just a set of parentheses):\f[R] .PD 0 .P .PD that is removed, making it an empty value. \f[CR]\[dq]+\[dq]\f[R] or \f[CR]\[dq]\-\[dq]\f[R] or \f[CR]\[dq]()\[dq]\f[R] becomes \f[CR]\[dq]\[dq]\f[R]. .PP It\[aq]s not possible (without preprocessing the CSV) to set an amount to its absolute value, ie discard its sign. .SS Setting currency/commodity If the currency/commodity symbol is included in the CSV\[aq]s amount field(s): .IP .EX 2023\-01\-01,foo,$123.00 .EE .PP you don\[aq]t have to do anything special for the commodity symbol, it will be assigned as part of the amount. Eg: .IP .EX fields date,description,amount .EE .IP .EX 2023\-01\-01 foo expenses:unknown $123.00 income:unknown $\-123.00 .EE .PP If the currency is provided as a separate CSV field: .IP .EX 2023\-01\-01,foo,USD,123.00 .EE .PP You can assign that to the \f[CR]currency\f[R] pseudo\-field, which has the special effect of prepending itself to every amount in the transaction (on the left, with no separating space): .IP .EX fields date,description,currency,amount .EE .IP .EX 2023\-01\-01 foo expenses:unknown USD123.00 income:unknown USD\-123.00 .EE .PP Or, you can use a field assignment to construct the amount yourself, with more control. Eg to put the symbol on the right, and separated by a space: .IP .EX fields date,description,cur,amt amount %amt %cur .EE .IP .EX 2023\-01\-01 foo expenses:unknown 123.00 USD income:unknown \-123.00 USD .EE .PP Note we used a temporary field name (\f[CR]cur\f[R]) that is not \f[CR]currency\f[R] \- that would trigger the prepending effect, which we don\[aq]t want here. .SS Amount decimal places Like amounts in a journal file, the amounts generated by CSV rules like \f[CR]amount1\f[R] influence commodity display styles, such as the number of decimal places displayed in reports. .PP The original amounts as written in the CSV file do not affect display style (because we don\[aq]t yet reliably know their commodity). .SS Referencing other fields In field assignments, you can interpolate only CSV fields, not hledger fields. In the example below, there\[aq]s both a CSV field and a hledger field named amount1, but %amount1 always means the CSV field, not the hledger field: .IP .EX # Name the third CSV field \[dq]amount1\[dq] fields date,description,amount1 # Set hledger\[aq]s amount1 to the CSV amount1 field followed by USD amount1 %amount1 USD # Set comment to the CSV amount1 (not the amount1 assigned above) comment %amount1 .EE .PP Here, since there\[aq]s no CSV amount1 field, %amount1 will produce a literal \[dq]amount1\[dq]: .IP .EX fields date,description,csvamount amount1 %csvamount USD # Can\[aq]t interpolate amount1 here comment %amount1 .EE .PP When there are multiple field assignments to the same hledger field, only the last one takes effect. Here, comment\[aq]s value will be be B, or C if \[dq]something\[dq] is matched, but never A: .IP .EX comment A comment B if something comment C .EE .SS How CSV rules are evaluated Here\[aq]s how to think of CSV rules being evaluated (if you really need to). First, .IP \[bu] 2 \f[CR]include\f[R] \- all includes are inlined, from top to bottom, depth first. (At each include point the file is inlined and scanned for further includes, recursively, before proceeding.) .PP Then \[dq]global\[dq] rules are evaluated, top to bottom. If a rule is repeated, the last one wins: .IP \[bu] 2 \f[CR]skip\f[R] (at top level) .IP \[bu] 2 \f[CR]date\-format\f[R] .IP \[bu] 2 \f[CR]newest\-first\f[R] .IP \[bu] 2 \f[CR]fields\f[R] \- names the CSV fields, optionally sets up initial assignments to hledger fields .PP Then for each CSV record in turn: .IP \[bu] 2 test all \f[CR]if\f[R] blocks. If any of them contain a \f[CR]end\f[R] rule, skip all remaining CSV records. Otherwise if any of them contain a \f[CR]skip\f[R] rule, skip that many CSV records. If there are multiple matched \f[CR]skip\f[R] rules, the first one wins. .IP \[bu] 2 collect all field assignments at top level and in matched \f[CR]if\f[R] blocks. When there are multiple assignments for a field, keep only the last one. .IP \[bu] 2 compute a value for each hledger field \- either the one that was assigned to it (and interpolate the %CSVFIELD references), or a default .IP \[bu] 2 generate a hledger transaction (journal entry) from these values. .PP This is all part of the CSV reader, one of several readers hledger can use to parse input files. When all files have been read successfully, the transactions are passed as input to whichever hledger command the user specified. .PP .SS Well factored rules Some things than can help reduce duplication and complexity in rules files: .IP \[bu] 2 Extracting common rules usable with multiple CSV files into a \f[CR]common.rules\f[R], and adding \f[CR]include common.rules\f[R] to each CSV\[aq]s rules file. .IP \[bu] 2 Splitting if blocks into smaller if blocks, extracting the frequently used parts. .SS CSV rules examples .SS Bank of Ireland Here\[aq]s a CSV with two amount fields (Debit and Credit), and a balance field, which we can use to add balance assertions, which is not necessary but provides extra error checking: .IP .EX Date,Details,Debit,Credit,Balance 07/12/2012,LODGMENT 529898,,10.0,131.21 07/12/2012,PAYMENT,5,,126 .EE .IP .EX # bankofireland\-checking.csv.rules # skip the header line skip # name the csv fields, and assign some of them as journal entry fields fields date, description, amount\-out, amount\-in, balance # We generate balance assertions by assigning to \[dq]balance\[dq] # above, but you may sometimes need to remove these because: # # \- the CSV balance differs from the true balance, # by up to 0.0000000000005 in my experience # # \- it is sometimes calculated based on non\-chronological ordering, # eg when multiple transactions clear on the same day # date is in UK/Ireland format date\-format %d/%m/%Y # set the currency currency EUR # set the base account for all txns account1 assets:bank:boi:checking .EE .IP .EX $ hledger \-f bankofireland\-checking.csv print 2012\-12\-07 LODGMENT 529898 assets:bank:boi:checking EUR10.0 = EUR131.2 income:unknown EUR\-10.0 2012\-12\-07 PAYMENT assets:bank:boi:checking EUR\-5.0 = EUR126.0 expenses:unknown EUR5.0 .EE .PP The balance assertions don\[aq]t raise an error above, because we\[aq]re reading directly from CSV, but they will be checked if these entries are imported into a journal file. .SS Coinbase A simple example with some CSV from Coinbase. The spot price is recorded using cost notation. The legacy \f[CR]amount\f[R] field name conveniently sets amount 2 (posting 2\[aq]s amount) to the total cost. .IP .EX # Timestamp,Transaction Type,Asset,Quantity Transacted,Spot Price Currency,Spot Price at Transaction,Subtotal,Total (inclusive of fees and/or spread),Fees and/or Spread,Notes # 2021\-12\-30T06:57:59Z,Receive,USDC,100,GBP,0.740000,\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]Received 100.00 USDC from an external account\[dq] .EE .IP .EX # coinbase.csv.rules skip 1 fields Timestamp,Transaction_Type,Asset,Quantity_Transacted,Spot_Price_Currency,Spot_Price_at_Transaction,Subtotal,Total,Fees_Spread,Notes date %Timestamp date\-format %Y\-%m\-%dT%T%Z description %Notes account1 assets:coinbase:cc amount %Quantity_Transacted %Asset \[at] %Spot_Price_at_Transaction %Spot_Price_Currency .EE .IP .EX $ hledger print \-f coinbase.csv 2021\-12\-30 Received 100.00 USDC from an external account assets:coinbase:cc 100 USDC \[at] 0.740000 GBP income:unknown \-74.000000 GBP .EE .SS Amazon Here we convert amazon.com order history, and use an if block to generate a third posting if there\[aq]s a fee. (In practice you\[aq]d probably get this data from your bank instead, but it\[aq]s an example.) .IP .EX \[dq]Date\[dq],\[dq]Type\[dq],\[dq]To/From\[dq],\[dq]Name\[dq],\[dq]Status\[dq],\[dq]Amount\[dq],\[dq]Fees\[dq],\[dq]Transaction ID\[dq] \[dq]Jul 29, 2012\[dq],\[dq]Payment\[dq],\[dq]To\[dq],\[dq]Foo.\[dq],\[dq]Completed\[dq],\[dq]$20.00\[dq],\[dq]$0.00\[dq],\[dq]16000000000000DGLNJPI1P9B8DKPVHL\[dq] \[dq]Jul 30, 2012\[dq],\[dq]Payment\[dq],\[dq]To\[dq],\[dq]Adapteva, Inc.\[dq],\[dq]Completed\[dq],\[dq]$25.00\[dq],\[dq]$1.00\[dq],\[dq]17LA58JSKRD4HDGLNJPI1P9B8DKPVHL\[dq] .EE .IP .EX # amazon\-orders.csv.rules # skip one header line skip 1 # name the csv fields, and assign the transaction\[aq]s date, amount and code. # Avoided the \[dq]status\[dq] and \[dq]amount\[dq] hledger field names to prevent confusion. fields date, _, toorfrom, name, amzstatus, amzamount, fees, code # how to parse the date date\-format %b %\-d, %Y # combine two fields to make the description description %toorfrom %name # save the status as a tag comment status:%amzstatus # set the base account for all transactions account1 assets:amazon # leave amount1 blank so it can balance the other(s). # I\[aq]m assuming amzamount excludes the fees, don\[aq]t remember # set a generic account2 account2 expenses:misc amount2 %amzamount # and maybe refine it further: #include categorisation.rules # add a third posting for fees, but only if they are non\-zero. if %fees [1\-9] account3 expenses:fees amount3 %fees .EE .IP .EX $ hledger \-f amazon\-orders.csv print 2012\-07\-29 (16000000000000DGLNJPI1P9B8DKPVHL) To Foo. ; status:Completed assets:amazon expenses:misc $20.00 2012\-07\-30 (17LA58JSKRD4HDGLNJPI1P9B8DKPVHL) To Adapteva, Inc. ; status:Completed assets:amazon expenses:misc $25.00 expenses:fees $1.00 .EE .SS Paypal Here\[aq]s a real\-world rules file for (customised) Paypal CSV, with some Paypal\-specific rules, and a second rules file included: .IP .EX \[dq]Date\[dq],\[dq]Time\[dq],\[dq]TimeZone\[dq],\[dq]Name\[dq],\[dq]Type\[dq],\[dq]Status\[dq],\[dq]Currency\[dq],\[dq]Gross\[dq],\[dq]Fee\[dq],\[dq]Net\[dq],\[dq]From Email Address\[dq],\[dq]To Email Address\[dq],\[dq]Transaction ID\[dq],\[dq]Item Title\[dq],\[dq]Item ID\[dq],\[dq]Reference Txn ID\[dq],\[dq]Receipt ID\[dq],\[dq]Balance\[dq],\[dq]Note\[dq] \[dq]10/01/2019\[dq],\[dq]03:46:20\[dq],\[dq]PDT\[dq],\[dq]Calm Radio\[dq],\[dq]Subscription Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]\-6.99\[dq],\[dq]0.00\[dq],\[dq]\-6.99\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]memberships\[at]calmradio.com\[dq],\[dq]60P57143A8206782E\[dq],\[dq]MONTHLY \- $1 for the first 2 Months: Me \- Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month\[dq],\[dq]\[dq],\[dq]I\-R8YLY094FJYR\[dq],\[dq]\[dq],\[dq]\-6.99\[dq],\[dq]\[dq] \[dq]10/01/2019\[dq],\[dq]03:46:20\[dq],\[dq]PDT\[dq],\[dq]\[dq],\[dq]Bank Deposit to PP Account \[dq],\[dq]Pending\[dq],\[dq]USD\[dq],\[dq]6.99\[dq],\[dq]0.00\[dq],\[dq]6.99\[dq],\[dq]\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]0TU1544T080463733\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]60P57143A8206782E\[dq],\[dq]\[dq],\[dq]0.00\[dq],\[dq]\[dq] \[dq]10/01/2019\[dq],\[dq]08:57:01\[dq],\[dq]PDT\[dq],\[dq]Patreon\[dq],\[dq]PreApproved Payment Bill User Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]\-7.00\[dq],\[dq]0.00\[dq],\[dq]\-7.00\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]support\[at]patreon.com\[dq],\[dq]2722394R5F586712G\[dq],\[dq]Patreon* Membership\[dq],\[dq]\[dq],\[dq]B\-0PG93074E7M86381M\[dq],\[dq]\[dq],\[dq]\-7.00\[dq],\[dq]\[dq] \[dq]10/01/2019\[dq],\[dq]08:57:01\[dq],\[dq]PDT\[dq],\[dq]\[dq],\[dq]Bank Deposit to PP Account \[dq],\[dq]Pending\[dq],\[dq]USD\[dq],\[dq]7.00\[dq],\[dq]0.00\[dq],\[dq]7.00\[dq],\[dq]\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]71854087RG994194F\[dq],\[dq]Patreon* Membership\[dq],\[dq]\[dq],\[dq]2722394R5F586712G\[dq],\[dq]\[dq],\[dq]0.00\[dq],\[dq]\[dq] \[dq]10/19/2019\[dq],\[dq]03:02:12\[dq],\[dq]PDT\[dq],\[dq]Wikimedia Foundation, Inc.\[dq],\[dq]Subscription Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]\-2.00\[dq],\[dq]0.00\[dq],\[dq]\-2.00\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]tle\[at]wikimedia.org\[dq],\[dq]K9U43044RY432050M\[dq],\[dq]Monthly donation to the Wikimedia Foundation\[dq],\[dq]\[dq],\[dq]I\-R5C3YUS3285L\[dq],\[dq]\[dq],\[dq]\-2.00\[dq],\[dq]\[dq] \[dq]10/19/2019\[dq],\[dq]03:02:12\[dq],\[dq]PDT\[dq],\[dq]\[dq],\[dq]Bank Deposit to PP Account \[dq],\[dq]Pending\[dq],\[dq]USD\[dq],\[dq]2.00\[dq],\[dq]0.00\[dq],\[dq]2.00\[dq],\[dq]\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]3XJ107139A851061F\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]K9U43044RY432050M\[dq],\[dq]\[dq],\[dq]0.00\[dq],\[dq]\[dq] \[dq]10/22/2019\[dq],\[dq]05:07:06\[dq],\[dq]PDT\[dq],\[dq]Noble Benefactor\[dq],\[dq]Subscription Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]10.00\[dq],\[dq]\-0.59\[dq],\[dq]9.41\[dq],\[dq]noble\[at]bene.fac.tor\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]6L8L1662YP1334033\[dq],\[dq]Joyful Systems\[dq],\[dq]\[dq],\[dq]I\-KC9VBGY2GWDB\[dq],\[dq]\[dq],\[dq]9.41\[dq],\[dq]\[dq] .EE .IP .EX # paypal\-custom.csv.rules # Tips: # Export from Activity \-> Statements \-> Custom \-> Activity download # Suggested transaction type: \[dq]Balance affecting\[dq] # Paypal\[aq]s default fields in 2018 were: # \[dq]Date\[dq],\[dq]Time\[dq],\[dq]TimeZone\[dq],\[dq]Name\[dq],\[dq]Type\[dq],\[dq]Status\[dq],\[dq]Currency\[dq],\[dq]Gross\[dq],\[dq]Fee\[dq],\[dq]Net\[dq],\[dq]From Email Address\[dq],\[dq]To Email Address\[dq],\[dq]Transaction ID\[dq],\[dq]Shipping Address\[dq],\[dq]Address Status\[dq],\[dq]Item Title\[dq],\[dq]Item ID\[dq],\[dq]Shipping and Handling Amount\[dq],\[dq]Insurance Amount\[dq],\[dq]Sales Tax\[dq],\[dq]Option 1 Name\[dq],\[dq]Option 1 Value\[dq],\[dq]Option 2 Name\[dq],\[dq]Option 2 Value\[dq],\[dq]Reference Txn ID\[dq],\[dq]Invoice Number\[dq],\[dq]Custom Number\[dq],\[dq]Quantity\[dq],\[dq]Receipt ID\[dq],\[dq]Balance\[dq],\[dq]Address Line 1\[dq],\[dq]Address Line 2/District/Neighborhood\[dq],\[dq]Town/City\[dq],\[dq]State/Province/Region/County/Territory/Prefecture/Republic\[dq],\[dq]Zip/Postal Code\[dq],\[dq]Country\[dq],\[dq]Contact Phone Number\[dq],\[dq]Subject\[dq],\[dq]Note\[dq],\[dq]Country Code\[dq],\[dq]Balance Impact\[dq] # This rules file assumes the following more detailed fields, configured in \[dq]Customize report fields\[dq]: # \[dq]Date\[dq],\[dq]Time\[dq],\[dq]TimeZone\[dq],\[dq]Name\[dq],\[dq]Type\[dq],\[dq]Status\[dq],\[dq]Currency\[dq],\[dq]Gross\[dq],\[dq]Fee\[dq],\[dq]Net\[dq],\[dq]From Email Address\[dq],\[dq]To Email Address\[dq],\[dq]Transaction ID\[dq],\[dq]Item Title\[dq],\[dq]Item ID\[dq],\[dq]Reference Txn ID\[dq],\[dq]Receipt ID\[dq],\[dq]Balance\[dq],\[dq]Note\[dq] fields date, time, timezone, description_, type, status_, currency, grossamount, feeamount, netamount, fromemail, toemail, code, itemtitle, itemid, referencetxnid, receiptid, balance, note skip 1 date\-format %\-m/%\-d/%Y # ignore some paypal events if In Progress Temporary Hold Update to skip # add more fields to the description description %description_ %itemtitle # save some other fields as tags comment itemid:%itemid, fromemail:%fromemail, toemail:%toemail, time:%time, type:%type, status:%status_ # convert to short currency symbols if %currency USD currency $ if %currency EUR currency E if %currency GBP currency P # generate postings # the first posting will be the money leaving/entering my paypal account # (negative means leaving my account, in all amount fields) account1 assets:online:paypal amount1 %netamount # the second posting will be money sent to/received from other party # (account2 is set below) amount2 \-%grossamount # if there\[aq]s a fee, add a third posting for the money taken by paypal. if %feeamount [1\-9] account3 expenses:banking:paypal amount3 \-%feeamount comment3 business: # choose an account for the second posting # override the default account names: # if the amount is positive, it\[aq]s income (a debit) if %grossamount \[ha][\[ha]\-] account2 income:unknown # if negative, it\[aq]s an expense (a credit) if %grossamount \[ha]\- account2 expenses:unknown # apply common rules for setting account2 & other tweaks include common.rules # apply some overrides specific to this csv # Transfers from/to bank. These are usually marked Pending, # which can be disregarded in this case. if Bank Account Bank Deposit to PP Account description %type for %referencetxnid %itemtitle account2 assets:bank:wf:pchecking account1 assets:online:paypal # Currency conversions if Currency Conversion account2 equity:currency conversion .EE .IP .EX # common.rules if darcs noble benefactor account2 revenues:foss donations:darcshub comment2 business: if Calm Radio account2 expenses:online:apps if electronic frontier foundation Patreon wikimedia Advent of Code account2 expenses:dues if Google account2 expenses:online:apps description google | music .EE .IP .EX $ hledger \-f paypal\-custom.csv print 2019\-10\-01 (60P57143A8206782E) Calm Radio MONTHLY \- $1 for the first 2 Months: Me \- Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month ; itemid:, fromemail:simon\[at]joyful.com, toemail:memberships\[at]calmradio.com, time:03:46:20, type:Subscription Payment, status:Completed assets:online:paypal $\-6.99 = $\-6.99 expenses:online:apps $6.99 2019\-10\-01 (0TU1544T080463733) Bank Deposit to PP Account for 60P57143A8206782E ; itemid:, fromemail:, toemail:simon\[at]joyful.com, time:03:46:20, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $6.99 = $0.00 assets:bank:wf:pchecking $\-6.99 2019\-10\-01 (2722394R5F586712G) Patreon Patreon* Membership ; itemid:, fromemail:simon\[at]joyful.com, toemail:support\[at]patreon.com, time:08:57:01, type:PreApproved Payment Bill User Payment, status:Completed assets:online:paypal $\-7.00 = $\-7.00 expenses:dues $7.00 2019\-10\-01 (71854087RG994194F) Bank Deposit to PP Account for 2722394R5F586712G Patreon* Membership ; itemid:, fromemail:, toemail:simon\[at]joyful.com, time:08:57:01, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $7.00 = $0.00 assets:bank:wf:pchecking $\-7.00 2019\-10\-19 (K9U43044RY432050M) Wikimedia Foundation, Inc. Monthly donation to the Wikimedia Foundation ; itemid:, fromemail:simon\[at]joyful.com, toemail:tle\[at]wikimedia.org, time:03:02:12, type:Subscription Payment, status:Completed assets:online:paypal $\-2.00 = $\-2.00 expenses:dues $2.00 expenses:banking:paypal ; business: 2019\-10\-19 (3XJ107139A851061F) Bank Deposit to PP Account for K9U43044RY432050M ; itemid:, fromemail:, toemail:simon\[at]joyful.com, time:03:02:12, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $2.00 = $0.00 assets:bank:wf:pchecking $\-2.00 2019\-10\-22 (6L8L1662YP1334033) Noble Benefactor Joyful Systems ; itemid:, fromemail:noble\[at]bene.fac.tor, toemail:simon\[at]joyful.com, time:05:07:06, type:Subscription Payment, status:Completed assets:online:paypal $9.41 = $9.41 revenues:foss donations:darcshub $\-10.00 ; business: expenses:banking:paypal $0.59 ; business: .EE .SH Timeclock The time logging format of timeclock.el, as read by hledger. .PP hledger can read time logs in timeclock format. As with Ledger, these are (a subset of) timeclock.el\[aq]s format, containing clock\-in and clock\-out entries as in the example below. The date is a simple date. The time format is HH:MM[:SS][+\-ZZZZ]. Seconds and timezone are optional. The timezone, if present, must be four digits and is ignored (currently the time is always interpreted as a local time). Lines beginning with \f[CR]#\f[R] or \f[CR];\f[R] or \f[CR]*\f[R], and blank lines, are ignored. .IP .EX i 2015/03/30 09:00:00 some account optional description after 2 spaces ; optional comment, tags: o 2015/03/30 09:20:00 i 2015/03/31 22:21:45 another:account o 2015/04/01 02:00:34 .EE .PP hledger treats each clock\-in/clock\-out pair as a transaction posting some number of hours to an account. Or if the session spans more than one day, it is split into several transactions, one for each day. For the above time log, \f[CR]hledger print\f[R] generates these journal entries: .IP .EX $ hledger \-f t.timeclock print 2015\-03\-30 * optional description after 2 spaces ; optional comment, tags: (some account) 0.33h 2015\-03\-31 * 22:21\-23:59 (another:account) 1.64h 2015\-04\-01 * 00:00\-02:00 (another:account) 2.01h .EE .PP Here is a sample.timeclock to download and some queries to try: .IP .EX $ hledger \-f sample.timeclock balance # current time balances $ hledger \-f sample.timeclock register \-p 2009/3 # sessions in march 2009 $ hledger \-f sample.timeclock register \-p weekly \-\-depth 1 \-\-empty # time summary by week .EE .PP To generate time logs, ie to clock in and clock out, you could: .IP \[bu] 2 use emacs and the built\-in timeclock.el, or the extended timeclock\-x.el and perhaps the extras in ledgerutils.el .IP \[bu] 2 at the command line, use these bash aliases: \f[CR]shell alias ti=\[dq]echo i \[ga]date \[aq]+%Y\-%m\-%d %H:%M:%S\[aq]\[ga] \[rs]$* >>$TIMELOG\[dq] alias to=\[dq]echo o \[ga]date \[aq]+%Y\-%m\-%d %H:%M:%S\[aq]\[ga] >>$TIMELOG\[dq]\f[R] .IP \[bu] 2 or use the old \f[CR]ti\f[R] and \f[CR]to\f[R] scripts in the ledger 2.x repository. These rely on a \[dq]timeclock\[dq] executable which I think is just the ledger 2 executable renamed. .PP .SH Timedot \f[CR]timedot\f[R] format is hledger\[aq]s human\-friendly time logging format. Compared to \f[CR]timeclock\f[R] format, it is more convenient for quick, approximate, and retroactive time logging, and more human\-readable (you can see at a glance where time was spent). A quick example: .IP .EX 2023\-05\-01 hom:errands .... .... ; two hours; the space is ignored fos:hledger:timedot .. ; half an hour per:admin:finance ; no time spent yet .EE .PP hledger reads this as a transaction on this day with three (unbalanced) postings, where each dot represents \[dq]0.25\[dq]. No commodity symbol is assumed, but we typically interpret it as hours. .IP .EX $ hledger \-f a.timedot print # .timedot file extension (or timedot: prefix) is required 2023\-05\-01 * (hom:errands) 2.00 ; two hours (fos:hledger:timedot) 0.50 ; half an hour (per:admin:finance) 0 .EE .PP A timedot file contains a series of transactions (usually one per day). Each begins with a \f[B]simple date\f[R] (Y\-M\-D, Y/M/D, or Y.M.D), optionally be followed on the same line by a transaction description, and/or a transaction comment following a semicolon. .PP After the date line are zero or more time postings, consisting of: .IP \[bu] 2 \f[B]An account name\f[R] \- any hledger\-style account name, optionally indented. .IP \[bu] 2 \f[B]Two or more spaces\f[R] \- required if there is an amount (as in journal format). .IP \[bu] 2 \f[B]A timedot amount\f[R], which can be .RS 2 .IP \[bu] 2 empty (representing zero) .IP \[bu] 2 a number, optionally followed by a unit \f[CR]s\f[R], \f[CR]m\f[R], \f[CR]h\f[R], \f[CR]d\f[R], \f[CR]w\f[R], \f[CR]mo\f[R], or \f[CR]y\f[R], representing a precise number of seconds, minutes, hours, days weeks, months or years (hours is assumed by default), which will be converted to hours according to 60s = 1m, 60m = 1h, 24h = 1d, 7d = 1w, 30d = 1mo, 365d = 1y. .IP \[bu] 2 one or more dots (period characters), each representing 0.25. These are the dots in \[dq]timedot\[dq]. Spaces are ignored and can be used for grouping/alignment. .IP \[bu] 2 one or more letters. These are like dots but they also generate a tag \f[CR]t:\f[R] (short for \[dq]type\[dq]) with the letter as its value, and a separate posting for each of the values. This provides a second dimension of categorisation, viewable in reports with \f[CR]\-\-pivot t\f[R]. .RE .IP \[bu] 2 \f[B]An optional comment\f[R] following a semicolon (a hledger\-style posting comment). .PP There is some flexibility to help with keeping time log data and notes in the same file: .IP \[bu] 2 Blank lines and lines beginning with \f[CR]#\f[R] or \f[CR];\f[R] are ignored. .IP \[bu] 2 After the first date line, lines which do not contain a double space are parsed as postings with zero amount. (hledger\[aq]s register reports will show these if you add \-E). .IP \[bu] 2 Before the first date line, lines beginning with \f[CR]*\f[R] (eg org headings) are ignored. And from the first date line onward, Emacs org mode heading prefixes at the start of lines (one or more \f[CR]*\f[R]\[aq]s followed by a space) will be ignored. This means the time log can also be a org outline. .SS Timedot examples Numbers: .IP .EX 2016/2/3 inc:client1 4 fos:hledger 3h biz:research 60m .EE .PP Dots: .IP .EX # on this day, 6h was spent on client work, 1.5h on haskell FOSS work, etc. 2016/2/1 inc:client1 .... .... .... .... .... .... fos:haskell .... .. biz:research . 2016/2/2 inc:client1 .... .... biz:research . .EE .IP .EX $ hledger \-f a.timedot print date:2016/2/2 2016\-02\-02 * (inc:client1) 2.00 2016\-02\-02 * (biz:research) 0.25 .EE .IP .EX $ hledger \-f a.timedot bal \-\-daily \-\-tree Balance changes in 2016\-02\-01\-2016\-02\-03: || 2016\-02\-01d 2016\-02\-02d 2016\-02\-03d ============++======================================== biz || 0.25 0.25 1.00 research || 0.25 0.25 1.00 fos || 1.50 0 3.00 haskell || 1.50 0 0 hledger || 0 0 3.00 inc || 6.00 2.00 4.00 client1 || 6.00 2.00 4.00 \-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || 7.75 2.25 8.00 .EE .PP Letters: .IP .EX # Activity types: # c cleanup/catchup/repair # e enhancement # s support # l learning/research 2023\-11\-01 work:adm ccecces .EE .IP .EX $ hledger \-f a.timedot print 2023\-11\-01 (work:adm) 1 ; t:c (work:adm) 0.5 ; t:e (work:adm) 0.25 ; t:s .EE .IP .EX $ hledger \-f a.timedot bal 1.75 work:adm \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 1.75 .EE .IP .EX $ hledger \-f a.timedot bal \-\-pivot t 1.00 c 0.50 e 0.25 s \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 1.75 .EE .PP Org: .IP .EX * 2023 Work Diary ** Q1 *** 2023\-02\-29 **** DONE 0700 yoga **** UNPLANNED **** BEGUN hom:chores cleaning ... water plants outdoor \- one full watering can indoor \- light watering **** TODO adm:planning: trip *** LATER .EE .PP Using \f[CR].\f[R] as account name separator: .IP .EX 2016/2/4 fos.hledger.timedot 4h fos.ledger .. .EE .IP .EX $ hledger \-f a.timedot \-\-alias \[aq]/\[rs]./=:\[aq] bal \-t 4.50 fos 4.00 hledger:timedot 0.50 ledger \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 4.50 .EE .SH PART 3: REPORTING CONCEPTS .SH Amount formatting, parseability If you\[aq]re wondering why your \f[CR]print\f[R] report sometimes shows trailing decimal marks, with no decimal digits; it does this when showing amounts that have digit group marks but no decimal digits, to disambiguate them and allow them to be re\-parsed reliably (see also Decimal marks, digit group marks. Eg: .IP .EX commodity $1,000.00 2023\-01\-02 (a) $1000 .EE .IP .EX $ hledger print 2023\-01\-02 (a) $1,000. .EE .PP If this is a problem (eg when exporting to Ledger), you can avoid it by disabling digit group marks, eg with \-c/\-\-commodity (for each affected commodity): .IP .EX $ hledger print \-c \[aq]$1000.00\[aq] 2023\-01\-02 (a) $1000 .EE .PP or by forcing print to always show decimal digits, with \-\-round: .IP .EX $ hledger print \-c \[aq]$1,000.00\[aq] \-\-round=soft 2023\-01\-02 (a) $1,000.00 .EE .PP More generally: hledger output falls into three rough categories, which format amounts a little bit differently to suit different consumers: .PP \f[B]1. \[dq]hledger\-readable output\[dq] \- should be readable by hledger (and by humans)\f[R] .IP \[bu] 2 This is produced by reports that show full journal entries: \f[CR]print\f[R], \f[CR]import\f[R], \f[CR]close\f[R], \f[CR]rewrite\f[R] etc. .IP \[bu] 2 It shows amounts with their original journal precisions, which may not be consistent. .IP \[bu] 2 It adds a trailing decimal mark when needed to avoid showing ambiguous amounts. .IP \[bu] 2 It can be parsed reliably (by hledger and ledger2beancount at least, but perhaps not by Ledger..) .PP \f[B]2. \[dq]human\-readable output\[dq] \- usually for humans\f[R] .IP \[bu] 2 This is produced by all other reports. .IP \[bu] 2 It shows amounts with standard display precisions, which will be consistent within each commodity. .IP \[bu] 2 It shows ambiguous amounts unmodified. .IP \[bu] 2 It can be parsed reliably in the context of a known report (when you know decimals are consistently not being shown, you can assume a single mark is a digit group mark). .PP \f[B]3. \[dq]machine\-readable output\[dq] \- usually for other software\f[R] .IP \[bu] 2 This is produced by all reports when an output format like \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]json\f[R], or \f[CR]sql\f[R] is selected. .IP \[bu] 2 It shows amounts as 1 or 2 do, but without digit group marks. .IP \[bu] 2 It can be parsed reliably (if needed, the decimal mark can be changed with \-c/\-\-commodity\-style). .SH Time periods .SS Report start & end date By default, most hledger reports will show the full span of time represented by the journal. The report start date will be the earliest transaction or posting date, and the report end date will be the latest transaction, posting, or market price date. .PP Often you will want to see a shorter time span, such as the current month. You can specify a start and/or end date using \f[CR]\-b/\-\-begin\f[R], \f[CR]\-e/\-\-end\f[R], \f[CR]\-p/\-\-period\f[R] or a \f[CR]date:\f[R] query (described below). All of these accept the smart date syntax (below). .PP Some notes: .IP \[bu] 2 End dates are exclusive, as in Ledger, so you should write the date \f[I]after\f[R] the last day you want to see in the report. .IP \[bu] 2 As noted in reporting options: among start/end dates specified with \f[I]options\f[R], the last (i.e. right\-most) option takes precedence. .IP \[bu] 2 The effective report start and end dates are the intersection of the start/end dates from options and that from \f[CR]date:\f[R] queries. That is, \f[CR]date:2019\-01 date:2019 \-p\[aq]2000 to 2030\[aq]\f[R] yields January 2019, the smallest common time span. .IP \[bu] 2 In some cases a report interval will adjust start/end dates to fall on interval boundaries (see below). .PP Examples: .PP .TS tab(@); lw(12.4n) lw(57.6n). T{ \f[CR]\-b 2016/3/17\f[R] T}@T{ begin on St.\ Patrick\[cq]s day 2016 T} T{ \f[CR]\-e 12/1\f[R] T}@T{ end at the start of december 1st of the current year (11/30 will be the last date included) T} T{ \f[CR]\-b thismonth\f[R] T}@T{ all transactions on or after the 1st of the current month T} T{ \f[CR]\-p thismonth\f[R] T}@T{ all transactions in the current month T} T{ \f[CR]date:2016/3/17..\f[R] T}@T{ the above written as queries instead (\f[CR]..\f[R] can also be replaced with \f[CR]\-\f[R]) T} T{ \f[CR]date:..12/1\f[R] T}@T{ T} T{ \f[CR]date:thismonth..\f[R] T}@T{ T} T{ \f[CR]date:thismonth\f[R] T}@T{ T} .TE .SS Smart dates hledger\[aq]s user interfaces accept a \[dq]smart date\[dq] syntax for added convenience. Smart dates optionally can be relative to today\[aq]s date, be written with english words, and have less\-significant parts omitted (missing parts are inferred as 1). Some examples: .PP .TS tab(@); lw(24.2n) lw(45.8n). T{ \f[CR]2004/10/1\f[R], \f[CR]2004\-01\-01\f[R], \f[CR]2004.9.1\f[R] T}@T{ exact date, several separators allowed. Year is 4+ digits, month is 1\-12, day is 1\-31 T} T{ \f[CR]2004\f[R] T}@T{ start of year T} T{ \f[CR]2004/10\f[R] T}@T{ start of month T} T{ \f[CR]10/1\f[R] T}@T{ month and day in current year T} T{ \f[CR]21\f[R] T}@T{ day in current month T} T{ \f[CR]october, oct\f[R] T}@T{ start of month in current year T} T{ \f[CR]yesterday, today, tomorrow\f[R] T}@T{ \-1, 0, 1 days from today T} T{ \f[CR]last/this/next day/week/month/quarter/year\f[R] T}@T{ \-1, 0, 1 periods from the current period T} T{ \f[CR]in n days/weeks/months/quarters/years\f[R] T}@T{ n periods from the current period T} T{ \f[CR]n days/weeks/months/quarters/years ahead\f[R] T}@T{ n periods from the current period T} T{ \f[CR]n days/weeks/months/quarters/years ago\f[R] T}@T{ \-n periods from the current period T} T{ \f[CR]20181201\f[R] T}@T{ 8 digit YYYYMMDD with valid year month and day T} T{ \f[CR]201812\f[R] T}@T{ 6 digit YYYYMM with valid year and month T} .TE .PP Some counterexamples \- malformed digit sequences might give surprising results: .PP .TS tab(@); lw(11.4n) lw(58.6n). T{ \f[CR]201813\f[R] T}@T{ 6 digits with an invalid month is parsed as start of 6\-digit year T} T{ \f[CR]20181301\f[R] T}@T{ 8 digits with an invalid month is parsed as start of 8\-digit year T} T{ \f[CR]20181232\f[R] T}@T{ 8 digits with an invalid day gives an error T} T{ \f[CR]201801012\f[R] T}@T{ 9+ digits beginning with a valid YYYYMMDD gives an error T} .TE .PP \[dq]Today\[aq]s date\[dq] can be overridden with the \f[CR]\-\-today\f[R] option, in case it\[aq]s needed for testing or for recreating old reports. (Except for periodic transaction rules, which are not affected by \f[CR]\-\-today\f[R].) .SS Report intervals A report interval can be specified so that reports like register, balance or activity become multi\-period, showing each subperiod as a separate row or column. .PP The following standard intervals can be enabled with command\-line flags: .IP \[bu] 2 \f[CR]\-D/\-\-daily\f[R] .IP \[bu] 2 \f[CR]\-W/\-\-weekly\f[R] .IP \[bu] 2 \f[CR]\-M/\-\-monthly\f[R] .IP \[bu] 2 \f[CR]\-Q/\-\-quarterly\f[R] .IP \[bu] 2 \f[CR]\-Y/\-\-yearly\f[R] .PP More complex intervals can be specified using \f[CR]\-p/\-\-period\f[R], described below. .SS Date adjustment When there is a report interval (other than daily), report start/end dates which have been inferred, eg from the journal, are automatically adjusted to natural period boundaries. This is convenient for producing simple periodic reports. More precisely: .IP \[bu] 2 an inferred start date will be adjusted earlier if needed to fall on a natural period boundary .IP \[bu] 2 an inferred end date will be adjusted later if needed to make the last period the same length as the others. .PP By contrast, start/end dates which have been specified explicitly, with \f[CR]\-b\f[R], \f[CR]\-e\f[R], \f[CR]\-p\f[R] or \f[CR]date:\f[R], will not be adjusted (since hledger 1.29). This makes it possible to specify non\-standard report periods, but it also means that if you are specifying a start date, you should pick one that\[aq]s on a period boundary if you want to see simple report period headings. .SS Period expressions The \f[CR]\-p/\-\-period\f[R] option specifies a period expression, which is a compact way of expressing a start date, end date, and/or report interval. .PP Here\[aq]s a period expression with a start and end date (specifying the first quarter of 2009): .PP .TS tab(@); l. T{ \f[CR]\-p \[dq]from 2009/1/1 to 2009/4/1\[dq]\f[R] T} .TE .PP Several keywords like \[dq]from\[dq] and \[dq]to\[dq] are supported for readability; these are optional. \[dq]to\[dq] can also be written as \[dq]..\[dq] or \[dq]\-\[dq]. The spaces are also optional, as long as you don\[aq]t run two dates together. So the following are equivalent to the above: .PP .TS tab(@); l. T{ \f[CR]\-p \[dq]2009/1/1 2009/4/1\[dq]\f[R] T} T{ \f[CR]\-p2009/1/1to2009/4/1\f[R] T} T{ \f[CR]\-p2009/1/1..2009/4/1\f[R] T} .TE .PP Dates are smart dates, so if the current year is 2009, these are also equivalent to the above: .PP .TS tab(@); l. T{ \f[CR]\-p \[dq]1/1 4/1\[dq]\f[R] T} T{ \f[CR]\-p \[dq]jan\-apr\[dq]\f[R] T} T{ \f[CR]\-p \[dq]this year to 4/1\[dq]\f[R] T} .TE .PP If you specify only one date, the missing start or end date will be the earliest or latest transaction date in the journal: .PP .TS tab(@); l l. T{ \f[CR]\-p \[dq]from 2009/1/1\[dq]\f[R] T}@T{ everything after january 1, 2009 T} T{ \f[CR]\-p \[dq]since 2009/1\[dq]\f[R] T}@T{ the same, since is a synonym T} T{ \f[CR]\-p \[dq]from 2009\[dq]\f[R] T}@T{ the same T} T{ \f[CR]\-p \[dq]to 2009\[dq]\f[R] T}@T{ everything before january 1, 2009 T} .TE .PP You can also specify a period by writing a single partial or full date: .PP .TS tab(@); lw(14.5n) lw(55.5n). T{ \f[CR]\-p \[dq]2009\[dq]\f[R] T}@T{ the year 2009; equivalent to \[lq]2009/1/1 to 2010/1/1\[rq] T} T{ \f[CR]\-p \[dq]2009/1\[dq]\f[R] T}@T{ the month of january 2009; equivalent to \[lq]2009/1/1 to 2009/2/1\[rq] T} T{ \f[CR]\-p \[dq]2009/1/1\[dq]\f[R] T}@T{ the first day of 2009; equivalent to \[lq]2009/1/1 to 2009/1/2\[rq] T} .TE .PP or by using the \[dq]Q\[dq] quarter\-year syntax (case insensitive): .PP .TS tab(@); lw(15.3n) lw(54.7n). T{ \f[CR]\-p \[dq]2009Q1\[dq]\f[R] T}@T{ first quarter of 2009, equivalent to \[lq]2009/1/1 to 2009/4/1\[rq] T} T{ \f[CR]\-p \[dq]q4\[dq]\f[R] T}@T{ fourth quarter of the current year T} .TE .SS Period expressions with a report interval A period expression can also begin with a report interval, separated from the start/end dates (if any) by a space or the word \f[CR]in\f[R]: .PP .TS tab(@); l. T{ \f[CR]\-p \[dq]weekly from 2009/1/1 to 2009/4/1\[dq]\f[R] T} T{ \f[CR]\-p \[dq]monthly in 2008\[dq]\f[R] T} T{ \f[CR]\-p \[dq]quarterly\[dq]\f[R] T} .TE .SS More complex report intervals Some more complex intervals can be specified within period expressions, such as: .IP \[bu] 2 \f[CR]biweekly\f[R] (every two weeks) .IP \[bu] 2 \f[CR]fortnightly\f[R] .IP \[bu] 2 \f[CR]bimonthly\f[R] (every two months) .IP \[bu] 2 \f[CR]every day|week|month|quarter|year\f[R] .IP \[bu] 2 \f[CR]every N days|weeks|months|quarters|years\f[R] .PP Weekly on a custom day: .IP \[bu] 2 \f[CR]every Nth day of week\f[R] (\f[CR]th\f[R], \f[CR]nd\f[R], \f[CR]rd\f[R], or \f[CR]st\f[R] are all accepted after the number) .IP \[bu] 2 \f[CR]every WEEKDAYNAME\f[R] (full or three\-letter english weekday name, case insensitive) .PP Monthly on a custom day: .IP \[bu] 2 \f[CR]every Nth day [of month]\f[R] .IP \[bu] 2 \f[CR]every Nth WEEKDAYNAME [of month]\f[R] .PP Yearly on a custom day: .IP \[bu] 2 \f[CR]every MM/DD [of year]\f[R] (month number and day of month number) .IP \[bu] 2 \f[CR]every MONTHNAME DDth [of year]\f[R] (full or three\-letter english month name, case insensitive, and day of month number) .IP \[bu] 2 \f[CR]every DDth MONTHNAME [of year]\f[R] (equivalent to the above) .PP Examples: .PP .TS tab(@); lw(26.8n) lw(43.2n). T{ \f[CR]\-p \[dq]bimonthly from 2008\[dq]\f[R] T}@T{ T} T{ \f[CR]\-p \[dq]every 2 weeks\[dq]\f[R] T}@T{ T} T{ \f[CR]\-p \[dq]every 5 months from 2009/03\[dq]\f[R] T}@T{ T} T{ \f[CR]\-p \[dq]every 2nd day of week\[dq]\f[R] T}@T{ periods will go from Tue to Tue T} T{ \f[CR]\-p \[dq]every Tue\[dq]\f[R] T}@T{ same T} T{ \f[CR]\-p \[dq]every 15th day\[dq]\f[R] T}@T{ period boundaries will be on 15th of each month T} T{ \f[CR]\-p \[dq]every 2nd Monday\[dq]\f[R] T}@T{ period boundaries will be on second Monday of each month T} T{ \f[CR]\-p \[dq]every 11/05\[dq]\f[R] T}@T{ yearly periods with boundaries on 5th of November T} T{ \f[CR]\-p \[dq]every 5th November\[dq]\f[R] T}@T{ same T} T{ \f[CR]\-p \[dq]every Nov 5th\[dq]\f[R] T}@T{ same T} .TE .PP Show historical balances at end of the 15th day of each month (N is an end date, exclusive as always): .IP .EX $ hledger balance \-H \-p \[dq]every 16th day\[dq] .EE .PP Group postings from the start of wednesday to end of the following tuesday (N is both (inclusive) start date and (exclusive) end date): .IP .EX $ hledger register checking \-p \[dq]every 3rd day of week\[dq] .EE .SS Multiple weekday intervals This special form is also supported: .IP \[bu] 2 \f[CR]every WEEKDAYNAME,WEEKDAYNAME,...\f[R] (full or three\-letter english weekday names, case insensitive) .PP Also, \f[CR]weekday\f[R] and \f[CR]weekendday\f[R] are shorthand for \f[CR]mon,tue,wed,thu,fri\f[R] and \f[CR]sat,sun\f[R]. .PP This is mainly intended for use with \f[CR]\-\-forecast\f[R], to generate periodic transactions on arbitrary days of the week. It may be less useful with \f[CR]\-p\f[R], since it divides each week into subperiods of unequal length, which is unusual. (Related: #1632) .PP Examples: .PP .TS tab(@); lw(17.8n) lw(52.2n). T{ \f[CR]\-p \[dq]every mon,wed,fri\[dq]\f[R] T}@T{ dates will be Mon, Wed, Fri; periods will be Mon\-Tue, Wed\-Thu, Fri\-Sun T} T{ \f[CR]\-p \[dq]every weekday\[dq]\f[R] T}@T{ dates will be Mon, Tue, Wed, Thu, Fri; periods will be Mon, Tue, Wed, Thu, Fri\-Sun T} T{ \f[CR]\-p \[dq]every weekendday\[dq]\f[R] T}@T{ dates will be Sat, Sun; periods will be Sat, Sun\-Fri T} .TE .SH Depth With the \f[CR]\-\-depth NUM\f[R] option (short form: \f[CR]\-NUM\f[R]), reports will show accounts only to the specified depth, hiding deeper subaccounts. Use this when you want a summary with less detail. This flag has the same effect as a \f[CR]depth:\f[R] query argument: \f[CR]depth:2\f[R], \f[CR]\-\-depth=2\f[R] or \f[CR]\-2\f[R] are equivalent. .SH Queries One of hledger\[aq]s strengths is being able to quickly report on a precise subset of your data. Most hledger commands accept query arguments, to restrict their scope. Multiple query terms can be provided to build up a more complex query. .IP \[bu] 2 By default, a query term is interpreted as a case\-insensitive substring pattern for matching account names: .RS 2 .PP \f[CR]car:fuel\f[R] .PD 0 .P .PD \f[CR]dining groceries\f[R] .PD 0 .P .PD .RE .IP \[bu] 2 Patterns containing spaces or other special characters must be enclosed in single or double quotes: .RS 2 .PP \f[CR]\[aq]personal care\[aq]\f[R] .PD 0 .P .PD .RE .IP \[bu] 2 These patterns are actually regular expressions, so you can add regexp metacharacters for more precision (see \[dq]Regular expressions\[dq] above for details): .RS 2 .PP \f[CR]\[aq]\[ha]expenses\[rs]b\[aq]\f[R] .PD 0 .P .PD \f[CR]\[aq]food$\[aq]\f[R] .PD 0 .P .PD \f[CR]\[aq]fuel|repair\[aq]\f[R] .PD 0 .P .PD \f[CR]\[aq]accounts (payable|receivable)\[aq]\f[R] .PD 0 .P .PD .RE .IP \[bu] 2 To match something other than account name, add one of the query type prefixes described in \[dq]Query types\[dq] below: .RS 2 .PP \f[CR]date:202312\-\f[R] .PD 0 .P .PD \f[CR]status:\f[R] .PD 0 .P .PD \f[CR]desc:amazon\f[R] .PD 0 .P .PD \f[CR]cur:USD\f[R] .PD 0 .P .PD \f[CR]cur:\[rs]\[rs]$\f[R] .PD 0 .P .PD \f[CR]amt:\[aq]>0\[aq]\f[R] .PD 0 .P .PD .RE .IP \[bu] 2 Add a \f[CR]not:\f[R] prefix to negate a term: .RS 2 .PP \f[CR]not:status:\[aq]*\[aq]\f[R] .PD 0 .P .PD \f[CR]not:desc:\[aq]opening|closing\[aq]\f[R] .PD 0 .P .PD \f[CR]not:cur:USD\f[R] .PD 0 .P .PD .RE .IP \[bu] 2 Terms with different types are AND\-ed, terms with the same type are OR\-ed (mostly; see \[dq]Combining query terms\[dq] below). The following query: .RS 2 .PP \f[CR]date:2022 desc:amazon desc:amzn\f[R] .PP is interpreted as: .PP \f[I]date is in 2022 AND ( transaction description contains \[dq]amazon\[dq] OR \[dq]amzn\[dq] )\f[R] .RE .SS Query types Here are the types of query term available. Remember these can also be prefixed with \f[B]\f[CB]not:\f[B]\f[R] to convert them into a negative match. .PP \f[B]\f[CB]acct:REGEX\f[B]\f[R] or \f[B]\f[CB]REGEX\f[B]\f[R] .PD 0 .P .PD Match account names containing this case insensitive regular expression. This is the default query type, so we usually don\[aq]t bother writing the \[dq]acct:\[dq] prefix. .PP \f[B]\f[CB]amt:N, amt:N, amt:>=N\f[B]\f[R] .PD 0 .P .PD Match postings with a single\-commodity amount equal to, less than, or greater than N. (Postings with multi\-commodity amounts are not tested and will always match.) The comparison has two modes: if N is preceded by a + or \- sign (or is 0), the two signed numbers are compared. Otherwise, the absolute magnitudes are compared, ignoring sign. .PP \f[B]\f[CB]code:REGEX\f[B]\f[R] .PD 0 .P .PD Match by transaction code (eg check number). .PP \f[B]\f[CB]cur:REGEX\f[B]\f[R] .PD 0 .P .PD Match postings or transactions including any amounts whose currency/commodity symbol is fully matched by REGEX. (For a partial match, use \f[CR].*REGEX.*\f[R]). Note, to match special characters which are regex\-significant, you need to escape them with \f[CR]\[rs]\f[R]. And for characters which are significant to your shell you may need one more level of escaping. So eg to match the dollar sign: .PD 0 .P .PD \f[CR]hledger print cur:\[rs]\[rs]$\f[R]. .PP \f[B]\f[CB]desc:REGEX\f[B]\f[R] .PD 0 .P .PD Match transaction descriptions. .PP \f[B]\f[CB]date:PERIODEXPR\f[B]\f[R] .PD 0 .P .PD Match dates (or with the \f[CR]\-\-date2\f[R] flag, secondary dates) within the specified period. PERIODEXPR is a period expression with no report interval. Examples: .PD 0 .P .PD \f[CR]date:2016\f[R], \f[CR]date:thismonth\f[R], \f[CR]date:2/1\-2/15\f[R], \f[CR]date:2021\-07\-27..nextquarter\f[R]. .PP \f[B]\f[CB]date2:PERIODEXPR\f[B]\f[R] .PD 0 .P .PD Match secondary dates within the specified period (independent of the \f[CR]\-\-date2\f[R] flag). .PP \f[B]\f[CB]depth:N\f[B]\f[R] .PD 0 .P .PD Match (or display, depending on command) accounts at or above this depth. .PP \f[B]\f[CB]expr:\[dq]TERM AND NOT (TERM OR TERM)\[dq]\f[B]\f[R] (eg) .PD 0 .P .PD Match with a boolean combination of queries (which must be enclosed in quotes). See Combining query terms below. .PP \f[B]\f[CB]note:REGEX\f[B]\f[R] .PD 0 .P .PD Match transaction notes (the part of the description right of \f[CR]|\f[R], or the whole description if there\[aq]s no \f[CR]|\f[R]). .PP \f[B]\f[CB]payee:REGEX\f[B]\f[R] .PD 0 .P .PD Match transaction payee/payer names (the part of the description left of \f[CR]|\f[R], or the whole description if there\[aq]s no \f[CR]|\f[R]). .PP \f[B]\f[CB]real:, real:0\f[B]\f[R] .PD 0 .P .PD Match real or virtual postings respectively. .PP \f[B]\f[CB]status:, status:!, status:*\f[B]\f[R] .PD 0 .P .PD Match unmarked, pending, or cleared transactions respectively. .PP \f[B]\f[CB]type:TYPECODES\f[B]\f[R] .PD 0 .P .PD Match by account type (see Declaring accounts > Account types). \f[CR]TYPECODES\f[R] is one or more of the single\-letter account type codes \f[CR]ALERXCV\f[R], case insensitive. Note \f[CR]type:A\f[R] and \f[CR]type:E\f[R] will also match their respective subtypes \f[CR]C\f[R] (Cash) and \f[CR]V\f[R] (Conversion). Certain kinds of account alias can disrupt account types, see Rewriting accounts > Aliases and account types. .PP \f[B]\f[CB]tag:REGEX[=REGEX]\f[B]\f[R] .PD 0 .P .PD Match by tag name, and optionally also by tag value. (To match only by value, use \f[CR]tag:.=REGEX\f[R].) .PP When querying by tag, note that: .IP \[bu] 2 Accounts also inherit the tags of their parent accounts .IP \[bu] 2 Postings also inherit the tags of their account and their transaction .IP \[bu] 2 Transactions also acquire the tags of their postings. .PP (\f[B]\f[CB]inacct:ACCTNAME\f[B]\f[R] .PD 0 .P .PD A special query term used automatically in hledger\-web only: tells hledger\-web to show the transaction register for an account.) .SS Combining query terms When given multiple space\-separated query terms, most commands select things which match: .IP \[bu] 2 any of the description terms AND .IP \[bu] 2 any of the account terms AND .IP \[bu] 2 any of the status terms AND .IP \[bu] 2 all the other terms. .PP The print command is a little different, showing transactions which: .IP \[bu] 2 match any of the description terms AND .IP \[bu] 2 have any postings matching any of the positive account terms AND .IP \[bu] 2 have no postings matching any of the negative account terms AND .IP \[bu] 2 match all the other terms. .PP We also support more complex boolean queries with the \[aq]expr:\[aq] prefix. This allows one to combine queries using one of three operators: AND, OR, and NOT, where NOT is different syntax for \[aq]not:\[aq]. .PP Examples of such queries are: .IP \[bu] 2 Match transactions with \[aq]cool\[aq] in the description AND with the \[aq]A\[aq] tag .RS 2 .PP \f[CR]expr:\[dq]desc:cool AND tag:A\[dq]\f[R] .RE .IP \[bu] 2 Match transactions NOT to the \[aq]expenses:food\[aq] account OR with the \[aq]A\[aq] tag .RS 2 .PP \f[CR]expr:\[dq]NOT expenses:food OR tag:A\[dq]\f[R] .RE .IP \[bu] 2 Match transactions NOT involving the \[aq]expenses:food\[aq] account OR with the \[aq]A\[aq] tag AND involving the \[aq]expenses:drink\[aq] account. (the AND is implicitly added by space\-separation, following the rules above) .RS 2 .PP \f[CR]expr:\[dq]expenses:food OR (tag:A expenses:drink)\[dq]\f[R] .RE .SS Queries and command options Some queries can also be expressed as command\-line options: \f[CR]depth:2\f[R] is equivalent to \f[CR]\-\-depth 2\f[R], \f[CR]date:2023\f[R] is equivalent to \f[CR]\-p 2023\f[R], etc. When you mix command options and query arguments, generally the resulting query is their intersection. .SS Queries and valuation When amounts are converted to other commodities in cost or value reports, \f[CR]cur:\f[R] and \f[CR]amt:\f[R] match the old commodity symbol and the old amount quantity, not the new ones (except in hledger 1.22.0 where it\[aq]s reversed, see #1625). .SS Querying with account aliases When account names are rewritten with \f[CR]\-\-alias\f[R] or \f[CR]alias\f[R], note that \f[CR]acct:\f[R] will match either the old or the new account name. .SS Querying with cost or value When amounts are converted to other commodities in cost or value reports, note that \f[CR]cur:\f[R] matches the new commodity symbol, and not the old one, and \f[CR]amt:\f[R] matches the new quantity, and not the old one. Note: this changed in hledger 1.22, previously it was the reverse, see the discussion at #1625. .SH Pivoting Normally, hledger groups and sums amounts within each account. The \f[CR]\-\-pivot FIELD\f[R] option substitutes some other transaction field for account names, causing amounts to be grouped and summed by that field\[aq]s value instead. FIELD can be any of the transaction fields \f[CR]acct\f[R], \f[CR]status\f[R], \f[CR]code\f[R], \f[CR]desc\f[R], \f[CR]payee\f[R], \f[CR]note\f[R], or a tag name. When pivoting on a tag and a posting has multiple values of that tag, only the first value is displayed. Values containing \f[CR]colon:separated:parts\f[R] will be displayed hierarchically, like account names. Multiple, colon\-delimited fields can be pivoted simultaneously, generating a hierarchical account name. .PP Some examples: .IP .EX 2016/02/16 Yearly Dues Payment assets:bank account 2 EUR income:dues \-2 EUR ; member: John Doe, kind: Lifetime .EE .PP Normal balance report showing account names: .IP .EX $ hledger balance 2 EUR assets:bank account \-2 EUR income:dues \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP Pivoted balance report, using member: tag values instead: .IP .EX $ hledger balance \-\-pivot member 2 EUR \-2 EUR John Doe \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP One way to show only amounts with a member: value (using a query): .IP .EX $ hledger balance \-\-pivot member tag:member=. \-2 EUR John Doe \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \-2 EUR .EE .PP Another way (the acct: query matches against the pivoted \[dq]account name\[dq]): .IP .EX $ hledger balance \-\-pivot member acct:. \-2 EUR John Doe \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \-2 EUR .EE .PP Hierarchical reports can be generated with multiple pivots: .IP .EX $ hledger balance Income:Dues \-\-pivot kind:member \-2 EUR Lifetime:John Doe \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \-2 EUR .EE .SH Generating data hledger has several features for generating data, such as: .IP \[bu] 2 Periodic transaction rules can generate single or repeating transactions following a template. These are usually dated in the future, eg to help with forecasting. They are activated by the \f[CR]\-\-forecast\f[R] option. .IP \[bu] 2 The balance command\[aq]s \f[CR]\-\-budget\f[R] option uses these same periodic rules to generate goals for the budget report. .IP \[bu] 2 Auto posting rules can generate extra postings on certain matched transactions. They are always applied to forecast transactions; with the \f[CR]\-\-auto\f[R] flag they are applied to transactions recorded in the journal as well. .IP \[bu] 2 The \f[CR]\-\-infer\-equity\f[R] flag infers missing conversion equity postings from \[at]/\[at]\[at] costs. And the inverse \f[CR]\-\-infer\-costs\f[R] flag infers missing \[at]/\[at]\[at] costs from conversion equity postings. .PP Generated data of this kind is temporary, existing only at report time. But you can see it in the output of \f[CR]hledger print\f[R], and you can save that to your journal, in effect converting it from temporary generated data to permanent recorded data. This could be useful as a data entry aid. .PP If you are wondering what data is being generated and why, add the \f[CR]\-\-verbose\-tags\f[R] flag. In \f[CR]hledger print\f[R] output you will see extra tags like \f[CR]generated\-transaction\f[R], \f[CR]generated\-posting\f[R], and \f[CR]modified\f[R] on generated/modified data. Also, even without \f[CR]\-\-verbose\-tags\f[R], generated data always has equivalen hidden tags (with an underscore prefix), so eg you could match generated transactions with \f[CR]tag:_generated\-transaction\f[R]. .SH Forecasting Forecasting, or speculative future reporting, can be useful for estimating future balances, or for exploring different future scenarios. .PP The simplest and most flexible way to do it with hledger is to manually record a bunch of future\-dated transactions. You could keep these in a separate \f[CR]future.journal\f[R] and include that with \f[CR]\-f\f[R] only when you want to see them. .SS \-\-forecast There is another way: with the \f[CR]\-\-forecast\f[R] option, hledger can generate temporary \[dq]forecast transactions\[dq] for reporting purposes, according to periodic transaction rules defined in the journal. Each rule can generate multiple recurring transactions, so by changing one rule you can change many forecasted transactions. .PP Forecast transactions usually start after ordinary transactions end. By default, they begin after your latest\-dated ordinary transaction, or today, whichever is later, and they end six months from today. (The exact rules are a little more complicated, and are given below.) .PP This is the \[dq]forecast period\[dq], which need not be the same as the report period. You can override it \- eg to forecast farther into the future, or to force forecast transactions to overlap your ordinary transactions \- by giving the \-\-forecast option a period expression argument, like \f[CR]\-\-forecast=..2099\f[R] or \f[CR]\-\-forecast=2023\-02\-15..\f[R]. Note that the \f[CR]=\f[R] is required. .SS Inspecting forecast transactions \f[CR]print\f[R] is the best command for inspecting and troubleshooting forecast transactions. Eg: .IP .EX \[ti] monthly from 2022\-12\-20 rent assets:bank:checking expenses:rent $1000 .EE .IP .EX $ hledger print \-\-forecast \-\-today=2023/4/21 2023\-05\-20 rent ; generated\-transaction: \[ti] monthly from 2022\-12\-20 assets:bank:checking expenses:rent $1000 2023\-06\-20 rent ; generated\-transaction: \[ti] monthly from 2022\-12\-20 assets:bank:checking expenses:rent $1000 2023\-07\-20 rent ; generated\-transaction: \[ti] monthly from 2022\-12\-20 assets:bank:checking expenses:rent $1000 2023\-08\-20 rent ; generated\-transaction: \[ti] monthly from 2022\-12\-20 assets:bank:checking expenses:rent $1000 2023\-09\-20 rent ; generated\-transaction: \[ti] monthly from 2022\-12\-20 assets:bank:checking expenses:rent $1000 .EE .PP Here there are no ordinary transactions, so the forecasted transactions begin on the first occurence after today\[aq]s date. (You won\[aq]t normally use \f[CR]\-\-today\f[R]; it\[aq]s just to make these examples reproducible.) .SS Forecast reports Forecast transactions affect all reports, as you would expect. Eg: .IP .EX $ hledger areg rent \-\-forecast \-\-today=2023/4/21 Transactions in expenses:rent and subaccounts: 2023\-05\-20 rent as:ba:checking $1000 $1000 2023\-06\-20 rent as:ba:checking $1000 $2000 2023\-07\-20 rent as:ba:checking $1000 $3000 2023\-08\-20 rent as:ba:checking $1000 $4000 2023\-09\-20 rent as:ba:checking $1000 $5000 .EE .IP .EX $ hledger bal \-M expenses \-\-forecast \-\-today=2023/4/21 Balance changes in 2023\-05\-01..2023\-09\-30: || May Jun Jul Aug Sep ===============++=================================== expenses:rent || $1000 $1000 $1000 $1000 $1000 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || $1000 $1000 $1000 $1000 $1000 .EE .SS Forecast tags Forecast transactions generated by \-\-forecast have a hidden tag, \f[CR]_generated\-transaction\f[R]. So if you ever need to match forecast transactions, you could use \f[CR]tag:_generated\-transaction\f[R] (or just \f[CR]tag:generated\f[R]) in a query. .PP For troubleshooting, you can add the \f[CR]\-\-verbose\-tags\f[R] flag. Then, visible \f[CR]generated\-transaction\f[R] tags will be added also, so you can view them with the \f[CR]print\f[R] command. Their value indicates which periodic rule was responsible. .SS Forecast period, in detail Forecast start/end dates are chosen so as to do something useful by default in almost all situations, while also being flexible. Here are (with luck) the exact rules, to help with troubleshooting: .PP The forecast period starts on: .IP \[bu] 2 the later of .RS 2 .IP \[bu] 2 the start date in the periodic transaction rule .IP \[bu] 2 the start date in \f[CR]\-\-forecast\f[R]\[aq]s argument .RE .IP \[bu] 2 otherwise (if those are not available): the later of .RS 2 .IP \[bu] 2 the report start date specified with \f[CR]\-b\f[R]/\f[CR]\-p\f[R]/\f[CR]date:\f[R] .IP \[bu] 2 the day after the latest ordinary transaction in the journal .RE .IP \[bu] 2 otherwise (if none of these are available): today. .PP The forecast period ends on: .IP \[bu] 2 the earlier of .RS 2 .IP \[bu] 2 the end date in the periodic transaction rule .IP \[bu] 2 the end date in \f[CR]\-\-forecast\f[R]\[aq]s argument .RE .IP \[bu] 2 otherwise: the report end date specified with \f[CR]\-e\f[R]/\f[CR]\-p\f[R]/\f[CR]date:\f[R] .IP \[bu] 2 otherwise: 180 days (\[ti]6 months) from today. .SS Forecast troubleshooting When \-\-forecast is not doing what you expect, one of these tips should help: .IP \[bu] 2 Remember to use the \f[CR]\-\-forecast\f[R] option. .IP \[bu] 2 Remember to have at least one periodic transaction rule in your journal. .IP \[bu] 2 Test with \f[CR]print \-\-forecast\f[R]. .IP \[bu] 2 Check for typos or too\-restrictive start/end dates in your periodic transaction rule. .IP \[bu] 2 Leave at least 2 spaces between the rule\[aq]s period expression and description fields. .IP \[bu] 2 Check for future\-dated ordinary transactions suppressing forecasted transactions. .IP \[bu] 2 Try setting explicit report start and/or end dates with \f[CR]\-b\f[R], \f[CR]\-e\f[R], \f[CR]\-p\f[R] or \f[CR]date:\f[R] .IP \[bu] 2 Try adding the \f[CR]\-E\f[R] flag to encourage display of empty periods/zero transactions. .IP \[bu] 2 Try setting explicit forecast start and/or end dates with \f[CR]\-\-forecast=START..END\f[R] .IP \[bu] 2 Consult Forecast period, in detail, above. .IP \[bu] 2 Check inside the engine: add \f[CR]\-\-debug=2\f[R] (eg). .SH Budgeting With the balance command\[aq]s \f[CR]\-\-budget\f[R] report, each periodic transaction rule generates recurring budget goals in specified accounts, and goals and actual performance can be compared. See the balance command\[aq]s doc below. .PP You can generate budget goals and forecast transactions at the same time, from the same or different periodic transaction rules: \f[CR]hledger bal \-M \-\-budget \-\-forecast ...\f[R] .PP See also: Budgeting and Forecasting. .SH Cost reporting In some transactions \- for example a currency conversion, or a purchase or sale of stock \- one commodity is exchanged for another. In these transactions there is a conversion rate, also called the cost (when buying) or selling price (when selling). In hledger docs we just say \[dq]cost\[dq], for convenience; feel free to mentally translate to \[dq]conversion rate\[dq] or \[dq]selling price\[dq] if helpful. .SS Recording costs We\[aq]ll explore several ways of recording transactions involving costs. These are also summarised at hledger Cookbook > Cost notation. .PP Costs can be recorded explicitly in the journal, using the \f[CR]\[at] UNITCOST\f[R] or \f[CR]\[at]\[at] TOTALCOST\f[R] notation described in Journal > Costs: .PP \f[B]Variant 1\f[R] .IP .EX 2022\-01\-01 assets:dollars $\-135 assets:euros €100 \[at] $1.35 ; $1.35 per euro (unit cost) .EE .PP \f[B]Variant 2\f[R] .IP .EX 2022\-01\-01 assets:dollars $\-135 assets:euros €100 \[at]\[at] $135 ; $135 total cost .EE .PP Typically, writing the unit cost (variant 1) is preferable; it can be more effort, requiring more attention to decimal digits; but it reveals the per\-unit cost basis, and makes stock sales easier. .PP Costs can also be left implicit, and hledger will infer the cost that is consistent with a balanced transaction: .PP \f[B]Variant 3\f[R] .IP .EX 2022\-01\-01 assets:dollars $\-135 assets:euros €100 .EE .PP Here, hledger will attach a \f[CR]\[at]\[at] €100\f[R] cost to the first amount (you can see it with \f[CR]hledger print \-x\f[R]). This form looks convenient, but there are downsides: .IP \[bu] 2 It sacrifices some error checking. For example, if you accidentally wrote €10 instead of €100, hledger would not be able to detect the mistake. .IP \[bu] 2 It is sensitive to the order of postings \- if they were reversed, a different entry would be inferred and reports would be different. .IP \[bu] 2 The per\-unit cost basis is not easy to read. .PP So generally this kind of entry is not recommended. You can make sure you have none of these by using \f[CR]\-s\f[R] (strict mode), or by running \f[CR]hledger check balanced\f[R]. .SS Reporting at cost Now when you add the \f[CR]\-B\f[R]/\f[CR]\-\-cost\f[R] flag to reports (\[dq]B\[dq] is from Ledger\[aq]s \-B/\-\-basis/\-\-cost flag), any amounts which have been annotated with costs will be converted to their cost\[aq]s commodity (in the report output). Ie they will be displayed \[dq]at cost\[dq] or \[dq]at sale price\[dq]. .PP Some things to note: .IP \[bu] 2 Costs are attached to specific posting amounts in specific transactions, and once recorded they do not change. This contrasts with market prices, which are ambient and fluctuating. .IP \[bu] 2 Conversion to cost is performed before conversion to market value (described below). .SS Equity conversion postings There is a problem with the entries above \- they are not conventional Double Entry Bookkeeping (DEB) notation, and because of the \[dq]magical\[dq] transformation of one commodity into another, they cause an imbalance in the Accounting Equation. This shows up as a non\-zero grand total in balance reports like \f[CR]hledger bse\f[R]. .PP For most hledger users, this doesn\[aq]t matter in practice and can safely be ignored ! But if you\[aq]d like to learn more, keep reading. .PP Conventional DEB uses an extra pair of equity postings to balance the transaction. Of course you can do this in hledger as well: .PP \f[B]Variant 4\f[R] .IP .EX 2022\-01\-01 assets:dollars $\-135 assets:euros €100 equity:conversion $135 equity:conversion €\-100 .EE .PP Now the transaction is perfectly balanced according to standard DEB, and \f[CR]hledger bse\f[R]\[aq]s total will not be disrupted. .PP And, hledger can still infer the cost for cost reporting, but it\[aq]s not done by default \- you must add the \f[CR]\-\-infer\-costs\f[R] flag like so: .IP .EX $ hledger print \-\-infer\-costs 2022\-01\-01 one hundred euros purchased at $1.35 each assets:dollars $\-135 \[at]\[at] €100 assets:euros €100 equity:conversion $135 equity:conversion €\-100 .EE .IP .EX $ hledger bal \-\-infer\-costs \-B €\-100 assets:dollars €100 assets:euros \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP Here are some downsides of this kind of entry: .IP \[bu] 2 The per\-unit cost basis is not easy to read. .IP \[bu] 2 Instead of \f[CR]\-B\f[R] you must remember to type \f[CR]\-B \-\-infer\-costs\f[R]. .IP \[bu] 2 \f[CR]\-\-infer\-costs\f[R] works only where hledger can identify the two equity:conversion postings and match them up with the two non\-equity postings. So writing the journal entry in a particular format becomes more important. More on this below. .SS Inferring equity conversion postings Can we go in the other direction ? Yes, if you have transactions written with the \[at]/\[at]\[at] cost notation, hledger can infer the missing equity postings, if you add the \f[CR]\-\-infer\-equity\f[R] flag. Eg: .IP .EX 2022\-01\-01 assets:dollars \-$135 assets:euros €100 \[at] $1.35 .EE .IP .EX $ hledger print \-\-infer\-equity 2022\-01\-01 assets:dollars $\-135 assets:euros €100 \[at] $1.35 equity:conversion:$\-€:€ €\-100 equity:conversion:$\-€:$ $135.00 .EE .PP The equity account names will be \[dq]equity:conversion:A\-B:A\[dq] and \[dq]equity:conversion:A\-B:B\[dq] where A is the alphabetically first commodity symbol. You can customise the \[dq]equity:conversion\[dq] part by declaring an account with the \f[CR]V\f[R]/\f[CR]Conversion\f[R] account type. .SS Combining costs and equity conversion postings Finally, you can use both the \[at]/\[at]\[at] cost notation and equity postings at the same time. This in theory gives the best of all worlds \- preserving the accounting equation, revealing the per\-unit cost basis, and providing more flexibility in how you write the entry: .PP \f[B]Variant 5\f[R] .IP .EX 2022\-01\-01 one hundred euros purchased at $1.35 each assets:dollars $\-135 equity:conversion $135 equity:conversion €\-100 assets:euros €100 \[at] $1.35 .EE .PP All the other variants above can (usually) be rewritten to this final form with: .IP .EX $ hledger print \-x \-\-infer\-costs \-\-infer\-equity .EE .PP Downsides: .IP \[bu] 2 This was added in hledger\-1.29 and is still somewhat experimental. .IP \[bu] 2 The precise format of the journal entry becomes more important. If hledger can\[aq]t detect and match up the cost and equity postings, it will give a transaction balancing error. .IP \[bu] 2 The add command does not yet accept this kind of entry (#2056). .IP \[bu] 2 This is the most verbose form. .SS Requirements for detecting equity conversion postings \f[CR]\-\-infer\-costs\f[R] has certain requirements (unlike \f[CR]\-\-infer\-equity\f[R], which always works). It will infer costs only in transactions with: .IP \[bu] 2 Two non\-equity postings, in different commodities. Their order is significant: the cost will be added to the first of them. .IP \[bu] 2 Two postings to equity conversion accounts, next to one another, which balance the two non\-equity postings. This balancing is checked to the same precision (number of decimal places) used in the conversion posting\[aq]s amount. Equity conversion accounts are: .RS 2 .IP \[bu] 2 any accounts declared with account type \f[CR]V\f[R]/\f[CR]Conversion\f[R], or their subaccounts .IP \[bu] 2 otherwise, accounts named \f[CR]equity:conversion\f[R], \f[CR]equity:trade\f[R], or \f[CR]equity:trading\f[R], or their subaccounts. .RE .PP And multiple such four\-posting groups can coexist within a single transaction. When \f[CR]\-\-infer\-costs\f[R] fails, it does not infer a cost in that transaction, and does not raise an error (ie, it infers costs where it can). .PP Reading variant 5 journal entries, combining cost notation and equity postings, has all the same requirements. When reading such an entry fails, hledger raises an \[dq]unbalanced transaction\[dq] error. .SS Infer cost and equity by default ? Should \f[CR]\-\-infer\-costs\f[R] and \f[CR]\-\-infer\-equity\f[R] be enabled by default ? Try using them always, eg with a shell alias: .IP .EX alias h=\[dq]hledger \-\-infer\-equity \-\-infer\-costs\[dq] .EE .PP and let us know what problems you find. .PP .SH Value reporting Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), and/or to market value (using some market price on a certain date). This is controlled by the \f[CR]\-\-value=TYPE[,COMMODITY]\f[R] option, which will be described below. We also provide the simpler \f[CR]\-V\f[R] and \f[CR]\-X COMMODITY\f[R] options, and often one of these is all you need: .SS \-V: Value The \f[CR]\-V/\-\-market\f[R] flag converts amounts to market value in their default \f[I]valuation commodity\f[R], using the market prices in effect on the \f[I]valuation date(s)\f[R], if any. More on these in a minute. .SS \-X: Value in specified commodity The \f[CR]\-X/\-\-exchange=COMM\f[R] option is like \f[CR]\-V\f[R], except you tell it which currency you want to convert to, and it tries to convert everything to that. .SS Valuation date Market prices can change from day to day. hledger will use the prices on a particular valuation date (or on more than one date). By default hledger uses \[dq]end\[dq] dates for valuation. More specifically: .IP \[bu] 2 For single period reports (including normal print and register reports): .RS 2 .IP \[bu] 2 If an explicit report end date is specified, that is used .IP \[bu] 2 Otherwise the latest transaction date or P directive date is used (even if it\[aq]s in the future) .RE .IP \[bu] 2 For multiperiod reports, each period is valued on its last day. .PP This can be customised with the \-\-value option described below, which can select either \[dq]then\[dq], \[dq]end\[dq], \[dq]now\[dq], or \[dq]custom\[dq] dates. (Note, this has a bug in hledger\-ui <=1.31: turning on valuation with the \f[CR]V\f[R] key always resets it to \[dq]end\[dq].) .SS Finding market price To convert a commodity A to its market value in another commodity B, hledger looks for a suitable market price (exchange rate) as follows, in this order of preference: .IP "1." 3 A \f[I]declared market price\f[R] or \f[I]inferred market price\f[R]: A\[aq]s latest market price in B on or before the valuation date as declared by a P directive, or (with the \f[CR]\-\-infer\-market\-prices\f[R] flag) inferred from costs. \ .IP "2." 3 A \f[I]reverse market price\f[R]: the inverse of a declared or inferred market price from B to A. .IP "3." 3 A \f[I]forward chain of market prices\f[R]: a synthetic price formed by combining the shortest chain of \[dq]forward\[dq] (only 1 above) market prices, leading from A to B. .IP "4." 3 \f[I]Any chain of market prices\f[R]: a chain of any market prices, including both forward and reverse prices (1 and 2 above), leading from A to B. .PP There is a limit to the length of these price chains; if hledger reaches that length without finding a complete chain or exhausting all possibilities, it will give up (with a \[dq]gave up\[dq] message visible in \f[CR]\-\-debug=2\f[R] output). That limit is currently 1000. .PP Amounts for which no suitable market price can be found, are not converted. .SS \-\-infer\-market\-prices: market prices from transactions Normally, market value in hledger is fully controlled by, and requires, P directives in your journal. Since adding and updating those can be a chore, and since transactions usually take place at close to market value, why not use the recorded costs as additional market prices (as Ledger does) ? Adding the \f[CR]\-\-infer\-market\-prices\f[R] flag to \f[CR]\-V\f[R], \f[CR]\-X\f[R] or \f[CR]\-\-value\f[R] enables this. .PP So for example, \f[CR]hledger bs \-V \-\-infer\-market\-prices\f[R] will get market prices both from P directives and from transactions. If both occur on the same day, the P directive takes precedence. .PP There is a downside: value reports can sometimes be affected in confusing/undesired ways by your journal entries. If this happens to you, read all of this Value reporting section carefully, and try adding \f[CR]\-\-debug\f[R] or \f[CR]\-\-debug=2\f[R] to troubleshoot. .PP \f[CR]\-\-infer\-market\-prices\f[R] can infer market prices from: .IP \[bu] 2 multicommodity transactions with explicit prices (\f[CR]\[at]\f[R]/\f[CR]\[at]\[at]\f[R]) .IP \[bu] 2 multicommodity transactions with implicit prices (no \f[CR]\[at]\f[R], two commodities, unbalanced). (With these, the order of postings matters. \f[CR]hledger print \-x\f[R] can be useful for troubleshooting.) .IP \[bu] 2 multicommodity transactions with equity postings, if cost is inferred with \f[CR]\-\-infer\-costs\f[R]. .PP There is a limitation (bug) currently: when a valuation commodity is not specified, prices inferred with \f[CR]\-\-infer\-market\-prices\f[R] do not help select a default valuation commodity, as \f[CR]P\f[R] prices would. So conversion might not happen because no valuation commodity was detected (\f[CR]\-\-debug=2\f[R] will show this). To be safe, specify the valuation commmodity, eg: .IP \[bu] 2 \f[CR]\-X EUR \-\-infer\-market\-prices\f[R], not \f[CR]\-V \-\-infer\-market\-prices\f[R] .IP \[bu] 2 \f[CR]\-\-value=then,EUR \-\-infer\-market\-prices\f[R], not \f[CR]\-\-value=then \-\-infer\-market\-prices\f[R] .PP Signed costs and market prices can be confusing. For reference, here is the current behaviour, since hledger 1.25. (If you think it should work differently, see #1870.) .IP .EX 2022\-01\-01 Positive Unit prices a A 1 b B \-1 \[at] A 1 2022\-01\-01 Positive Total prices a A 1 b B \-1 \[at]\[at] A 1 2022\-01\-02 Negative unit prices a A 1 b B 1 \[at] A \-1 2022\-01\-02 Negative total prices a A 1 b B 1 \[at]\[at] A \-1 2022\-01\-03 Double Negative unit prices a A \-1 b B \-1 \[at] A \-1 2022\-01\-03 Double Negative total prices a A \-1 b B \-1 \[at]\[at] A \-1 .EE .PP All of the transactions above are considered balanced (and on each day, the two transactions are considered equivalent). Here are the market prices inferred for B: .IP .EX $ hledger \-f\- \-\-infer\-market\-prices prices P 2022\-01\-01 B A 1 P 2022\-01\-01 B A 1.0 P 2022\-01\-02 B A \-1 P 2022\-01\-02 B A \-1.0 P 2022\-01\-03 B A \-1 P 2022\-01\-03 B A \-1.0 .EE .SS Valuation commodity \f[B]When you specify a valuation commodity (\f[CB]\-X COMM\f[B] or \f[CB]\-\-value TYPE,COMM\f[B]):\f[R] .PD 0 .P .PD hledger will convert all amounts to COMM, wherever it can find a suitable market price (including by reversing or chaining prices). .PP \f[B]When you leave the valuation commodity unspecified (\f[CB]\-V\f[B] or \f[CB]\-\-value TYPE\f[B]):\f[R] .PD 0 .P .PD For each commodity A, hledger picks a default valuation commodity as follows, in this order of preference: .IP "1." 3 The price commodity from the latest P\-declared market price for A on or before valuation date. .IP "2." 3 The price commodity from the latest P\-declared market price for A on any date. (Allows conversion to proceed when there are inferred prices before the valuation date.) .IP "3." 3 If there are no P directives at all (any commodity or date) and the \f[CR]\-\-infer\-market\-prices\f[R] flag is used: the price commodity from the latest transaction\-inferred price for A on or before valuation date. .PP This means: .IP \[bu] 2 If you have P directives, they determine which commodities \f[CR]\-V\f[R] will convert, and to what. .IP \[bu] 2 If you have no P directives, and use the \f[CR]\-\-infer\-market\-prices\f[R] flag, costs determine it. .PP Amounts for which no valuation commodity can be found are not converted. .SS Simple valuation examples Here are some quick examples of \f[CR]\-V\f[R]: .IP .EX ; one euro is worth this many dollars from nov 1 P 2016/11/01 € $1.10 ; purchase some euros on nov 3 2016/11/3 assets:euros €100 assets:checking ; the euro is worth fewer dollars by dec 21 P 2016/12/21 € $1.03 .EE .PP How many euros do I have ? .IP .EX $ hledger \-f t.j bal \-N euros €100 assets:euros .EE .PP What are they worth at end of nov 3 ? .IP .EX $ hledger \-f t.j bal \-N euros \-V \-e 2016/11/4 $110.00 assets:euros .EE .PP What are they worth after 2016/12/21 ? (no report end date specified, defaults to today) .IP .EX $ hledger \-f t.j bal \-N euros \-V $103.00 assets:euros .EE .SS \-\-value: Flexible valuation \f[CR]\-V\f[R] and \f[CR]\-X\f[R] are special cases of the more general \f[CR]\-\-value\f[R] option: .IP .EX \-\-value=TYPE[,COMM] TYPE is then, end, now or YYYY\-MM\-DD. COMM is an optional commodity symbol. Shows amounts converted to: \- default valuation commodity (or COMM) using market prices at posting dates \- default valuation commodity (or COMM) using market prices at period end(s) \- default valuation commodity (or COMM) using current market prices \- default valuation commodity (or COMM) using market prices at some date .EE .PP The TYPE part selects cost or value and valuation date: .TP \f[CR]\-\-value=then\f[R] Convert amounts to their value in the default valuation commodity, using market prices on each posting\[aq]s date. .TP \f[CR]\-\-value=end\f[R] Convert amounts to their value in the default valuation commodity, using market prices on the last day of the report period (or if unspecified, the journal\[aq]s end date); or in multiperiod reports, market prices on the last day of each subperiod. .TP \f[CR]\-\-value=now\f[R] Convert amounts to their value in the default valuation commodity using current market prices (as of when report is generated). .TP \f[CR]\-\-value=YYYY\-MM\-DD\f[R] Convert amounts to their value in the default valuation commodity using market prices on this date. .PP To select a different valuation commodity, add the optional \f[CR],COMM\f[R] part: a comma, then the target commodity\[aq]s symbol. Eg: \f[B]\f[CB]\-\-value=now,EUR\f[B]\f[R]. hledger will do its best to convert amounts to this commodity, deducing market prices as described above. .SS More valuation examples Here are some examples showing the effect of \f[CR]\-\-value\f[R], as seen with \f[CR]print\f[R]: .IP .EX P 2000\-01\-01 A 1 B P 2000\-02\-01 A 2 B P 2000\-03\-01 A 3 B P 2000\-04\-01 A 4 B 2000\-01\-01 (a) 1 A \[at] 5 B 2000\-02\-01 (a) 1 A \[at] 6 B 2000\-03\-01 (a) 1 A \[at] 7 B .EE .PP Show the cost of each posting: .IP .EX $ hledger \-f\- print \-\-cost 2000\-01\-01 (a) 5 B 2000\-02\-01 (a) 6 B 2000\-03\-01 (a) 7 B .EE .PP Show the value as of the last day of the report period (2000\-02\-29): .IP .EX $ hledger \-f\- print \-\-value=end date:2000/01\-2000/03 2000\-01\-01 (a) 2 B 2000\-02\-01 (a) 2 B .EE .PP With no report period specified, that shows the value as of the last day of the journal (2000\-03\-01): .IP .EX $ hledger \-f\- print \-\-value=end 2000\-01\-01 (a) 3 B 2000\-02\-01 (a) 3 B 2000\-03\-01 (a) 3 B .EE .PP Show the current value (the 2000\-04\-01 price is still in effect today): .IP .EX $ hledger \-f\- print \-\-value=now 2000\-01\-01 (a) 4 B 2000\-02\-01 (a) 4 B 2000\-03\-01 (a) 4 B .EE .PP Show the value on 2000/01/15: .IP .EX $ hledger \-f\- print \-\-value=2000\-01\-15 2000\-01\-01 (a) 1 B 2000\-02\-01 (a) 1 B 2000\-03\-01 (a) 1 B .EE .SS Interaction of valuation and queries When matching postings based on queries in the presence of valuation, the following happens. .IP "1." 3 The query is separated into two parts: .RS 4 .IP "1." 3 the currency (\f[CR]cur:\f[R]) or amount (\f[CR]amt:\f[R]). .IP "2." 3 all other parts. .RE .IP "2." 3 The postings are matched to the currency and amount queries based on pre\-valued amounts. .IP "3." 3 Valuation is applied to the postings. .IP "4." 3 The postings are matched to the other parts of the query based on post\-valued amounts. .PP See: 1625 .SS Effect of valuation on reports Here is a reference for how valuation is supposed to affect each part of hledger\[aq]s reports (and a glossary). (It\[aq]s wide, you\[aq]ll have to scroll sideways.) It may be useful when troubleshooting. If you find problems, please report them, ideally with a reproducible example. Related: #329, #1083. .PP .TS tab(@); lw(9.5n) lw(11.8n) lw(12.0n) lw(17.2n) lw(12.0n) lw(7.4n). T{ Report type T}@T{ \f[CR]\-B\f[R], \f[CR]\-\-cost\f[R] T}@T{ \f[CR]\-V\f[R], \f[CR]\-X\f[R] T}@T{ \f[CR]\-\-value=then\f[R] T}@T{ \f[CR]\-\-value=end\f[R] T}@T{ \f[CR]\-\-value=DATE\f[R], \f[CR]\-\-value=now\f[R] T} _ T{ \f[B]print\f[R] T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ posting amounts T}@T{ cost T}@T{ value at report end or today T}@T{ value at posting date T}@T{ value at report or journal end T}@T{ value at DATE/today T} T{ balance assertions/assignments T}@T{ unchanged T}@T{ unchanged T}@T{ unchanged T}@T{ unchanged T}@T{ unchanged T} T{ T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ \f[B]register\f[R] T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ starting balance (\-H) T}@T{ cost T}@T{ value at report or journal end T}@T{ valued at day each historical posting was made T}@T{ value at report or journal end T}@T{ value at DATE/today T} T{ starting balance (\-H) with report interval T}@T{ cost T}@T{ value at day before report or journal start T}@T{ valued at day each historical posting was made T}@T{ value at day before report or journal start T}@T{ value at DATE/today T} T{ posting amounts T}@T{ cost T}@T{ value at report or journal end T}@T{ value at posting date T}@T{ value at report or journal end T}@T{ value at DATE/today T} T{ summary posting amounts with report interval T}@T{ summarised cost T}@T{ value at period ends T}@T{ sum of postings in interval, valued at interval start T}@T{ value at period ends T}@T{ value at DATE/today T} T{ running total/average T}@T{ sum/average of displayed values T}@T{ sum/average of displayed values T}@T{ sum/average of displayed values T}@T{ sum/average of displayed values T}@T{ sum/average of displayed values T} T{ T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ \f[B]balance (bs, bse, cf, is)\f[R] T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ balance changes T}@T{ sums of costs T}@T{ value at report end or today of sums of postings T}@T{ value at posting date T}@T{ value at report or journal end of sums of postings T}@T{ value at DATE/today of sums of postings T} T{ budget amounts (\-\-budget) T}@T{ like balance changes T}@T{ like balance changes T}@T{ like balance changes T}@T{ like balances T}@T{ like balance changes T} T{ grand total T}@T{ sum of displayed values T}@T{ sum of displayed values T}@T{ sum of displayed valued T}@T{ sum of displayed values T}@T{ sum of displayed values T} T{ T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ \f[B]balance (bs, bse, cf, is) with report interval\f[R] T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ starting balances (\-H) T}@T{ sums of costs of postings before report start T}@T{ value at report start of sums of all postings before report start T}@T{ sums of values of postings before report start at respective posting dates T}@T{ value at report start of sums of all postings before report start T}@T{ sums of postings before report start T} T{ balance changes (bal, is, bs \-\-change, cf \-\-change) T}@T{ sums of costs of postings in period T}@T{ same as \-\-value=end T}@T{ sums of values of postings in period at respective posting dates T}@T{ balance change in each period, valued at period ends T}@T{ value at DATE/today of sums of postings T} T{ end balances (bal \-H, is \-\-H, bs, cf) T}@T{ sums of costs of postings from before report start to period end T}@T{ same as \-\-value=end T}@T{ sums of values of postings from before period start to period end at respective posting dates T}@T{ period end balances, valued at period ends T}@T{ value at DATE/today of sums of postings T} T{ budget amounts (\-\-budget) T}@T{ like balance changes/end balances T}@T{ like balance changes/end balances T}@T{ like balance changes/end balances T}@T{ like balances T}@T{ like balance changes/end balances T} T{ row totals, row averages (\-T, \-A) T}@T{ sums, averages of displayed values T}@T{ sums, averages of displayed values T}@T{ sums, averages of displayed values T}@T{ sums, averages of displayed values T}@T{ sums, averages of displayed values T} T{ column totals T}@T{ sums of displayed values T}@T{ sums of displayed values T}@T{ sums of displayed values T}@T{ sums of displayed values T}@T{ sums of displayed values T} T{ grand total, grand average T}@T{ sum, average of column totals T}@T{ sum, average of column totals T}@T{ sum, average of column totals T}@T{ sum, average of column totals T}@T{ sum, average of column totals T} T{ T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} .TE .PP \f[CR]\-\-cumulative\f[R] is omitted to save space, it works like \f[CR]\-H\f[R] but with a zero starting balance. .PP \f[B]Glossary:\f[R] .TP \f[I]cost\f[R] calculated using price(s) recorded in the transaction(s). .TP \f[I]value\f[R] market value using available market price declarations, or the unchanged amount if no conversion rate can be found. .TP \f[I]report start\f[R] the first day of the report period specified with \-b or \-p or date:, otherwise today. .TP \f[I]report or journal start\f[R] the first day of the report period specified with \-b or \-p or date:, otherwise the earliest transaction date in the journal, otherwise today. .TP \f[I]report end\f[R] the last day of the report period specified with \-e or \-p or date:, otherwise today. .TP \f[I]report or journal end\f[R] the last day of the report period specified with \-e or \-p or date:, otherwise the latest transaction date in the journal, otherwise today. .TP \f[I]report interval\f[R] a flag (\-D/\-W/\-M/\-Q/\-Y) or period expression that activates the report\[aq]s multi\-period mode (whether showing one or many subperiods). .SH PART 4: COMMANDS .SS Commands overview Here are the built\-in commands: .SS DATA ENTRY These data entry commands are the only ones which can modify your journal file. .IP \[bu] 2 add \- add transactions using terminal prompts .IP \[bu] 2 import \- add new transactions from other files, eg CSV files .SS DATA CREATION .IP \[bu] 2 close \- generate balance\-zeroing/restoring transactions .IP \[bu] 2 rewrite \- generate auto postings, like print \-\-auto .SS DATA MANAGEMENT .IP \[bu] 2 check \- check for various kinds of error in the data .IP \[bu] 2 diff \- compare account transactions in two journal files .SS REPORTS, FINANCIAL .IP \[bu] 2 aregister (areg) \- show transactions in a particular account .IP \[bu] 2 balancesheet (bs) \- show assets, liabilities and net worth .IP \[bu] 2 balancesheetequity (bse) \- show assets, liabilities and equity .IP \[bu] 2 cashflow (cf) \- show changes in liquid assets .IP \[bu] 2 incomestatement (is) \- show revenues and expenses .SS REPORTS, VERSATILE .IP \[bu] 2 balance (bal) \- show balance changes, end balances, budgets, gains.. .IP \[bu] 2 print \- show transactions or export journal data .IP \[bu] 2 register (reg) \- show postings in one or more accounts & running total .IP \[bu] 2 roi \- show return on investments .SS REPORTS, BASIC .IP \[bu] 2 accounts \- show account names .IP \[bu] 2 activity \- show bar charts of posting counts per period .IP \[bu] 2 codes \- show transaction codes .IP \[bu] 2 commodities \- show commodity/currency symbols .IP \[bu] 2 descriptions \- show transaction descriptions .IP \[bu] 2 files \- show input file paths .IP \[bu] 2 notes \- show note parts of transaction descriptions .IP \[bu] 2 payees \- show payee parts of transaction descriptions .IP \[bu] 2 prices \- show market prices .IP \[bu] 2 stats \- show journal statistics .IP \[bu] 2 tags \- show tag names .IP \[bu] 2 test \- run self tests .SS HELP .IP \[bu] 2 help \- show the hledger manual with info/man/pager .IP \[bu] 2 demo \- show small hledger demos in the terminal .PP \ .SS ADD\-ONS And here are some typical add\-on commands. Some of these are installed by the hledger\-install script. If installed, they will appear in hledger\[aq]s commands list: .IP \[bu] 2 ui \- run hledger\[aq]s terminal UI .IP \[bu] 2 web \- run hledger\[aq]s web UI .IP \[bu] 2 iadd \- add transactions using a TUI (currently hard to build) .IP \[bu] 2 interest \- generate interest transactions .IP \[bu] 2 stockquotes \- download market prices from AlphaVantage .IP \[bu] 2 Scripts and add\-ons \- check\-fancyassertions, edit, fifo, git, move, pijul, plot, and more.. .PP Next, each command is described in detail, in alphabetical order. .SS accounts Show account names. .PP This command lists account names. By default it shows all known accounts, either used in transactions or declared with account directives. .PP With query arguments, only matched account names and account names referenced by matched postings are shown. .PP Or it can show just the used accounts (\f[CR]\-\-used\f[R]/\f[CR]\-u\f[R]), the declared accounts (\f[CR]\-\-declared\f[R]/\f[CR]\-d\f[R]), the accounts declared but not used (\f[CR]\-\-unused\f[R]), the accounts used but not declared (\f[CR]\-\-undeclared\f[R]), or the first account matched by an account name pattern, if any (\f[CR]\-\-find\f[R]). .PP It shows a flat list by default. With \f[CR]\-\-tree\f[R], it uses indentation to show the account hierarchy. In flat mode you can add \f[CR]\-\-drop N\f[R] to omit the first few account name components. Account names can be depth\-clipped with \f[CR]depth:N\f[R] or \f[CR]\-\-depth N\f[R] or \f[CR]\-N\f[R]. .PP With \f[CR]\-\-types\f[R], it also shows each account\[aq]s type, if it\[aq]s known. (See Declaring accounts > Account types.) .PP With \f[CR]\-\-positions\f[R], it also shows the file and line number of each account\[aq]s declaration, if any, and the account\[aq]s overall declaration order; these may be useful when troubleshooting account display order. .PP With \f[CR]\-\-directives\f[R], it adds the \f[CR]account\f[R] keyword, showing valid account directives which can be pasted into a journal file. This is useful together with \f[CR]\-\-undeclared\f[R] when updating your account declarations to satisfy \f[CR]hledger check accounts\f[R]. .PP The \f[CR]\-\-find\f[R] flag can be used to look up a single account name, in the same way that the \f[CR]aregister\f[R] command does. It returns the alphanumerically\-first matched account name, or if none can be found, it fails with a non\-zero exit code. .PP Examples: .IP .EX $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts .EE .IP .EX $ hledger accounts \-\-undeclared \-\-directives >> $LEDGER_FILE $ hledger check accounts .EE .SS activity Show an ascii barchart of posting counts per interval. .PP The activity command displays an ascii histogram showing transaction counts by day, week, month or other reporting interval (by day is the default). With query arguments, it counts only matched transactions. .PP Examples: .IP .EX $ hledger activity \-\-quarterly 2008\-01\-01 ** 2008\-04\-01 ******* 2008\-07\-01 2008\-10\-01 ** .EE .SS add Prompt for transactions and add them to the journal. Any arguments will be used as default inputs for the first N prompts. .PP Many hledger users edit their journals directly with a text editor, or generate them from CSV. For more interactive data entry, there is the \f[CR]add\f[R] command, which prompts interactively on the console for new transactions, and appends them to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also \f[CR]import\f[R]). .PP To use it, just run \f[CR]hledger add\f[R] and follow the prompts. You can add as many transactions as you like; when you are finished, enter \f[CR].\f[R] or press control\-d or control\-c to exit. .PP Features: .IP \[bu] 2 add tries to provide useful defaults, using the most similar (by description) recent transaction (filtered by the query, if any) as a template. .IP \[bu] 2 You can also set the initial defaults with command line arguments. .IP \[bu] 2 Readline\-style edit keys can be used during data entry. .IP \[bu] 2 The tab key will auto\-complete whenever possible \- accounts, payees/descriptions, dates (\f[CR]yesterday\f[R], \f[CR]today\f[R], \f[CR]tomorrow\f[R]). If the input area is empty, it will insert the default value. .IP \[bu] 2 If the journal defines a default commodity, it will be added to any bare numbers entered. .IP \[bu] 2 A parenthesised transaction code may be entered following a date. .IP \[bu] 2 Comments and tags may be entered following a description or amount. .IP \[bu] 2 If you make a mistake, enter \f[CR]<\f[R] at any prompt to go one step backward. .IP \[bu] 2 Input prompts are displayed in a different colour when the terminal supports it. .PP Example (see https://hledger.org/add.html for a detailed tutorial): .IP .EX $ hledger add Adding transactions to journal file /src/hledger/examples/sample.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control\-d or control\-c. Date [2015/05/22]: Description: supermarket Account 1: expenses:food Amount 1: $10 Account 2: assets:checking Amount 2 [$\-10.0]: Account 3 (or . or enter to finish this transaction): . 2015/05/22 supermarket expenses:food $10 assets:checking $\-10.0 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl\-D/ctrl\-C to quit) Date [2015/05/22]: $ .EE .PP On Microsoft Windows, the add command makes sure that no part of the file path ends with a period, as that would cause problems (#1056). .SS aregister (areg) .PP Show the transactions and running historical balance of a single account, with each transaction displayed as one line. .PP \f[CR]aregister\f[R] shows the overall transactions affecting a particular account (and any subaccounts). Each report line represents one transaction in this account. Transactions before the report start date are always included in the running balance (\f[CR]\-\-historical\f[R] mode is always on). .PP This is a more \[dq]real world\[dq], bank\-like view than the \f[CR]register\f[R] command (which shows individual postings, possibly from multiple accounts, not necessarily in historical mode). As a quick rule of thumb: \- use \f[CR]aregister\f[R] for reviewing and reconciling real\-world asset/liability accounts \- use \f[CR]register\f[R] for reviewing detailed revenues/expenses. .PP \f[CR]aregister\f[R] requires one argument: the account to report on. You can write either the full account name, or a case\-insensitive regular expression which will select the alphabetically first matched account. .PP When there are multiple matches, the alphabetically\-first choice can be surprising; eg if you have \f[CR]assets:per:checking 1\f[R] and \f[CR]assets:biz:checking 2\f[R] accounts, \f[CR]hledger areg checking\f[R] would select \f[CR]assets:biz:checking 2\f[R]. It\[aq]s just a convenience to save typing, so if in doubt, write the full account name, or a distinctive substring that matches uniquely. .PP Transactions involving subaccounts of this account will also be shown. \f[CR]aregister\f[R] ignores depth limits, so its final total will always match a balance report with similar arguments. .PP Any additional arguments form a query which will filter the transactions shown. Note some queries will disturb the running balance, causing it to be different from the account\[aq]s real\-world running balance. .PP An example: this shows the transactions and historical running balance during july, in the first account whose name contains \[dq]checking\[dq]: .IP .EX $ hledger areg checking date:jul .EE .PP Each \f[CR]aregister\f[R] line item shows: .IP \[bu] 2 the transaction\[aq]s date (or the relevant posting\[aq]s date if different, see below) .IP \[bu] 2 the names of all the other account(s) involved in this transaction (probably abbreviated) .IP \[bu] 2 the total change to this account\[aq]s balance from this transaction .IP \[bu] 2 the account\[aq]s historical running balance after this transaction. .PP Transactions making a net change of zero are not shown by default; add the \f[CR]\-E/\-\-empty\f[R] flag to show them. .PP For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the \f[CR]\-\-align\-all\f[R] flag. .PP This command also supports the output destination and output format options. The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], and \f[CR]json\f[R]. .SS aregister and posting dates aregister always shows one line (and date and amount) per transaction. But sometimes transactions have postings with different dates. Also, not all of a transaction\[aq]s postings may be within the report period. To resolve this, aregister shows the earliest of the transaction\[aq]s date and posting dates that is in\-period, and the sum of the in\-period postings. In other words it will show a combined line item with just the earliest date, and the running balance will (temporarily, until the transaction\[aq]s last posting) be inaccurate. Use \f[CR]register \-H\f[R] if you need to see the individual postings. .PP There is also a \f[CR]\-\-txn\-dates\f[R] flag, which filters strictly by transaction date, ignoring posting dates. This too can cause an inaccurate running balance. .SS balance (bal) .PP Show accounts and their balances. .PP \f[CR]balance\f[R] is one of hledger\[aq]s oldest and most versatile commands, for listing account balances, balance changes, values, value changes and more, during one time period or many. Generally it shows a table, with rows representing accounts, and columns representing periods. .PP Note there are some higher\-level variants of the \f[CR]balance\f[R] command with convenient defaults, which can be simpler to use: \f[CR]balancesheet\f[R], \f[CR]balancesheetequity\f[R], \f[CR]cashflow\f[R] and \f[CR]incomestatement\f[R]. When you need more control, then use \f[CR]balance\f[R]. .SS balance features Here\[aq]s a quick overview of the \f[CR]balance\f[R] command\[aq]s features, followed by more detailed descriptions and examples. Many of these work with the higher\-level commands as well. .PP \f[CR]balance\f[R] can show.. .IP \[bu] 2 accounts as a list (\f[CR]\-l\f[R]) or a tree (\f[CR]\-t\f[R]) .IP \[bu] 2 optionally depth\-limited (\f[CR]\-[1\-9]\f[R]) .IP \[bu] 2 sorted by declaration order and name, or by amount .PP \&..and their.. .IP \[bu] 2 balance changes (the default) .IP \[bu] 2 or actual and planned balance changes (\f[CR]\-\-budget\f[R]) .IP \[bu] 2 or value of balance changes (\f[CR]\-V\f[R]) .IP \[bu] 2 or change of balance values (\f[CR]\-\-valuechange\f[R]) .IP \[bu] 2 or unrealised capital gain/loss (\f[CR]\-\-gain\f[R]) .IP \[bu] 2 or postings count (\f[CR]\-\-count\f[R]) .PP \&..in.. .IP \[bu] 2 one time period (the whole journal period by default) .IP \[bu] 2 or multiple periods (\f[CR]\-D\f[R], \f[CR]\-W\f[R], \f[CR]\-M\f[R], \f[CR]\-Q\f[R], \f[CR]\-Y\f[R], \f[CR]\-p INTERVAL\f[R]) .PP \&..either.. .IP \[bu] 2 per period (the default) .IP \[bu] 2 or accumulated since report start date (\f[CR]\-\-cumulative\f[R]) .IP \[bu] 2 or accumulated since account creation (\f[CR]\-\-historical/\-H\f[R]) .PP \&..possibly converted to.. .IP \[bu] 2 cost (\f[CR]\-\-value=cost[,COMM]\f[R]/\f[CR]\-\-cost\f[R]/\f[CR]\-B\f[R]) .IP \[bu] 2 or market value, as of transaction dates (\f[CR]\-\-value=then[,COMM]\f[R]) .IP \[bu] 2 or at period ends (\f[CR]\-\-value=end[,COMM]\f[R]) .IP \[bu] 2 or now (\f[CR]\-\-value=now\f[R]) .IP \[bu] 2 or at some other date (\f[CR]\-\-value=YYYY\-MM\-DD\f[R]) .PP \&..with.. .IP \[bu] 2 totals (\f[CR]\-T\f[R]), averages (\f[CR]\-A\f[R]), percentages (\f[CR]\-%\f[R]), inverted sign (\f[CR]\-\-invert\f[R]) .IP \[bu] 2 rows and columns swapped (\f[CR]\-\-transpose\f[R]) .IP \[bu] 2 another field used as account name (\f[CR]\-\-pivot\f[R]) .IP \[bu] 2 custom\-formatted line items (single\-period reports only) (\f[CR]\-\-format\f[R]) .IP \[bu] 2 commodities displayed on the same line or multiple lines (\f[CR]\-\-layout\f[R]) .PP This command supports the output destination and output format options, with output formats \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]json\f[R], and (multi\-period reports only:) \f[CR]html\f[R]. In \f[CR]txt\f[R] output in a colour\-supporting terminal, negative amounts are shown in red. .PP The \f[CR]\-\-related\f[R]/\f[CR]\-r\f[R] flag shows the balance of the \f[I]other\f[R] postings in the transactions of the postings which would normally be shown. .SS Simple balance report With no arguments, \f[CR]balance\f[R] shows a list of all accounts and their change of balance \- ie, the sum of posting amounts, both inflows and outflows \- during the entire period of the journal. (\[dq]Simple\[dq] here means just one column of numbers, covering a single period. You can also have multi\-period reports, described later.) .PP For real\-world accounts, these numbers will normally be their end balance at the end of the journal period; more on this below. .PP Accounts are sorted by declaration order if any, and then alphabetically by account name. For instance (using examples/sample.journal): .IP .EX $ hledger \-f examples/sample.journal bal $1 assets:bank:saving $\-2 assets:cash $1 expenses:food $1 expenses:supplies $\-1 income:gifts $\-1 income:salary $1 liabilities:debts \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP Accounts with a zero balance (and no non\-zero subaccounts, in tree mode \- see below) are hidden by default. Use \f[CR]\-E/\-\-empty\f[R] to show them (revealing \f[CR]assets:bank:checking\f[R] here): .IP .EX $ hledger \-f examples/sample.journal bal \-E 0 assets:bank:checking $1 assets:bank:saving $\-2 assets:cash $1 expenses:food $1 expenses:supplies $\-1 income:gifts $\-1 income:salary $1 liabilities:debts \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP The total of the amounts displayed is shown as the last line, unless \f[CR]\-N\f[R]/\f[CR]\-\-no\-total\f[R] is used. .SS Balance report line format For single\-period balance reports displayed in the terminal (only), you can use \f[CR]\-\-format FMT\f[R] to customise the format and content of each line. Eg: .IP .EX $ hledger \-f examples/sample.journal balance \-\-format \[dq]%20(account) %12(total)\[dq] assets $\-1 bank:saving $1 cash $\-2 expenses $2 food $1 supplies $1 income $\-2 gifts $\-1 salary $\-1 liabilities:debts $1 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP The FMT format string specifies the formatting applied to each account/balance pair. It may contain any suitable text, with data fields interpolated like so: .PP \f[CR]%[MIN][.MAX](FIELDNAME)\f[R] .IP \[bu] 2 MIN pads with spaces to at least this width (optional) .IP \[bu] 2 MAX truncates at this width (optional) .IP \[bu] 2 FIELDNAME must be enclosed in parentheses, and can be one of: .RS 2 .IP \[bu] 2 \f[CR]depth_spacer\f[R] \- a number of spaces equal to the account\[aq]s depth, or if MIN is specified, MIN * depth spaces. .IP \[bu] 2 \f[CR]account\f[R] \- the account\[aq]s name .IP \[bu] 2 \f[CR]total\f[R] \- the account\[aq]s balance/posted total, right justified .RE .PP Also, FMT can begin with an optional prefix to control how multi\-commodity amounts are rendered: .IP \[bu] 2 \f[CR]%_\f[R] \- render on multiple lines, bottom\-aligned (the default) .IP \[bu] 2 \f[CR]%\[ha]\f[R] \- render on multiple lines, top\-aligned .IP \[bu] 2 \f[CR]%,\f[R] \- render on one line, comma\-separated .PP There are some quirks. Eg in one\-line mode, \f[CR]%(depth_spacer)\f[R] has no effect, instead \f[CR]%(account)\f[R] has indentation built in. \ Experimentation may be needed to get pleasing results. .PP Some example formats: .IP \[bu] 2 \f[CR]%(total)\f[R] \- the account\[aq]s total .IP \[bu] 2 \f[CR]%\-20.20(account)\f[R] \- the account\[aq]s name, left justified, padded to 20 characters and clipped at 20 characters .IP \[bu] 2 \f[CR]%,%\-50(account) %25(total)\f[R] \- account name padded to 50 characters, total padded to 20 characters, with multiple commodities rendered on one line .IP \[bu] 2 \f[CR]%20(total) %2(depth_spacer)%\-(account)\f[R] \- the default format for the single\-column balance report .SS Filtered balance report You can show fewer accounts, a different time period, totals from cleared transactions only, etc. by using query arguments or options to limit the postings being matched. Eg: .IP .EX $ hledger \-f examples/sample.journal bal \-\-cleared assets date:200806 $\-2 assets:cash \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-2 .EE .SS List or tree mode By default, or with \f[CR]\-l/\-\-flat\f[R], accounts are shown as a flat list with their full names visible, as in the examples above. .PP With \f[CR]\-t/\-\-tree\f[R], the account hierarchy is shown, with subaccounts\[aq] \[dq]leaf\[dq] names indented below their parent: .IP .EX $ hledger \-f examples/sample.journal balance $\-1 assets $1 bank:saving $\-2 cash $2 expenses $1 food $1 supplies $\-2 income $\-1 gifts $\-1 salary $1 liabilities:debts \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP Notes: .IP \[bu] 2 \[dq]Boring\[dq] accounts are combined with their subaccount for more compact output, unless \f[CR]\-\-no\-elide\f[R] is used. Boring accounts have no balance of their own and just one subaccount (eg \f[CR]assets:bank\f[R] and \f[CR]liabilities\f[R] above). .IP \[bu] 2 All balances shown are \[dq]inclusive\[dq], ie including the balances from all subaccounts. Note this means some repetition in the output, which requires explanation when sharing reports with non\-plaintextaccounting\-users. A tree mode report\[aq]s final total is the sum of the top\-level balances shown, not of all the balances shown. .IP \[bu] 2 Each group of sibling accounts (ie, under a common parent) is sorted separately. .SS Depth limiting With a \f[CR]depth:NUM\f[R] query, or \f[CR]\-\-depth NUM\f[R] option, or just \f[CR]\-NUM\f[R] (eg: \f[CR]\-3\f[R]) balance reports will show accounts only to the specified depth, hiding the deeper subaccounts. This can be useful for getting an overview without too much detail. .PP Account balances at the depth limit always include the balances from any deeper subaccounts (even in list mode). Eg, limiting to depth 1: .IP .EX $ hledger \-f examples/sample.journal balance \-1 $\-1 assets $2 expenses $\-2 income $1 liabilities \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .SS Dropping top\-level accounts You can also hide one or more top\-level account name parts, using \f[CR]\-\-drop NUM\f[R]. This can be useful for hiding repetitive top\-level account names: .IP .EX $ hledger \-f examples/sample.journal bal expenses \-\-drop 1 $1 food $1 supplies \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $2 .EE .PP .SS Showing declared accounts With \f[CR]\-\-declared\f[R], accounts which have been declared with an account directive will be included in the balance report, even if they have no transactions. (Since they will have a zero balance, you will also need \f[CR]\-E/\-\-empty\f[R] to see them.) .PP More precisely, \f[I]leaf\f[R] declared accounts (with no subaccounts) will be included, since those are usually the more useful in reports. .PP The idea of this is to be able to see a useful \[dq]complete\[dq] balance report, even when you don\[aq]t have transactions in all of your declared accounts yet. .SS Sorting by amount With \f[CR]\-S/\-\-sort\-amount\f[R], accounts with the largest (most positive) balances are shown first. Eg: \f[CR]hledger bal expenses \-MAS\f[R] shows your biggest averaged monthly expenses first. When more than one commodity is present, they will be sorted by the alphabetically earliest commodity first, and then by subsequent commodities (if an amount is missing a commodity, it is treated as 0). .PP Revenues and liability balances are typically negative, however, so \f[CR]\-S\f[R] shows these in reverse order. To work around this, you can add \f[CR]\-\-invert\f[R] to flip the signs. (Or, use one of the higher\-level reports, which flip the sign automatically. Eg: \f[CR]hledger incomestatement \-MAS\f[R]). .PP .SS Percentages With \f[CR]\-%/\-\-percent\f[R], balance reports show each account\[aq]s value expressed as a percentage of the (column) total. .PP Note it is not useful to calculate percentages if the amounts in a column have mixed signs. In this case, make a separate report for each sign, eg: .IP .EX $ hledger bal \-% amt:\[ga]>0\[ga] $ hledger bal \-% amt:\[ga]<0\[ga] .EE .PP Similarly, if the amounts in a column have mixed commodities, convert them to one commodity with \f[CR]\-B\f[R], \f[CR]\-V\f[R], \f[CR]\-X\f[R] or \f[CR]\-\-value\f[R], or make a separate report for each commodity: .IP .EX $ hledger bal \-% cur:\[rs]\[rs]$ $ hledger bal \-% cur:€ .EE .SS Multi\-period balance report With a report interval (set by the \f[CR]\-D/\-\-daily\f[R], \f[CR]\-W/\-\-weekly\f[R], \f[CR]\-M/\-\-monthly\f[R], \f[CR]\-Q/\-\-quarterly\f[R], \f[CR]\-Y/\-\-yearly\f[R], or \f[CR]\-p/\-\-period\f[R] flag), \f[CR]balance\f[R] shows a tabular report, with columns representing successive time periods (and a title): .IP .EX $ hledger \-f examples/sample.journal bal \-\-quarterly income expenses \-E Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 ===================++================================= expenses:food || 0 $1 0 0 expenses:supplies || 0 $1 0 0 income:gifts || 0 $\-1 0 0 income:salary || $\-1 0 0 0 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || $\-1 $1 0 0 .EE .PP Notes: .IP \[bu] 2 The report\[aq]s start/end dates will be expanded, if necessary, to fully encompass the displayed subperiods (so that the first and last subperiods have the same duration as the others). .IP \[bu] 2 Leading and trailing periods (columns) containing all zeroes are not shown, unless \f[CR]\-E/\-\-empty\f[R] is used. .IP \[bu] 2 Accounts (rows) containing all zeroes are not shown, unless \f[CR]\-E/\-\-empty\f[R] is used. .IP \[bu] 2 Amounts with many commodities are shown in abbreviated form, unless \f[CR]\-\-no\-elide\f[R] is used. \f[I](experimental)\f[R] .IP \[bu] 2 Average and/or total columns can be added with the \f[CR]\-A/\-\-average\f[R] and \f[CR]\-T/\-\-row\-total\f[R] flags. .IP \[bu] 2 The \f[CR]\-\-transpose\f[R] flag can be used to exchange rows and columns. .IP \[bu] 2 The \f[CR]\-\-pivot FIELD\f[R] option causes a different transaction field to be used as \[dq]account name\[dq]. See PIVOTING. .PP Multi\-period reports with many periods can be too wide for easy viewing in the terminal. Here are some ways to handle that: .IP \[bu] 2 Hide the totals row with \f[CR]\-N/\-\-no\-total\f[R] .IP \[bu] 2 Convert to a single currency with \f[CR]\-V\f[R] .IP \[bu] 2 Maximize the terminal window .IP \[bu] 2 Reduce the terminal\[aq]s font size .IP \[bu] 2 View with a pager like less, eg: \f[CR]hledger bal \-D \-\-color=yes | less \-RS\f[R] .IP \[bu] 2 Output as CSV and use a CSV viewer like visidata (\f[CR]hledger bal \-D \-O csv | vd \-f csv\f[R]), Emacs\[aq] csv\-mode (\f[CR]M\-x csv\-mode, C\-c C\-a\f[R]), or a spreadsheet (\f[CR]hledger bal \-D \-o a.csv && open a.csv\f[R]) .IP \[bu] 2 Output as HTML and view with a browser: \f[CR]hledger bal \-D \-o a.html && open a.html\f[R] .SS Balance change, end balance It\[aq]s important to be clear on the meaning of the numbers shown in balance reports. Here is some terminology we use: .PP A \f[B]\f[BI]balance change\f[B]\f[R] is the net amount added to, or removed from, an account during some period. .PP An \f[B]\f[BI]end balance\f[B]\f[R] is the amount accumulated in an account as of some date (and some time, but hledger doesn\[aq]t store that; assume end of day in your timezone). It is the sum of previous balance changes. .PP We call it a \f[B]\f[BI]historical end balance\f[B]\f[R] if it includes all balance changes since the account was created. For a real world account, this means it will match the \[dq]historical record\[dq], eg the balances reported in your bank statements or bank web UI. (If they are correct!) .PP In general, balance changes are what you want to see when reviewing revenues and expenses, and historical end balances are what you want to see when reviewing or reconciling asset, liability and equity accounts. .PP \f[CR]balance\f[R] shows balance changes by default. To see accurate historical end balances: .IP "1." 3 Initialise account starting balances with an \[dq]opening balances\[dq] transaction (a transfer from equity to the account), unless the journal covers the account\[aq]s full lifetime. .IP "2." 3 Include all of of the account\[aq]s prior postings in the report, by not specifying a report start date, or by using the \f[CR]\-H/\-\-historical\f[R] flag. (\f[CR]\-H\f[R] causes report start date to be ignored when summing postings.) .SS Balance report types The balance command is quite flexible; here is the full detail on how to control what it reports. If the following seems complicated, don\[aq]t worry \- this is for advanced reporting, and it does take time and experimentation to get familiar with all the report modes. .PP There are three important option groups: .PP \f[CR]hledger balance [CALCULATIONTYPE] [ACCUMULATIONTYPE] [VALUATIONTYPE] ...\f[R] .SS Calculation type The basic calculation to perform for each table cell. It is one of: .IP \[bu] 2 \f[CR]\-\-sum\f[R] : sum the posting amounts (\f[B]default\f[R]) .IP \[bu] 2 \f[CR]\-\-budget\f[R] : sum the amounts, but also show the budget goal amount (for each account/period) .IP \[bu] 2 \f[CR]\-\-valuechange\f[R] : show the change in period\-end historical balance values (caused by deposits, withdrawals, and/or market price fluctuations) .IP \[bu] 2 \f[CR]\-\-gain\f[R] : show the unrealised capital gain/loss, (the current valued balance minus each amount\[aq]s original cost) .IP \[bu] 2 \f[CR]\-\-count\f[R] : show the count of postings .SS Accumulation type How amounts should accumulate across report periods. Another way to say it: which time period\[aq]s postings should contribute to each cell\[aq]s calculation. It is one of: .IP \[bu] 2 \f[CR]\-\-change\f[R] : calculate with postings from column start to column end, ie \[dq]just this column\[dq]. Typically used to see revenues/expenses. (\f[B]default for balance, incomestatement\f[R]) .IP \[bu] 2 \f[CR]\-\-cumulative\f[R] : calculate with postings from report start to column end, ie \[dq]previous columns plus this column\[dq]. Typically used to show changes accumulated since the report\[aq]s start date. Not often used. .IP \[bu] 2 \f[CR]\-\-historical/\-H\f[R] : calculate with postings from journal start to column end, ie \[dq]all postings from before report start date until this column\[aq]s end\[dq]. Typically used to see historical end balances of assets/liabilities/equity. (\f[B]default for balancesheet, balancesheetequity, cashflow\f[R]) .SS Valuation type Which kind of value or cost conversion should be applied, if any, before displaying the report. It is one of: .IP \[bu] 2 no valuation type : don\[aq]t convert to cost or value (\f[B]default\f[R]) .IP \[bu] 2 \f[CR]\-\-value=cost[,COMM]\f[R] : convert amounts to cost (then optionally to some other commodity) .IP \[bu] 2 \f[CR]\-\-value=then[,COMM]\f[R] : convert amounts to market value on transaction dates .IP \[bu] 2 \f[CR]\-\-value=end[,COMM]\f[R] : convert amounts to market value on period end date(s) .PD 0 .P .PD (\f[B]default with \f[CB]\-\-valuechange\f[B], \f[CB]\-\-gain\f[B]\f[R]) .IP \[bu] 2 \f[CR]\-\-value=now[,COMM]\f[R] : convert amounts to market value on today\[aq]s date .IP \[bu] 2 \f[CR]\-\-value=YYYY\-MM\-DD[,COMM]\f[R] : convert amounts to market value on another date .PP or one of the equivalent simpler flags: .IP \[bu] 2 \f[CR]\-B/\-\-cost\f[R] : like \-\-value=cost (though, note \-\-cost and \-\-value are independent options which can both be used at once) .IP \[bu] 2 \f[CR]\-V/\-\-market\f[R] : like \-\-value=end .IP \[bu] 2 \f[CR]\-X COMM/\-\-exchange COMM\f[R] : like \-\-value=end,COMM .PP See Cost reporting and Value reporting for more about these. .SS Combining balance report types Most combinations of these options should produce reasonable reports, but if you find any that seem wrong or misleading, let us know. The following restrictions are applied: .IP \[bu] 2 \f[CR]\-\-valuechange\f[R] implies \f[CR]\-\-value=end\f[R] .IP \[bu] 2 \f[CR]\-\-valuechange\f[R] makes \f[CR]\-\-change\f[R] the default when used with the \f[CR]balancesheet\f[R]/\f[CR]balancesheetequity\f[R] commands .IP \[bu] 2 \f[CR]\-\-cumulative\f[R] or \f[CR]\-\-historical\f[R] disables \f[CR]\-\-row\-total/\-T\f[R] .PP For reference, here is what the combinations of accumulation and valuation show: .PP .TS tab(@); lw(7.9n) lw(16.4n) lw(16.9n) lw(15.1n) lw(13.7n). T{ Valuation:> Accumulation:v T}@T{ no valuation T}@T{ \f[CR]\-\-value= then\f[R] T}@T{ \f[CR]\-\-value= end\f[R] T}@T{ \f[CR]\-\-value= YYYY\-MM\-DD /now\f[R] T} _ T{ \f[CR]\-\-change\f[R] T}@T{ change in period T}@T{ sum of posting\-date market values in period T}@T{ period\-end value of change in period T}@T{ DATE\-value of change in period T} T{ \f[CR]\-\-cumulative\f[R] T}@T{ change from report start to period end T}@T{ sum of posting\-date market values from report start to period end T}@T{ period\-end value of change from report start to period end T}@T{ DATE\-value of change from report start to period end T} T{ \f[CR]\-\-historical /\-H\f[R] T}@T{ change from journal start to period end (historical end balance) T}@T{ sum of posting\-date market values from journal start to period end T}@T{ period\-end value of change from journal start to period end T}@T{ DATE\-value of change from journal start to period end T} .TE .SS Budget report The \f[CR]\-\-budget\f[R] report type is like a regular balance report, but with two main differences: .IP \[bu] 2 Budget goals and performance percentages are also shown, in brackets .IP \[bu] 2 Accounts which don\[aq]t have budget goals are hidden by default. .PP This is useful for comparing planned and actual income, expenses, time usage, etc. .PP Periodic transaction rules are used to define budget goals. For example, here\[aq]s a periodic rule defining monthly goals for bus travel and food expenses: .IP .EX ;; Budget \[ti] monthly (expenses:bus) $30 (expenses:food) $400 .EE .PP After recording some actual expenses, .IP .EX ;; Two months worth of expenses 2017\-11\-01 income $\-1950 expenses:bus $35 expenses:food:groceries $310 expenses:food:dining $42 expenses:movies $38 assets:bank:checking 2017\-12\-01 income $\-2100 expenses:bus $53 expenses:food:groceries $380 expenses:food:dining $32 expenses:gifts $100 assets:bank:checking .EE .PP we can see a budget report like this: .IP .EX $ hledger bal \-M \-\-budget Budget performance in 2017\-11\-01..2017\-12\-31: || Nov Dec ===============++============================================ || $\-425 $\-565 expenses || $425 [ 99% of $430] $565 [131% of $430] expenses:bus || $35 [117% of $30] $53 [177% of $30] expenses:food || $352 [ 88% of $400] $412 [103% of $400] \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || 0 [ 0% of $430] 0 [ 0% of $430] .EE .PP This is \[dq]goal\-based budgeting\[dq]; you define goals for accounts and periods, often recurring, and hledger shows performance relative to the goals. This contrasts with \[dq]envelope budgeting\[dq], which is more detailed and strict \- useful when cash is tight, but also quite a bit more work. https://plaintextaccounting.org/Budgeting has more on this topic. .SS Using the budget report Historically this report has been confusing and fragile. hledger\[aq]s version should be relatively robust and intuitive, but you may still find surprises. Here are more notes to help with learning and troubleshooting. .IP \[bu] 2 In the above example, \f[CR]expenses:bus\f[R] and \f[CR]expenses:food\f[R] are shown because they have budget goals during the report period. .IP \[bu] 2 Their parent \f[CR]expenses\f[R] is also shown, with budget goals aggregated from the children. .IP \[bu] 2 The subaccounts \f[CR]expenses:food:groceries\f[R] and \f[CR]expenses:food:dining\f[R] are not shown since they have no budget goal of their own, but they contribute to \f[CR]expenses:food\f[R]\[aq]s actual amount. .IP \[bu] 2 Unbudgeted accounts \f[CR]expenses:movies\f[R] and \f[CR]expenses:gifts\f[R] are also not shown, but they contribute to \f[CR]expenses\f[R]\[aq]s actual amount. .IP \[bu] 2 The other unbudgeted accounts \f[CR]income\f[R] and \f[CR]assets:bank:checking\f[R] are grouped as \f[CR]\f[R]. .IP \[bu] 2 \f[CR]\-\-depth\f[R] or \f[CR]depth:\f[R] can be used to limit report depth in the usual way (but will not reveal unbudgeted subaccounts). .IP \[bu] 2 Amounts are always inclusive of subaccounts (even in \f[CR]\-l/\-\-list\f[R] mode). .IP \[bu] 2 Numbers displayed in a \-\-budget report will not always agree with the totals, because of hidden unbudgeted accounts; this is normal. \f[CR]\-E/\-\-empty\f[R] can be used to reveal the hidden accounts. .IP \[bu] 2 In the periodic rules used for setting budget goals, unbalanced postings are convenient. .IP \[bu] 2 You can filter budget reports with the usual queries, eg to focus on particular accounts. It\[aq]s common to restrict them to just expenses. (The \f[CR]\f[R] account is occasionally hard to exclude; this is because of date surprises, discussed below.) .IP \[bu] 2 When you have multiple currencies, you may want to convert them to one (\f[CR]\-X COMM \-\-infer\-market\-prices\f[R]) and/or show just one at a time (\f[CR]cur:COMM\f[R]). If you do need to show multiple currencies at once, \f[CR]\-\-layout bare\f[R] can be helpful. .IP \[bu] 2 You can \[dq]roll over\[dq] amounts (actual and budgeted) to the next period with \f[CR]\-\-cumulative\f[R]. .PP See also: https://hledger.org/budgeting.html. .SS Budget date surprises With small data, or when starting out, some of the generated budget goal transaction dates might fall outside the report periods. Eg with the following journal and report, the first period appears to have no \f[CR]expenses:food\f[R] budget. (Also the \f[CR]\f[R] account should be excluded by the \f[CR]expenses\f[R] query, but isn\[aq]t.): .IP .EX \[ti] monthly in 2020 (expenses:food) $500 2020\-01\-15 expenses:food $400 assets:checking .EE .IP .EX $ hledger bal \-\-budget expenses Budget performance in 2020\-01\-15: || 2020\-01\-15 ===============++==================== || $400 expenses:food || 0 [ 0% of $500] \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || $400 [80% of $500] .EE .PP In this case, the budget goal transactions are generated on first days of of month (this can be seen with \f[CR]hledger print \-\-forecast tag:generated expenses\f[R]). Whereas the report period defaults to just the 15th day of january (this can be seen from the report table\[aq]s column headings). .PP To fix this kind of thing, be more explicit about the report period (and/or the periodic rules\[aq] dates). In this case, adding \f[CR]\-b 2020\f[R] does the trick. .SS Selecting budget goals By default, the budget report uses all available periodic transaction rules to generate goals. This includes rules with a different report interval from your report. Eg if you have daily, weekly and monthly periodic rules, all of these will contribute to the goals in a monthly budget report. .PP You can select a subset of periodic rules by providing an argument to the \f[CR]\-\-budget\f[R] flag. \f[CR]\-\-budget=DESCPAT\f[R] will match all periodic rules whose description contains DESCPAT, a case\-insensitive substring (not a regular expression or query). This means you can give your periodic rules descriptions (remember that two spaces are needed between period expression and description), and then select from multiple budgets defined in your journal. .SS Budgeting vs forecasting \f[CR]\-\-budget\f[R] and \f[CR]\-\-forecast\f[R] both use the periodic transaction rules in the journal to generate temporary transactions for reporting purposes. However they are separate features \- though you can use both at the same time if you want. Here are some differences between them: .IP "1." 3 \f[CR]\-\-budget\f[R] is a command\-specific option; it selects the \f[B]budget report\f[R]. .RS 4 .PP \f[CR]\-\-forecast\f[R] is a general option; \f[B]forecasting works with all reports\f[R]. .RE .IP "2." 3 \f[CR]\-\-budget\f[R] uses \f[B]all periodic rules\f[R]; \f[CR]\-\-budget=DESCPAT\f[R] uses \f[B]just the rules matched\f[R] by DESCPAT. .RS 4 .PP \f[CR]\-\-forecast\f[R] uses \f[B]all periodic rules\f[R]. .RE .IP "3." 3 \f[CR]\-\-budget\f[R]\[aq]s budget goal transactions are invisible, except that they produce \f[B]goal amounts\f[R]. .RS 4 .PP \f[CR]\-\-forecast\f[R]\[aq]s forecast transactions are visible, and \f[B]appear in reports\f[R]. .RE .IP "4." 3 \f[CR]\-\-budget\f[R] generates budget goal transactions \f[B]throughout the report period\f[R], optionally restricted by periods specified in the periodic transaction rules. .RS 4 .PP \f[CR]\-\-forecast\f[R] generates forecast transactions from \f[B]after the last regular transaction\f[R], to the end of the report period; while \f[CR]\-\-forecast=PERIODEXPR\f[R] generates them \f[B]throughout the specified period\f[R]; both optionally restricted by periods specified in the periodic transaction rules. .RE .SS Balance report layout The \f[CR]\-\-layout\f[R] option affects how balance reports show multi\-commodity amounts and commodity symbols, which can improve readability. It can also normalise the data for easy consumption by other programs. It has four possible values: .IP \[bu] 2 \f[CR]\-\-layout=wide[,WIDTH]\f[R]: commodities are shown on a single line, optionally elided to WIDTH .IP \[bu] 2 \f[CR]\-\-layout=tall\f[R]: each commodity is shown on a separate line .IP \[bu] 2 \f[CR]\-\-layout=bare\f[R]: commodity symbols are in their own column, amounts are bare numbers .IP \[bu] 2 \f[CR]\-\-layout=tidy\f[R]: data is normalised to easily\-consumed \[dq]tidy\[dq] form, with one row per data value .PP Here are the \f[CR]\-\-layout\f[R] modes supported by each output format; note only CSV output supports all of them: .PP .TS tab(@); l l l l l l. T{ \- T}@T{ txt T}@T{ csv T}@T{ html T}@T{ json T}@T{ sql T} _ T{ wide T}@T{ Y T}@T{ Y T}@T{ Y T}@T{ T}@T{ T} T{ tall T}@T{ Y T}@T{ Y T}@T{ Y T}@T{ T}@T{ T} T{ bare T}@T{ Y T}@T{ Y T}@T{ Y T}@T{ T}@T{ T} T{ tidy T}@T{ T}@T{ Y T}@T{ T}@T{ T}@T{ T} .TE .PP Examples: .IP \[bu] 2 Wide layout. With many commodities, reports can be very wide: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-T \-Y \-\-layout=wide Balance changes in 2012\-01\-01..2014\-12\-31: || 2012 2013 2014 Total ==================++==================================================================================================================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, \-98.12 USD, 10.00 VEA, 18.00 VHT \-11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, \-98.12 USD, 10.00 VEA, 18.00 VHT \-11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT .EE .RE .IP \[bu] 2 Limited wide layout. A width limit reduces the width, but some commodities will be hidden: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-T \-Y \-\-layout=wide,32 Balance changes in 2012\-01\-01..2014\-12\-31: || 2012 2013 2014 Total ==================++=========================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. \-11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. \-11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. .EE .RE .IP \[bu] 2 Tall layout. Each commodity gets a new line (may be different in each column), and account names are repeated: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-T \-Y \-\-layout=tall Balance changes in 2012\-01\-01..2014\-12\-31: || 2012 2013 2014 Total ==================++================================================== Assets:US:ETrade || 10.00 ITOT 70.00 GLD \-11.00 ITOT 70.00 GLD Assets:US:ETrade || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT Assets:US:ETrade || 12.00 VEA \-98.12 USD 14.00 VEA 5120.50 USD Assets:US:ETrade || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA Assets:US:ETrade || 18.00 VHT 294.00 VHT \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || 10.00 ITOT 70.00 GLD \-11.00 ITOT 70.00 GLD || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT || 12.00 VEA \-98.12 USD 14.00 VEA 5120.50 USD || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA || 18.00 VHT 294.00 VHT .EE .RE .IP \[bu] 2 Bare layout. Commodity symbols are kept in one column, each commodity gets its own report row, account names are repeated: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-T \-Y \-\-layout=bare Balance changes in 2012\-01\-01..2014\-12\-31: || Commodity 2012 2013 2014 Total ==================++============================================= Assets:US:ETrade || GLD 0 70.00 0 70.00 Assets:US:ETrade || ITOT 10.00 18.00 \-11.00 17.00 Assets:US:ETrade || USD 337.18 \-98.12 4881.44 5120.50 Assets:US:ETrade || VEA 12.00 10.00 14.00 36.00 Assets:US:ETrade || VHT 106.00 18.00 170.00 294.00 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || GLD 0 70.00 0 70.00 || ITOT 10.00 18.00 \-11.00 17.00 || USD 337.18 \-98.12 4881.44 5120.50 || VEA 12.00 10.00 14.00 36.00 || VHT 106.00 18.00 170.00 294.00 .EE .RE .IP \[bu] 2 Bare layout also affects CSV output, which is useful for producing data that is easier to consume, eg for making charts: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-O csv \-\-layout=bare \[dq]account\[dq],\[dq]commodity\[dq],\[dq]balance\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]GLD\[dq],\[dq]70.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]ITOT\[dq],\[dq]17.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]USD\[dq],\[dq]5120.50\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]VEA\[dq],\[dq]36.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]VHT\[dq],\[dq]294.00\[dq] \[dq]total\[dq],\[dq]GLD\[dq],\[dq]70.00\[dq] \[dq]total\[dq],\[dq]ITOT\[dq],\[dq]17.00\[dq] \[dq]total\[dq],\[dq]USD\[dq],\[dq]5120.50\[dq] \[dq]total\[dq],\[dq]VEA\[dq],\[dq]36.00\[dq] \[dq]total\[dq],\[dq]VHT\[dq],\[dq]294.00\[dq] .EE .RE .IP \[bu] 2 Note: bare layout will sometimes display an extra row for the no\-symbol commodity, because of zero amounts (hledger treats zeroes as commodity\-less, usually). This can break \f[CR]hledger\-bar\f[R] confusingly (workaround: add a \f[CR]cur:\f[R] query to exclude the no\-symbol row). .IP \[bu] 2 Tidy layout produces normalised \[dq]tidy data\[dq], where every variable has its own column and each row represents a single data point. See https://cran.r\-project.org/web/packages/tidyr/vignettes/tidy\-data.html for more. This is the easiest kind of data for other software to consume. Here\[aq]s how it looks: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-Y \-O csv \-\-layout=tidy \[dq]account\[dq],\[dq]period\[dq],\[dq]start_date\[dq],\[dq]end_date\[dq],\[dq]commodity\[dq],\[dq]value\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2012\[dq],\[dq]2012\-01\-01\[dq],\[dq]2012\-12\-31\[dq],\[dq]GLD\[dq],\[dq]0\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2012\[dq],\[dq]2012\-01\-01\[dq],\[dq]2012\-12\-31\[dq],\[dq]ITOT\[dq],\[dq]10.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2012\[dq],\[dq]2012\-01\-01\[dq],\[dq]2012\-12\-31\[dq],\[dq]USD\[dq],\[dq]337.18\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2012\[dq],\[dq]2012\-01\-01\[dq],\[dq]2012\-12\-31\[dq],\[dq]VEA\[dq],\[dq]12.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2012\[dq],\[dq]2012\-01\-01\[dq],\[dq]2012\-12\-31\[dq],\[dq]VHT\[dq],\[dq]106.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2013\[dq],\[dq]2013\-01\-01\[dq],\[dq]2013\-12\-31\[dq],\[dq]GLD\[dq],\[dq]70.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2013\[dq],\[dq]2013\-01\-01\[dq],\[dq]2013\-12\-31\[dq],\[dq]ITOT\[dq],\[dq]18.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2013\[dq],\[dq]2013\-01\-01\[dq],\[dq]2013\-12\-31\[dq],\[dq]USD\[dq],\[dq]\-98.12\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2013\[dq],\[dq]2013\-01\-01\[dq],\[dq]2013\-12\-31\[dq],\[dq]VEA\[dq],\[dq]10.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2013\[dq],\[dq]2013\-01\-01\[dq],\[dq]2013\-12\-31\[dq],\[dq]VHT\[dq],\[dq]18.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2014\[dq],\[dq]2014\-01\-01\[dq],\[dq]2014\-12\-31\[dq],\[dq]GLD\[dq],\[dq]0\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2014\[dq],\[dq]2014\-01\-01\[dq],\[dq]2014\-12\-31\[dq],\[dq]ITOT\[dq],\[dq]\-11.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2014\[dq],\[dq]2014\-01\-01\[dq],\[dq]2014\-12\-31\[dq],\[dq]USD\[dq],\[dq]4881.44\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2014\[dq],\[dq]2014\-01\-01\[dq],\[dq]2014\-12\-31\[dq],\[dq]VEA\[dq],\[dq]14.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2014\[dq],\[dq]2014\-01\-01\[dq],\[dq]2014\-12\-31\[dq],\[dq]VHT\[dq],\[dq]170.00\[dq] .EE .RE .SS Useful balance reports Some frequently used \f[CR]balance\f[R] options/reports are: .IP \[bu] 2 \f[CR]bal \-M revenues expenses\f[R] .PD 0 .P .PD Show revenues/expenses in each month. Also available as the \f[CR]incomestatement\f[R] command. .IP \[bu] 2 \f[CR]bal \-M \-H assets liabilities\f[R] .PD 0 .P .PD Show historical asset/liability balances at each month end. Also available as the \f[CR]balancesheet\f[R] command. .IP \[bu] 2 \f[CR]bal \-M \-H assets liabilities equity\f[R] .PD 0 .P .PD Show historical asset/liability/equity balances at each month end. Also available as the \f[CR]balancesheetequity\f[R] command. .IP \[bu] 2 \f[CR]bal \-M assets not:receivable\f[R] .PD 0 .P .PD Show changes to liquid assets in each month. Also available as the \f[CR]cashflow\f[R] command. .PP Also: .IP \[bu] 2 \f[CR]bal \-M expenses \-2 \-SA\f[R] .PD 0 .P .PD Show monthly expenses summarised to depth 2 and sorted by average amount. .IP \[bu] 2 \f[CR]bal \-M \-\-budget expenses\f[R] .PD 0 .P .PD Show monthly expenses and budget goals. .IP \[bu] 2 \f[CR]bal \-M \-\-valuechange investments\f[R] .PD 0 .P .PD Show monthly change in market value of investment assets. .IP \[bu] 2 \f[CR]bal investments \-\-valuechange \-D date:lastweek amt:\[aq]>1000\[aq] \-STA [\-\-invert]\f[R] .PD 0 .P .PD Show top gainers [or losers] last week .SS balancesheet (bs) .PP This command displays a balance sheet, showing historical ending balances of asset and liability accounts. (To see equity as well, use the balancesheetequity command.) Amounts are shown with normal positive sign, as in conventional financial statements. .PP This report shows accounts declared with the \f[CR]Asset\f[R], \f[CR]Cash\f[R] or \f[CR]Liability\f[R] type (see account types). Or if no such accounts are declared, it shows top\-level accounts named \f[CR]asset\f[R] or \f[CR]liability\f[R] (case insensitive, plurals allowed) and their subaccounts. .PP Example: .IP .EX $ hledger balancesheet Balance Sheet Assets: $\-1 assets $1 bank:saving $\-2 cash \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-1 Liabilities: $1 liabilities:debts \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $1 Total: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP This command is a higher\-level variant of the \f[CR]balance\f[R] command, and supports many of that command\[aq]s features, such as multi\-period reports. It is similar to \f[CR]hledger balance \-H assets liabilities\f[R], but with smarter account detection, and liabilities displayed with their sign flipped. .PP This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]html\f[R], and (experimental) \f[CR]json\f[R]. .SS balancesheetequity (bse) .PP This command displays a balance sheet, showing historical ending balances of asset, liability and equity accounts. Amounts are shown with normal positive sign, as in conventional financial statements. .PP This report shows accounts declared with the \f[CR]Asset\f[R], \f[CR]Cash\f[R], \f[CR]Liability\f[R] or \f[CR]Equity\f[R] type (see account types). Or if no such accounts are declared, it shows top\-level accounts named \f[CR]asset\f[R], \f[CR]liability\f[R] or \f[CR]equity\f[R] (case insensitive, plurals allowed) and their subaccounts. .PP Example: .IP .EX $ hledger balancesheetequity Balance Sheet With Equity Assets: $\-2 assets $1 bank:saving $\-3 cash \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-2 Liabilities: $1 liabilities:debts \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $1 Equity: $1 equity:owner \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $1 Total: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP This command is a higher\-level variant of the \f[CR]balance\f[R] command, and supports many of that command\[aq]s features, such as multi\-period reports. It is similar to \f[CR]hledger balance \-H assets liabilities equity\f[R], but with smarter account detection, and liabilities/equity displayed with their sign flipped. .PP This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]html\f[R], and (experimental) \f[CR]json\f[R]. .SS cashflow (cf) .PP This command displays a cashflow statement, showing the inflows and outflows affecting \[dq]cash\[dq] (ie, liquid, easily convertible) assets. Amounts are shown with normal positive sign, as in conventional financial statements. .PP This report shows accounts declared with the \f[CR]Cash\f[R] type (see account types). Or if no such accounts are declared, it shows accounts .IP \[bu] 2 under a top\-level account named \f[CR]asset\f[R] (case insensitive, plural allowed) .IP \[bu] 2 whose name contains some variation of \f[CR]cash\f[R], \f[CR]bank\f[R], \f[CR]checking\f[R] or \f[CR]saving\f[R]. .PP More precisely: all accounts matching this case insensitive regular expression: .PP \f[CR]\[ha]assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|currentcash)(:|$)\f[R] .PP and their subaccounts. .PP An example cashflow report: .IP .EX $ hledger cashflow Cashflow Statement Cash flows: $\-1 assets $1 bank:saving $\-2 cash \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-1 Total: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-1 .EE .PP This command is a higher\-level variant of the \f[CR]balance\f[R] command, and supports many of that command\[aq]s features, such as multi\-period reports. It is similar to \f[CR]hledger balance assets not:fixed not:investment not:receivable\f[R], but with smarter account detection. .PP This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]html\f[R], and (experimental) \f[CR]json\f[R]. .SS check Check for various kinds of errors in your data. .PP hledger provides a number of built\-in error checks to help prevent problems in your data. Some of these are run automatically; or, you can use this \f[CR]check\f[R] command to run them on demand, with no output and a zero exit code if all is well. Specify their names (or a prefix) as argument(s). .PP Some examples: .IP .EX hledger check # basic checks hledger check \-s # basic + strict checks hledger check ordereddates payees # basic + two other checks .EE .PP If you are an Emacs user, you can also configure flycheck\-hledger to run these checks, providing instant feedback as you edit the journal. .PP Here are the checks currently available: .SS Default checks These checks are run automatically by (almost) all hledger commands: .IP \[bu] 2 \f[B]parseable\f[R] \- data files are in a supported format, with no syntax errors and no invalid include directives. .IP \[bu] 2 \f[B]autobalanced\f[R] \- all transactions are balanced, after converting to cost. Missing amounts and missing costs are inferred automatically where possible. .IP \[bu] 2 \f[B]assertions\f[R] \- all balance assertions in the journal are passing. (This check can be disabled with \f[CR]\-I\f[R]/\f[CR]\-\-ignore\-assertions\f[R].) .SS Strict checks These additional checks are run when the \f[CR]\-s\f[R]/\f[CR]\-\-strict\f[R] (strict mode) flag is used. Or, they can be run by giving their names as arguments to \f[CR]check\f[R]: .IP \[bu] 2 \f[B]balanced\f[R] \- all transactions are balanced after converting to cost, without inferring missing costs. If conversion costs are required, they must be explicit. .IP \[bu] 2 \f[B]accounts\f[R] \- all account names used by transactions have been declared .IP \[bu] 2 \f[B]commodities\f[R] \- all commodity symbols used have been declared .SS Other checks These checks can be run only by giving their names as arguments to \f[CR]check\f[R]. They are more specialised and not desirable for everyone: .IP \[bu] 2 \f[B]ordereddates\f[R] \- transactions are ordered by date within each file .IP \[bu] 2 \f[B]payees\f[R] \- all payees used by transactions have been declared .IP \[bu] 2 \f[B]recentassertions\f[R] \- all accounts with balance assertions have a balance assertion within 7 days of their latest posting .IP \[bu] 2 \f[B]tags\f[R] \- all tags used by transactions have been declared .IP \[bu] 2 \f[B]uniqueleafnames\f[R] \- all account leaf names are unique .SS Custom checks A few more checks are are available as separate add\-on commands, in https://github.com/simonmichael/hledger/tree/master/bin: .IP \[bu] 2 \f[B]hledger\-check\-tagfiles\f[R] \- all tag values containing / (a forward slash) exist as file paths .IP \[bu] 2 \f[B]hledger\-check\-fancyassertions\f[R] \- more complex balance assertions are passing .PP You could make similar scripts to perform your own custom checks. See: Cookbook \-> Scripting. .SS More about specific checks \f[CR]hledger check recentassertions\f[R] will complain if any balance\-asserted account has postings more than 7 days after its latest balance assertion. This aims to prevent the situation where you are regularly updating your journal, but forgetting to check your balances against the real world, then one day must dig back through months of data to find an error. It assumes that adding a balance assertion requires/reminds you to check the real\-world balance. (That may not be true if you auto\-generate balance assertions from bank data; in that case, I recommend to import transactions uncleared, and when you manually review and clear them, also check the latest assertion against the real\-world balance.) .SS close (equity) .PP Generate transactions which transfer account balances to and/or from another account (typically equity). This can be useful for migrating balances to a new journal file, or for merging earnings into equity at end of accounting period. .PP By default, it prints a transaction that zeroes out ALE accounts (asset, liability, equity accounts; this requires account types to be configured); or if ACCTQUERY is provided, the accounts matched by that. .PP \f[I](experimental)\f[R] .PP This command has four main modes, corresponding to the most common use cases: .IP "1." 3 With \f[CR]\-\-close\f[R] (default), it prints a \[dq]closing balances\[dq] transaction that zeroes out ALE (asset, liability, equity) accounts by default (this requires account types to be inferred or declared); or, the accounts matched by the provided ACCTQUERY arguments. .IP "2." 3 With \f[CR]\-\-open\f[R], it prints an opposite \[dq]opening balances\[dq] transaction that restores those balances from zero. This is similar to Ledger\[aq]s equity command. .IP "3." 3 With \f[CR]\-\-migrate\f[R], it prints both the closing and opening transactions. This is the preferred way to migrate balances to a new file: run \f[CR]hledger close \-\-migrate\f[R], add the closing transaction at the end of the old file, and add the opening transaction at the start of the new file. The matching closing/opening transactions cancel each other out, preserving correct balances during multi\-file reporting. .IP "4." 3 With \f[CR]\-\-retain\f[R], it prints a \[dq]retain earnings\[dq] transaction that transfers RX (revenue and expense) balances to \f[CR]equity:retained earnings\f[R]. Businesses traditionally do this at the end of each accounting period; it is less necessary with computer\-based accounting, but it could still be useful if you want to see the accounting equation (A=L+E) satisfied. .PP In all modes, the defaults can be overridden: .IP \[bu] 2 the transaction descriptions can be changed with \f[CR]\-\-close\-desc=DESC\f[R] and \f[CR]\-\-open\-desc=DESC\f[R] .IP \[bu] 2 the account to transfer to/from can be changed with \f[CR]\-\-close\-acct=ACCT\f[R] and \f[CR]\-\-open\-acct=ACCT\f[R] .IP \[bu] 2 the accounts to be closed/opened can be changed with \f[CR]ACCTQUERY\f[R] (account query arguments). .IP \[bu] 2 the closing/opening dates can be changed with \f[CR]\-e DATE\f[R] (a report end date) .PP By default just one destination/source posting will be used, with its amount left implicit. With \f[CR]\-\-x/\-\-explicit\f[R], the amount will be shown explicitly, and if it involves multiple commodities, a separate posting will be generated for each of them (similar to \f[CR]print \-x\f[R]). .PP With \f[CR]\-\-show\-costs\f[R], any amount costs are shown, with separate postings for each cost. This is currently the best way to view investment lots. If you have many currency conversion or investment transactions, it can generate very large journal entries. .PP With \f[CR]\-\-interleaved\f[R], each individual transfer is shown with source and destination postings next to each other. This could be useful for troubleshooting. .PP The default closing date is yesterday, or the journal\[aq]s end date, whichever is later. You can change this by specifying a report end date with \f[CR]\-e\f[R]. The last day of the report period will be the closing date, eg \f[CR]\-e 2024\f[R] means \[dq]close on 2023\-12\-31\[dq]. The opening date is always the day after the closing date. .SS close and balance assertions Balance assertions will be generated, verifying that the accounts have been reset to zero (and then restored to their previous balances, if there is an opening transaction). .PP These provide useful error checking, but you can ignore them temporarily with \f[CR]\-I\f[R], or remove them if you prefer. .PP You probably should avoid filtering transactions by status or realness (\f[CR]\-C\f[R], \f[CR]\-R\f[R], \f[CR]status:\f[R]), or generating postings (\f[CR]\-\-auto\f[R]), with this command, since the balance assertions would depend on these. .PP Note custom posting dates spanning the file boundary will disrupt the balance assertions: .IP .EX 2023\-12\-30 a purchase made in december, cleared in january expenses:food 5 assets:bank:checking \-5 ; date: 2023\-01\-02 .EE .PP To solve that you can transfer the money to and from a temporary account, in effect splitting the multi\-day transaction into two single\-day transactions: .IP .EX ; in 2022.journal: 2022\-12\-30 a purchase made in december, cleared in january expenses:food 5 equity:pending \-5 ; in 2023.journal: 2023\-01\-02 last year\[aq]s transaction cleared equity:pending 5 = 0 assets:bank:checking \-5 .EE .SS Example: retain earnings Record 2022\[aq]s revenues/expenses as retained earnings on 2022\-12\-31, appending the generated transaction to the journal: .IP .EX $ hledger close \-\-retain \-f 2022.journal \-p 2022 >> 2022.journal .EE .PP Note 2022\[aq]s income statement will now show only zeroes, because revenues and expenses have been moved entirely to equity. To see them again, you could exclude the retain transaction: .IP .EX $ hledger \-f 2022.journal is not:desc:\[aq]retain earnings\[aq] .EE .SS Example: migrate balances to a new file Close assets/liabilities/equity on 2022\-12\-31 and re\-open them on 2023\-01\-01: .IP .EX $ hledger close \-\-migrate \-f 2022.journal \-p 2022 # copy/paste the closing transaction to the end of 2022.journal # copy/paste the opening transaction to the start of 2023.journal .EE .PP Now 2022\[aq]s balance sheet will show only zeroes, indicating a balanced accounting equation. (Unless you are using \[at]/\[at]\[at] notation \- in that case, try adding \-\-infer\-equity.) To see the end\-of\-year balances again, you could exclude the closing transaction: .IP .EX $ hledger \-f 2022.journal bs not:desc:\[aq]closing balances\[aq] .EE .SS Example: excluding closing/opening transactions When combining many files for multi\-year reports, the closing/opening transactions cause some noise in transaction\-oriented reports like \f[CR]print\f[R] and \f[CR]register\f[R]. You can exclude them as shown above, but \f[CR]not:desc:...\f[R] is not ideal as it depends on consistent descriptions; also you will want to avoid excluding the very first opening transaction, which could be awkward. Here is one alternative, using tags: .PP Add \f[CR]clopen:\f[R] tags to all opening/closing balances transactions except the first, like this: .IP .EX ; 2021.journal 2021\-06\-01 first opening balances \&... 2021\-12\-31 closing balances ; clopen:2022 \&... .EE .IP .EX ; 2022.journal 2022\-01\-01 opening balances ; clopen:2022 \&... 2022\-12\-31 closing balances ; clopen:2023 \&... .EE .IP .EX ; 2023.journal 2023\-01\-01 opening balances ; clopen:2023 \&... .EE .PP Now, assuming a combined journal like: .IP .EX ; all.journal include 2021.journal include 2022.journal include 2023.journal .EE .PP The \f[CR]clopen:\f[R] tag can exclude all but the first opening transaction. To show a clean multi\-year checking register: .IP .EX $ hledger \-f all.journal areg checking not:tag:clopen .EE .PP And the year values allow more precision. To show 2022\[aq]s year\-end balance sheet: .IP .EX $ hledger \-f all.journal bs \-e2023 not:tag:clopen=2023 .EE .SS codes List the codes seen in transactions, in the order parsed. .PP This command prints the value of each transaction\[aq]s code field, in the order transactions were parsed. The transaction code is an optional value written in parentheses between the date and description, often used to store a cheque number, order number or similar. .PP Transactions aren\[aq]t required to have a code, and missing or empty codes will not be shown by default. With the \f[CR]\-E\f[R]/\f[CR]\-\-empty\f[R] flag, they will be printed as blank lines. .PP You can add a query to select a subset of transactions. .PP Examples: .IP .EX 2022/1/1 (123) Supermarket Food $5.00 Checking 2022/1/2 (124) Post Office Postage $8.32 Checking 2022/1/3 Supermarket Food $11.23 Checking 2022/1/4 (126) Post Office Postage $3.21 Checking .EE .IP .EX $ hledger codes 123 124 126 .EE .IP .EX $ hledger codes \-E 123 124 126 .EE .SS commodities List all commodity/currency symbols used or declared in the journal. .SS demo Play demos of hledger usage in the terminal, if asciinema is installed. .PP Run this command with no argument to list the demos. To play a demo, write its number or a prefix or substring of its title. Tips: .PP Make your terminal window large enough to see the demo clearly. .PP Use the \-s/\-\-speed SPEED option to set your preferred playback speed, eg \f[CR]\-s4\f[R] to play at 4x original speed or \f[CR]\-s.5\f[R] to play at half speed. The default speed is 2x. .PP Other asciinema options can be added following a double dash, eg \f[CR]\-\- \-i.1\f[R] to limit pauses or \f[CR]\-\- \-h\f[R] to list asciinema\[aq]s other options. .PP During playback, several keys are available: SPACE to pause/unpause, . to step forward (while paused), CTRL\-c quit. .PP Examples: .IP .EX $ hledger demo # list available demos $ hledger demo 1 # play the first demo at default speed (2x) $ hledger demo install \-s4 # play the \[dq]install\[dq] demo at 4x speed .EE .SS descriptions List the unique descriptions that appear in transactions. .PP This command lists the unique descriptions that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. .PP Example: .IP .EX $ hledger descriptions Store Name Gas Station | Petrol Person A .EE .SS diff Compares a particular account\[aq]s transactions in two input files. It shows any transactions to this account which are in one file but not in the other. .PP More precisely, for each posting affecting this account in either file, it looks for a corresponding posting in the other file which posts the same amount to the same account (ignoring date, description, etc.) Since postings not transactions are compared, this also works when multiple bank transactions have been combined into a single journal entry. .PP This is useful eg if you have downloaded an account\[aq]s transactions from your bank (eg as CSV data). When hledger and your bank disagree about the account balance, you can compare the bank data with your journal to find out the cause. .PP Examples: .IP .EX $ hledger diff \-f $LEDGER_FILE \-f bank.csv assets:bank:giro These transactions are in the first file only: 2014/01/01 Opening Balances assets:bank:giro EUR ... ... equity:opening balances EUR \-... These transactions are in the second file only: .EE .SS files List all files included in the journal. With a REGEX argument, only file names matching the regular expression (case sensitive) are shown. .SS help Show the hledger user manual in the terminal, with \f[CR]info\f[R], \f[CR]man\f[R], or a pager. With a TOPIC argument, open it at that topic if possible. TOPIC can be any heading in the manual, or a heading prefix, case insensitive. Eg: \f[CR]commands\f[R], \f[CR]print\f[R], \f[CR]forecast\f[R], \f[CR]journal\f[R], \f[CR]amount\f[R], \f[CR]\[dq]auto postings\[dq]\f[R]. .PP This command shows the hledger manual built in to your hledger version. It can be useful when offline, or when you prefer the terminal to a web browser, or when the appropriate hledger manual or viewing tools are not installed on your system. .PP By default it chooses the best viewer found in $PATH, trying (in this order): \f[CR]info\f[R], \f[CR]man\f[R], \f[CR]$PAGER\f[R], \f[CR]less\f[R], \f[CR]more\f[R]. You can force the use of info, man, or a pager with the \f[CR]\-i\f[R], \f[CR]\-m\f[R], or \f[CR]\-p\f[R] flags, If no viewer can be found, or the command is run non\-interactively, it just prints the manual to stdout. .PP If using \f[CR]info\f[R], note that version 6 or greater is needed for TOPIC lookup. If you are on mac you will likely have info 4.8, and should consider installing a newer version, eg with \f[CR]brew install texinfo\f[R] (#1770). .PP Examples .IP .EX $ hledger help \-\-help # show how the help command works $ hledger help # show the hledger manual with info, man or $PAGER $ hledger help journal # show the journal topic in the hledger manual $ hledger help \-m journal # show it with man, even if info is installed .EE .SS import Read new transactions added to each FILE provided as arguments since last run, and add them to the journal. Or with \-\-dry\-run, just print the transactions that would be added. Or with \-\-catchup, just mark all of the FILEs\[aq] current transactions as imported, without importing them. .PP This command may append new transactions to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also \f[CR]add\f[R]). .PP Unlike other hledger commands, with \f[CR]import\f[R] the journal file is an output file, and will be modified, though only by appending (existing data will not be changed). The input files are specified as arguments, so to import one or more CSV files to your main journal, you will run \f[CR]hledger import bank.csv\f[R] or perhaps \f[CR]hledger import *.csv\f[R]. .PP Note you can import from any file format, though CSV files are the most common import source, and these docs focus on that case. .SS Deduplication \f[CR]import\f[R] does \f[I]time\-based deduplication\f[R], to detect only the new transactions since the last successful import. (This does not mean \[dq]ignore transactions that look the same\[dq], but rather \[dq]ignore transactions that have been seen before\[dq].) This is intended for when you are periodically importing downloaded data, which may overlap with previous downloads. Eg if every week (or every day) you download a bank\[aq]s last three months of CSV data, you can safely run \f[CR]hledger import thebank.csv\f[R] each time and only new transactions will be imported. .PP Since the items being read (CSV records, eg) often do not come with unique identifiers, hledger detects new transactions by date, assuming that: .IP "1." 3 new items always have the newest dates .IP "2." 3 item dates do not change across reads .IP "3." 3 and items with the same date remain in the same relative order across reads. .PP These are often true of CSV files representing transactions, or true enough so that it works pretty well in practice. 1 is important, but violations of 2 and 3 amongst the old transactions won\[aq]t matter (and if you import often, the new transactions will be few, so less likely to be the ones affected). .PP hledger remembers the latest date processed in each input file by saving a hidden \[dq].latest.FILE\[dq] file in FILE\[aq]s directory (after a succesful import). .PP Eg when reading \f[CR]finance/bank.csv\f[R], it will look for and update the \f[CR]finance/.latest.bank.csv\f[R] state file. The format is simple: one or more lines containing the same ISO\-format date (YYYY\-MM\-DD), meaning \[dq]I have processed transactions up to this date, and this many of them on that date.\[dq] Normally you won\[aq]t see or manipulate these state files yourself. But if needed, you can delete them to reset the state (making all transactions \[dq]new\[dq]), or you can construct them to \[dq]catch up\[dq] to a certain date. .PP Note deduplication (and updating of state files) can also be done by \f[CR]print \-\-new\f[R], but this is less often used. .PP Related: CSV > Working with CSV > Deduplicating, importing. .SS Import testing With \f[CR]\-\-dry\-run\f[R], the transactions that will be imported are printed to the terminal, without updating your journal or state files. The output is valid journal format, like the print command, so you can re\-parse it. Eg, to see any importable transactions which CSV rules have not categorised: .IP .EX $ hledger import \-\-dry bank.csv | hledger \-f\- \-I print unknown .EE .PP or (live updating): .IP .EX $ ls bank.csv* | entr bash \-c \[aq]echo ====; hledger import \-\-dry bank.csv | hledger \-f\- \-I print unknown\[aq] .EE .PP Note: when importing from multiple files at once, it\[aq]s currently possible for some .latest files to be updated successfully, while the actual import fails because of a problem in one of the files, leaving them out of sync (and causing some transactions to be missed). To prevent this, do a \-\-dry\-run first and fix any problems before the real import. .SS Importing balance assignments Entries added by import will have their posting amounts made explicit (like \f[CR]hledger print \-x\f[R]). This means that any balance assignments in imported files must be evaluated; but, imported files don\[aq]t get to see the main file\[aq]s account balances. As a result, importing entries with balance assignments (eg from an institution that provides only balances and not posting amounts) will probably generate incorrect posting amounts. To avoid this problem, use print instead of import: .IP .EX $ hledger print IMPORTFILE [\-\-new] >> $LEDGER_FILE .EE .PP (If you think import should leave amounts implicit like print does, please test it and send a pull request.) .SS Commodity display styles Imported amounts will be formatted according to the canonical commodity styles (declared or inferred) in the main journal file. .SS incomestatement (is) .PP This command displays an income statement, showing revenues and expenses during one or more periods. Amounts are shown with normal positive sign, as in conventional financial statements. .PP This report shows accounts declared with the \f[CR]Revenue\f[R] or \f[CR]Expense\f[R] type (see account types). Or if no such accounts are declared, it shows top\-level accounts named \f[CR]revenue\f[R] or \f[CR]income\f[R] or \f[CR]expense\f[R] (case insensitive, plurals allowed) and their subaccounts. .PP Example: .IP .EX $ hledger incomestatement Income Statement Revenues: $\-2 income $\-1 gifts $\-1 salary \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-2 Expenses: $2 expenses $1 food $1 supplies \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $2 Total: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP This command is a higher\-level variant of the \f[CR]balance\f[R] command, and supports many of that command\[aq]s features, such as multi\-period reports. It is similar to \f[CR]hledger balance \[aq](revenues|income)\[aq] expenses\f[R], but with smarter account detection, and revenues/income displayed with their sign flipped. .PP This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]html\f[R], and (experimental) \f[CR]json\f[R]. .SS notes List the unique notes that appear in transactions. .PP This command lists the unique notes that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. The note is the part of the transaction description after a | character (or if there is no |, the whole description). .PP Example: .IP .EX $ hledger notes Petrol Snacks .EE .SS payees List the unique payee/payer names that appear in transactions. .PP This command lists unique payee/payer names which have been declared with payee directives (\-\-declared), used in transaction descriptions (\-\-used), or both (the default). .PP The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). .PP You can add query arguments to select a subset of transactions. This implies \-\-used. .PP Example: .IP .EX $ hledger payees Store Name Gas Station Person A .EE .SS prices Print the market prices declared with P directives. With \-\-infer\-market\-prices, also show any additional prices inferred from costs. With \-\-show\-reverse, also show additional prices inferred by reversing known prices. .PP Price amounts are always displayed with their full precision, except for reverse prices which are limited to 8 decimal digits. .PP Prices can be filtered by a date:, cur: or amt: query. .PP Generally if you run this command with \-\-infer\-market\-prices \-\-show\-reverse, it will show the same prices used internally to calculate value reports. But if in doubt, you can inspect those directly by running the value report with \-\-debug=2. .SS print Show transaction journal entries, sorted by date. .PP The print command displays full journal entries (transactions) from the journal file, sorted by date (or with \f[CR]\-\-date2\f[R], by secondary date). .PP Directives and inter\-transaction comments are not shown, currently. This means the print command is somewhat lossy, and if you are using it to reformat/regenerate your journal you should take care to also copy over the directives and inter\-transaction comments. .PP Eg: .IP .EX $ hledger print \-f examples/sample.journal date:200806 2008/06/01 gift assets:bank:checking $1 income:gifts $\-1 2008/06/02 save assets:bank:saving $1 assets:bank:checking $\-1 2008/06/03 * eat & shop expenses:food $1 expenses:supplies $1 assets:cash $\-2 .EE .SS print explicitness Normally, whether posting amounts are implicit or explicit is preserved. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, if a conversion cost is implied but not written, it will not appear in the output. .PP You can use the \f[CR]\-x\f[R]/\f[CR]\-\-explicit\f[R] flag to force explicit display of all amounts and costs. This can be useful for troubleshooting or for making your journal more readable and robust against data entry errors. \f[CR]\-x\f[R] is also implied by using any of \f[CR]\-B\f[R],\f[CR]\-V\f[R],\f[CR]\-X\f[R],\f[CR]\-\-value\f[R]. .PP The \f[CR]\-x\f[R]/\f[CR]\-\-explicit\f[R] flag will cause any postings with a multi\-commodity amount (which can arise when a multi\-commodity transaction has an implicit amount) to be split into multiple single\-commodity postings, keeping the output parseable. .SS print amount style Amounts are shown right\-aligned within each transaction (but not aligned across all transactions; you can do that with ledger\-mode in Emacs). .PP Amounts will be (mostly) normalised to their commodity display style: their symbol placement, decimal mark, and digit group marks will be made consistent. By default, decimal digits are shown as they are written in the journal. .PP With the \f[CR]\-\-round\f[R] option, \f[CR]print\f[R] will try increasingly hard to display decimal digits according to the commodity display styles: .IP \[bu] 2 \f[CR]\-\-round=none\f[R] show amounts with original precisions (default) .IP \[bu] 2 \f[CR]\-\-round=soft\f[R] add/remove decimal zeros in amounts (except costs) .IP \[bu] 2 \f[CR]\-\-round=hard\f[R] round amounts (except costs), possibly hiding significant digits .IP \[bu] 2 \f[CR]\-\-round=all\f[R] round all amounts and costs .PP \f[CR]soft\f[R] is good for non\-lossy cleanup, formatting amounts more consistently where it\[aq]s safe to do so. .PP \f[CR]hard\f[R] and \f[CR]all\f[R] can cause \f[CR]print\f[R] to show invalid unbalanced journal entries; they may be useful eg for stronger cleanup, with manual fixups when needed. .SS print parseability print\[aq]s output is usually a valid hledger journal, and you can process it again with a second hledger command. This can be useful for certain kinds of search (though the same can be achieved with \f[CR]expr:\f[R] queries now): .IP .EX # Show running total of food expenses paid from cash. # \-f\- reads from stdin. \-I/\-\-ignore\-assertions is sometimes needed. $ hledger print assets:cash | hledger \-f\- \-I reg expenses:food .EE .PP There are some situations where print\[aq]s output can become unparseable: .IP \[bu] 2 Value reporting affects posting amounts but not balance assertion or balance assignment amounts, potentially causing those to fail. .IP \[bu] 2 Auto postings can generate postings with too many missing amounts. .IP \[bu] 2 Account aliases can generate bad account names. .SS print, other features With \f[CR]\-B\f[R]/\f[CR]\-\-cost\f[R], amounts with costs are shown converted to cost. .PP With \f[CR]\-\-new\f[R], print shows only transactions it has not seen on a previous run. This uses the same deduplication system as the \f[CR]import\f[R] command. (See import\[aq]s docs for details.) .PP With \f[CR]\-m DESC\f[R]/\f[CR]\-\-match=DESC\f[R], print shows one recent transaction whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar\-enough match, no transaction will be shown and the program exit code will be non\-zero. .SS print output format This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]beancount\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]json\f[R] and \f[CR]sql\f[R]. .PP \f[I]Experimental:\f[R] The \f[CR]beancount\f[R] format tries to produce Beancount\-compatible output, as follows: .IP \[bu] 2 Transaction and postings with unmarked status are converted to cleared (\f[CR]*\f[R]) status. .IP \[bu] 2 Transactions\[aq] payee and note are backslash\-escaped and double\-quote\-escaped and wrapped in double quotes. .IP \[bu] 2 Transaction tags are copied to Beancount #tag format. .IP \[bu] 2 Commodity symbols are converted to upper case, and a small number of currency symbols like \f[CR]$\f[R] are converted to the corresponding currency names. .IP \[bu] 2 Account name parts are capitalised and unsupported characters are replaced with \f[CR]\-\f[R]. If an account name part does not begin with a letter, or if the first part is not Assets, Liabilities, Equity, Income, or Expenses, an error is raised. (Use \f[CR]\-\-alias\f[R] options to bring your accounts into compliance.) .IP \[bu] 2 An \f[CR]open\f[R] directive is generated for each account used, on the earliest transaction date. .PP Some limitations: .IP \[bu] 2 Balance assertions are removed. .IP \[bu] 2 Balance assignments become missing amounts. .IP \[bu] 2 Virtual and balanced virtual postings become regular postings. .IP \[bu] 2 Directives are not converted. .PP Here\[aq]s an example of print\[aq]s CSV output: .IP .EX $ hledger print \-Ocsv \[dq]txnidx\[dq],\[dq]date\[dq],\[dq]date2\[dq],\[dq]status\[dq],\[dq]code\[dq],\[dq]description\[dq],\[dq]comment\[dq],\[dq]account\[dq],\[dq]amount\[dq],\[dq]commodity\[dq],\[dq]credit\[dq],\[dq]debit\[dq],\[dq]posting\-status\[dq],\[dq]posting\-comment\[dq] \[dq]1\[dq],\[dq]2008/01/01\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]income\[dq],\[dq]\[dq],\[dq]assets:bank:checking\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]1\[dq],\[dq]2008/01/01\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]income\[dq],\[dq]\[dq],\[dq]income:salary\[dq],\[dq]\-1\[dq],\[dq]$\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]2\[dq],\[dq]2008/06/01\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]gift\[dq],\[dq]\[dq],\[dq]assets:bank:checking\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]2\[dq],\[dq]2008/06/01\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]gift\[dq],\[dq]\[dq],\[dq]income:gifts\[dq],\[dq]\-1\[dq],\[dq]$\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]3\[dq],\[dq]2008/06/02\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]save\[dq],\[dq]\[dq],\[dq]assets:bank:saving\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]3\[dq],\[dq]2008/06/02\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]save\[dq],\[dq]\[dq],\[dq]assets:bank:checking\[dq],\[dq]\-1\[dq],\[dq]$\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]4\[dq],\[dq]2008/06/03\[dq],\[dq]\[dq],\[dq]*\[dq],\[dq]\[dq],\[dq]eat & shop\[dq],\[dq]\[dq],\[dq]expenses:food\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]4\[dq],\[dq]2008/06/03\[dq],\[dq]\[dq],\[dq]*\[dq],\[dq]\[dq],\[dq]eat & shop\[dq],\[dq]\[dq],\[dq]expenses:supplies\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]4\[dq],\[dq]2008/06/03\[dq],\[dq]\[dq],\[dq]*\[dq],\[dq]\[dq],\[dq]eat & shop\[dq],\[dq]\[dq],\[dq]assets:cash\[dq],\[dq]\-2\[dq],\[dq]$\[dq],\[dq]2\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]5\[dq],\[dq]2008/12/31\[dq],\[dq]\[dq],\[dq]*\[dq],\[dq]\[dq],\[dq]pay off\[dq],\[dq]\[dq],\[dq]liabilities:debts\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]5\[dq],\[dq]2008/12/31\[dq],\[dq]\[dq],\[dq]*\[dq],\[dq]\[dq],\[dq]pay off\[dq],\[dq]\[dq],\[dq]assets:bank:checking\[dq],\[dq]\-1\[dq],\[dq]$\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq] .EE .IP \[bu] 2 There is one CSV record per posting, with the parent transaction\[aq]s fields repeated. .IP \[bu] 2 The \[dq]txnidx\[dq] (transaction index) field shows which postings belong to the same transaction. (This number might change if transactions are reordered within the file, files are parsed/included in a different order, etc.) .IP \[bu] 2 The amount is separated into \[dq]commodity\[dq] (the symbol) and \[dq]amount\[dq] (numeric quantity) fields. .IP \[bu] 2 The numeric amount is repeated in either the \[dq]credit\[dq] or \[dq]debit\[dq] column, for convenience. (Those names are not accurate in the accounting sense; it just puts negative amounts under credit and zero or greater amounts under debit.) .SS register (reg) .PP Show postings and their running total. .PP The register command displays matched postings, across all accounts, in date order, with their running total or running historical balance. (See also the \f[CR]aregister\f[R] command, which shows matched transactions in a specific account.) .PP register normally shows line per posting, but note that multi\-commodity amounts will occupy multiple lines (one line per commodity). .PP It is typically used with a query selecting a particular account, to see that account\[aq]s activity: .IP .EX $ hledger register checking 2008/01/01 income assets:bank:checking $1 $1 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $\-1 $1 2008/12/31 pay off assets:bank:checking $\-1 0 .EE .PP With \f[CR]\-\-date2\f[R], it shows and sorts by secondary date instead. .PP For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the \f[CR]\-\-align\-all\f[R] flag. .PP The \f[CR]\-\-historical\f[R]/\f[CR]\-H\f[R] flag adds the balance from any undisplayed prior postings to the running total. This is useful when you want to see only recent activity, with a historically accurate running balance: .IP .EX $ hledger register checking \-b 2008/6 \-\-historical 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $\-1 $1 2008/12/31 pay off assets:bank:checking $\-1 0 .EE .PP The \f[CR]\-\-depth\f[R] option limits the amount of sub\-account detail displayed. .PP The \f[CR]\-\-average\f[R]/\f[CR]\-A\f[R] flag shows the running average posting amount instead of the running total (so, the final number displayed is the average for the whole report period). This flag implies \f[CR]\-\-empty\f[R] (see below). It is affected by \f[CR]\-\-historical\f[R]. It works best when showing just one account and one commodity. .PP The \f[CR]\-\-related\f[R]/\f[CR]\-r\f[R] flag shows the \f[I]other\f[R] postings in the transactions of the postings which would normally be shown. .PP The \f[CR]\-\-invert\f[R] flag negates all amounts. For example, it can be used on an income account where amounts are normally displayed as negative numbers. It\[aq]s also useful to show postings on the checking account together with the related account: .IP .EX $ hledger register \-\-related \-\-invert assets:checking .EE .PP With a reporting interval, register shows summary postings, one per interval, aggregating the postings to each account: .IP .EX $ hledger register \-\-monthly income 2008/01 income:salary $\-1 $\-1 2008/06 income:gifts $\-1 $\-2 .EE .PP Periods with no activity, and summary postings with a zero amount, are not shown by default; use the \f[CR]\-\-empty\f[R]/\f[CR]\-E\f[R] flag to see them: .IP .EX $ hledger register \-\-monthly income \-E 2008/01 income:salary $\-1 $\-1 2008/02 0 $\-1 2008/03 0 $\-1 2008/04 0 $\-1 2008/05 0 $\-1 2008/06 income:gifts $\-1 $\-2 2008/07 0 $\-2 2008/08 0 $\-2 2008/09 0 $\-2 2008/10 0 $\-2 2008/11 0 $\-2 2008/12 0 $\-2 .EE .PP Often, you\[aq]ll want to see just one line per interval. The \f[CR]\-\-depth\f[R] option helps with this, causing subaccounts to be aggregated: .IP .EX $ hledger register \-\-monthly assets \-\-depth 1h 2008/01 assets $1 $1 2008/06 assets $\-1 0 2008/12 assets $\-1 $\-1 .EE .PP Note when using report intervals, if you specify start/end dates these will be adjusted outward if necessary to contain a whole number of intervals. This ensures that the first and last intervals are full length and comparable to the others in the report. .PP With \f[CR]\-m DESC\f[R]/\f[CR]\-\-match=DESC\f[R], register does a fuzzy search for one recent posting whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar\-enough match, no posting will be shown and the program exit code will be non\-zero. .SS Custom register output register uses the full terminal width by default, except on windows. You can override this by setting the \f[CR]COLUMNS\f[R] environment variable (not a bash shell variable) or by using the \f[CR]\-\-width\f[R]/\f[CR]\-w\f[R] option. .PP The description and account columns normally share the space equally (about half of (width \- 40) each). You can adjust this by adding a description width as part of \-\-width\[aq]s argument, comma\-separated: \f[CR]\-\-width W,D\f[R] . Here\[aq]s a diagram (won\[aq]t display correctly in \-\-help): .IP .EX <\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- width (W) \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-> date (10) description (D) account (W\-41\-D) amount (12) balance (12) DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA .EE .PP and some examples: .IP .EX $ hledger reg # use terminal width (or 80 on windows) $ hledger reg \-w 100 # use width 100 $ COLUMNS=100 hledger reg # set with one\-time environment variable $ export COLUMNS=100; hledger reg # set till session end (or window resize) $ hledger reg \-w 100,40 # set overall width 100, description width 40 $ hledger reg \-w $COLUMNS,40 # use terminal width, & description width 40 .EE .PP This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], and (experimental) \f[CR]json\f[R]. .SS rewrite Print all transactions, rewriting the postings of matched transactions. For now the only rewrite available is adding new postings, like print \-\-auto. .PP This is a start at a generic rewriter of transaction entries. It reads the default journal and prints the transactions, like print, but adds one or more specified postings to any transactions matching QUERY. The posting amounts can be fixed, or a multiplier of the existing transaction\[aq]s first posting amount. .PP Examples: .IP .EX $ hledger\-rewrite.hs \[ha]income \-\-add\-posting \[aq](liabilities:tax) *.33 ; income tax\[aq] \-\-add\-posting \[aq](reserve:gifts) $100\[aq] $ hledger\-rewrite.hs expenses:gifts \-\-add\-posting \[aq](reserve:gifts) *\-1\[dq]\[aq] $ hledger\-rewrite.hs \-f rewrites.hledger .EE .PP rewrites.hledger may consist of entries like: .IP .EX = \[ha]income amt:<0 date:2017 (liabilities:tax) *0.33 ; tax on income (reserve:grocery) *0.25 ; reserve 25% for grocery (reserve:) *0.25 ; reserve 25% for grocery .EE .PP Note the single quotes to protect the dollar sign from bash, and the two spaces between account and amount. .PP More: .IP .EX $ hledger rewrite \-\- [QUERY] \-\-add\-posting \[dq]ACCT AMTEXPR\[dq] ... $ hledger rewrite \-\- \[ha]income \-\-add\-posting \[aq](liabilities:tax) *.33\[aq] $ hledger rewrite \-\- expenses:gifts \-\-add\-posting \[aq](budget:gifts) *\-1\[dq]\[aq] $ hledger rewrite \-\- \[ha]income \-\-add\-posting \[aq](budget:foreign currency) *0.25 JPY; diversify\[aq] .EE .PP Argument for \f[CR]\-\-add\-posting\f[R] option is a usual posting of transaction with an exception for amount specification. More precisely, you can use \f[CR]\[aq]*\[aq]\f[R] (star symbol) before the amount to indicate that that this is a factor for an amount of original matched posting. If the amount includes a commodity name, the new posting amount will be in the new commodity; otherwise, it will be in the matched posting amount\[aq]s commodity. .SS Re\-write rules in a file During the run this tool will execute so called \[dq]Automated Transactions\[dq] found in any journal it process. I.e instead of specifying this operations in command line you can put them in a journal file. .IP .EX $ rewrite\-rules.journal .EE .PP Make contents look like this: .IP .EX = \[ha]income (liabilities:tax) *.33 = expenses:gifts budget:gifts *\-1 assets:budget *1 .EE .PP Note that \f[CR]\[aq]=\[aq]\f[R] (equality symbol) that is used instead of date in transactions you usually write. It indicates the query by which you want to match the posting to add new ones. .IP .EX $ hledger rewrite \-\- \-f input.journal \-f rewrite\-rules.journal > rewritten\-tidy\-output.journal .EE .PP This is something similar to the commands pipeline: .IP .EX $ hledger rewrite \-\- \-f input.journal \[aq]\[ha]income\[aq] \-\-add\-posting \[aq](liabilities:tax) *.33\[aq] \[rs] | hledger rewrite \-\- \-f \- expenses:gifts \-\-add\-posting \[aq]budget:gifts *\-1\[aq] \[rs] \-\-add\-posting \[aq]assets:budget *1\[aq] \[rs] > rewritten\-tidy\-output.journal .EE .PP It is important to understand that relative order of such entries in journal is important. You can re\-use result of previously added postings. .SS Diff output format To use this tool for batch modification of your journal files you may find useful output in form of unified diff. .IP .EX $ hledger rewrite \-\- \-\-diff \-f examples/sample.journal \[aq]\[ha]income\[aq] \-\-add\-posting \[aq](liabilities:tax) *.33\[aq] .EE .PP Output might look like: .IP .EX \-\-\- /tmp/examples/sample.journal +++ /tmp/examples/sample.journal \[at]\[at] \-18,3 +18,4 \[at]\[at] 2008/01/01 income \- assets:bank:checking $1 + assets:bank:checking $1 income:salary + (liabilities:tax) 0 \[at]\[at] \-22,3 +23,4 \[at]\[at] 2008/06/01 gift \- assets:bank:checking $1 + assets:bank:checking $1 income:gifts + (liabilities:tax) 0 .EE .PP If you\[aq]ll pass this through \f[CR]patch\f[R] tool you\[aq]ll get transactions containing the posting that matches your query be updated. Note that multiple files might be update according to list of input files specified via \f[CR]\-\-file\f[R] options and \f[CR]include\f[R] directives inside of these files. .PP Be careful. Whole transaction being re\-formatted in a style of output from \f[CR]hledger print\f[R]. .PP See also: .PP https://github.com/simonmichael/hledger/issues/99 .SS rewrite vs. print \-\-auto This command predates print \-\-auto, and currently does much the same thing, but with these differences: .IP \[bu] 2 with multiple files, rewrite lets rules in any file affect all other files. print \-\-auto uses standard directive scoping; rules affect only child files. .IP \[bu] 2 rewrite\[aq]s query limits which transactions can be rewritten; all are printed. print \-\-auto\[aq]s query limits which transactions are printed. .IP \[bu] 2 rewrite applies rules specified on command line or in the journal. print \-\-auto applies rules specified in the journal. .SS roi Shows the time\-weighted (TWR) and money\-weighted (IRR) rate of return on your investments. .PP At a minimum, you need to supply a query (which could be just an account name) to select your investment(s) with \f[CR]\-\-inv\f[R], and another query to identify your profit and loss transactions with \f[CR]\-\-pnl\f[R]. .PP If you do not record changes in the value of your investment manually, or do not require computation of time\-weighted return (TWR), \f[CR]\-\-pnl\f[R] could be an empty query (\f[CR]\-\-pnl \[dq]\[dq]\f[R] or \f[CR]\-\-pnl STR\f[R] where \f[CR]STR\f[R] does not match any of your accounts). .PP This command will compute and display the internalized rate of return (IRR, also known as money\-weighted rate of return) and time\-weighted rate of return (TWR) for your investments for the time period requested. IRR is always annualized due to the way it is computed, but TWR is reported both as a rate over the chosen reporting period and as an annual rate. .PP Price directives will be taken into account if you supply appropriate \f[CR]\-\-cost\f[R] or \f[CR]\-\-value\f[R] flags (see VALUATION). .PP Note, in some cases this report can fail, for these reasons: .IP \[bu] 2 Error (NotBracketed): No solution for Internal Rate of Return (IRR). Possible causes: IRR is huge (>1000000%), balance of investment becomes negative at some point in time. .IP \[bu] 2 Error (SearchFailed): Failed to find solution for Internal Rate of Return (IRR). Either search does not converge to a solution, or converges too slowly. .PP Examples: .IP \[bu] 2 Using roi to compute total return of investment in stocks: https://github.com/simonmichael/hledger/blob/master/examples/investing/roi\-unrealised.ledger .IP \[bu] 2 Cookbook > Return on Investment: https://hledger.org/roi.html .SS Spaces and special characters in \f[CR]\-\-inv\f[R] and \f[CR]\-\-pnl\f[R] Note that \f[CR]\-\-inv\f[R] and \f[CR]\-\-pnl\f[R]\[aq]s argument is a query, and queries could have several space\-separated terms (see QUERIES). .PP To indicate that all search terms form single command\-line argument, you will need to put them in quotes (see Special characters): .IP .EX $ hledger roi \-\-inv \[aq]term1 term2 term3 ...\[aq] .EE .PP If any query terms contain spaces themselves, you will need an extra level of nested quoting, eg: .IP .EX $ hledger roi \-\-inv=\[dq]\[aq]Assets:Test 1\[aq]\[dq] \-\-pnl=\[dq]\[aq]Equity:Unrealized Profit and Loss\[aq]\[dq] .EE .SS Semantics of \f[CR]\-\-inv\f[R] and \f[CR]\-\-pnl\f[R] Query supplied to \f[CR]\-\-inv\f[R] has to match all transactions that are related to your investment. Transactions not matching \f[CR]\-\-inv\f[R] will be ignored. .PP In these transactions, ROI will conside postings that match \f[CR]\-\-inv\f[R] to be \[dq]investment postings\[dq] and other postings (not matching \f[CR]\-\-inv\f[R]) will be sorted into two categories: \[dq]cash flow\[dq] and \[dq]profit and loss\[dq], as ROI needs to know which part of the investment value is your contributions and which is due to the return on investment. .IP \[bu] 2 \[dq]Cash flow\[dq] is depositing or withdrawing money, buying or selling assets, or otherwise converting between your investment commodity and any other commodity. Example: .RS 2 .IP .EX 2019\-01\-01 Investing in Snake Oil assets:cash \-$100 investment:snake oil 2020\-01\-01 Selling my Snake Oil assets:cash $10 investment:snake oil = 0 .EE .RE .IP \[bu] 2 \[dq]Profit and loss\[dq] is change in the value of your investment: .RS 2 .IP .EX 2019\-06\-01 Snake Oil falls in value investment:snake oil = $57 equity:unrealized profit or loss .EE .RE .PP All non\-investment postings are assumed to be \[dq]cash flow\[dq], unless they match \f[CR]\-\-pnl\f[R] query. Changes in value of your investment due to \[dq]profit and loss\[dq] postings will be considered as part of your investment return. .PP Example: if you use \f[CR]\-\-inv snake \-\-pnl equity:unrealized\f[R], then postings in the example below would be classifed as: .IP .EX 2019\-01\-01 Snake Oil #1 assets:cash \-$100 ; cash flow posting investment:snake oil ; investment posting 2019\-03\-01 Snake Oil #2 equity:unrealized pnl \-$100 ; profit and loss posting snake oil ; investment posting 2019\-07\-01 Snake Oil #3 equity:unrealized pnl ; profit and loss posting cash \-$100 ; cash flow posting snake oil $50 ; investment posting .EE .SS IRR and TWR explained \[dq]ROI\[dq] stands for \[dq]return on investment\[dq]. Traditionally this was computed as a difference between current value of investment and its initial value, expressed in percentage of the initial value. .PP However, this approach is only practical in simple cases, where investments receives no in\-flows or out\-flows of money, and where rate of growth is fixed over time. For more complex scenarios you need different ways to compute rate of return, and this command implements two of them: IRR and TWR. .PP Internal rate of return, or \[dq]IRR\[dq] (also called \[dq]money\-weighted rate of return\[dq]) takes into account effects of in\-flows and out\-flows, and the time between them. Investment at a particular fixed interest rate is going to give you more interest than the same amount invested at the same interest rate, but made later in time. If you are withdrawing from your investment, your future gains would be smaller (in absolute numbers), and will be a smaller percentage of your initial investment, so your IRR will be smaller. And if you are adding to your investment, you will receive bigger absolute gains, which will be a bigger percentage of your initial investment, so your IRR will be larger. .PP As mentioned before, in\-flows and out\-flows would be any cash that you personally put in or withdraw, and for the \[dq]roi\[dq] command, these are the postings that match the query in the\f[CR]\-\-inv\f[R] argument and NOT match the query in the\f[CR]\-\-pnl\f[R] argument. .PP If you manually record changes in the value of your investment as transactions that balance them against \[dq]profit and loss\[dq] (or \[dq]unrealized gains\[dq]) account or use price directives, then in order for IRR to compute the precise effect of your in\-flows and out\-flows on the rate of return, you will need to record the value of your investement on or close to the days when in\- or out\-flows occur. .PP In technical terms, IRR uses the same approach as computation of net present value, and tries to find a discount rate that makes net present value of all the cash flows of your investment to add up to zero. This could be hard to wrap your head around, especially if you haven\[aq]t done discounted cash flow analysis before. Implementation of IRR in hledger should produce results that match the \f[CR]=XIRR\f[R] formula in Excel. .PP Second way to compute rate of return that \f[CR]roi\f[R] command implements is called \[dq]time\-weighted rate of return\[dq] or \[dq]TWR\[dq]. Like IRR, it will account for the effect of your in\-flows and out\-flows, but unlike IRR it will try to compute the true rate of return of the underlying asset, compensating for the effect that deposits and withdrawas have on the apparent rate of growth of your investment. .PP TWR represents your investment as an imaginary \[dq]unit fund\[dq] where in\-flows/ out\-flows lead to buying or selling \[dq]units\[dq] of your investment and changes in its value change the value of \[dq]investment unit\[dq]. Change in \[dq]unit price\[dq] over the reporting period gives you rate of return of your investment, and make TWR less sensitive than IRR to the effects of cash in\-flows and out\-flows. .PP References: .IP \[bu] 2 Explanation of rate of return .IP \[bu] 2 Explanation of IRR .IP \[bu] 2 Explanation of TWR .IP \[bu] 2 IRR vs TWR .IP \[bu] 2 Examples of computing IRR and TWR and discussion of the limitations of both metrics .SS stats Show journal and performance statistics. .PP The stats command displays summary information for the whole journal, or a matched part of it. With a reporting interval, it shows a report for each report period. .PP At the end, it shows (in the terminal) the overall run time and number of transactions processed per second. Note these are approximate and will vary based on machine, current load, data size, hledger version, haskell lib versions, GHC version.. but they may be of interest. The \f[CR]stats\f[R] command\[aq]s run time is similar to that of a single\-column balance report. .PP Example: .IP .EX $ hledger stats \-f examples/1000x1000x10.journal Main file : /Users/simon/src/hledger/examples/1000x1000x10.journal Included files : Transactions span : 2000\-01\-01 to 2002\-09\-27 (1000 days) Last transaction : 2002\-09\-26 (6995 days ago) Transactions : 1000 (1.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 1000 Accounts : 1000 (depth 10) Commodities : 26 (A, B, C, D, E, F, G, H, I, J, K, L, M, N, O, P, Q, R, S, T, U, V, W, X, Y, Z) Market prices : 1000 (A) Run time : 0.12 s Throughput : 8342 txns/s .EE .PP This command supports the \-o/\-\-output\-file option (but not \-O/\-\-output\-format selection). .SS tags List the tags used in the journal, or their values. .PP This command lists the tag names used in the journal, whether on transactions, postings, or account declarations. .PP With a TAGREGEX argument, only tag names matching this regular expression (case insensitive, infix matched) are shown. .PP With QUERY arguments, only transactions and accounts matching this query are considered. If the query involves transaction fields (date:, desc:, amt:, ...), the search is restricted to the matched transactions and their accounts. .PP With the \-\-values flag, the tags\[aq] unique non\-empty values are listed instead. With \-E/\-\-empty, blank/empty values are also shown. .PP With \-\-parsed, tags or values are shown in the order they were parsed, with duplicates included. (Except, tags from account declarations are always shown first.) .PP Tip: remember, accounts also acquire tags from their parents, postings also acquire tags from their account and transaction, transactions also acquire tags from their postings. .SS test Run built\-in unit tests. .PP This command runs the unit tests built in to hledger and hledger\-lib, printing the results on stdout. If any test fails, the exit code will be non\-zero. .PP This is mainly used by hledger developers, but you can also use it to sanity\-check the installed hledger executable on your platform. All tests are expected to pass \- if you ever see a failure, please report as a bug! .PP This command also accepts tasty test runner options, written after a \-\- (double hyphen). Eg to run only the tests in Hledger.Data.Amount, with ANSI colour codes disabled: .IP .EX $ hledger test \-\- \-pData.Amount \-\-color=never .EE .PP For help on these, see https://github.com/feuerbach/tasty#options (\f[CR]\-\- \-\-help\f[R] currently doesn\[aq]t show them). .PP .SH PART 5: COMMON TASKS Here are some quick examples of how to do some basic tasks with hledger. .SS Getting help Here\[aq]s how to list commands and view options and command docs: .IP .EX $ hledger # show available commands $ hledger \-\-help # show common options $ hledger CMD \-\-help # show CMD\[aq]s options, common options and CMD\[aq]s documentation .EE .PP You can also view your hledger version\[aq]s manual in several formats by using the help command. Eg: .IP .EX $ hledger help # show the hledger manual with info, man or $PAGER (best available) $ hledger help journal # show the journal topic in the hledger manual $ hledger help \-\-help # find out more about the help command .EE .PP To view manuals and introductory docs on the web, visit https://hledger.org. Chat and mail list support and discussion archives can be found at https://hledger.org/support. .SS Constructing command lines hledger has a flexible command line interface. We strive to keep it simple and ergonomic, but if you run into one of the sharp edges described in OPTIONS, here are some tips that might help: .IP \[bu] 2 command\-specific options must go after the command (it\[aq]s fine to put common options there too: \f[CR]hledger CMD OPTS ARGS\f[R]) .IP \[bu] 2 running add\-on executables directly simplifies command line parsing (\f[CR]hledger\-ui OPTS ARGS\f[R]) .IP \[bu] 2 enclose \[dq]problematic\[dq] args in single quotes .IP \[bu] 2 if needed, also add a backslash to hide regular expression metacharacters from the shell .IP \[bu] 2 to see how a misbehaving command line is being parsed, add \f[CR]\-\-debug=2\f[R]. .SS Starting a journal file hledger looks for your accounting data in a journal file, \f[CR]$HOME/.hledger.journal\f[R] by default: .IP .EX $ hledger stats The hledger journal file \[dq]/Users/simon/.hledger.journal\[dq] was not found. Please create it first, eg with \[dq]hledger add\[dq] or a text editor. Or, specify an existing journal file with \-f or LEDGER_FILE. .EE .PP You can override this by setting the \f[CR]LEDGER_FILE\f[R] environment variable (see below). It\[aq]s a good practice to keep this important file under version control, and to start a new file each year. So you could do something like this: .IP .EX $ mkdir \[ti]/finance $ cd \[ti]/finance $ git init Initialized empty Git repository in /Users/simon/finance/.git/ $ touch 2023.journal $ echo \[dq]export LEDGER_FILE=$HOME/finance/2023.journal\[dq] >> \[ti]/.profile $ source \[ti]/.profile $ hledger stats Main file : /Users/simon/finance/2023.journal Included files : Transactions span : to (0 days) Last transaction : none Transactions : 0 (0.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 0 Accounts : 0 (depth 0) Commodities : 0 () Market prices : 0 () .EE .SS Setting LEDGER_FILE How to set \f[CR]LEDGER_FILE\f[R] permanently depends on your setup: .PP On unix and mac, running these commands in the terminal will work for many people; adapt as needed: .IP .EX $ echo \[aq]export LEDGER_FILE=\[ti]/finance/2023.journal\[aq] >> \[ti]/.profile $ source \[ti]/.profile .EE .PP When correctly configured, in a new terminal window \f[CR]env | grep LEDGER_FILE\f[R] will show your file, and so will \f[CR]hledger files\f[R]. .PP On mac, this additional step might be helpful for GUI applications (like Emacs started from the dock): add an entry to \f[CR]\[ti]/.MacOSX/environment.plist\f[R] like .IP .EX { \[dq]LEDGER_FILE\[dq] : \[dq]\[ti]/finance/2023.journal\[dq] } .EE .PP and then run \f[CR]killall Dock\f[R] in a terminal window (or restart the machine). .PP On Windows, see https://www.java.com/en/download/help/path.html, or try running these commands in a powershell window (let us know if it persists across a reboot, and if you need to be an Administrator): .IP .EX > CD > MKDIR finance > SETX LEDGER_FILE \[dq]C:\[rs]Users\[rs]USERNAME\[rs]finance\[rs]2023.journal\[dq] .EE .SS Setting opening balances Pick a starting date for which you can look up the balances of some real\-world assets (bank accounts, wallet..) and liabilities (credit cards..). .PP To avoid a lot of data entry, you may want to start with just one or two accounts, like your checking account or cash wallet; and pick a recent starting date, like today or the start of the week. You can always come back later and add more accounts and older transactions, eg going back to january 1st. .PP Add an opening balances transaction to the journal, declaring the balances on this date. Here are two ways to do it: .IP \[bu] 2 The first way: open the journal in any text editor and save an entry like this: .RS 2 .IP .EX 2023\-01\-01 * opening balances assets:bank:checking $1000 = $1000 assets:bank:savings $2000 = $2000 assets:cash $100 = $100 liabilities:creditcard $\-50 = $\-50 equity:opening/closing balances .EE .PP These are start\-of\-day balances, ie whatever was in the account at the end of the previous day. .PP The * after the date is an optional status flag. Here it means \[dq]cleared & confirmed\[dq]. .PP The currency symbols are optional, but usually a good idea as you\[aq]ll be dealing with multiple currencies sooner or later. .PP The = amounts are optional balance assertions, providing extra error checking. .RE .IP \[bu] 2 The second way: run \f[CR]hledger add\f[R] and follow the prompts to record a similar transaction: .RS 2 .IP .EX $ hledger add Adding transactions to journal file /Users/simon/finance/2023.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control\-d or control\-c. Date [2023\-02\-07]: 2023\-01\-01 Description: * opening balances Account 1: assets:bank:checking Amount 1: $1000 Account 2: assets:bank:savings Amount 2 [$\-1000]: $2000 Account 3: assets:cash Amount 3 [$\-3000]: $100 Account 4: liabilities:creditcard Amount 4 [$\-3100]: $\-50 Account 5: equity:opening/closing balances Amount 5 [$\-3050]: Account 6 (or . or enter to finish this transaction): . 2023\-01\-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $\-50 equity:opening/closing balances $\-3050 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl\-D/ctrl\-C to quit) Date [2023\-01\-01]: . .EE .RE .PP If you\[aq]re using version control, this could be a good time to commit the journal. Eg: .IP .EX $ git commit \-m \[aq]initial balances\[aq] 2023.journal .EE .SS Recording transactions As you spend or receive money, you can record these transactions using one of the methods above (text editor, hledger add) or by using the hledger\-iadd or hledger\-web add\-ons, or by using the import command to convert CSV data downloaded from your bank. .PP Here are some simple transactions, see the hledger_journal(5) manual and hledger.org for more ideas: .IP .EX 2023/1/10 * gift received assets:cash $20 income:gifts 2023.1.12 * farmers market expenses:food $13 assets:cash 2023\-01\-15 paycheck income:salary assets:bank:checking $1000 .EE .SS Reconciling Periodically you should reconcile \- compare your hledger\-reported balances against external sources of truth, like bank statements or your bank\[aq]s website \- to be sure that your ledger accurately represents the real\-world balances (and, that the real\-world institutions have not made a mistake!). This gets easy and fast with (1) practice and (2) frequency. If you do it daily, it can take 2\-10 minutes. If you let it pile up, expect it to take longer as you hunt down errors and discrepancies. .PP A typical workflow: .IP "1." 3 Reconcile cash. Count what\[aq]s in your wallet. Compare with what hledger reports (\f[CR]hledger bal cash\f[R]). If they are different, try to remember the missing transaction, or look for the error in the already\-recorded transactions. A register report can be helpful (\f[CR]hledger reg cash\f[R]). If you can\[aq]t find the error, add an adjustment transaction. Eg if you have $105 after the above, and can\[aq]t explain the missing $2, it could be: .RS 4 .IP .EX 2023\-01\-16 * adjust cash assets:cash $\-2 = $105 expenses:misc .EE .RE .IP "2." 3 Reconcile checking. Log in to your bank\[aq]s website. Compare today\[aq]s (cleared) balance with hledger\[aq]s cleared balance (\f[CR]hledger bal checking \-C\f[R]). If they are different, track down the error or record the missing transaction(s) or add an adjustment transaction, similar to the above. Unlike the cash case, you can usually compare the transaction history and running balance from your bank with the one reported by \f[CR]hledger reg checking \-C\f[R]. This will be easier if you generally record transaction dates quite similar to your bank\[aq]s clearing dates. .IP "3." 3 Repeat for other asset/liability accounts. .PP Tip: instead of the register command, use hledger\-ui to see a live\-updating register while you edit the journal: \f[CR]hledger\-ui \-\-watch \-\-register checking \-C\f[R] .PP After reconciling, it could be a good time to mark the reconciled transactions\[aq] status as \[dq]cleared and confirmed\[dq], if you want to track that, by adding the \f[CR]*\f[R] marker. Eg in the paycheck transaction above, insert \f[CR]*\f[R] between \f[CR]2023\-01\-15\f[R] and \f[CR]paycheck\f[R] .PP If you\[aq]re using version control, this can be another good time to commit: .IP .EX $ git commit \-m \[aq]txns\[aq] 2023.journal .EE .SS Reporting Here are some basic reports. .PP Show all transactions: .IP .EX $ hledger print 2023\-01\-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $\-50 equity:opening/closing balances $\-3050 2023\-01\-10 * gift received assets:cash $20 income:gifts 2023\-01\-12 * farmers market expenses:food $13 assets:cash 2023\-01\-15 * paycheck income:salary assets:bank:checking $1000 2023\-01\-16 * adjust cash assets:cash $\-2 = $105 expenses:misc .EE .PP Show account names, and their hierarchy: .IP .EX $ hledger accounts \-\-tree assets bank checking savings cash equity opening/closing balances expenses food misc income gifts salary liabilities creditcard .EE .PP Show all account totals: .IP .EX $ hledger balance $4105 assets $4000 bank $2000 checking $2000 savings $105 cash $\-3050 equity:opening/closing balances $15 expenses $13 food $2 misc $\-1020 income $\-20 gifts $\-1000 salary $\-50 liabilities:creditcard \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP Show only asset and liability balances, as a flat list, limited to depth 2: .IP .EX $ hledger bal assets liabilities \-2 $4000 assets:bank $105 assets:cash $\-50 liabilities:creditcard \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $4055 .EE .PP Show the same thing without negative numbers, formatted as a simple balance sheet: .IP .EX $ hledger bs \-2 Balance Sheet 2023\-01\-16 || 2023\-01\-16 ========================++============ Assets || \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\- assets:bank || $4000 assets:cash || $105 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\- || $4105 ========================++============ Liabilities || \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\- liabilities:creditcard || $50 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\- || $50 ========================++============ Net: || $4055 .EE .PP The final total is your \[dq]net worth\[dq] on the end date. (Or use \f[CR]bse\f[R] for a full balance sheet with equity.) .PP Show income and expense totals, formatted as an income statement: .IP .EX hledger is Income Statement 2023\-01\-01\-2023\-01\-16 || 2023\-01\-01\-2023\-01\-16 ===============++======================= Revenues || \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- income:gifts || $20 income:salary || $1000 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || $1020 ===============++======================= Expenses || \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- expenses:food || $13 expenses:misc || $2 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || $15 ===============++======================= Net: || $1005 .EE .PP The final total is your net income during this period. .PP Show transactions affecting your wallet, with running total: .IP .EX $ hledger register cash 2023\-01\-01 opening balances assets:cash $100 $100 2023\-01\-10 gift received assets:cash $20 $120 2023\-01\-12 farmers market assets:cash $\-13 $107 2023\-01\-16 adjust cash assets:cash $\-2 $105 .EE .PP Show weekly posting counts as a bar chart: .IP .EX $ hledger activity \-W 2019\-12\-30 ***** 2023\-01\-06 **** 2023\-01\-13 **** .EE .SS Migrating to a new file At the end of the year, you may want to continue your journal in a new file, so that old transactions don\[aq]t slow down or clutter your reports, and to help ensure the integrity of your accounting history. See the close command. .PP If using version control, don\[aq]t forget to \f[CR]git add\f[R] the new file. .SH BUGS We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). .PP Some known issues and limitations: .PP The need to precede add\-on command options with \f[CR]\-\-\f[R] when invoked from hledger is awkward. (See Command options, Constructing command lines.) .PP A UTF\-8\-aware system locale must be configured to work with non\-ascii data. (See Unicode characters, Troubleshooting.) .PP On Microsoft Windows, depending whether you are running in a CMD window or a Cygwin/MSYS/Mintty window and how you installed hledger, non\-ascii characters and colours may not be supported, and the tab key may not be supported by \f[CR]hledger add\f[R]. (Running in a WSL window should resolve these.) .PP When processing large data files, hledger uses more memory than Ledger. .SS Troubleshooting Here are some common issues you might encounter when you run hledger, and how to resolve them (and remember also you can usually get quick Support): .PP \f[B]PATH issues: I get an error like \[dq]No command \[aq]hledger\[aq] found\[dq]\f[R] .PD 0 .P .PD Depending how you installed hledger, the executables may not be in your shell\[aq]s PATH. Eg on unix systems, stack installs hledger in \f[CR]\[ti]/.local/bin\f[R] and cabal installs it in \f[CR]\[ti]/.cabal/bin\f[R]. You may need to add one of these directories to your shell\[aq]s PATH, and/or open a new terminal window. .PP \f[B]LEDGER_FILE issues: I configured LEDGER_FILE but hledger is not using it\f[R] .PD 0 .P .PD .IP \[bu] 2 \f[CR]LEDGER_FILE\f[R] should be a real environment variable, not just a shell variable. Eg on unix, the command \f[CR]env | grep LEDGER_FILE\f[R] should show it. You may need to use \f[CR]export\f[R] (see https://stackoverflow.com/a/7411509). .IP \[bu] 2 You may need to force your shell to see the new configuration. A simple way is to close your terminal window and open a new one. .PP \f[B]LANG issues: I get errors like \[dq]Illegal byte sequence\[dq] or \[dq]Invalid or incomplete multibyte or wide character\[dq] or \[dq]commitAndReleaseBuffer: invalid argument (invalid character)\[dq]\f[R] .PD 0 .P .PD Programs compiled with GHC (hledger, haskell build tools, etc.) need the system locale to be UTF\-8\-aware, or they will fail when they encounter non\-ascii characters. To fix it, set the LANG environment variable to a locale which supports UTF\-8 and which is installed on your system. .PP On unix, \f[CR]locale \-a\f[R] lists the installed locales. Look for one which mentions \f[CR]utf8\f[R], \f[CR]UTF\-8\f[R] or similar. Some examples: \f[CR]C.UTF\-8\f[R], \f[CR]en_US.utf\-8\f[R], \f[CR]fr_FR.utf8\f[R]. If necessary, use your system package manager to install one. Then select it by setting the \f[CR]LANG\f[R] environment variable. Note, exact spelling and capitalisation of the locale name may be important: Here\[aq]s one common way to configure this permanently for your shell: .IP .EX $ echo \[dq]export LANG=en_US.utf8\[dq] >>\[ti]/.profile # close and re\-open terminal window .EE .PP If you are using Nix (not NixOS) for GHC and Hledger, you might need to set the \f[CR]LOCALE_ARCHIVE\f[R] variable: .IP .EX $ echo \[dq]export LOCALE_ARCHIVE=${glibcLocales}/lib/locale/locale\-archive\[dq] >>\[ti]/.profile # close and re\-open terminal window .EE .PP \f[B]COMPATIBILITY ISSUES: hledger gives an error with my Ledger file\f[R] .PD 0 .P .PD Not all of Ledger\[aq]s journal file syntax or feature set is supported. See hledger and Ledger for full details. .SH AUTHORS Simon Michael and contributors. .br See http://hledger.org/CREDITS.html .SH COPYRIGHT Copyright 2007-2023 Simon Michael and contributors. .SH LICENSE Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), ledger(1) hledger-1.32.3/hledger.txt0000644000000000000000000137546714555433336013615 0ustar0000000000000000 HLEDGER(1) hledger User Manuals HLEDGER(1) NAME hledger - robust, friendly plain text accounting (CLI version) SYNOPSIS hledger hledger COMMAND [OPTS] [ARGS] hledger ADDONCMD -- [OPTS] [ARGS] DESCRIPTION hledger is a robust, user-friendly, cross-platform set of programs for tracking money, time, or any other commodity, using double-entry ac- counting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). This manual is for hledger's command line interface, version 1.32.3. It also describes the common options, file formats and concepts used by all hledger programs. It might accidentally teach you some bookkeep- ing/accounting as well! You don't need to know everything in here to use hledger productively, but when you have a question about function- ality, this doc should answer it. It is detailed, so do skip ahead or skim when needed. You can read it on hledger.org, or as an info manual or man page on your system. You can also get it from hledger itself with hledger --man, hledger --info or hledger help [TOPIC]. The main function of the hledger CLI is to read plain text files de- scribing financial transactions, crunch the numbers, and print a useful report on the terminal (or save it as HTML, CSV, JSON or SQL). Many reports are available, as subcommands. hledger will also detect other hledger-* executables as extra subcommands. hledger usually reads from (and appends to) a journal file specified by the LEDGER_FILE environment variable (defaulting to $HOME/.hledger.journal); or you can specify files with -f options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. Here is a small journal file describing one transaction: 2015-10-16 bought food expenses:food $10 assets:cash Transactions are dated movements of money (etc.) between two or more accounts: bank accounts, your wallet, revenue/expense categories, peo- ple, etc. You can choose any account names you wish, using : to indi- cate subaccounts. There must be at least two spaces between account name and amount. Positive amounts are inflow to that account (debit), negatives are outflow from it (credit). (Some reports show revenue, liability and equity account balances as negative numbers as a result; this is normal.) hledger's add command can help you add transactions, or you can install other data entry UIs like hledger-web or hledger-iadd. For more exten- sive/efficient changes, use a text editor: Emacs + ledger-mode, VIM + vim-ledger, or VS Code + hledger-vscode are some good choices (see https://hledger.org/editors.html). To get started, run hledger add and follow the prompts, or save some entries like the above in $HOME/.hledger.journal, then try commands like: hledger print -x hledger aregister assets hledger balance hledger balancesheet hledger incomestatement. Run hledger to list the commands. See also the "Starting a journal file" and "Setting opening balances" sections in PART 5: COMMON TASKS. PART 1: USER INTERFACE Input hledger reads one or more data files, each time you run it. You can specify a file with -f, like so $ hledger -f FILE print Files are most often in hledger's journal format, with the .journal file extension (.hledger or .j also work); these files describe trans- actions, like an accounting general journal. When no file is specified, hledger looks for .hledger.journal in your home directory. But most people prefer to keep financial files in a dedicated folder, perhaps with version control. Also, starting a new journal file each year is common (it's not required, but helps keep things fast and or- ganised). So we usually configure a different journal file, by setting the LEDGER_FILE environment variable, to something like ~/fi- nance/2023.journal. For more about how to do that on your system, see Common tasks > Setting LEDGER_FILE. Data formats Usually the data file is in hledger's journal format, but it can be in any of the supported file formats, which currently are: Reader: Reads: Used for file extensions: ----------------------------------------------------------------------------- journal hledger journal files and some .journal .j .hledger .ledger Ledger journals, for transac- tions timeclock timeclock files, for precise .timeclock time logging timedot timedot files, for approximate .timedot time logging csv CSV/SSV/TSV/character-sepa- .csv .ssv .tsv .csv.rules rated values, for data import .ssv.rules .tsv.rules These formats are described in more detail below. hledger detects the format automatically based on the file extensions shown above. If it can't recognise the file extension, it assumes journal format. So for non-journal files, it's important to use a recognised file extension, so as to either read successfully or to show relevant error messages. You can also force a specific reader/format by prefixing the file path with the format and a colon. Eg, to read a .dat file as csv format: $ hledger -f csv:/some/csv-file.dat stats Standard input The file name - means standard input: $ cat FILE | hledger -f- print If reading non-journal data in this way, you'll need to add a file for- mat prefix, like: $ echo 'i 2009/13/1 08:00:00' | hledger print -f timeclock:- Multiple files You can specify multiple -f options, to read multiple files as one big journal. When doing this, note that certain features (described below) will be affected: o Balance assertions will not see the effect of transactions in previ- ous files. (Usually this doesn't matter as each file will set the corresponding opening balances.) o Some directives will not affect previous or subsequent files. If needed, you can work around these by using a single parent file which includes the others, or concatenating the files into one, eg: cat a.journal b.journal | hledger -f- CMD. Strict mode hledger checks input files for valid data. By default, the most impor- tant errors are detected, while still accepting easy journal files without a lot of declarations: o Are the input files parseable, with valid syntax ? o Are all transactions balanced ? o Do all balance assertions pass ? With the -s/--strict flag, additional checks are performed: o Are all accounts posted to, declared with an account directive ? (Account error checking) o Are all commodities declared with a commodity directive ? (Commodity error checking) o Are all commodity conversions declared explicitly ? You can use the check command to run individual checks -- the ones listed above and some more. Commands hledger provides various subcommands for getting things done. Most of these commands do not change the journal file; they just read it and output a report. A few commands assist with adding data and file man- agement. To show the commands list, run hledger with no arguments. The commands are described in detail in PART 4: COMMANDS, below. To use a particular command, run hledger CMD [CMDOPTS] [CMDARGS], o CMD is the full command name, or its standard abbreviation shown in the commands list, or any unambiguous prefix of the name. o CMDOPTS are command-specific options, if any. Command-specific op- tions must be written after the command name. Eg: hledger print -x. o CMDARGS are additional arguments to the command, if any. Most hledger commands accept arguments representing a query, to limit the data in some way. Eg: hledger reg assets:checking. To list a command's options, arguments, and documentation in the termi- nal, run hledger CMD -h. Eg: hledger bal -h. Add-on commands In addition to the built-in commands, you can install add-on commands: programs or scripts named "hledger-SOMETHING", which will also appear in hledger's commands list. If you used the hledger-install script, you will have several add-ons installed already. Some more can be found in hledger's bin/ directory, documented at https://hledger.org/scripts.html. More precisely, add-on commands are programs or scripts in your shell's PATH, whose name starts with "hledger-" and ends with no extension or a recognised extension (".bat", ".com", ".exe", ".hs", ".js", ".lhs", ".lua", ".php", ".pl", ".py", ".rb", ".rkt", or ".sh"), and (on unix and mac) which has executable permission for the current user. You can run add-on commands using hledger, much like built-in commands: hledger ADDONCMD [-- ADDONCMDOPTS] [ADDONCMDARGS]. But note the double hyphen argument, required before add-on-specific options. Eg: hledger ui -- --watch or hledger web -- --serve. If this causes difficulty, you can always run the add-on directly, without using hledger: hledger-ui --watch or hledger-web --serve. Options Run hledger -h to see general command line help, and general options which are common to most hledger commands. These options can be writ- ten anywhere on the command line. They can be grouped into help, in- put, and reporting options: General help options -h --help show general or COMMAND help --man show general or COMMAND user manual with man --info show general or COMMAND user manual with info --version show general or ADDONCMD version --debug[=N] show debug output (levels 1-9, default: 1) General input options -f FILE --file=FILE use a different input file. For stdin, use - (default: $LEDGER_FILE or $HOME/.hledger.journal) --rules-file=RULESFILE Conversion rules file to use when reading CSV (default: FILE.rules) --separator=CHAR Field separator to expect when reading CSV (default: ',') --alias=OLD=NEW rename accounts named OLD to NEW --pivot FIELDNAME use some other field or tag for the account name -I --ignore-assertions disable balance assertion checks (note: does not disable balance assignments) -s --strict do extra error checking (check that all posted accounts are de- clared) General reporting options -b --begin=DATE include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) -e --end=DATE include postings/txns before this date (will be adjusted to fol- lowing subperiod end when using a report interval) -D --daily multiperiod/multicolumn report by day -W --weekly multiperiod/multicolumn report by week -M --monthly multiperiod/multicolumn report by month -Q --quarterly multiperiod/multicolumn report by quarter -Y --yearly multiperiod/multicolumn report by year -p --period=PERIODEXP set start date, end date, and/or reporting interval all at once using period expressions syntax --date2 match the secondary date instead (see command help for other ef- fects) --today=DATE override today's date (affects relative smart dates, for tests/examples) -U --unmarked include only unmarked postings/txns (can combine with -P or -C) -P --pending include only pending postings/txns -C --cleared include only cleared postings/txns -R --real include only non-virtual postings -NUM --depth=NUM hide/aggregate accounts or postings more than NUM levels deep -E --empty show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) -B --cost convert amounts to their cost/selling amount at transaction time -V --market convert amounts to their market value in default valuation com- modities -X --exchange=COMM convert amounts to their market value in commodity COMM --value convert amounts to cost or market value, more flexibly than -B/-V/-X --infer-equity infer conversion equity postings from costs --infer-costs infer costs from conversion equity postings --infer-market-prices use costs as additional market prices, as if they were P direc- tives --forecast generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger-ui make fu- ture-dated transactions visible. --auto generate extra postings by applying auto posting rules to all txns (not just forecast txns) --verbose-tags add visible tags indicating transactions or postings which have been generated/modified --commodity-style Override the commodity style in the output for the specified commodity. For example 'EUR1.000,00'. --color=WHEN (or --colour=WHEN) Should color-supporting commands use ANSI color codes in text output. 'auto' (default): whenever stdout seems to be a color-supporting terminal. 'always' or 'yes': always, useful eg when piping output into 'less -R'. 'never' or 'no': never. A NO_COLOR environment variable overrides this. --pretty[=WHEN] Show prettier output, e.g. using unicode box-drawing charac- ters. Accepts 'yes' (the default) or 'no' ('y', 'n', 'always', 'never' also work). If you provide an argument you must use '=', e.g. '--pretty=yes'. When a reporting option appears more than once in the command line, the last one takes precedence. Some reporting options can also be written as query arguments. Command line tips Here are some details useful to know about for hledger command lines (and elsewhere). Feel free to skip this section until you need it. Option repetition If options are repeated in a command line, hledger will generally use the last (right-most) occurence. Special characters Single escaping (shell metacharacters) In shell command lines, characters significant to your shell - such as spaces, <, >, (, ), |, $ and \ - should be "shell-escaped" if you want hledger to see them. This is done by enclosing them in single or dou- ble quotes, or by writing a backslash before them. Eg to match an ac- count name containing a space: $ hledger register 'credit card' or: $ hledger register credit\ card Windows users should keep in mind that cmd treats single quote as a regular character, so you should be using double quotes exclusively. PowerShell treats both single and double quotes as quotes. Double escaping (regular expression metacharacters) Characters significant in regular expressions (described below) - such as ., ^, $, [, ], (, ), |, and \ - may need to be "regex-escaped" if you don't want them to be interpreted by hledger's regular expression engine. This is done by writing backslashes before them, but since backslash is typically also a shell metacharacter, both shell-escaping and regex-escaping will be needed. Eg to match a literal $ sign while using the bash shell: $ hledger balance cur:'\$' or: $ hledger balance cur:\\$ Triple escaping (for add-on commands) When you use hledger to run an external add-on command (described be- low), one level of shell-escaping is lost from any options or arguments intended for by the add-on command, so those need an extra level of shell-escaping. Eg to match a literal $ sign while using the bash shell and running an add-on command (ui): $ hledger ui cur:'\\$' or: $ hledger ui cur:\\\\$ If you wondered why four backslashes, perhaps this helps: unescaped: $ escaped: \$ double-escaped: \\$ triple-escaped: \\\\$ Or, you can avoid the extra escaping by running the add-on executable directly: $ hledger-ui cur:\\$ Less escaping Options and arguments are sometimes used in places other than the shell command line, where shell-escaping is not needed, so there you should use one less level of escaping. Those places include: o an @argumentfile o hledger-ui's filter field o hledger-web's search form o GHCI's prompt (used by developers). Unicode characters hledger is expected to handle non-ascii characters correctly: o they should be parsed correctly in input files and on the command line, by all hledger tools (add, iadd, hledger-web's search/add/edit forms, etc.) o they should be displayed correctly by all hledger tools, and on-screen alignment should be preserved. This requires a well-configured environment. Here are some tips: o A system locale must be configured, and it must be one that can de- code the characters being used. In bash, you can set a locale like this: export LANG=en_US.UTF-8. There are some more details in Trou- bleshooting. This step is essential - without it, hledger will quit on encountering a non-ascii character (as with all GHC-compiled pro- grams). o your terminal software (eg Terminal.app, iTerm, CMD.exe, xterm..) must support unicode o the terminal must be using a font which includes the required unicode glyphs o the terminal should be configured to display wide characters as dou- ble width (for report alignment) o on Windows, for best results you should run hledger in the same kind of environment in which it was built. Eg hledger built in the stan- dard CMD.EXE environment (like the binaries on our download page) might show display problems when run in a cygwin or msys terminal, and vice versa. (See eg #961). Regular expressions A regular expression (regexp) is a small piece of text where certain characters (like ., ^, $, +, *, (), |, [], \) have special meanings, forming a tiny language for matching text precisely - very useful in hledger and elsewhere. To learn all about them, visit regular-expres- sions.info. hledger supports regexps whenever you are entering a pattern to match something, eg in query arguments, account aliases, CSV if rules, hledger-web's search form, hledger-ui's / search, etc. You may need to wrap them in quotes, especially at the command line (see Special char- acters above). Here are some examples: Account name queries (quoted for command line use): Regular expression: Matches: ------------------- ------------------------------------------------------------ bank assets:bank, assets:bank:savings, expenses:art:banksy, ... :bank assets:bank:savings, expenses:art:banksy :bank: assets:bank:savings '^bank' none of those ( ^ matches beginning of text ) 'bank$' assets:bank ( $ matches end of text ) 'big \$ bank' big $ bank ( \ disables following character's special meaning ) '\bbank\b' assets:bank, assets:bank:savings ( \b matches word boundaries ) '(sav|check)ing' saving or checking ( (|) matches either alternative ) 'saving|checking' saving or checking ( outer parentheses are not needed ) 'savings?' saving or savings ( ? matches 0 or 1 of the preceding thing ) 'my +bank' my bank, my bank, ... ( + matches 1 or more of the preceding thing ) 'my *bank' mybank, my bank, my bank, ... ( * matches 0 or more of the preceding thing ) 'b.nk' bank, bonk, b nk, ... ( . matches any character ) Some other queries: desc:'amazon|amzn|audible' Amazon transactions cur:EUR amounts with commodity symbol containing EUR cur:'\$' amounts with commodity symbol containing $ cur:'^\$$' only $ amounts, not eg AU$ or CA$ cur:....? amounts with 4-or-more-character symbols tag:.=202[1-3] things with any tag whose value contains 2021, 2022 or 2023 Account name aliases: accept . instead of : as account separator: alias /\./=: replaces all periods in account names with colons Show multiple top-level accounts combined as one: --alias='/^[^:]+/=combined' ( [^:] matches any character other than : ) Show accounts with the second-level part removed: --alias '/^([^:]+):[^:]+/ = \1' match a top-level account and a second-level account and replace those with just the top-level account ( \1 in the replacement text means "whatever was matched by the first parenthesised part of the regexp" CSV rules: match CSV records containing dining-related MCC codes: if \?MCC581[124] Match CSV records with a specific amount around the end/start of month: if %amount \b3\.99 & %date (29|30|31|01|02|03)$ hledger's regular expressions hledger's regular expressions come from the regex-tdfa library. If they're not doing what you expect, it's important to know exactly what they support: 1. they are case insensitive 2. they are infix matching (they do not need to match the entire thing being matched) 3. they are POSIX ERE (extended regular expressions) 4. they also support GNU word boundaries (\b, \B, \<, \>) 5. backreferences are supported when doing text replacement in account aliases or CSV rules, where backreferences can be used in the re- placement string to reference capturing groups in the search regexp. Otherwise, if you write \1, it will match the digit 1. 6. they do not support mode modifiers ((?s)), character classes (\w, \d), or anything else not mentioned above. Some things to note: o In the alias directive and --alias option, regular expressions must be enclosed in forward slashes (/REGEX/). Elsewhere in hledger, these are not required. o In queries, to match a regular expression metacharacter like $ as a literal character, prepend a backslash. Eg to search for amounts with the dollar sign in hledger-web, write cur:\$. o On the command line, some metacharacters like $ have a special mean- ing to the shell and so must be escaped at least once more. See Spe- cial characters. Argument files You can save a set of command line options and arguments in a file, and then reuse them by writing @FILENAME as a command line argument. Eg: hledger bal @foo.args. Inside the argument file, each line should contain just one option or argument. Don't use spaces except inside quotes (or you'll see a con- fusing error); write = (or nothing) between a flag and its argument. For the special characters mentioned above, use one less level of quot- ing than you would at the command prompt. Output Output destination hledger commands send their output to the terminal by default. You can of course redirect this, eg into a file, using standard shell syntax: $ hledger print > foo.txt Some commands (print, register, stats, the balance commands) also pro- vide the -o/--output-file option, which does the same thing without needing the shell. Eg: $ hledger print -o foo.txt $ hledger print -o - # write to stdout (the default) Output format Some commands offer other kinds of output, not just text on the termi- nal. Here are those commands and the formats currently supported: - txt csv/tsv html json sql -------------------------------------------------------------------------------------- aregister Y Y Y Y balance Y 1 Y 1 Y 1,2 Y balancesheet Y 1 Y 1 Y 1 Y balancesheete- Y 1 Y 1 Y 1 Y quity cashflow Y 1 Y 1 Y 1 Y incomestatement Y 1 Y 1 Y 1 Y print Y Y Y Y register Y Y Y o 1 Also affected by the balance commands' --layout option. o 2 balance does not support html output without a report interval or with --budget. The output format is selected by the -O/--output-format=FMT option: $ hledger print -O csv # print CSV on stdout or by the filename extension of an output file specified with the -o/--output-file=FILE.FMT option: $ hledger balancesheet -o foo.csv # write CSV to foo.csv The -O option can be combined with -o to override the file extension, if needed: $ hledger balancesheet -o foo.txt -O csv # write CSV to foo.txt Some notes about the various output formats: CSV output o In CSV output, digit group marks (such as thousands separators) are disabled automatically. HTML output o HTML output can be styled by an optional hledger.css file in the same directory. JSON output o This is not yet much used; real-world feedback is welcome. o Our JSON is rather large and verbose, since it is a faithful repre- sentation of hledger's internal data types. To understand the JSON, read the Haskell type definitions, which are mostly in https://github.com/simonmichael/hledger/blob/mas- ter/hledger-lib/Hledger/Data/Types.hs. o hledger represents quantities as Decimal values storing up to 255 significant digits, eg for repeating decimals. Such numbers can arise in practice (from automatically-calculated transaction prices), and would break most JSON consumers. So in JSON, we show quantities as simple Numbers with at most 10 decimal places. We don't limit the number of integer digits, but that part is under your control. We hope this approach will not cause problems in practice; if you find otherwise, please let us know. (Cf #1195) SQL output o This is not yet much used; real-world feedback is welcome. o SQL output is expected to work at least with SQLite, MySQL and Post- gres. o For SQLite, it will be more useful if you modify the generated id field to be a PRIMARY KEY. Eg: $ hledger print -O sql | sed 's/id serial/id INTEGER PRIMARY KEY AUTOINCREMENT NOT NULL/g' | ... o SQL output is structured with the expectations that statements will be executed in the empty database. If you already have tables cre- ated via SQL output of hledger, you would probably want to either clear tables of existing data (via delete or truncate SQL statements) or drop tables completely as otherwise your postings will be duped. Commodity styles When displaying amounts, hledger infers a standard display style for each commodity/currency, as described below in Commodity display style. If needed, this can be overridden by a -c/--commodity-style option (ex- cept for cost amounts and amounts displayed by the print command, which are always displayed with all decimal digits). For example, the fol- lowing will force dollar amounts to be displayed as shown: $ hledger print -c '$1.000,0' This option can repeated to set the display style for multiple commodi- ties/currencies. Its argument is as described in the commodity direc- tive. Colour In terminal output, some commands can produce colour when the terminal supports it: o if the --color/--colour option is given a value of yes or always (or no or never), colour will (or will not) be used; o otherwise, if the NO_COLOR environment variable is set, colour will not be used; o otherwise, colour will be used if the output (terminal or file) sup- ports it. Box-drawing In terminal output, you can enable unicode box-drawing characters to render prettier tables: o if the --pretty option is given a value of yes or always (or no or never), unicode characters will (or will not) be used; o otherwise, unicode characters will not be used. Paging When showing long output in the terminal, hledger will try to use the pager specified by the PAGER environment variable, or less, or more. (A pager is a helper program that shows one page at a time rather than scrolling everything off screen). Currently it does this only for help output, not for reports; specifically, o when listing commands, with hledger o when showing help with hledger [CMD] --help, o when viewing manuals with hledger help or hledger --man. Note the pager is expected to handle ANSI codes, which hledger uses eg for bold emphasis. For the common pager less (and its more compatibil- ity mode), we add R to the LESS and MORE environment variables to make this work. If you use a different pager, you might need to configure it similarly, to avoid seeing junk on screen (let us know). Otherwise, you can set the NO_COLOR environment variable to 1 to disable all ANSI output (see Colour). Debug output We intend hledger to be relatively easy to troubleshoot, introspect and develop. You can add --debug[=N] to any hledger command line to see additional debug output. N ranges from 1 (least output, the default) to 9 (maximum output). Typically you would start with 1 and increase until you are seeing enough. Debug output goes to stderr, and is not affected by -o/--output-file (unless you redirect stderr to stdout, eg: 2>&1). It will be interleaved with normal output, which can help re- veal when parts of the code are evaluated. To capture debug output in a log file instead, you can usually redirect stderr, eg: hledger bal --debug=3 2>hledger.log Environment These environment variables affect hledger: COLUMNS This is normally set by your terminal; some hledger commands (register) will format their output to this width. If not set, they will try to use the available terminal width. LEDGER_FILE The main journal file to use when not specified with -f/--file. Default: $HOME/.hledger.journal. NO_COLOR If this environment variable is set (with any value), hledger will not use ANSI color codes in terminal output, unless overridden by an explicit --color/--colour option. PART 2: DATA FORMATS Journal hledger's default file format, representing a General Journal. Here's a cheatsheet/mini-tutorial, or you can skip ahead to About journal for- mat. Journal cheatsheet # Here is the main syntax of hledger's journal format # (omitting extra Ledger compatibility syntax). # hledger journals contain comments, directives, and transactions, in any order: ############################################################################### # 1. Comment lines are for notes or temporarily disabling things. # They begin with #, ;, or a line containing the word "comment". # hash comment line ; semicolon comment line comment These lines are commented. end comment # Some but not all hledger entries can have same-line comments attached to them, # from ; (semicolon) to end of line. ############################################################################### # 2. Directives modify parsing or reports in some way. # They begin with a word or letter (or symbol). account actifs ; type:A, declare an account that is an Asset. 2+ spaces before ;. account passifs ; type:L, declare an account that is a Liability, and so on.. (ALERX) alias chkg = assets:checking commodity $0.00 decimal-mark . include /dev/null payee Whole Foods P 2022-01-01 AAAA $1.40 ~ monthly budget goals ; <- 2+ spaces between period expression and description expenses:food $400 expenses:home $1000 budgeted ############################################################################### # 3. Transactions are what it's all about; they are dated events, # usually describing movements of money. # They begin with a date. # DATE DESCRIPTION ; This is a transaction comment. # ACCOUNT NAME 1 AMOUNT1 ; <- posting 1. This is a posting comment. # ACCOUNT NAME 2 AMOUNT2 ; <- posting 2. Postings must be indented. # ; ^^ At least 2 spaces between account and amount. # ... ; Any number of postings is allowed. The amounts must balance (sum to 0). 2022-01-01 opening balances are declared this way assets:checking $1000 ; Account names can be anything. lower case is easy to type. assets:savings $1000 ; assets, liabilities, equity, revenues, expenses are common. assets:cash:wallet $100 ; : indicates subaccounts. liabilities:credit card $-200 ; liabilities, equity, revenues balances are usually negative. equity ; One amount can be left blank; $-1900 is inferred here. 2022-04-15 * (#12345) pay taxes ; There can be a ! or * after the date meaning "pending" or "cleared". ; There can be a transaction code (text in parentheses) after the date/status. ; Amounts' sign represents direction of flow, or credit/debit: assets:checking $-500 ; minus means removed from this account (credit) expenses:tax:us:2021 $500 ; plus means added to this account (debit) ; revenue/expense categories are also "accounts" 2022-01-01 ; The description is optional. ; Any currency/commodity symbols are allowed, on either side. assets:cash:wallet GBP -10 expenses:clothing GBP 10 assets:gringotts -10 gold assets:pouch 10 gold revenues:gifts -2 "Liquorice Wands" ; Complex symbols assets:bag 2 "Liquorice Wands" ; must be double-quoted. 2022-01-01 Cost in another commodity can be noted with @ or @@ assets:investments 2.0 AAAA @ $1.50 ; @ means per-unit cost assets:investments 3.0 AAAA @@ $4 ; @@ means total cost assets:checking $-7.00 2022-01-02 assert balances ; Balances can be asserted for extra error checking, in any transaction. assets:investments 0 AAAA = 5.0 AAAA assets:pouch 0 gold = 10 gold assets:savings $0 = $1000 1999-12-31 Ordering transactions by date is recommended but not required. ; Postings are not required. 2022.01.01 These date 2022/1/1 formats are 12/31 also allowed (but consistent YYYY-MM-DD is recommended). About journal format hledger's usual data source is a plain text file containing journal en- tries in hledger journal format. This file represents a standard ac- counting general journal. I use file names ending in .journal, but that's not required. The journal file contains a number of transaction entries, each describing a transfer of money (or any commodity) between two or more named accounts, in a simple format readable by both hledger and humans. hledger's journal format is compatible with most of Ledger's journal format, but not all of it. The differences and interoperation tips are described at hledger and Ledger. With some care, and by avoiding in- compatible features, you can keep your hledger journal readable by Ledger and vice versa. This can useful eg for comparing the behaviour of one app against the other. You can use hledger without learning any more about this file; just use the add or web or import commands to create and update it. Many users, though, edit the journal file with a text editor, and track changes with a version control system such as git. Editor addons such as ledger-mode or hledger-mode for Emacs, vim-ledger for Vim, and hledger-vscode for Visual Studio Code, make this easier, adding colour, formatting, tab completion, and useful commands. See Editor configura- tion at hledger.org for the full list. Here's a description of each part of the file format (and hledger's data model). A hledger journal file can contain three kinds of thing: file comments, transactions, and/or directives (counting periodic transaction rules and auto posting rules as directives). Comments Lines in the journal will be ignored if they begin with a hash (#) or a semicolon (;). (See also Other syntax.) hledger will also ignore re- gions beginning with a comment line and ending with an end comment line (or file end). Here's a suggestion for choosing between them: o # for top-level notes o ; for commenting out things temporarily o comment for quickly commenting large regions (remember it's there, or you might get confused) Eg: # a comment line ; another commentline comment A multi-line comment block, continuing until "end comment" directive or the end of the current file. end comment Some hledger entries can have same-line comments attached to them, from ; (semicolon) to end of line. See Transaction comments, Posting com- ments, and Account comments below. Transactions Transactions are the main unit of information in a journal file. They represent events, typically a movement of some quantity of commodities between two or more named accounts. Each transaction is recorded as a journal entry, beginning with a sim- ple date in column 0. This can be followed by any of the following op- tional fields, separated by spaces: o a status character (empty, !, or *) o a code (any short number or text, enclosed in parentheses) o a description (any remaining text until end of line or a semicolon) o a comment (any remaining text following a semicolon until end of line, and any following indented lines beginning with a semicolon) o 0 or more indented posting lines, describing what was transferred and the accounts involved (indented comment lines are also allowed, but not blank lines or non-indented lines). Here's a simple journal file containing one transaction: 2008/01/01 income assets:bank:checking $1 income:salary $-1 Dates Simple dates Dates in the journal file use simple dates format: YYYY-MM-DD or YYYY/MM/DD or YYYY.MM.DD, with leading zeros optional. The year may be omitted, in which case it will be inferred from the context: the cur- rent transaction, the default year set with a Y directive, or the cur- rent date when the command is run. Some examples: 2010-01-31, 2010/01/31, 2010.1.31, 1/31. (The UI also accepts simple dates, as well as the more flexible smart dates documented in the hledger manual.) Posting dates You can give individual postings a different date from their parent transaction, by adding a posting comment containing a tag (see below) like date:DATE. This is probably the best way to control posting dates precisely. Eg in this example the expense should appear in May re- ports, and the deduction from checking should be reported on 6/1 for easy bank reconciliation: 2015/5/30 expenses:food $10 ; food purchased on saturday 5/30 assets:checking ; bank cleared it on monday, date:6/1 $ hledger -f t.j register food 2015-05-30 expenses:food $10 $10 $ hledger -f t.j register checking 2015-06-01 assets:checking $-10 $-10 DATE should be a simple date; if the year is not specified it will use the year of the transaction's date. The date: tag must have a valid simple date value if it is present, eg a date: tag with no value is not allowed. Status Transactions, or individual postings within a transaction, can have a status mark, which is a single character before the transaction de- scription or posting account name, separated from it by a space, indi- cating one of three statuses: mark status ------------------ unmarked ! pending * cleared When reporting, you can filter by status with the -U/--unmarked, -P/--pending, and -C/--cleared flags; or the status:, status:!, and status:* queries; or the U, P, C keys in hledger-ui. Note, in Ledger and in older versions of hledger, the "unmarked" state is called "uncleared". As of hledger 1.3 we have renamed it to un- marked for clarity. To replicate Ledger and old hledger's behaviour of also matching pend- ing, combine -U and -P. Status marks are optional, but can be helpful eg for reconciling with real-world accounts. Some editor modes provide highlighting and short- cuts for working with status. Eg in Emacs ledger-mode, you can toggle transaction status with C-c C-e, or posting status with C-c C-c. What "uncleared", "pending", and "cleared" actually mean is up to you. Here's one suggestion: status meaning -------------------------------------------------------------------------- uncleared recorded but not yet reconciled; needs review pending tentatively reconciled (if needed, eg during a big reconcil- iation) cleared complete, reconciled as far as possible, and considered cor- rect With this scheme, you would use -PC to see the current balance at your bank, -U to see things which will probably hit your bank soon (like un- cashed checks), and no flags to see the most up-to-date state of your finances. Code After the status mark, but before the description, you can optionally write a transaction "code", enclosed in parentheses. This is a good place to record a check number, or some other important transaction id or reference number. Description A transaction's description is the rest of the line following the date and status mark (or until a comment begins). Sometimes called the "narration" in traditional bookkeeping, it can be used for whatever you wish, or left blank. Transaction descriptions can be queried, unlike comments. Payee and note You can optionally include a | (pipe) character in descriptions to sub- divide the description into separate fields for payee/payer name on the left (up to the first |) and an additional note field on the right (af- ter the first |). This may be worthwhile if you need to do more pre- cise querying and pivoting by payee or by note. Transaction comments Text following ;, after a transaction description, and/or on indented lines immediately below it, form comments for that transaction. They are reproduced by print but otherwise ignored, except they may contain tags, which are not ignored. 2012-01-01 something ; a transaction comment ; a second line of transaction comment expenses 1 assets Postings A posting is an addition of some amount to, or removal of some amount from, an account. Each posting line begins with at least one space or tab (2 or 4 spaces is common), followed by: o (optional) a status character (empty, !, or *), followed by a space o (required) an account name (any text, optionally containing single spaces, until end of line or a double space) o (optional) two or more spaces or tabs followed by an amount. Positive amounts are being added to the account, negative amounts are being removed. The amounts within a transaction must always sum up to zero. As a con- venience, one amount may be left blank; it will be inferred so as to balance the transaction. Be sure to note the unusual two-space delimiter between account name and amount. This makes it easy to write account names containing spaces. But if you accidentally leave only one space (or tab) before the amount, the amount will be considered part of the account name. Account names Accounts are the main way of categorising things in hledger. As in Double Entry Bookkeeping, they can represent real world accounts (such as a bank account), or more abstract categories such as "money borrowed from Frank" or "money spent on electricity". You can use any account names you like, but we usually start with the traditional accounting categories, which in english are assets, liabil- ities, equity, revenues, expenses. (You might see these referred to as A, L, E, R, X for short.) For more precise reporting, we usually divide the top level accounts into more detailed subaccounts, by writing a full colon between account name parts. For example, from the account names assets:bank:checking and expenses:food, hledger will infer this hierarchy of five accounts: assets assets:bank assets:bank:checking expenses expenses:food Shown as an outline, the hierarchical tree structure is more clear: assets bank checking expenses food hledger reports can summarise the account tree to any depth, so you can go as deep as you like with subcategories, but keeping your account names relatively simple may be best when starting out. Account names may be capitalised or not; they may contain letters, num- bers, symbols, or single spaces. Note, when an account name and an amount are written on the same line, they must be separated by two or more spaces (or tabs). Parentheses or brackets enclosing the full account name indicate vir- tual postings, described below. Parentheses or brackets internal to the account name have no special meaning. Account names can be altered temporarily or permanently by account aliases. Amounts After the account name, there is usually an amount. (Important: be- tween account name and amount, there must be two or more spaces.) hledger's amount format is flexible, supporting several international formats. Here are some examples. Amounts have a number (the "quan- tity"): 1 ..and usually a currency symbol or commodity name (more on this below), to the left or right of the quantity, with or without a separating space: $1 4000 AAPL 3 "green apples" Amounts can be preceded by a minus sign (or a plus sign, though plus is the default), The sign can be written before or after a left-side com- modity symbol: -$1 $-1 One or more spaces between the sign and the number are acceptable when parsing (but they won't be displayed in output): + $1 $- 1 Scientific E notation is allowed: 1E-6 EUR 1E3 Decimal marks, digit group marks A decimal mark can be written as a period or a comma: 1.23 1,23 In the integer part of the quantity (left of the decimal mark), groups of digits can optionally be separated by a digit group mark - a space, comma, or period (different from the decimal mark): $1,000,000.00 EUR 2.000.000,00 INR 9,99,99,999.00 1 000 000.9455 hledger is not biased towards period or comma decimal marks, so a num- ber containing just one period or comma, like 1,000 or 1.000, is am- biguous. In such cases hledger assumes it is a decimal mark, parsing both of these as 1. To disambiguate these and ensure accurate number parsing, especially if you use digit group marks, we recommend declaring the decimal mark. You can declare it for each file with decimal-mark directives, or for each commodity with commodity directives (described below). Commodity Amounts in hledger have both a "quantity", which is a signed decimal number, and a "commodity", which is a currency symbol, stock ticker, or any word or phrase describing something you are tracking. If the commodity name contains non-letters (spaces, numbers, or punctu- ation), you must always write it inside double quotes ("green apples", "ABC123"). If you write just a bare number, that too will have a commodity, with name ""; we call that the "no-symbol commodity". Actually, hledger combines these single-commodity amounts into more powerful multi-commodity amounts, which are what it works with most of the time. A multi-commodity amount could be, eg: 1 USD, 2 EUR, 3.456 TSLA. In practice, you will only see multi-commodity amounts in hledger's output; you can't write them directly in the journal file. (If you are writing scripts or working with hledger's internals, these are the Amount and MixedAmount types.) Directives influencing number parsing and display You can add decimal-mark and commodity directives to the journal, to declare and control these things more explicitly and precisely. These are described below, but here's a quick example: # the decimal mark character used by all amounts in this file (all commodities) decimal-mark . # display styles for the $, EUR, INR and no-symbol commodities: commodity $1,000.00 commodity EUR 1.000,00 commodity INR 9,99,99,999.00 commodity 1 000 000.9455 Commodity display style For the amounts in each commodity, hledger chooses a consistent display style (symbol placement, decimal mark and digit group marks, number of decimal digits) to use in most reports. This is inferred as follows: First, if there's a D directive declaring a default commodity, that commodity symbol and amount format is applied to all no-symbol amounts in the journal. Then each commodity's display style is determined from its commodity directive. We recommend always declaring commodities with commodity directives, since they help ensure consistent display styles and preci- sions, and bring other benefits such as error checking for commodity symbols. But if a commodity directive is not present, hledger infers a commod- ity's display styles from its amounts as they are written in the jour- nal (excluding cost amounts and amounts in periodic transaction rules or auto posting rules). It uses o the symbol placement and decimal mark of the first amount seen o the digit group marks of the first amount with digit group marks o and the maximum number of decimal digits seen across all amounts. And as fallback if no applicable amounts are found, it would use a de- fault style, like $1000.00 (symbol on the left with no space, period as decimal mark, and two decimal digits). Finally, commodity styles can be overridden by the -c/--commodity-style command line option. Rounding Amounts are stored internally as decimal numbers with up to 255 decimal places. They are displayed with their original journal precisions by print and print-like reports, and rounded to their display precision (the number of decimal digits specified by the commodity display style) by other reports. When rounding, hledger uses banker's rounding (it rounds to the nearest even digit). So eg 0.5 displayed with zero deci- mal digits appears as "0". Costs After a posting amount, you can note its cost (when buying) or selling price (when selling) in another commodity, by writing either @ UNIT- PRICE or @@ TOTALPRICE after it. This indicates a conversion transac- tion, where one commodity is exchanged for another. (You might also see this called "transaction price" in hledger docs, discussions, or code; that term was directionally neutral and reminded that it is a price specific to a transaction, but we now just call it "cost", with the understanding that the transaction could be a purchase or a sale.) Costs are usually written explicitly with @ or @@, but can also be in- ferred automatically for simple multi-commodity transactions. Note, if costs are inferred, the order of postings is significant; the first posting will have a cost attached, in the commodity of the second. As an example, here are several ways to record purchases of a foreign currency in hledger, using the cost notation either explicitly or im- plicitly: 1. Write the price per unit, as @ UNITPRICE after the amount: 2009/1/1 assets:euros 100 @ $1.35 ; one hundred euros purchased at $1.35 each assets:dollars ; balancing amount is -$135.00 2. Write the total price, as @@ TOTALPRICE after the amount: 2009/1/1 assets:euros 100 @@ $135 ; one hundred euros purchased at $135 for the lot assets:dollars 3. Specify amounts for all postings, using exactly two commodities, and let hledger infer the price that balances the transaction. Note the effect of posting order: the price is added to first posting, making it 100 @@ $135, as in example 2: 2009/1/1 assets:euros 100 ; one hundred euros purchased assets:dollars $-135 ; for $135 Amounts can be converted to cost at report time using the -B/--cost flag; this is discussed more in the Cost reporting section. Note that the cost normally should be a positive amount, though it's not required to be. This can be a little confusing, see discussion at --infer-market-prices: market prices from transactions. Other cost/lot notations A slight digression for Ledger and Beancount users. Ledger has a num- ber of cost/lot-related notations: o @ UNITCOST and @@ TOTALCOST o expresses a conversion rate, as in hledger o when buying, also creates a lot than can be selected at selling time o (@) UNITCOST and (@@) TOTALCOST (virtual cost) o like the above, but also means "this cost was exceptional, don't use it when inferring market prices". Currently, hledger treats the above like @ and @@; the parentheses are ignored. o {=FIXEDUNITCOST} and {{=FIXEDTOTALCOST}} (fixed price) o when buying, means "this cost is also the fixed price, don't let it fluctuate in value reports" o {UNITCOST} and {{TOTALCOST}} (lot price) o can be used identically to @ UNITCOST and @@ TOTALCOST, also cre- ates a lot o when selling, combined with @ ..., specifies an investment lot by its cost basis; does not check if that lot is present o and related: [YYYY/MM/DD] (lot date) o when buying, attaches this acquisition date to the lot o when selling, selects a lot by its acquisition date o (SOME TEXT) (lot note) o when buying, attaches this note to the lot o when selling, selects a lot by its note Currently, hledger accepts any or all of the above in any order after the posting amount, but ignores them. (This can break transaction bal- ancing.) For Beancount users, the notation and behaviour is different: o @ UNITCOST and @@ TOTALCOST o expresses a cost without creating a lot, as in hledger o when buying (augmenting) or selling (reducing) a lot, combined with {...}: documents the cost/selling price (not used for transaction balancing) o {UNITCOST} and {{TOTALCOST}} o when buying (augmenting), expresses the cost for transaction bal- ancing, and also creates a lot with this cost basis attached o when selling (reducing), o selects a lot by its cost basis o raises an error if that lot is not present or can not be selected unambiguously (depending on booking method configured) o expresses the selling price for transaction balancing Currently, hledger accepts the {UNITCOST}/{{TOTALCOST}} notation but ignores it. o variations: {}, {YYYY-MM-DD}, {"LABEL"}, {UNITCOST, "LABEL"}, {UNIT- COST, YYYY-MM-DD, "LABEL"} etc. Currently, hledger rejects these. Balance assertions hledger supports Ledger-style balance assertions in journal files. These look like, for example, = EXPECTEDBALANCE following a posting's amount. Eg here we assert the expected dollar balance in accounts a and b after each posting: 2013/1/1 a $1 =$1 b =$-1 2013/1/2 a $1 =$2 b $-1 =$-2 After reading a journal file, hledger will check all balance assertions and report an error if any of them fail. Balance assertions can pro- tect you from, eg, inadvertently disrupting reconciled balances while cleaning up old entries. You can disable them temporarily with the -I/--ignore-assertions flag, which can be useful for troubleshooting or for reading Ledger files. (Note: this flag currently does not disable balance assignments, described below). Assertions and ordering hledger sorts an account's postings and assertions first by date and then (for postings on the same day) by parse order. Note this is dif- ferent from Ledger, which sorts assertions only by parse order. (Also, Ledger assertions do not see the accumulated effect of repeated post- ings to the same account within a transaction.) So, hledger balance assertions keep working if you reorder differ- ently-dated transactions within the journal. But if you reorder same-dated transactions or postings, assertions might break and require updating. This order dependence does bring an advantage: precise con- trol over the order of postings and assertions within a day, so you can assert intra-day balances. Assertions and multiple included files Multiple files included with the include directive are processed as if concatenated into one file, preserving their order and the posting or- der within each file. It means that balance assertions in later files will see balance from earlier files. And if you have multiple postings to an account on the same day, split across multiple files, and you want to assert the account's balance on that day, you'll need to put the assertion in the right file - the last one in the sequence, probably. Assertions and multiple -f files Unlike include, when multiple files are specified on the command line with multiple -f/--file options, balance assertions will not see bal- ance from earlier files. This can be useful when you do not want prob- lems in earlier files to disrupt valid assertions in later files. If you do want assertions to see balance from earlier files, use in- clude, or concatenate the files temporarily. Assertions and commodities The asserted balance must be a simple single-commodity amount, and in fact the assertion checks only this commodity's balance within the (possibly multi-commodity) account balance. This is how assertions work in Ledger also. We could call this a "partial" balance assertion. To assert the balance of more than one commodity in an account, you can write multiple postings, each asserting one commodity's balance. You can make a stronger "total" balance assertion by writing a double equals sign (== EXPECTEDBALANCE). This asserts that there are no other commodities in the account besides the asserted one (or at least, that their balance is 0). 2013/1/1 a $1 a 1 b $-1 c -1 2013/1/2 ; These assertions succeed a 0 = $1 a 0 = 1 b 0 == $-1 c 0 == -1 2013/1/3 ; This assertion fails as 'a' also contains 1 a 0 == $1 It's not yet possible to make a complete assertion about a balance that has multiple commodities. One workaround is to isolate each commodity into its own subaccount: 2013/1/1 a:usd $1 a:euro 1 b 2013/1/2 a 0 == 0 a:usd 0 == $1 a:euro 0 == 1 Assertions and costs Balance assertions ignore costs, and should normally be written without one: 2019/1/1 (a) $1 @ 1 = $1 We do allow costs to be written in balance assertion amounts, however, and print shows them, but they don't affect whether the assertion passes or fails. This is for backward compatibility (hledger's close command used to generate balance assertions with costs), and because balance assignments do use costs (see below). Assertions and subaccounts The balance assertions above (= and ==) do not count the balance from subaccounts; they check the account's exclusive balance only. You can assert the balance including subaccounts by writing =* or ==*, eg: 2019/1/1 equity:opening balances checking:a 5 checking:b 5 checking 1 ==* 11 Assertions and virtual postings Balance assertions always consider both real and virtual postings; they are not affected by the --real/-R flag or real: query. Assertions and auto postings Balance assertions are affected by the --auto flag, which generates auto postings, which can alter account balances. Because auto postings are optional in hledger, accounts affected by them effectively have two balances. But balance assertions can only test one or the other of these. So to avoid making fragile assertions, either: o assert the balance calculated with --auto, and always use --auto with that file o or assert the balance calculated without --auto, and never use --auto with that file o or avoid balance assertions on accounts affected by auto postings (or avoid auto postings entirely). Assertions and precision Balance assertions compare the exactly calculated amounts, which are not always what is shown by reports. Eg a commodity directive may limit the display precision, but this will not affect balance asser- tions. Balance assertion failure messages show exact amounts. Posting comments Text following ;, at the end of a posting line, and/or on indented lines immediately below it, form comments for that posting. They are reproduced by print but otherwise ignored, except they may contain tags, which are not ignored. 2012-01-01 expenses 1 ; a comment for posting 1 assets ; a comment for posting 2 ; a second comment line for posting 2 Tags Tags are a way to add extra labels or labelled data to transactions, postings, or accounts, which you can then search or pivot on. They are written as a word (optionally hyphenated) immediately followed by a full colon, in a transaction or posting or account directive's comment. (This is an exception to the usual rule that things in com- ments are ignored.) Eg, here four different tags are recorded: one on the checking account, two on the transaction, and one on the expenses posting: account assets:checking ; accounttag: 2017/1/16 bought groceries ; transactiontag-1: ; transactiontag-2: assets:checking $-1 expenses:food $1 ; postingtag: Postings also inherit tags from their transaction and their account. And transactions also acquire tags from their postings (and postings' accounts). So in the example above, the expenses posting effectively has all four tags (by inheriting from account and transaction), and the transaction also has all four tags (by acquiring from the expenses posting). You can list tag names with hledger tags [NAMEREGEX], or match by tag name with a tag:NAMEREGEX query. Tag values Tags can have a value, which is any text after the colon up until a comma or end of line (with surrounding whitespace removed). Note this means that hledger tag values can not contain commas. Eg in the fol- lowing posting, the three tags' values are "value 1", "value 2", and "" (empty) respectively: expenses:food $10 ; foo, tag1: value 1 , tag2:value 2, bar tag3: , baz Note that tags can be repeated, and are additive rather than overrid- ing: when the same tag name is seen again with a new value, the new name:value pair is added to the tags. (It is not possible to override a tag's value or remove a tag.) You can list a tag's values with hledger tags TAGNAME --values, or match by tag value with a tag:NAMEREGEX=VALUEREGEX query. Directives Besides transactions, there is something else you can put in a journal file: directives. These are declarations, beginning with a keyword, that modify hledger's behaviour. Some directives can have more spe- cific subdirectives, indented below them. hledger's directives are similar to Ledger's in many cases, but there are also many differences. Directives are not required, but can be useful. Here are the main di- rectives: purpose directive -------------------------------------------------------------------------- READING DATA: Rewrite account names alias Comment out sections of the file comment Declare file's decimal mark, to help decimal-mark parse amounts accurately Include other data files include GENERATING DATA: Generate recurring transactions or bud- ~ get goals Generate extra postings on existing = transactions CHECKING FOR ERRORS: Define valid entities to provide more account, commodity, payee, tag error checking REPORTING: Declare accounts' type and display order account Declare commodity display styles commodity Declare market prices P Directives and multiple files Directives vary in their scope, ie which journal entries and which in- put files they affect. Most often, a directive will affect the follow- ing entries and included files if any, until the end of the current file - and no further. You might find this inconvenient! For example, alias directives do not affect parent or sibling files. But there are usually workarounds; for example, put alias directives in your top-most file, before including other files. The restriction, though it may be annoying at first, is in a good cause; it allows reports to be stable and deterministic, independent of the order of input. Without it, reports could show different numbers depending on the order of -f options, or the positions of include di- rectives in your files. Directive effects Here are all hledger's directives, with their effects and scope sum- marised - nine main directives, plus four others which we consider non-essential: di- what it does ends rec- at tive file end? -------------------------------------------------------------------------------------- ac- Declares an account, for checking all entries in all files; and N count its display order and type. Subdirectives: any text, ignored. alias Rewrites account names, in following entries until end of cur- Y rent file or end aliases. Command line equivalent: --alias com- Ignores part of the journal file, until end of current file or Y ment end comment. com- Declares up to four things: 1. a commodity symbol, for checking N,Y,N,N mod- all amounts in all files 2. the decimal mark for parsing ity amounts of this commodity, in the following entries until end of current file (if there is no decimal-mark directive) 3. and the display style for amounts of this commodity 4. which is also the precision to use for balanced-transaction checking in this commodity. Takes precedence over D. Subdirectives: format (Ledger-compatible syntax). Command line equivalent: -c/--com- modity-style deci- Declares the decimal mark, for parsing amounts of all commodi- Y mal-mark ties in following entries until next decimal-mark or end of cur- rent file. Included files can override. Takes precedence over commodity and D. include Includes entries and directives from another file, as if they N were written inline. Command line alternative: multiple -f/--file payee Declares a payee name, for checking all entries in all files. N P Declares the market price of a commodity on some date, for value N reports. ~ Declares a periodic transaction rule that generates future N (tilde) transactions with --forecast and budget goals with balance --budget. Other syntax: apply Prepends a common parent account to all account names, in fol- Y account lowing entries until end of current file or end apply account. D Sets a default commodity to use for no-symbol amounts;and, if Y,Y,N,N there is no commodity directive for this commodity: its decimal mark, balancing precision, and display style, as above. Y Sets a default year to use for any yearless dates, in following Y entries until end of current file. = Declares an auto posting rule that generates extra postings on partly (equals) matched transactions with --auto, in current, parent, and child files (but not sibling files, see #1212). Other Other directives from Ledger's file format are accepted but ig- Ledger nored. direc- tives account directive account directives can be used to declare accounts (ie, the places that amounts are transferred from and to). Though not required, these dec- larations can provide several benefits: o They can document your intended chart of accounts, providing a refer- ence. o In strict mode, they restrict which accounts may be posted to by transactions, which helps detect typos. o They control account display order in reports, allowing non-alpha- betic sorting (eg Revenues to appear above Expenses). o They help with account name completion (in hledger add, hledger-web, hledger-iadd, ledger-mode, etc.) o They can store additional account information as comments, or as tags which can be used to filter or pivot reports. o They can help hledger know your accounts' types (asset, liability, equity, revenue, expense), affecting reports like balancesheet and incomestatement. They are written as the word account followed by a hledger-style ac- count name, eg: account assets:bank:checking Note, however, that accounts declared in account directives are not al- lowed to have surrounding brackets and parentheses, unlike accounts used in postings. So the following journal will not parse: account (assets:bank:checking) Account comments Text following two or more spaces and ; at the end of an account direc- tive line, and/or following ; on indented lines immediately below it, form comments for that account. They are ignored except they may con- tain tags, which are not ignored. The two-space requirement for same-line account comments is because ; is allowed in account names. account assets:bank:checking ; same-line comment, at least 2 spaces before the semicolon ; next-line comment ; some tags - type:A, acctnum:12345 Account subdirectives Ledger-style indented subdirectives are also accepted, but currently ignored: account assets:bank:checking format subdirective is ignored Account error checking By default, accounts need not be declared; they come into existence when a posting references them. This is convenient, but it means hledger can't warn you when you mis-spell an account name in the jour- nal. Usually you'll find that error later, as an extra account in bal- ance reports, or an incorrect balance when reconciling. In strict mode, enabled with the -s/--strict flag, hledger will report an error if any transaction uses an account name that has not been de- clared by an account directive. Some notes: o The declaration is case-sensitive; transactions must use the correct account name capitalisation. o The account directive's scope is "whole file and below" (see direc- tives). This means it affects all of the current file, and any files it includes, but not parent or sibling files. The position of ac- count directives within the file does not matter, though it's usual to put them at the top. o Accounts can only be declared in journal files, but will affect in- cluded files of all types. o It's currently not possible to declare "all possible subaccounts" with a wildcard; every account posted to must be declared. Account display order The order in which account directives are written influences the order in which accounts appear in reports, hledger-ui, hledger-web etc. By default accounts appear in alphabetical order, but if you add these ac- count directives to the journal file: account assets account liabilities account equity account revenues account expenses those accounts will be displayed in declaration order: $ hledger accounts -1 assets liabilities equity revenues expenses Any undeclared accounts are displayed last, in alphabetical order. Sorting is done at each level of the account tree, within each group of sibling accounts under the same parent. And currently, this directive: account other:zoo would influence the position of zoo among other's subaccounts, but not the position of other among the top-level accounts. This means: o you will sometimes declare parent accounts (eg account other above) that you don't intend to post to, just to customize their display or- der o sibling accounts stay together (you couldn't display x:y in between a:b and a:c). Account types hledger knows that accounts come in several types: assets, liabilities, expenses and so on. This enables easy reports like balancesheet and incomestatement, and filtering by account type with the type: query. As a convenience, hledger will detect these account types automatically if you are using common english-language top-level account names (de- scribed below). But generally we recommend you declare types explic- itly, by adding a type: tag to your top-level account directives. Sub- accounts will inherit the type of their parent. The tag's value should be one of the five main account types: o A or Asset (things you own) o L or Liability (things you owe) o E or Equity (investment/ownership; balanced counterpart of assets & liabilities) o R or Revenue (what you received money from, AKA income; technically part of Equity) o X or Expense (what you spend money on; technically part of Equity) or, it can be (these are used less often): o C or Cash (a subtype of Asset, indicating liquid assets for the cash- flow report) o V or Conversion (a subtype of Equity, for conversions (see Cost re- porting).) Here is a typical set of account type declarations: account assets ; type: A account liabilities ; type: L account equity ; type: E account revenues ; type: R account expenses ; type: X account assets:bank ; type: C account assets:cash ; type: C account equity:conversion ; type: V Here are some tips for working with account types. o The rules for inferring types from account names are as follows. These are just a convenience that sometimes help new users get going; if they don't work for you, just ignore them and declare your account types. See also Regular expressions. If account's name contains this (CI) regular expression: | its type is: --------------------------------------------------------------------|------------- ^assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|current)(:|$) | Cash ^assets?(:|$) | Asset ^(debts?|liabilit(y|ies))(:|$) | Liability ^equity:(trad(e|ing)|conversion)s?(:|$) | Conversion ^equity(:|$) | Equity ^(income|revenue)s?(:|$) | Revenue ^expenses?(:|$) | Expense o If you declare any account types, it's a good idea to declare an ac- count for all of the account types, because a mixture of declared and name-inferred types can disrupt certain reports. o Certain uses of account aliases can disrupt account types. See Rewriting accounts > Aliases and account types. o As mentioned above, subaccounts will inherit a type from their parent account. More precisely, an account's type is decided by the first of these that exists: 1. A type: declaration for this account. 2. A type: declaration in the parent accounts above it, preferring the nearest. 3. An account type inferred from this account's name. 4. An account type inferred from a parent account's name, preferring the nearest parent. 5. Otherwise, it will have no type. o For troubleshooting, you can list accounts and their types with: $ hledger accounts --types [ACCTPAT] [-DEPTH] [type:TYPECODES] alias directive You can define account alias rules which rewrite your account names, or parts of them, before generating reports. This can be useful for: o expanding shorthand account names to their full form, allowing easier data entry and a less verbose journal o adapting old journals to your current chart of accounts o experimenting with new account organisations, like a new hierarchy o combining two accounts into one, eg to see their sum or difference on one line o customising reports Account aliases also rewrite account names in account directives. They do not affect account names being entered via hledger add or hledger-web. Account aliases are very powerful. They are generally easy to use cor- rectly, but you can also generate invalid account names with them; more on this below. See also Rewrite account names. Basic aliases To set an account alias, use the alias directive in your journal file. This affects all subsequent journal entries in the current file or its included files (but note: not sibling or parent files). The spaces around the = are optional: alias OLD = NEW Or, you can use the --alias 'OLD=NEW' option on the command line. This affects all entries. It's useful for trying out aliases interactively. OLD and NEW are case sensitive full account names. hledger will re- place any occurrence of the old account name with the new one. Subac- counts are also affected. Eg: alias checking = assets:bank:wells fargo:checking ; rewrites "checking" to "assets:bank:wells fargo:checking", or "checking:a" to "assets:bank:wells fargo:checking:a" Regex aliases There is also a more powerful variant that uses a regular expression, indicated by wrapping the pattern in forward slashes. (This is the only place where hledger requires forward slashes around a regular ex- pression.) Eg: alias /REGEX/ = REPLACEMENT or: $ hledger --alias '/REGEX/=REPLACEMENT' ... Any part of an account name matched by REGEX will be replaced by RE- PLACEMENT. REGEX is case-insensitive as usual. If you need to match a forward slash, escape it with a backslash, eg /\/=:. If REGEX contains parenthesised match groups, these can be referenced by the usual backslash and number in REPLACEMENT: alias /^(.+):bank:([^:]+):(.*)/ = \1:\2 \3 ; rewrites "assets:bank:wells fargo:checking" to "assets:wells fargo checking" REPLACEMENT continues to the end of line (or on command line, to end of option argument), so it can contain trailing whitespace. Combining aliases You can define as many aliases as you like, using journal directives and/or command line options. Recursive aliases - where an account name is rewritten by one alias, then by another alias, and so on - are allowed. Each alias sees the effect of previously applied aliases. In such cases it can be important to understand which aliases will be applied and in which order. For (each account name in) each journal entry, we apply: 1. alias directives preceding the journal entry, most recently parsed first (ie, reading upward from the journal entry, bottom to top) 2. --alias options, in the order they appeared on the command line (left to right). In other words, for (an account name in) a given journal entry: o the nearest alias declaration before/above the entry is applied first o the next alias before/above that will be be applied next, and so on o aliases defined after/below the entry do not affect it. This gives nearby aliases precedence over distant ones, and helps pro- vide semantic stability - aliases will keep working the same way inde- pendent of which files are being read and in which order. In case of trouble, adding --debug=6 to the command line will show which aliases are being applied when. Aliases and multiple files As explained at Directives and multiple files, alias directives do not affect parent or sibling files. Eg in this command, hledger -f a.aliases -f b.journal account aliases defined in a.aliases will not affect b.journal. In- cluding the aliases doesn't work either: include a.aliases 2023-01-01 ; not affected by a.aliases foo 1 bar This means that account aliases should usually be declared at the start of your top-most file, like this: alias foo=Foo alias bar=Bar 2023-01-01 ; affected by aliases above foo 1 bar include c.journal ; also affected end aliases directive You can clear (forget) all currently defined aliases (seen in the jour- nal so far, or defined on the command line) with this directive: end aliases Aliases can generate bad account names Be aware that account aliases can produce malformed account names, which could cause confusing reports or invalid print output. For exam- ple, you could erase all account names: 2021-01-01 a:aa 1 b $ hledger print --alias '/.*/=' 2021-01-01 1 The above print output is not a valid journal. Or you could insert an illegal double space, causing print output that would give a different journal when reparsed: 2021-01-01 old 1 other $ hledger print --alias old="new USD" | hledger -f- print 2021-01-01 new USD 1 other Aliases and account types If an account with a type declaration (see Declaring accounts > Account types) is renamed by an alias, normally the account type remains in ef- fect. However, renaming in a way that reshapes the account tree (eg renaming parent accounts but not their children, or vice versa) could prevent child accounts from inheriting the account type of their parents. Secondly, if an account's type is being inferred from its name, renam- ing it by an alias could prevent or alter that. If you are using account aliases and the type: query is not matching accounts as you expect, try troubleshooting with the accounts command, eg something like: $ hledger accounts --alias assets=bassetts type:a commodity directive The commodity directive performs several functions: 1. It declares which commodity symbols may be used in the journal, en- abling useful error checking with strict mode or the check command. (See Commodity error checking below.) 2. It declares the precision with which this commodity's amounts should be compared when checking for balanced transactions. 3. It declares how this commodity's amounts should be displayed, eg their symbol placement, digit group mark if any, digit group sizes, decimal mark (period or comma), and the number of decimal places. (See Commodity display style above.) 4. It sets which decimal mark (period or comma) to expect when parsing subsequent amounts in this commodity (if there is no decimal-mark directive in effect. See Decimal marks, digit group marks above. For related dev discussion, see #793.) Declaring commodities solves several common parsing/display problems, so we recommend it. Generally you should put commodity directives at the top of your journal file (because function 4 is position-sensi- tive). Commodity directive syntax A commodity directive is normally the word commodity followed by a sam- ple amount (and optionally a comment). Only the amount's symbol and format is significant. Eg: commodity $1000.00 commodity 1.000,00 EUR commodity 1 000 000.0000 ; the no-symbol commodity Commodities do not have tags (tags in the comment will be ignored). A commodity directive's sample amount must always include a period or comma decimal mark (this rule helps disambiguate decimal marks and digit group marks). If you don't want to show any decimal digits, write the decimal mark at the end: commodity 1000. AAAA ; show AAAA with no decimals Commodity symbols containing spaces, numbers, or punctuation must be enclosed in double quotes, as usual: commodity 1.0000 "AAAA 2023" Commodity directives normally include a sample amount, but can declare only a symbol (ie, just function 1 above): commodity $ commodity INR commodity "AAAA 2023" commodity "" ; the no-symbol commodity Commodity directives may also be written with an indented format subdi- rective, as in Ledger. The symbol is repeated and must be the same in both places. Other subdirectives are currently ignored: ; display indian rupees with currency name on the left, ; thousands, lakhs and crores comma-separated, ; period as decimal point, and two decimal places. commodity INR format INR 1,00,00,000.00 an unsupported subdirective ; ignored by hledger Commodity error checking In strict mode (-s/--strict) (or when you run hledger check commodi- ties), hledger will report an error if an undeclared commodity symbol is used. (With one exception: zero amounts are always allowed to have no commodity symbol.) It works like account error checking (described above). decimal-mark directive You can use a decimal-mark directive - usually one per file, at the top of the file - to declare which character represents a decimal mark when parsing amounts in this file. It can look like decimal-mark . or decimal-mark , This prevents any ambiguity when parsing numbers in the file, so we recommend it, especially if the file contains digit group marks (eg thousands separators). include directive You can pull in the content of additional files by writing an include directive, like this: include FILEPATH Only journal files can include, and only journal, timeclock or timedot files can be included (not CSV files, currently). If the file path does not begin with a slash, it is relative to the current file's folder. A tilde means home directory, eg: include ~/main.journal. The path may contain glob patterns to match multiple files, eg: include *.journal. There is limited support for recursive wildcards: **/ (the slash is re- quired) matches 0 or more subdirectories. It's not super convenient since you have to avoid include cycles and including directories, but this can be done, eg: include */**/*.journal. The path may also be prefixed to force a specific file format, overrid- ing the file extension (as described in Data formats): include time- dot:~/notes/2023*.md. P directive The P directive declares a market price, which is a conversion rate be- tween two commodities on a certain date. This allows value reports to convert amounts of one commodity to their value in another, on or after that date. These prices are often obtained from a stock exchange, cryptocurrency exchange, the or foreign exchange market. The format is: P DATE COMMODITY1SYMBOL COMMODITY2AMOUNT DATE is a simple date, COMMODITY1SYMBOL is the symbol of the commodity being priced, and COMMODITY2AMOUNT is the amount (symbol and quantity) of commodity 2 that one unit of commodity 1 is worth on this date. Ex- amples: # one euro was worth $1.35 from 2009-01-01 onward: P 2009-01-01 $1.35 # and $1.40 from 2010-01-01 onward: P 2010-01-01 $1.40 The -V, -X and --value flags use these market prices to show amount values in another commodity. See Value reporting. payee directive payee PAYEE NAME This directive can be used to declare a limited set of payees which may appear in transaction descriptions. The "payees" check will report an error if any transaction refers to a payee that has not been declared. Eg: payee Whole Foods ; a comment Payees do not have tags (tags in the comment will be ignored). To declare the empty payee name, use "". payee "" Ledger-style indented subdirectives, if any, are currently ignored. tag directive tag TAGNAME This directive can be used to declare a limited set of tag names al- lowed in tags. TAGNAME should be a valid tag name (no spaces). Eg: tag item-id Any indented subdirectives are currently ignored. The "tags" check will report an error if any undeclared tag name is used. It is quite easy to accidentally create a tag through normal use of colons in comments(#comments]; if you want to prevent this, you can declare and check your tags . Periodic transactions The ~ directive declares a "periodic rule" which generates temporary extra transactions, usually recurring at some interval, when hledger is run with the --forecast flag. These "forecast transactions" are useful for forecasting future activity. They exist only for the duration of the report, and only when --forecast is used; they are not saved in the journal file by hledger. Periodic rules also have a second use: with the --budget flag they set budget goals for budgeting. Periodic rules can be a little tricky, so before you use them, read this whole section, or at least the following tips: 1. Two spaces accidentally added or omitted will cause you trouble - read about this below. 2. For troubleshooting, show the generated transactions with hledger print --forecast tag:generated or hledger register --forecast tag:generated. 3. Forecasted transactions will begin only after the last non-fore- casted transaction's date. 4. Forecasted transactions will end 6 months from today, by default. See below for the exact start/end rules. 5. period expressions can be tricky. Their documentation needs im- provement, but is worth studying. 6. Some period expressions with a repeating interval must begin on a natural boundary of that interval. Eg in weekly from DATE, DATE must be a monday. ~ weekly from 2019/10/1 (a tuesday) will give an error. 7. Other period expressions with an interval are automatically expanded to cover a whole number of that interval. (This is done to improve reports, but it also affects periodic transactions. Yes, it's a bit inconsistent with the above.) Eg: ~ every 10th day of month from 2023/01, which is equivalent to ~ every 10th day of month from 2023/01/01, will be adjusted to start on 2019/12/10. Periodic rule syntax A periodic transaction rule looks like a normal journal entry, with the date replaced by a tilde (~) followed by a period expression (mnemonic: ~ looks like a recurring sine wave.): # every first of month ~ monthly expenses:rent $2000 assets:bank:checking # every 15th of month in 2023's first quarter: ~ monthly from 2023-04-15 to 2023-06-16 expenses:utilities $400 assets:bank:checking The period expression is the same syntax used for specifying multi-pe- riod reports, just interpreted differently; there, it specifies report periods; here it specifies recurrence dates (the periods' start dates). Periodic rules and relative dates Partial or relative dates (like 12/31, 25, tomorrow, last week, next quarter) are usually not recommended in periodic rules, since the re- sults will change as time passes. If used, they will be interpreted relative to, in order of preference: 1. the first day of the default year specified by a recent Y directive 2. or the date specified with --today 3. or the date on which you are running the report. They will not be affected at all by report period or forecast period dates. Two spaces between period expression and description! If the period expression is followed by a transaction description, these must be separated by two or more spaces. This helps hledger know where the period expression ends, so that descriptions can not acciden- tally alter their meaning, as in this example: ; 2 or more spaces needed here, so the period is not understood as "every 2 months in 2023" ; || ; vv ~ every 2 months in 2023, we will review assets:bank:checking $1500 income:acme inc So, o Do write two spaces between your period expression and your transac- tion description, if any. o Don't accidentally write two spaces in the middle of your period ex- pression. Auto postings The = directive declares an "auto posting rule" which generates tempo- rary extra postings on existing transactions, when hledger is run with the --auto flag. (Remember, postings are the account name & amount lines.) The rule contains a query and one or more posting templates. Wherever the query matches an existing posting, the new posting(s) will be generated and added below that one. Optionally the generated amount(s) can depend on the matched posting's amount. These auto postings can be useful for, eg, adding tax postings with a standard percentage. They exist only for the duration of the report, and only when --auto is used; they are not saved in the journal file by hledger. Note that depending fully on generated data such as this has some draw- backs - it's less portable, less future-proof, less auditable by oth- ers, and less robust (eg your balance assertions will depend on whether you use or don't use --auto). An alternative is to use auto postings in "one time" fashion - use them to help build a complex journal entry, view it with hledger print --auto, and then copy that output into the journal file to make it permanent. Here's the journal file syntax. An auto posting rule looks a bit like a transaction: = QUERY ACCOUNT AMOUNT ... ACCOUNT [AMOUNT] except the first line is an equals sign (mnemonic: = suggests match- ing), followed by a query (which matches existing postings), and each "posting" line describes a posting to be generated, and the posting amounts can be: o a normal amount with a commodity symbol, eg $2. This will be used as-is. o a number, eg 2. The commodity symbol (if any) from the matched post- ing will be added to this. o a numeric multiplier, eg *2 (a star followed by a number N). The matched posting's amount (and total price, if any) will be multiplied by N. o a multiplier with a commodity symbol, eg *$2 (a star, number N, and symbol S). The matched posting's amount will be multiplied by N, and its commodity symbol will be replaced with S. Any query term containing spaces must be enclosed in single or double quotes, as on the command line. Eg, note the quotes around the second query term below: = expenses:groceries 'expenses:dining out' (budget:funds:dining out) *-1 Some examples: ; every time I buy food, schedule a dollar donation = expenses:food (liabilities:charity) $-1 ; when I buy a gift, also deduct that amount from a budget envelope subaccount = expenses:gifts assets:checking:gifts *-1 assets:checking *1 2017/12/1 expenses:food $10 assets:checking 2017/12/14 expenses:gifts $20 assets:checking $ hledger print --auto 2017-12-01 expenses:food $10 assets:checking (liabilities:charity) $-1 2017-12-14 expenses:gifts $20 assets:checking assets:checking:gifts -$20 assets:checking $20 Auto postings and multiple files An auto posting rule can affect any transaction in the current file, or in any parent file or child file. Note, currently it will not affect sibling files (when multiple -f/--file are used - see #1212). Auto postings and dates A posting date (or secondary date) in the matched posting, or (taking precedence) a posting date in the auto posting rule itself, will also be used in the generated posting. Auto postings and transaction balancing / inferred amounts / balance asser- tions Currently, auto postings are added: o after missing amounts are inferred, and transactions are checked for balancedness, o but before balance assertions are checked. Note this means that journal entries must be balanced both before and after auto postings are added. This changed in hledger 1.12+; see #893 for background. This also means that you cannot have more than one auto-posting with a missing amount applied to a given transaction, as it will be unable to infer amounts. Auto posting tags Automated postings will have some extra tags: o generated-posting:= QUERY - shows this was generated by an auto post- ing rule, and the query o _generated-posting:= QUERY - a hidden tag, which does not appear in hledger's output. This can be used to match postings generated "just now", rather than generated in the past and saved to the journal. Also, any transaction that has been changed by auto posting rules will have these tags added: o modified: - this transaction was modified o _modified: - a hidden tag not appearing in the comment; this transac- tion was modified "just now". Auto postings on forecast transactions only Tip: you can can make auto postings that will apply to forecast trans- actions but not recorded transactions, by adding tag:_generated-trans- action to their QUERY. This can be useful when generating new journal entries to be saved in the journal. Other syntax hledger journal format supports quite a few other features, mainly to make interoperating with or converting from Ledger easier. Note some of the features below are powerful and can be useful in special cases, but in general, features in this section are considered less important or even not recommended for most users. Downsides are mentioned to help you decide if you want to use them. Balance assignments Ledger-style balance assignments are also supported. These are like balance assertions, but with no posting amount on the left side of the equals sign; instead it is calculated automatically so as to satisfy the assertion. This can be a convenience during data entry, eg when setting opening balances: ; starting a new journal, set asset account balances 2016/1/1 opening balances assets:checking = $409.32 assets:savings = $735.24 assets:cash = $42 equity:opening balances or when adjusting a balance to reality: ; no cash left; update balance, record any untracked spending as a generic expense 2016/1/15 assets:cash = $0 expenses:misc The calculated amount depends on the account's balance in the commodity at that point (which depends on the previously-dated postings of the commodity to that account since the last balance assertion or assign- ment). Downsides: using balance assignments makes your journal less explicit; to know the exact amount posted, you have to run hledger or do the cal- culations yourself, instead of just reading it. Also balance assign- ments' forcing of balances can hide errors. These things make your fi- nancial data less portable, less future-proof, and less trustworthy in an audit. Balance assignments and prices A cost in a balance assignment will cause the calculated amount to have that price attached: 2019/1/1 (a) = $1 @ 2 $ hledger print --explicit 2019-01-01 (a) $1 @ 2 = $1 @ 2 Balance assignments and multiple files Balance assignments handle multiple files like balance assertions. They see balance from other files previously included from the current file, but not from previous sibling or parent files. Bracketed posting dates For setting posting dates and secondary posting dates, Ledger's brack- eted date syntax is also supported: [DATE], [DATE=DATE2] or [=DATE2] in posting comments. hledger will attempt to parse any square-bracketed sequence of the 0123456789/-.= characters in this way. With this syn- tax, DATE infers its year from the transaction and DATE2 infers its year from DATE. Downsides: another syntax to learn, redundant with hledger's date:/date2: tags, and confusingly similar to Ledger's lot date syntax. D directive D AMOUNT This directive sets a default commodity, to be used for any subsequent commodityless amounts (ie, plain numbers) seen while parsing the jour- nal. This effect lasts until the next D directive, or the end of the journal. For compatibility/historical reasons, D also acts like a commodity di- rective (setting the commodity's decimal mark for parsing and display style for output). So its argument is not just a commodity symbol, but a full amount demonstrating the style. The amount must include a deci- mal mark (either period or comma). Eg: ; commodity-less amounts should be treated as dollars ; (and displayed with the dollar sign on the left, thousands separators and two decimal places) D $1,000.00 1/1 a 5 ; <- commodity-less amount, parsed as $5 and displayed as $5.00 b Interactions with other directives: For setting a commodity's display style, a commodity directive has highest priority, then a D directive. For detecting a commodity's decimal mark during parsing, decimal-mark has highest priority, then commodity, then D. For checking commodity symbols with the check command, a commodity di- rective is required (hledger check commodities ignores D directives). Downsides: omitting commodity symbols makes your financial data less explicit, less portable, and less trustworthy in an audit. It is usu- ally an unsustainable shortcut; sooner or later you will want to track multiple commodities. D is overloaded with functions redundant with commodity and decimal-mark. And it works differently from Ledger's D. apply account directive This directive sets a default parent account, which will be prepended to all accounts in following entries, until an end apply account direc- tive or end of current file. Eg: apply account home 2010/1/1 food $10 cash end apply account is equivalent to: 2010/01/01 home:food $10 home:cash $-10 account directives are also affected, and so is any included content. Account names entered via hledger add or hledger-web are not affected. Account aliases, if any, are applied after the parent account is prepended. Downsides: this can make your financial data less explicit, less portable, and less trustworthy in an audit. Y directive Y YEAR or (deprecated backward-compatible forms): year YEAR apply year YEAR The space is optional. This sets a default year to be used for subse- quent dates which don't specify a year. Eg: Y2009 ; set default year to 2009 12/15 ; equivalent to 2009/12/15 expenses 1 assets year 2010 ; change default year to 2010 2009/1/30 ; specifies the year, not affected expenses 1 assets 1/31 ; equivalent to 2010/1/31 expenses 1 assets Downsides: omitting the year (from primary transaction dates, at least) makes your financial data less explicit, less portable, and less trust- worthy in an audit. Such dates can get separated from their corre- sponding Y directive, eg when evaluating a region of the journal in your editor. A missing Y directive makes reports dependent on today's date. Secondary dates A secondary date is written after the primary date, following an equals sign. If the year is omitted, the primary date's year is assumed. When running reports, the primary (left) date is used by default, but with the --date2 flag (or --aux-date or --effective), the secondary (right) date will be used instead. The meaning of secondary dates is up to you, but it's best to follow a consistent rule. Eg "primary = the bank's clearing date, secondary = date the transaction was initiated, if different". Downsides: makes your financial data more complicated, less portable, and less trustworthy in an audit. Keeping the meaning of the two dates consistent requires discipline, and you have to remember which report- ing mode is appropriate for a given report. Posting dates are simpler and better. Star comments Lines beginning with * (star/asterisk) are also comment lines. This feature allows Emacs users to insert org headings in their journal, al- lowing them to fold/unfold/navigate it like an outline when viewed with org mode. Downsides: another, unconventional comment syntax to learn. Decreases your journal's portability. And switching to Emacs org mode just for folding/unfolding meant losing the benefits of ledger mode; nowadays you can add outshine mode to ledger mode to get folding without losing ledger mode's features. Valuation expressions Ledger allows a valuation function or value to be written in double parentheses after an amount. hledger ignores these. Virtual postings A posting with parentheses around the account name ((some:account)) is called a unbalanced virtual posting. Such postings do not participate in transaction balancing. (And if you write them without an amount, a zero amount is always inferred.) These can occasionally be convenient for special circumstances, but they violate double entry bookkeeping and make your data less portable across applications, so many people avoid using them at all. A posting with brackets around the account name ([some:account]) is called a balanced virtual posting. The balanced virtual postings in a transaction must add up to zero, just like ordinary postings, but sepa- rately from them. These are not part of double entry bookkeeping ei- ther, but they are at least balanced. An example: 2022-01-01 buy food with cash, update budget envelope subaccounts, & something else assets:cash $-10 ; <- these balance each other expenses:food $7 ; <- expenses:food $3 ; <- [assets:checking:budget:food] $-10 ; <- and these balance each other [assets:checking:available] $10 ; <- (something:else) $5 ; <- this is not required to balance Ordinary postings, whose account names are neither parenthesised nor bracketed, are called real postings. You can exclude virtual postings from reports with the -R/--real flag or a real:1 query. Other Ledger directives These other Ledger directives are currently accepted but ignored. This allows hledger to read more Ledger files, but be aware that hledger's reports may differ from Ledger's if you use these. apply fixed COMM AMT apply tag TAG assert EXPR bucket / A ACCT capture ACCT REGEX check EXPR define VAR=EXPR end apply fixed end apply tag end apply year end tag eval / expr EXPR python PYTHONCODE tag NAME value EXPR --command-line-flags See also https://hledger.org/ledger.html for a detailed hledger/Ledger syntax comparison. CSV hledger can read CSV files (Character Separated Value - usually comma, semicolon, or tab) containing dated records, automatically converting each record into a transaction. (To learn about writing CSV, see CSV output.) For best error messages when reading CSV/TSV/SSV files, make sure they have a corresponding .csv, .tsv or .ssv file extension or use a hledger file prefix (see File Extension below). Each CSV file must be described by a corresponding rules file. This contains rules describing the CSV data (header line, fields lay- out, date format etc.), how to construct hledger transactions from it, and how to categorise transactions based on description or other at- tributes. By default hledger looks for a rules file named like the CSV file with an extra .rules extension, in the same directory. Eg when asked to read foo/FILE.csv, hledger looks for foo/FILE.csv.rules. You can spec- ify a different rules file with the --rules-file option. If no rules file is found, hledger will create a sample rules file, which you'll need to adjust. At minimum, the rules file must identify the date and amount fields, and often it also specifies the date format and how many header lines there are. Here's a simple CSV file and a rules file for it: Date, Description, Id, Amount 12/11/2019, Foo, 123, 10.23 # basic.csv.rules skip 1 fields date, description, , amount date-format %d/%m/%Y $ hledger print -f basic.csv 2019-11-12 Foo expenses:unknown 10.23 income:unknown -10.23 There's an introductory Importing CSV data tutorial on hledger.org, and more CSV rules examples below, and a larger collection at https://github.com/simonmichael/hledger/tree/master/examples/csv. CSV rules cheatsheet The following kinds of rule can appear in the rules file, in any order. (Blank lines and lines beginning with # or ; or * are ignored.) source optionally declare which file to read data from separator declare the field separator, instead of rely- ing on file extension skip skip one or more header lines at start of file date-format declare how to parse CSV dates/date-times timezone declare the time zone of ambiguous CSV date-times newest-first improve txn order when: there are multiple records, newest first, all with the same date intra-day-reversed improve txn order when: same-day txns are in opposite order to the overall file decimal-mark declare the decimal mark used in CSV amounts, when ambiguous fields list name CSV fields for easy reference, and op- tionally assign their values to hledger fields Field assignment assign a CSV value or interpolated text value to a hledger field if block conditionally assign values to hledger fields, or skip a record or end (skip rest of file) if table conditionally assign values to hledger fields, using compact syntax balance-type select which type of balance assertions/as- signments to generate include inline another CSV rules file Working with CSV tips can be found below, including How CSV rules are evaluated. source If you tell hledger to read a csv file with -f foo.csv, it will look for rules in foo.csv.rules. Or, you can tell it to read the rules file, with -f foo.csv.rules, and it will look for data in foo.csv (since 1.30). These are mostly equivalent, but the second method provides some extra features. For one, the data file can be missing, without causing an error; it is just considered empty. And, you can specify a different data file by adding a "source" rule: source ./Checking1.csv If you specify just a file name with no path, hledger will look for it in your system's downloads directory (~/Downloads, currently): source Checking1.csv And if you specify a glob pattern, hledger will read the most recent of the matched files (useful with repeated downloads): source Checking1*.csv See also "Working with CSV > Reading files specified by rule". separator You can use the separator rule to read other kinds of character-sepa- rated data. The argument is any single separator character, or the words tab or space (case insensitive). Eg, for comma-separated values (CSV): separator , or for semicolon-separated values (SSV): separator ; or for tab-separated values (TSV): separator TAB If the input file has a .csv, .ssv or .tsv file extension (or a csv:, ssv:, tsv: prefix), the appropriate separator will be inferred automat- ically, and you won't need this rule. skip skip N The word skip followed by a number (or no number, meaning 1) tells hledger to ignore this many non-empty lines at the start of the input data. You'll need this whenever your CSV data contains header lines. Note, empty and blank lines are skipped automatically, so you don't need to count those. skip has a second meaning: it can be used inside if blocks (described below), to skip one or more records whenever the condition is true. Records skipped in this way are ignored, except they are still required to be valid CSV. date-format date-format DATEFMT This is a helper for the date (and date2) fields. If your CSV dates are not formatted like YYYY-MM-DD, YYYY/MM/DD or YYYY.MM.DD, you'll need to add a date-format rule describing them with a strptime-style date parsing pattern - see https://hackage.haskell.org/pack- age/time/docs/Data-Time-Format.html#v:formatTime. The pattern must parse the CSV date value completely. Some examples: # MM/DD/YY date-format %m/%d/%y # D/M/YYYY # The - makes leading zeros optional. date-format %-d/%-m/%Y # YYYY-Mmm-DD date-format %Y-%h-%d # M/D/YYYY HH:MM AM some other junk # Note the time and junk must be fully parsed, though only the date is used. date-format %-m/%-d/%Y %l:%M %p some other junk timezone timezone TIMEZONE When CSV contains date-times that are implicitly in some time zone other than yours, but containing no explicit time zone information, you can use this rule to declare the CSV's native time zone, which helps prevent off-by-one dates. When the CSV date-times do contain time zone information, you don't need this rule; instead, use %Z in date-format (or %z, %EZ, %Ez; see the formatTime link above). In either of these cases, hledger will do a time-zone-aware conversion, localising the CSV date-times to your current system time zone. If you prefer to localise to some other time zone, eg for reproducibility, you can (on unix at least) set the output timezone with the TZ environment variable, eg: $ TZ=-1000 hledger print -f foo.csv # or TZ=-1000 hledger import foo.csv timezone currently does not understand timezone names, except "UTC", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", "PST", or "PDT". For others, use numeric format: +HHMM or -HHMM. newest-first hledger tries to ensure that the generated transactions will be ordered chronologically, including same-day transactions. Usually it can auto-detect how the CSV records are ordered. But if it encounters CSV where all records are on the same date, it assumes that the records are oldest first. If in fact the CSV's records are normally newest first, like: 2022-10-01, txn 3... 2022-10-01, txn 2... 2022-10-01, txn 1... you can add the newest-first rule to help hledger generate the transac- tions in correct order. # same-day CSV records are newest first newest-first intra-day-reversed If CSV records within a single day are ordered opposite to the overall record order, you can add the intra-day-reversed rule to improve the order of journal entries. Eg, here the overall record order is newest first, but same-day records are oldest first: 2022-10-02, txn 3... 2022-10-02, txn 4... 2022-10-01, txn 1... 2022-10-01, txn 2... # transactions within each day are reversed with respect to the overall date order intra-day-reversed decimal-mark decimal-mark . or: decimal-mark , hledger automatically accepts either period or comma as a decimal mark when parsing numbers (cf Amounts). However if any numbers in the CSV contain digit group marks, such as thousand-separating commas, you should declare the decimal mark explicitly with this rule, to avoid misparsed numbers. fields list fields FIELDNAME1, FIELDNAME2, ... A fields list (the word fields followed by comma-separated field names) is optional, but convenient. It does two things: 1. It names the CSV field in each column. This can be convenient if you are referencing them in other rules, so you can say %SomeField instead of remembering %13. 2. Whenever you use one of the special hledger field names (described below), it assigns the CSV value in this position to that hledger field. This is the quickest way to populate hledger's fields and build a transaction. Here's an example that says "use the 1st, 2nd and 4th fields as the transaction's date, description and amount; name the last two fields for later reference; and ignore the others": fields date, description, , amount, , , somefield, anotherfield In a fields list, the separator is always comma; it is unrelated to the CSV file's separator. Also: o There must be least two items in the list (at least one comma). o Field names may not contain spaces. Spaces before/after field names are optional. o Field names may contain _ (underscore) or - (hyphen). o Fields you don't care about can be given a dummy name or an empty name. If the CSV contains column headings, it's convenient to use these for your field names, suitably modified (eg lower-cased with spaces re- placed by underscores). Sometimes you may want to alter a CSV field name to avoid assigning to a hledger field with the same name. Eg you could call the CSV's "bal- ance" field balance_ to avoid directly setting hledger's balance field (and generating a balance assertion). Field assignment HLEDGERFIELD FIELDVALUE Field assignments are the more flexible way to assign CSV values to hledger fields. They can be used instead of or in addition to a fields list (see above). To assign a value to a hledger field, write the field name (any of the standard hledger field/pseudo-field names, defined below), a space, followed by a text value on the same line. This text value may inter- polate CSV fields, referenced either by their 1-based position in the CSV record (%N) or by the name they were given in the fields list (%CSVFIELD), and regular expression match groups (\N). Some examples: # set the amount to the 4th CSV field, with " USD" appended amount %4 USD # combine three fields to make a comment, containing note: and date: tags comment note: %somefield - %anotherfield, date: %1 Tips: o Interpolation strips outer whitespace (so a CSV value like " 1 " be- comes 1 when interpolated) (#1051). o Interpolations always refer to a CSV field - you can't interpolate a hledger field. (See Referencing other fields below). Field names Note the two kinds of field names mentioned here, and used only in hledger CSV rules files: 1. CSV field names (CSVFIELD in these docs): you can optionally name the CSV columns for easy reference (since hledger doesn't yet auto- matically recognise column headings in a CSV file), by writing arbi- trary names in a fields list, eg: fields When, What, Some_Id, Net, Total, Foo, Bar 2. Special hledger field names (HLEDGERFIELD in these docs): you must set at least some of these to generate the hledger transaction from a CSV record, by writing them as the left hand side of a field as- signment, eg: date %When code %Some_Id description %What comment %Foo %Bar amount1 $ %Total or directly in a fields list: fields date, description, code, , amount1, Foo, Bar currency $ comment %Foo %Bar Here are all the special hledger field names available, and what hap- pens when you assign values to them: date field Assigning to date sets the transaction date. date2 field date2 sets the transaction's secondary date, if any. status field status sets the transaction's status, if any. code field code sets the transaction's code, if any. description field description sets the transaction's description, if any. comment field comment sets the transaction's comment, if any. commentN, where N is a number, sets the Nth posting's comment. You can assign multi-line comments by writing literal \n in the code. A comment starting with \n will begin on a new line. Comments can contain tags, as usual. account field Assigning to accountN, where N is 1 to 99, sets the account name of the Nth posting, and causes that posting to be generated. Most often there are two postings, so you'll want to set account1 and account2. Typically account1 is associated with the CSV file, and is set once with a top-level assignment, while account2 is set based on each transaction's description, in conditional rules. If a posting's account name is left unset but its amount is set (see below), a default account name will be chosen (like "expenses:unknown" or "income:unknown"). amount field There are several ways to set posting amounts from CSV, useful in dif- ferent situations. 1. amount is the oldest and simplest. Assigning to this sets the amount of the first and second postings. In the second posting, the amount will be negated; also, if it has a cost attached, it will be converted to cost. 2. amount-in and amount-out work exactly like the above, but should be used when the CSV has two amount fields (such as "Debit" and "Credit", or "Inflow" and "Outflow"). Whichever field has a non-zero value will be used as the amount of the first and second postings. Here are some tips to avoid confusion: o It's not "amount-in for posting 1 and amount-out for posting 2", it is "extract a single amount from the amount-in or amount-out field, and use that for posting 1 and (negated) for posting 2". o Don't use both amount and amount-in/amount-out in the same rules file; choose based on whether the amount is in a single CSV field or spread across two fields. o In each record, at most one of the two CSV fields should contain a non-zero amount; the other field must contain a zero or noth- ing. o hledger assumes both CSV fields contain unsigned numbers, and it automatically negates the amount-out values. o If the data doesn't fit these requirements, you'll probably need an if rule (see below). 3. amountN (where N is a number from 1 to 99) sets the amount of only a single posting: the Nth posting in the transaction. You'll usually need at least two such assignments to make a balanced transaction. You can also generate more than two postings, to represent more com- plex transactions. The posting numbers don't have to be consecu- tive; with if rules, higher posting numbers can be useful to ensure a certain order of postings. 4. amountN-in and amountN-out work exactly like the above, but should be used when the CSV has two amount fields. This is analogous to amount-in and amount-out, and those tips also apply here. 5. Remember that a fields list can also do assignments. So in a fields list if you name a CSV field "amount", that counts as assigning to amount. (If you don't want that, call it something else in the fields list, like "amount_".) 6. The above don't handle every situation; if you need more flexibil- ity, use an if rule to set amounts conditionally. See "Working with CSV > Setting amounts" below for more on this and on amount-setting generally. currency field currency sets a currency symbol, to be prepended to all postings' amounts. You can use this if the CSV amounts do not have a currency symbol, eg if it is in a separate column. currencyN prepends a currency symbol to just the Nth posting's amount. balance field balanceN sets a balance assertion amount (or if the posting amount is left empty, a balance assignment) on posting N. balance is a compatibility spelling for hledger <1.17; it is equivalent to balance1. You can adjust the type of assertion/assignment with the balance-type rule (see below). See Tips below for more about setting amounts and currency. if block Rules can be applied conditionally, depending on patterns in the CSV data. This allows flexibility; in particular, it is how you can cate- gorise transactions, selecting an appropriate account name based on their description (for example). There are two ways to write condi- tional rules: "if blocks", described here, and "if tables", described below. An if block is the word if and one or more "matcher" expressions (can be a word or phrase), one per line, starting either on the same or next line; followed by one or more indented rules. Eg, if MATCHER RULE or if MATCHER MATCHER MATCHER RULE RULE If any of the matchers succeeds, all of the indented rules will be ap- plied. They are usually field assignments, but the following special rules may also be used within an if block: o skip - skips the matched CSV record (generating no transaction from it) o end - skips the rest of the current CSV file. Some examples: # if the record contains "groceries", set account2 to "expenses:groceries" if groceries account2 expenses:groceries # if the record contains any of these phrases, set account2 and a transaction comment as shown if monthly service fee atm transaction fee banking thru software account2 expenses:business:banking comment XXX deductible ? check it # if an empty record is seen (assuming five fields), ignore the rest of the CSV file if ,,,, end Matchers There are two kinds: 1. A record matcher is a word or single-line text fragment or regular expression (REGEX), which hledger will try to match case-insensi- tively anywhere within the CSV record. Eg: whole foods 2. A field matcher is preceded with a percent sign and CSV field name (%CSVFIELD REGEX). hledger will try to match these just within the named CSV field. Eg: %date 2023 The regular expression is (as usual in hledger) a POSIX extended regu- lar expression, that also supports GNU word boundaries (\b, \B, \<, \>), and nothing else. If you have trouble, see "Regular expressions" in the hledger manual (https://hledger.org/hledger.html#regular-expres- sions). What matchers match With record matchers, it's important to know that the record matched is not the original CSV record, but a modified one: separators will be converted to commas, and enclosing double quotes (but not enclosing whitespace) are removed. So for example, when reading an SSV file, if the original record was: 2023-01-01; "Acme, Inc."; 1,000 the regex would see, and try to match, this modified record text: 2023-01-01,Acme, Inc., 1,000 Combining matchers When an if block has multiple matchers, they are combined as follows: o By default they are OR'd (any one of them can match) o When a matcher is preceded by ampersand (&) it will be AND'ed with the previous matcher (both of them must match) o When a matcher is preceded by an exclamation mark (!), the matcher is negated (it may not match). Currently there is a limitation: you can't use both & and ! on the same line (you can't AND a negated matcher). Match groups Matchers can define match groups: parenthesised portions of the regular expression which are available for reference in field assignments. Groups are enclosed in regular parentheses (( and )) and can be nested. Each group is available in field assignments using the token \N, where N is an index into the match groups for this conditional block (e.g. \1, \2, etc.). Example: Warp credit card payment postings to the beginning of the billing period (Month start), to match how they are presented in state- ments, using posting dates: if %date (....-..)-.. comment2 date:\1-01 Another example: Read the expense account from the CSV field, but throw away a prefix: if %account1 liabilities:family:(expenses:.*) account1 \1 if table "if tables" are an alternative to if blocks; they can express many matchers and field assignments in a more compact tabular format, like this: if,HLEDGERFIELD1,HLEDGERFIELD2,... MATCHERA,VALUE1,VALUE2,... MATCHERB,VALUE1,VALUE2,... MATCHERC,VALUE1,VALUE2,... The first character after if is taken to be this if table's field sepa- rator. It is unrelated to the separator used in the CSV file. It should be a non-alphanumeric character like , or | that does not appear anywhere else in the table (it should not be used in field names or matchers or values, and it cannot be escaped with a backslash). Each line must contain the same number of separators; empty values are allowed. Whitespace can be used in the matcher lines for readability (but not in the if line, currently). The table must be terminated by an empty line (or end of file). An if table like the above is interpreted as follows: try all of the matchers; whenever a matcher succeeds, assign all of the values on that line to the corresponding hledger fields; later lines can overrider earlier ones. It is equivalent to this sequence of if blocks: if MATCHERA HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERB HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERC HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... Example: if,account2,comment atm transaction fee,expenses:business:banking,deductible? check it %description groceries,expenses:groceries, 2023/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call-out balance-type Balance assertions generated by assigning to balanceN are of the simple = type by default, which is a single-commodity, subaccount-excluding assertion. You may find the subaccount-including variants more useful, eg if you have created some virtual subaccounts of checking to help with budgeting. You can select a different type of assertion with the balance-type rule: # balance assertions will consider all commodities and all subaccounts balance-type ==* Here are the balance assertion types for quick reference: = single commodity, exclude subaccounts =* single commodity, include subaccounts == multi commodity, exclude subaccounts ==* multi commodity, include subaccounts include include RULESFILE This includes the contents of another CSV rules file at this point. RULESFILE is an absolute file path or a path relative to the current file's directory. This can be useful for sharing common rules between several rules files, eg: # someaccount.csv.rules ## someaccount-specific rules fields date,description,amount account1 assets:someaccount account2 expenses:misc ## common rules include categorisation.rules Working with CSV Some tips: Rapid feedback It's a good idea to get rapid feedback while creating/troubleshooting CSV rules. Here's a good way, using entr from eradman.com/entrproject: $ ls foo.csv* | entr bash -c 'echo ----; hledger -f foo.csv print desc:SOMEDESC' A desc: query (eg) is used to select just one, or a few, transactions of interest. "bash -c" is used to run multiple commands, so we can echo a separator each time the command re-runs, making it easier to read the output. Valid CSV Note that hledger will only accept valid CSV conforming to RFC 4180, and equivalent SSV and TSV formats (like RFC 4180 but with semicolon or tab as separators). This means, eg: o Values may be enclosed in double quotes, or not. Enclosing in single quotes is not allowed. (Eg 'A','B' is rejected.) o When values are enclosed in double quotes, spaces outside the quotes are not allowed. (Eg "A", "B" is rejected.) o When values are not enclosed in quotes, they may not contain double quotes. (Eg A"A, B is rejected.) If your CSV/SSV/TSV is not valid in this sense, you'll need to trans- form it before reading with hledger. Try using sed, or a more permis- sive CSV parser like python's csv lib. File Extension To help hledger choose the CSV file reader and show the right error messages (and choose the right field separator character by default), it's best if CSV/SSV/TSV files are named with a .csv, .ssv or .tsv filename extension. (More about this at Data formats.) When reading files with the "wrong" extension, you can ensure the CSV reader (and the default field separator) by prefixing the file path with csv:, ssv: or tsv:: Eg: $ hledger -f ssv:foo.dat print You can also override the default field separator with a separator rule if needed. Reading CSV from standard input You'll need the file format prefix when reading CSV from stdin also, since hledger assumes journal format by default. Eg: $ cat foo.dat | hledger -f ssv:- print Reading multiple CSV files If you use multiple -f options to read multiple CSV files at once, hledger will look for a correspondingly-named rules file for each CSV file. But if you use the --rules-file option, that rules file will be used for all the CSV files. Reading files specified by rule Instead of specifying a CSV file in the command line, you can specify a rules file, as in hledger -f foo.csv.rules CMD. By default this will read data from foo.csv in the same directory, but you can add a source rule to specify a different data file, perhaps located in your web browser's download directory. This feature was added in hledger 1.30, so you won't see it in most CSV rules examples. But it helps remove some of the busywork of managing CSV downloads. Most of your financial institutions's default CSV file- names are different and can be recognised by a glob pattern. So you can put a rule like source Checking1*.csv in foo-checking.csv.rules, and then periodically follow a workflow like: 1. Download CSV from Foo's website, using your browser's defaults 2. Run hledger import foo-checking.csv.rules to import any new transac- tions After import, you can: discard the CSV, or leave it where it is for a while, or move it into your archives, as you prefer. If you do noth- ing, next time your browser will save something like Checking1-2.csv, and hledger will use that because of the * wild card and because it is the most recent. Valid transactions After reading a CSV file, hledger post-processes and validates the gen- erated journal entries as it would for a journal file - balancing them, applying balance assignments, and canonicalising amount styles. Any errors at this stage will be reported in the usual way, displaying the problem entry. There is one exception: balance assertions, if you have generated them, will not be checked, since normally these will work only when the CSV data is part of the main journal. If you do need to check balance as- sertions generated from CSV right away, pipe into another hledger: $ hledger -f file.csv print | hledger -f- print Deduplicating, importing When you download a CSV file periodically, eg to get your latest bank transactions, the new file may overlap with the old one, containing some of the same records. The import command will (a) detect the new transactions, and (b) append just those transactions to your main journal. It is idempotent, so you don't have to remember how many times you ran it or with which version of the CSV. (It keeps state in a hidden .latest.FILE.csv file.) This is the easiest way to import CSV data. Eg: # download the latest CSV files, then run this command. # Note, no -f flags needed here. $ hledger import *.csv [--dry] This method works for most CSV files. (Where records have a stable chronological order, and new records appear only at the new end.) A number of other tools and workflows, hledger-specific and otherwise, exist for converting, deduplicating, classifying and managing CSV data. See: o https://hledger.org/cookbook.html#setups-and-workflows o https://plaintextaccounting.org -> data import/conversion Setting amounts Continuing from amount field above, here are more tips for amount-set- ting: 1. If the amount is in a single CSV field: a. If its sign indicates direction of flow: Assign it to amountN, to set the Nth posting's amount. N is usu- ally 1 or 2 but can go up to 99. b. If another field indicates direction of flow: Use one or more conditional rules to set the appropriate amount sign. Eg: # assume a withdrawal unless Type contains "deposit": amount1 -%Amount if %Type deposit amount1 %Amount 2. If the amount is in two CSV fields (such as Debit and Credit, or In and Out): a. If both fields are unsigned: Assign one field to amountN-in and the other to amountN-out. hledger will automatically negate the "out" field, and will use whichever field value is non-zero as posting N's amount. b. If either field is signed: You will probably need to override hledger's sign for one or the other field, as in the following example: # Negate the -out value, but only if it is not empty: fields date, description, amount1-in, amount1-out if %amount1-out [1-9] amount1-out -%amount1-out c. If both fields can contain a non-zero value (or both can be empty): The -in/-out rules normally choose the value which is non-zero/non-empty. Some value pairs can be ambiguous, such as 1 and none. For such cases, use conditional rules to help select the amount. Eg, to handle the above you could select the value con- taining non-zero digits: fields date, description, in, out if %in [1-9] amount1 %in if %out [1-9] amount1 %out 3. If you want posting 2's amount converted to cost: Use the unnumbered amount (or amount-in and amount-out) syntax. 4. If the CSV has only balance amounts, not transaction amounts: Assign to balanceN, to set a balance assignment on the Nth posting, causing the posting's amount to be calculated automatically. balance with no number is equivalent to balance1. In this situation hledger is more likely to guess the wrong default account name, so you may need to set that explicitly. Amount signs There is some special handling making it easier to parse and to reverse amount signs. (This only works for whole amounts, not for cost amounts such as COST in amount1 AMT @ COST): o If an amount value begins with a plus sign: that will be removed: +AMT becomes AMT o If an amount value is parenthesised: it will be de-parenthesised and sign-flipped: (AMT) becomes -AMT o If an amount value has two minus signs (or two sets of parentheses, or a minus sign and parentheses): they cancel out and will be removed: --AMT or -(AMT) becomes AMT o If an amount value contains just a sign (or just a set of parenthe- ses): that is removed, making it an empty value. "+" or "-" or "()" becomes "". It's not possible (without preprocessing the CSV) to set an amount to its absolute value, ie discard its sign. Setting currency/commodity If the currency/commodity symbol is included in the CSV's amount field(s): 2023-01-01,foo,$123.00 you don't have to do anything special for the commodity symbol, it will be assigned as part of the amount. Eg: fields date,description,amount 2023-01-01 foo expenses:unknown $123.00 income:unknown $-123.00 If the currency is provided as a separate CSV field: 2023-01-01,foo,USD,123.00 You can assign that to the currency pseudo-field, which has the special effect of prepending itself to every amount in the transaction (on the left, with no separating space): fields date,description,currency,amount 2023-01-01 foo expenses:unknown USD123.00 income:unknown USD-123.00 Or, you can use a field assignment to construct the amount yourself, with more control. Eg to put the symbol on the right, and separated by a space: fields date,description,cur,amt amount %amt %cur 2023-01-01 foo expenses:unknown 123.00 USD income:unknown -123.00 USD Note we used a temporary field name (cur) that is not currency - that would trigger the prepending effect, which we don't want here. Amount decimal places Like amounts in a journal file, the amounts generated by CSV rules like amount1 influence commodity display styles, such as the number of deci- mal places displayed in reports. The original amounts as written in the CSV file do not affect display style (because we don't yet reliably know their commodity). Referencing other fields In field assignments, you can interpolate only CSV fields, not hledger fields. In the example below, there's both a CSV field and a hledger field named amount1, but %amount1 always means the CSV field, not the hledger field: # Name the third CSV field "amount1" fields date,description,amount1 # Set hledger's amount1 to the CSV amount1 field followed by USD amount1 %amount1 USD # Set comment to the CSV amount1 (not the amount1 assigned above) comment %amount1 Here, since there's no CSV amount1 field, %amount1 will produce a lit- eral "amount1": fields date,description,csvamount amount1 %csvamount USD # Can't interpolate amount1 here comment %amount1 When there are multiple field assignments to the same hledger field, only the last one takes effect. Here, comment's value will be be B, or C if "something" is matched, but never A: comment A comment B if something comment C How CSV rules are evaluated Here's how to think of CSV rules being evaluated (if you really need to). First, o include - all includes are inlined, from top to bottom, depth first. (At each include point the file is inlined and scanned for further includes, recursively, before proceeding.) Then "global" rules are evaluated, top to bottom. If a rule is re- peated, the last one wins: o skip (at top level) o date-format o newest-first o fields - names the CSV fields, optionally sets up initial assignments to hledger fields Then for each CSV record in turn: o test all if blocks. If any of them contain a end rule, skip all re- maining CSV records. Otherwise if any of them contain a skip rule, skip that many CSV records. If there are multiple matched skip rules, the first one wins. o collect all field assignments at top level and in matched if blocks. When there are multiple assignments for a field, keep only the last one. o compute a value for each hledger field - either the one that was as- signed to it (and interpolate the %CSVFIELD references), or a default o generate a hledger transaction (journal entry) from these values. This is all part of the CSV reader, one of several readers hledger can use to parse input files. When all files have been read successfully, the transactions are passed as input to whichever hledger command the user specified. Well factored rules Some things than can help reduce duplication and complexity in rules files: o Extracting common rules usable with multiple CSV files into a com- mon.rules, and adding include common.rules to each CSV's rules file. o Splitting if blocks into smaller if blocks, extracting the frequently used parts. CSV rules examples Bank of Ireland Here's a CSV with two amount fields (Debit and Credit), and a balance field, which we can use to add balance assertions, which is not neces- sary but provides extra error checking: Date,Details,Debit,Credit,Balance 07/12/2012,LODGMENT 529898,,10.0,131.21 07/12/2012,PAYMENT,5,,126 # bankofireland-checking.csv.rules # skip the header line skip # name the csv fields, and assign some of them as journal entry fields fields date, description, amount-out, amount-in, balance # We generate balance assertions by assigning to "balance" # above, but you may sometimes need to remove these because: # # - the CSV balance differs from the true balance, # by up to 0.0000000000005 in my experience # # - it is sometimes calculated based on non-chronological ordering, # eg when multiple transactions clear on the same day # date is in UK/Ireland format date-format %d/%m/%Y # set the currency currency EUR # set the base account for all txns account1 assets:bank:boi:checking $ hledger -f bankofireland-checking.csv print 2012-12-07 LODGMENT 529898 assets:bank:boi:checking EUR10.0 = EUR131.2 income:unknown EUR-10.0 2012-12-07 PAYMENT assets:bank:boi:checking EUR-5.0 = EUR126.0 expenses:unknown EUR5.0 The balance assertions don't raise an error above, because we're read- ing directly from CSV, but they will be checked if these entries are imported into a journal file. Coinbase A simple example with some CSV from Coinbase. The spot price is recorded using cost notation. The legacy amount field name conve- niently sets amount 2 (posting 2's amount) to the total cost. # Timestamp,Transaction Type,Asset,Quantity Transacted,Spot Price Currency,Spot Price at Transaction,Subtotal,Total (inclusive of fees and/or spread),Fees and/or Spread,Notes # 2021-12-30T06:57:59Z,Receive,USDC,100,GBP,0.740000,"","","","Received 100.00 USDC from an external account" # coinbase.csv.rules skip 1 fields Timestamp,Transaction_Type,Asset,Quantity_Transacted,Spot_Price_Currency,Spot_Price_at_Transaction,Subtotal,Total,Fees_Spread,Notes date %Timestamp date-format %Y-%m-%dT%T%Z description %Notes account1 assets:coinbase:cc amount %Quantity_Transacted %Asset @ %Spot_Price_at_Transaction %Spot_Price_Currency $ hledger print -f coinbase.csv 2021-12-30 Received 100.00 USDC from an external account assets:coinbase:cc 100 USDC @ 0.740000 GBP income:unknown -74.000000 GBP Amazon Here we convert amazon.com order history, and use an if block to gener- ate a third posting if there's a fee. (In practice you'd probably get this data from your bank instead, but it's an example.) "Date","Type","To/From","Name","Status","Amount","Fees","Transaction ID" "Jul 29, 2012","Payment","To","Foo.","Completed","$20.00","$0.00","16000000000000DGLNJPI1P9B8DKPVHL" "Jul 30, 2012","Payment","To","Adapteva, Inc.","Completed","$25.00","$1.00","17LA58JSKRD4HDGLNJPI1P9B8DKPVHL" # amazon-orders.csv.rules # skip one header line skip 1 # name the csv fields, and assign the transaction's date, amount and code. # Avoided the "status" and "amount" hledger field names to prevent confusion. fields date, _, toorfrom, name, amzstatus, amzamount, fees, code # how to parse the date date-format %b %-d, %Y # combine two fields to make the description description %toorfrom %name # save the status as a tag comment status:%amzstatus # set the base account for all transactions account1 assets:amazon # leave amount1 blank so it can balance the other(s). # I'm assuming amzamount excludes the fees, don't remember # set a generic account2 account2 expenses:misc amount2 %amzamount # and maybe refine it further: #include categorisation.rules # add a third posting for fees, but only if they are non-zero. if %fees [1-9] account3 expenses:fees amount3 %fees $ hledger -f amazon-orders.csv print 2012-07-29 (16000000000000DGLNJPI1P9B8DKPVHL) To Foo. ; status:Completed assets:amazon expenses:misc $20.00 2012-07-30 (17LA58JSKRD4HDGLNJPI1P9B8DKPVHL) To Adapteva, Inc. ; status:Completed assets:amazon expenses:misc $25.00 expenses:fees $1.00 Paypal Here's a real-world rules file for (customised) Paypal CSV, with some Paypal-specific rules, and a second rules file included: "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" "10/01/2019","03:46:20","PDT","Calm Radio","Subscription Payment","Completed","USD","-6.99","0.00","-6.99","simon@joyful.com","memberships@calmradio.com","60P57143A8206782E","MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month","","I-R8YLY094FJYR","","-6.99","" "10/01/2019","03:46:20","PDT","","Bank Deposit to PP Account ","Pending","USD","6.99","0.00","6.99","","simon@joyful.com","0TU1544T080463733","","","60P57143A8206782E","","0.00","" "10/01/2019","08:57:01","PDT","Patreon","PreApproved Payment Bill User Payment","Completed","USD","-7.00","0.00","-7.00","simon@joyful.com","support@patreon.com","2722394R5F586712G","Patreon* Membership","","B-0PG93074E7M86381M","","-7.00","" "10/01/2019","08:57:01","PDT","","Bank Deposit to PP Account ","Pending","USD","7.00","0.00","7.00","","simon@joyful.com","71854087RG994194F","Patreon* Membership","","2722394R5F586712G","","0.00","" "10/19/2019","03:02:12","PDT","Wikimedia Foundation, Inc.","Subscription Payment","Completed","USD","-2.00","0.00","-2.00","simon@joyful.com","tle@wikimedia.org","K9U43044RY432050M","Monthly donation to the Wikimedia Foundation","","I-R5C3YUS3285L","","-2.00","" "10/19/2019","03:02:12","PDT","","Bank Deposit to PP Account ","Pending","USD","2.00","0.00","2.00","","simon@joyful.com","3XJ107139A851061F","","","K9U43044RY432050M","","0.00","" "10/22/2019","05:07:06","PDT","Noble Benefactor","Subscription Payment","Completed","USD","10.00","-0.59","9.41","noble@bene.fac.tor","simon@joyful.com","6L8L1662YP1334033","Joyful Systems","","I-KC9VBGY2GWDB","","9.41","" # paypal-custom.csv.rules # Tips: # Export from Activity -> Statements -> Custom -> Activity download # Suggested transaction type: "Balance affecting" # Paypal's default fields in 2018 were: # "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Shipping Address","Address Status","Item Title","Item ID","Shipping and Handling Amount","Insurance Amount","Sales Tax","Option 1 Name","Option 1 Value","Option 2 Name","Option 2 Value","Reference Txn ID","Invoice Number","Custom Number","Quantity","Receipt ID","Balance","Address Line 1","Address Line 2/District/Neighborhood","Town/City","State/Province/Region/County/Territory/Prefecture/Republic","Zip/Postal Code","Country","Contact Phone Number","Subject","Note","Country Code","Balance Impact" # This rules file assumes the following more detailed fields, configured in "Customize report fields": # "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" fields date, time, timezone, description_, type, status_, currency, grossamount, feeamount, netamount, fromemail, toemail, code, itemtitle, itemid, referencetxnid, receiptid, balance, note skip 1 date-format %-m/%-d/%Y # ignore some paypal events if In Progress Temporary Hold Update to skip # add more fields to the description description %description_ %itemtitle # save some other fields as tags comment itemid:%itemid, fromemail:%fromemail, toemail:%toemail, time:%time, type:%type, status:%status_ # convert to short currency symbols if %currency USD currency $ if %currency EUR currency E if %currency GBP currency P # generate postings # the first posting will be the money leaving/entering my paypal account # (negative means leaving my account, in all amount fields) account1 assets:online:paypal amount1 %netamount # the second posting will be money sent to/received from other party # (account2 is set below) amount2 -%grossamount # if there's a fee, add a third posting for the money taken by paypal. if %feeamount [1-9] account3 expenses:banking:paypal amount3 -%feeamount comment3 business: # choose an account for the second posting # override the default account names: # if the amount is positive, it's income (a debit) if %grossamount ^[^-] account2 income:unknown # if negative, it's an expense (a credit) if %grossamount ^- account2 expenses:unknown # apply common rules for setting account2 & other tweaks include common.rules # apply some overrides specific to this csv # Transfers from/to bank. These are usually marked Pending, # which can be disregarded in this case. if Bank Account Bank Deposit to PP Account description %type for %referencetxnid %itemtitle account2 assets:bank:wf:pchecking account1 assets:online:paypal # Currency conversions if Currency Conversion account2 equity:currency conversion # common.rules if darcs noble benefactor account2 revenues:foss donations:darcshub comment2 business: if Calm Radio account2 expenses:online:apps if electronic frontier foundation Patreon wikimedia Advent of Code account2 expenses:dues if Google account2 expenses:online:apps description google | music $ hledger -f paypal-custom.csv print 2019-10-01 (60P57143A8206782E) Calm Radio MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month ; itemid:, fromemail:simon@joyful.com, toemail:memberships@calmradio.com, time:03:46:20, type:Subscription Payment, status:Completed assets:online:paypal $-6.99 = $-6.99 expenses:online:apps $6.99 2019-10-01 (0TU1544T080463733) Bank Deposit to PP Account for 60P57143A8206782E ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:46:20, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $6.99 = $0.00 assets:bank:wf:pchecking $-6.99 2019-10-01 (2722394R5F586712G) Patreon Patreon* Membership ; itemid:, fromemail:simon@joyful.com, toemail:support@patreon.com, time:08:57:01, type:PreApproved Payment Bill User Payment, status:Completed assets:online:paypal $-7.00 = $-7.00 expenses:dues $7.00 2019-10-01 (71854087RG994194F) Bank Deposit to PP Account for 2722394R5F586712G Patreon* Membership ; itemid:, fromemail:, toemail:simon@joyful.com, time:08:57:01, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $7.00 = $0.00 assets:bank:wf:pchecking $-7.00 2019-10-19 (K9U43044RY432050M) Wikimedia Foundation, Inc. Monthly donation to the Wikimedia Foundation ; itemid:, fromemail:simon@joyful.com, toemail:tle@wikimedia.org, time:03:02:12, type:Subscription Payment, status:Completed assets:online:paypal $-2.00 = $-2.00 expenses:dues $2.00 expenses:banking:paypal ; business: 2019-10-19 (3XJ107139A851061F) Bank Deposit to PP Account for K9U43044RY432050M ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:02:12, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $2.00 = $0.00 assets:bank:wf:pchecking $-2.00 2019-10-22 (6L8L1662YP1334033) Noble Benefactor Joyful Systems ; itemid:, fromemail:noble@bene.fac.tor, toemail:simon@joyful.com, time:05:07:06, type:Subscription Payment, status:Completed assets:online:paypal $9.41 = $9.41 revenues:foss donations:darcshub $-10.00 ; business: expenses:banking:paypal $0.59 ; business: Timeclock The time logging format of timeclock.el, as read by hledger. hledger can read time logs in timeclock format. As with Ledger, these are (a subset of) timeclock.el's format, containing clock-in and clock-out entries as in the example below. The date is a simple date. The time format is HH:MM[:SS][+-ZZZZ]. Seconds and timezone are op- tional. The timezone, if present, must be four digits and is ignored (currently the time is always interpreted as a local time). Lines be- ginning with # or ; or *, and blank lines, are ignored. i 2015/03/30 09:00:00 some account optional description after 2 spaces ; optional comment, tags: o 2015/03/30 09:20:00 i 2015/03/31 22:21:45 another:account o 2015/04/01 02:00:34 hledger treats each clock-in/clock-out pair as a transaction posting some number of hours to an account. Or if the session spans more than one day, it is split into several transactions, one for each day. For the above time log, hledger print generates these journal entries: $ hledger -f t.timeclock print 2015-03-30 * optional description after 2 spaces ; optional comment, tags: (some account) 0.33h 2015-03-31 * 22:21-23:59 (another:account) 1.64h 2015-04-01 * 00:00-02:00 (another:account) 2.01h Here is a sample.timeclock to download and some queries to try: $ hledger -f sample.timeclock balance # current time balances $ hledger -f sample.timeclock register -p 2009/3 # sessions in march 2009 $ hledger -f sample.timeclock register -p weekly --depth 1 --empty # time summary by week To generate time logs, ie to clock in and clock out, you could: o use emacs and the built-in timeclock.el, or the extended time- clock-x.el and perhaps the extras in ledgerutils.el o at the command line, use these bash aliases: shell alias ti="echo i `date '+%Y-%m-%d %H:%M:%S'` \$* >>$TIMELOG" alias to="echo o `date '+%Y-%m-%d %H:%M:%S'` >>$TIMELOG" o or use the old ti and to scripts in the ledger 2.x repository. These rely on a "timeclock" executable which I think is just the ledger 2 executable renamed. Timedot timedot format is hledger's human-friendly time logging format. Com- pared to timeclock format, it is more convenient for quick, approxi- mate, and retroactive time logging, and more human-readable (you can see at a glance where time was spent). A quick example: 2023-05-01 hom:errands .... .... ; two hours; the space is ignored fos:hledger:timedot .. ; half an hour per:admin:finance ; no time spent yet hledger reads this as a transaction on this day with three (unbalanced) postings, where each dot represents "0.25". No commodity symbol is as- sumed, but we typically interpret it as hours. $ hledger -f a.timedot print # .timedot file extension (or timedot: prefix) is required 2023-05-01 * (hom:errands) 2.00 ; two hours (fos:hledger:timedot) 0.50 ; half an hour (per:admin:finance) 0 A timedot file contains a series of transactions (usually one per day). Each begins with a simple date (Y-M-D, Y/M/D, or Y.M.D), optionally be followed on the same line by a transaction description, and/or a trans- action comment following a semicolon. After the date line are zero or more time postings, consisting of: o An account name - any hledger-style account name, optionally in- dented. o Two or more spaces - required if there is an amount (as in journal format). o A timedot amount, which can be o empty (representing zero) o a number, optionally followed by a unit s, m, h, d, w, mo, or y, representing a precise number of seconds, minutes, hours, days weeks, months or years (hours is assumed by default), which will be converted to hours according to 60s = 1m, 60m = 1h, 24h = 1d, 7d = 1w, 30d = 1mo, 365d = 1y. o one or more dots (period characters), each representing 0.25. These are the dots in "timedot". Spaces are ignored and can be used for grouping/alignment. o one or more letters. These are like dots but they also generate a tag t: (short for "type") with the letter as its value, and a sepa- rate posting for each of the values. This provides a second dimen- sion of categorisation, viewable in reports with --pivot t. o An optional comment following a semicolon (a hledger-style posting comment). There is some flexibility to help with keeping time log data and notes in the same file: o Blank lines and lines beginning with # or ; are ignored. o After the first date line, lines which do not contain a double space are parsed as postings with zero amount. (hledger's register reports will show these if you add -E). o Before the first date line, lines beginning with * (eg org headings) are ignored. And from the first date line onward, Emacs org mode heading prefixes at the start of lines (one or more *'s followed by a space) will be ignored. This means the time log can also be a org outline. Timedot examples Numbers: 2016/2/3 inc:client1 4 fos:hledger 3h biz:research 60m Dots: # on this day, 6h was spent on client work, 1.5h on haskell FOSS work, etc. 2016/2/1 inc:client1 .... .... .... .... .... .... fos:haskell .... .. biz:research . 2016/2/2 inc:client1 .... .... biz:research . $ hledger -f a.timedot print date:2016/2/2 2016-02-02 * (inc:client1) 2.00 2016-02-02 * (biz:research) 0.25 $ hledger -f a.timedot bal --daily --tree Balance changes in 2016-02-01-2016-02-03: || 2016-02-01d 2016-02-02d 2016-02-03d ============++======================================== biz || 0.25 0.25 1.00 research || 0.25 0.25 1.00 fos || 1.50 0 3.00 haskell || 1.50 0 0 hledger || 0 0 3.00 inc || 6.00 2.00 4.00 client1 || 6.00 2.00 4.00 ------------++---------------------------------------- || 7.75 2.25 8.00 Letters: # Activity types: # c cleanup/catchup/repair # e enhancement # s support # l learning/research 2023-11-01 work:adm ccecces $ hledger -f a.timedot print 2023-11-01 (work:adm) 1 ; t:c (work:adm) 0.5 ; t:e (work:adm) 0.25 ; t:s $ hledger -f a.timedot bal 1.75 work:adm -------------------- 1.75 $ hledger -f a.timedot bal --pivot t 1.00 c 0.50 e 0.25 s -------------------- 1.75 Org: * 2023 Work Diary ** Q1 *** 2023-02-29 **** DONE 0700 yoga **** UNPLANNED **** BEGUN hom:chores cleaning ... water plants outdoor - one full watering can indoor - light watering **** TODO adm:planning: trip *** LATER Using . as account name separator: 2016/2/4 fos.hledger.timedot 4h fos.ledger .. $ hledger -f a.timedot --alias '/\./=:' bal -t 4.50 fos 4.00 hledger:timedot 0.50 ledger -------------------- 4.50 PART 3: REPORTING CONCEPTS Amount formatting, parseability If you're wondering why your print report sometimes shows trailing dec- imal marks, with no decimal digits; it does this when showing amounts that have digit group marks but no decimal digits, to disambiguate them and allow them to be re-parsed reliably (see also Decimal marks, digit group marks. Eg: commodity $1,000.00 2023-01-02 (a) $1000 $ hledger print 2023-01-02 (a) $1,000. If this is a problem (eg when exporting to Ledger), you can avoid it by disabling digit group marks, eg with -c/--commodity (for each affected commodity): $ hledger print -c '$1000.00' 2023-01-02 (a) $1000 or by forcing print to always show decimal digits, with --round: $ hledger print -c '$1,000.00' --round=soft 2023-01-02 (a) $1,000.00 More generally: hledger output falls into three rough categories, which format amounts a little bit differently to suit different consumers: 1. "hledger-readable output" - should be readable by hledger (and by humans) o This is produced by reports that show full journal entries: print, import, close, rewrite etc. o It shows amounts with their original journal precisions, which may not be consistent. o It adds a trailing decimal mark when needed to avoid showing ambigu- ous amounts. o It can be parsed reliably (by hledger and ledger2beancount at least, but perhaps not by Ledger..) 2. "human-readable output" - usually for humans o This is produced by all other reports. o It shows amounts with standard display precisions, which will be con- sistent within each commodity. o It shows ambiguous amounts unmodified. o It can be parsed reliably in the context of a known report (when you know decimals are consistently not being shown, you can assume a sin- gle mark is a digit group mark). 3. "machine-readable output" - usually for other software o This is produced by all reports when an output format like csv, tsv, json, or sql is selected. o It shows amounts as 1 or 2 do, but without digit group marks. o It can be parsed reliably (if needed, the decimal mark can be changed with -c/--commodity-style). Time periods Report start & end date By default, most hledger reports will show the full span of time repre- sented by the journal. The report start date will be the earliest transaction or posting date, and the report end date will be the latest transaction, posting, or market price date. Often you will want to see a shorter time span, such as the current month. You can specify a start and/or end date using -b/--begin, -e/--end, -p/--period or a date: query (described below). All of these accept the smart date syntax (below). Some notes: o End dates are exclusive, as in Ledger, so you should write the date after the last day you want to see in the report. o As noted in reporting options: among start/end dates specified with options, the last (i.e. right-most) option takes precedence. o The effective report start and end dates are the intersection of the start/end dates from options and that from date: queries. That is, date:2019-01 date:2019 -p'2000 to 2030' yields January 2019, the smallest common time span. o In some cases a report interval will adjust start/end dates to fall on interval boundaries (see below). Examples: -b 2016/3/17 begin on St. Patrick's day 2016 -e 12/1 end at the start of december 1st of the current year (11/30 will be the last date included) -b thismonth all transactions on or after the 1st of the current month -p thismonth all transactions in the current month date:2016/3/17.. the above written as queries instead (.. can also be re- placed with -) date:..12/1 date:thismonth.. date:thismonth Smart dates hledger's user interfaces accept a "smart date" syntax for added conve- nience. Smart dates optionally can be relative to today's date, be written with english words, and have less-significant parts omitted (missing parts are inferred as 1). Some examples: 2004/10/1, 2004-01-01, exact date, several separators allowed. Year 2004.9.1 is 4+ digits, month is 1-12, day is 1-31 2004 start of year 2004/10 start of month 10/1 month and day in current year 21 day in current month october, oct start of month in current year yesterday, today, tomor- -1, 0, 1 days from today row last/this/next -1, 0, 1 periods from the current period day/week/month/quar- ter/year in n n periods from the current period days/weeks/months/quar- ters/years n n periods from the current period days/weeks/months/quar- ters/years ahead n -n periods from the current period days/weeks/months/quar- ters/years ago 20181201 8 digit YYYYMMDD with valid year month and day 201812 6 digit YYYYMM with valid year and month Some counterexamples - malformed digit sequences might give surprising results: 201813 6 digits with an invalid month is parsed as start of 6-digit year 20181301 8 digits with an invalid month is parsed as start of 8-digit year 20181232 8 digits with an invalid day gives an error 201801012 9+ digits beginning with a valid YYYYMMDD gives an error "Today's date" can be overridden with the --today option, in case it's needed for testing or for recreating old reports. (Except for periodic transaction rules, which are not affected by --today.) Report intervals A report interval can be specified so that reports like register, bal- ance or activity become multi-period, showing each subperiod as a sepa- rate row or column. The following standard intervals can be enabled with command-line flags: o -D/--daily o -W/--weekly o -M/--monthly o -Q/--quarterly o -Y/--yearly More complex intervals can be specified using -p/--period, described below. Date adjustment When there is a report interval (other than daily), report start/end dates which have been inferred, eg from the journal, are automatically adjusted to natural period boundaries. This is convenient for produc- ing simple periodic reports. More precisely: o an inferred start date will be adjusted earlier if needed to fall on a natural period boundary o an inferred end date will be adjusted later if needed to make the last period the same length as the others. By contrast, start/end dates which have been specified explicitly, with -b, -e, -p or date:, will not be adjusted (since hledger 1.29). This makes it possible to specify non-standard report periods, but it also means that if you are specifying a start date, you should pick one that's on a period boundary if you want to see simple report period headings. Period expressions The -p/--period option specifies a period expression, which is a com- pact way of expressing a start date, end date, and/or report interval. Here's a period expression with a start and end date (specifying the first quarter of 2009): -p "from 2009/1/1 to 2009/4/1" Several keywords like "from" and "to" are supported for readability; these are optional. "to" can also be written as ".." or "-". The spaces are also optional, as long as you don't run two dates together. So the following are equivalent to the above: -p "2009/1/1 2009/4/1" -p2009/1/1to2009/4/1 -p2009/1/1..2009/4/1 Dates are smart dates, so if the current year is 2009, these are also equivalent to the above: -p "1/1 4/1" -p "jan-apr" -p "this year to 4/1" If you specify only one date, the missing start or end date will be the earliest or latest transaction date in the journal: -p "from 2009/1/1" everything after january 1, 2009 -p "since 2009/1" the same, since is a syn- onym -p "from 2009" the same -p "to 2009" everything before january 1, 2009 You can also specify a period by writing a single partial or full date: -p "2009" the year 2009; equivalent to "2009/1/1 to 2010/1/1" -p "2009/1" the month of january 2009; equivalent to "2009/1/1 to 2009/2/1" -p "2009/1/1" the first day of 2009; equivalent to "2009/1/1 to 2009/1/2" or by using the "Q" quarter-year syntax (case insensitive): -p "2009Q1" first quarter of 2009, equivalent to "2009/1/1 to 2009/4/1" -p "q4" fourth quarter of the current year Period expressions with a report interval A period expression can also begin with a report interval, separated from the start/end dates (if any) by a space or the word in: -p "weekly from 2009/1/1 to 2009/4/1" -p "monthly in 2008" -p "quarterly" More complex report intervals Some more complex intervals can be specified within period expressions, such as: o biweekly (every two weeks) o fortnightly o bimonthly (every two months) o every day|week|month|quarter|year o every N days|weeks|months|quarters|years Weekly on a custom day: o every Nth day of week (th, nd, rd, or st are all accepted after the number) o every WEEKDAYNAME (full or three-letter english weekday name, case insensitive) Monthly on a custom day: o every Nth day [of month] o every Nth WEEKDAYNAME [of month] Yearly on a custom day: o every MM/DD [of year] (month number and day of month number) o every MONTHNAME DDth [of year] (full or three-letter english month name, case insensitive, and day of month number) o every DDth MONTHNAME [of year] (equivalent to the above) Examples: -p "bimonthly from 2008" -p "every 2 weeks" -p "every 5 months from 2009/03" -p "every 2nd day of week" periods will go from Tue to Tue -p "every Tue" same -p "every 15th day" period boundaries will be on 15th of each month -p "every 2nd Monday" period boundaries will be on second Monday of each month -p "every 11/05" yearly periods with boundaries on 5th of November -p "every 5th November" same -p "every Nov 5th" same Show historical balances at end of the 15th day of each month (N is an end date, exclusive as always): $ hledger balance -H -p "every 16th day" Group postings from the start of wednesday to end of the following tuesday (N is both (inclusive) start date and (exclusive) end date): $ hledger register checking -p "every 3rd day of week" Multiple weekday intervals This special form is also supported: o every WEEKDAYNAME,WEEKDAYNAME,... (full or three-letter english week- day names, case insensitive) Also, weekday and weekendday are shorthand for mon,tue,wed,thu,fri and sat,sun. This is mainly intended for use with --forecast, to generate periodic transactions on arbitrary days of the week. It may be less useful with -p, since it divides each week into subperiods of unequal length, which is unusual. (Related: #1632) Examples: -p "every dates will be Mon, Wed, Fri; periods will be mon,wed,fri" Mon-Tue, Wed-Thu, Fri-Sun -p "every weekday" dates will be Mon, Tue, Wed, Thu, Fri; periods will be Mon, Tue, Wed, Thu, Fri-Sun -p "every weekend- dates will be Sat, Sun; periods will be Sat, Sun-Fri day" Depth With the --depth NUM option (short form: -NUM), reports will show ac- counts only to the specified depth, hiding deeper subaccounts. Use this when you want a summary with less detail. This flag has the same effect as a depth: query argument: depth:2, --depth=2 or -2 are equiva- lent. Queries One of hledger's strengths is being able to quickly report on a precise subset of your data. Most hledger commands accept query arguments, to restrict their scope. Multiple query terms can be provided to build up a more complex query. o By default, a query term is interpreted as a case-insensitive sub- string pattern for matching account names: car:fuel dining groceries o Patterns containing spaces or other special characters must be en- closed in single or double quotes: 'personal care' o These patterns are actually regular expressions, so you can add reg- exp metacharacters for more precision (see "Regular expressions" above for details): '^expenses\b' 'food$' 'fuel|repair' 'accounts (payable|receivable)' o To match something other than account name, add one of the query type prefixes described in "Query types" below: date:202312- status: desc:amazon cur:USD cur:\\$ amt:'>0' o Add a not: prefix to negate a term: not:status:'*' not:desc:'opening|closing' not:cur:USD o Terms with different types are AND-ed, terms with the same type are OR-ed (mostly; see "Combining query terms" below). The following query: date:2022 desc:amazon desc:amzn is interpreted as: date is in 2022 AND ( transaction description contains "amazon" OR "amzn" ) Query types Here are the types of query term available. Remember these can also be prefixed with not: to convert them into a negative match. acct:REGEX or REGEX Match account names containing this case insensitive regular expres- sion. This is the default query type, so we usually don't bother writ- ing the "acct:" prefix. amt:N, amt:N, amt:>=N Match postings with a single-commodity amount equal to, less than, or greater than N. (Postings with multi-commodity amounts are not tested and will always match.) The comparison has two modes: if N is preceded by a + or - sign (or is 0), the two signed numbers are compared. Oth- erwise, the absolute magnitudes are compared, ignoring sign. code:REGEX Match by transaction code (eg check number). cur:REGEX Match postings or transactions including any amounts whose cur- rency/commodity symbol is fully matched by REGEX. (For a partial match, use .*REGEX.*). Note, to match special characters which are regex-significant, you need to escape them with \. And for characters which are significant to your shell you may need one more level of es- caping. So eg to match the dollar sign: hledger print cur:\\$. desc:REGEX Match transaction descriptions. date:PERIODEXPR Match dates (or with the --date2 flag, secondary dates) within the specified period. PERIODEXPR is a period expression with no report in- terval. Examples: date:2016, date:thismonth, date:2/1-2/15, date:2021-07-27..nextquarter. date2:PERIODEXPR Match secondary dates within the specified period (independent of the --date2 flag). depth:N Match (or display, depending on command) accounts at or above this depth. expr:"TERM AND NOT (TERM OR TERM)" (eg) Match with a boolean combination of queries (which must be enclosed in quotes). See Combining query terms below. note:REGEX Match transaction notes (the part of the description right of |, or the whole description if there's no |). payee:REGEX Match transaction payee/payer names (the part of the description left of |, or the whole description if there's no |). real:, real:0 Match real or virtual postings respectively. status:, status:!, status:* Match unmarked, pending, or cleared transactions respectively. type:TYPECODES Match by account type (see Declaring accounts > Account types). TYPE- CODES is one or more of the single-letter account type codes ALERXCV, case insensitive. Note type:A and type:E will also match their respec- tive subtypes C (Cash) and V (Conversion). Certain kinds of account alias can disrupt account types, see Rewriting accounts > Aliases and account types. tag:REGEX[=REGEX] Match by tag name, and optionally also by tag value. (To match only by value, use tag:.=REGEX.) When querying by tag, note that: o Accounts also inherit the tags of their parent accounts o Postings also inherit the tags of their account and their transaction o Transactions also acquire the tags of their postings. (inacct:ACCTNAME A special query term used automatically in hledger-web only: tells hledger-web to show the transaction register for an account.) Combining query terms When given multiple space-separated query terms, most commands select things which match: o any of the description terms AND o any of the account terms AND o any of the status terms AND o all the other terms. The print command is a little different, showing transactions which: o match any of the description terms AND o have any postings matching any of the positive account terms AND o have no postings matching any of the negative account terms AND o match all the other terms. We also support more complex boolean queries with the 'expr:' prefix. This allows one to combine queries using one of three operators: AND, OR, and NOT, where NOT is different syntax for 'not:'. Examples of such queries are: o Match transactions with 'cool' in the description AND with the 'A' tag expr:"desc:cool AND tag:A" o Match transactions NOT to the 'expenses:food' account OR with the 'A' tag expr:"NOT expenses:food OR tag:A" o Match transactions NOT involving the 'expenses:food' account OR with the 'A' tag AND involving the 'expenses:drink' account. (the AND is implicitly added by space-separation, following the rules above) expr:"expenses:food OR (tag:A expenses:drink)" Queries and command options Some queries can also be expressed as command-line options: depth:2 is equivalent to --depth 2, date:2023 is equivalent to -p 2023, etc. When you mix command options and query arguments, generally the resulting query is their intersection. Queries and valuation When amounts are converted to other commodities in cost or value re- ports, cur: and amt: match the old commodity symbol and the old amount quantity, not the new ones (except in hledger 1.22.0 where it's re- versed, see #1625). Querying with account aliases When account names are rewritten with --alias or alias, note that acct: will match either the old or the new account name. Querying with cost or value When amounts are converted to other commodities in cost or value re- ports, note that cur: matches the new commodity symbol, and not the old one, and amt: matches the new quantity, and not the old one. Note: this changed in hledger 1.22, previously it was the reverse, see the discussion at #1625. Pivoting Normally, hledger groups and sums amounts within each account. The --pivot FIELD option substitutes some other transaction field for ac- count names, causing amounts to be grouped and summed by that field's value instead. FIELD can be any of the transaction fields acct, sta- tus, code, desc, payee, note, or a tag name. When pivoting on a tag and a posting has multiple values of that tag, only the first value is displayed. Values containing colon:separated:parts will be displayed hierarchically, like account names. Multiple, colon-delimited fields can be pivoted simultaneously, generating a hierarchical account name. Some examples: 2016/02/16 Yearly Dues Payment assets:bank account 2 EUR income:dues -2 EUR ; member: John Doe, kind: Lifetime Normal balance report showing account names: $ hledger balance 2 EUR assets:bank account -2 EUR income:dues -------------------- 0 Pivoted balance report, using member: tag values instead: $ hledger balance --pivot member 2 EUR -2 EUR John Doe -------------------- 0 One way to show only amounts with a member: value (using a query): $ hledger balance --pivot member tag:member=. -2 EUR John Doe -------------------- -2 EUR Another way (the acct: query matches against the pivoted "account name"): $ hledger balance --pivot member acct:. -2 EUR John Doe -------------------- -2 EUR Hierarchical reports can be generated with multiple pivots: $ hledger balance Income:Dues --pivot kind:member -2 EUR Lifetime:John Doe -------------------- -2 EUR Generating data hledger has several features for generating data, such as: o Periodic transaction rules can generate single or repeating transac- tions following a template. These are usually dated in the future, eg to help with forecasting. They are activated by the --forecast option. o The balance command's --budget option uses these same periodic rules to generate goals for the budget report. o Auto posting rules can generate extra postings on certain matched transactions. They are always applied to forecast transactions; with the --auto flag they are applied to transactions recorded in the journal as well. o The --infer-equity flag infers missing conversion equity postings from @/@@ costs. And the inverse --infer-costs flag infers missing @/@@ costs from conversion equity postings. Generated data of this kind is temporary, existing only at report time. But you can see it in the output of hledger print, and you can save that to your journal, in effect converting it from temporary generated data to permanent recorded data. This could be useful as a data entry aid. If you are wondering what data is being generated and why, add the --verbose-tags flag. In hledger print output you will see extra tags like generated-transaction, generated-posting, and modified on gener- ated/modified data. Also, even without --verbose-tags, generated data always has equivalen hidden tags (with an underscore prefix), so eg you could match generated transactions with tag:_generated-transaction. Forecasting Forecasting, or speculative future reporting, can be useful for esti- mating future balances, or for exploring different future scenarios. The simplest and most flexible way to do it with hledger is to manually record a bunch of future-dated transactions. You could keep these in a separate future.journal and include that with -f only when you want to see them. --forecast There is another way: with the --forecast option, hledger can generate temporary "forecast transactions" for reporting purposes, according to periodic transaction rules defined in the journal. Each rule can gen- erate multiple recurring transactions, so by changing one rule you can change many forecasted transactions. Forecast transactions usually start after ordinary transactions end. By default, they begin after your latest-dated ordinary transaction, or today, whichever is later, and they end six months from today. (The exact rules are a little more complicated, and are given below.) This is the "forecast period", which need not be the same as the report period. You can override it - eg to forecast farther into the future, or to force forecast transactions to overlap your ordinary transactions - by giving the --forecast option a period expression argument, like --forecast=..2099 or --forecast=2023-02-15... Note that the = is re- quired. Inspecting forecast transactions print is the best command for inspecting and troubleshooting forecast transactions. Eg: ~ monthly from 2022-12-20 rent assets:bank:checking expenses:rent $1000 $ hledger print --forecast --today=2023/4/21 2023-05-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-06-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-07-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-08-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-09-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 Here there are no ordinary transactions, so the forecasted transactions begin on the first occurence after today's date. (You won't normally use --today; it's just to make these examples reproducible.) Forecast reports Forecast transactions affect all reports, as you would expect. Eg: $ hledger areg rent --forecast --today=2023/4/21 Transactions in expenses:rent and subaccounts: 2023-05-20 rent as:ba:checking $1000 $1000 2023-06-20 rent as:ba:checking $1000 $2000 2023-07-20 rent as:ba:checking $1000 $3000 2023-08-20 rent as:ba:checking $1000 $4000 2023-09-20 rent as:ba:checking $1000 $5000 $ hledger bal -M expenses --forecast --today=2023/4/21 Balance changes in 2023-05-01..2023-09-30: || May Jun Jul Aug Sep ===============++=================================== expenses:rent || $1000 $1000 $1000 $1000 $1000 ---------------++----------------------------------- || $1000 $1000 $1000 $1000 $1000 Forecast tags Forecast transactions generated by --forecast have a hidden tag, _gen- erated-transaction. So if you ever need to match forecast transac- tions, you could use tag:_generated-transaction (or just tag:generated) in a query. For troubleshooting, you can add the --verbose-tags flag. Then, visi- ble generated-transaction tags will be added also, so you can view them with the print command. Their value indicates which periodic rule was responsible. Forecast period, in detail Forecast start/end dates are chosen so as to do something useful by de- fault in almost all situations, while also being flexible. Here are (with luck) the exact rules, to help with troubleshooting: The forecast period starts on: o the later of o the start date in the periodic transaction rule o the start date in --forecast's argument o otherwise (if those are not available): the later of o the report start date specified with -b/-p/date: o the day after the latest ordinary transaction in the journal o otherwise (if none of these are available): today. The forecast period ends on: o the earlier of o the end date in the periodic transaction rule o the end date in --forecast's argument o otherwise: the report end date specified with -e/-p/date: o otherwise: 180 days (~6 months) from today. Forecast troubleshooting When --forecast is not doing what you expect, one of these tips should help: o Remember to use the --forecast option. o Remember to have at least one periodic transaction rule in your jour- nal. o Test with print --forecast. o Check for typos or too-restrictive start/end dates in your periodic transaction rule. o Leave at least 2 spaces between the rule's period expression and de- scription fields. o Check for future-dated ordinary transactions suppressing forecasted transactions. o Try setting explicit report start and/or end dates with -b, -e, -p or date: o Try adding the -E flag to encourage display of empty periods/zero transactions. o Try setting explicit forecast start and/or end dates with --fore- cast=START..END o Consult Forecast period, in detail, above. o Check inside the engine: add --debug=2 (eg). Budgeting With the balance command's --budget report, each periodic transaction rule generates recurring budget goals in specified accounts, and goals and actual performance can be compared. See the balance command's doc below. You can generate budget goals and forecast transactions at the same time, from the same or different periodic transaction rules: hledger bal -M --budget --forecast ... See also: Budgeting and Forecasting. Cost reporting In some transactions - for example a currency conversion, or a purchase or sale of stock - one commodity is exchanged for another. In these transactions there is a conversion rate, also called the cost (when buying) or selling price (when selling). In hledger docs we just say "cost", for convenience; feel free to mentally translate to "conversion rate" or "selling price" if helpful. Recording costs We'll explore several ways of recording transactions involving costs. These are also summarised at hledger Cookbook > Cost notation. Costs can be recorded explicitly in the journal, using the @ UNITCOST or @@ TOTALCOST notation described in Journal > Costs: Variant 1 2022-01-01 assets:dollars $-135 assets:euros 100 @ $1.35 ; $1.35 per euro (unit cost) Variant 2 2022-01-01 assets:dollars $-135 assets:euros 100 @@ $135 ; $135 total cost Typically, writing the unit cost (variant 1) is preferable; it can be more effort, requiring more attention to decimal digits; but it reveals the per-unit cost basis, and makes stock sales easier. Costs can also be left implicit, and hledger will infer the cost that is consistent with a balanced transaction: Variant 3 2022-01-01 assets:dollars $-135 assets:euros 100 Here, hledger will attach a @@ 100 cost to the first amount (you can see it with hledger print -x). This form looks convenient, but there are downsides: o It sacrifices some error checking. For example, if you accidentally wrote 10 instead of 100, hledger would not be able to detect the mis- take. o It is sensitive to the order of postings - if they were reversed, a different entry would be inferred and reports would be different. o The per-unit cost basis is not easy to read. So generally this kind of entry is not recommended. You can make sure you have none of these by using -s (strict mode), or by running hledger check balanced. Reporting at cost Now when you add the -B/--cost flag to reports ("B" is from Ledger's -B/--basis/--cost flag), any amounts which have been annotated with costs will be converted to their cost's commodity (in the report out- put). Ie they will be displayed "at cost" or "at sale price". Some things to note: o Costs are attached to specific posting amounts in specific transac- tions, and once recorded they do not change. This contrasts with market prices, which are ambient and fluctuating. o Conversion to cost is performed before conversion to market value (described below). Equity conversion postings There is a problem with the entries above - they are not conventional Double Entry Bookkeeping (DEB) notation, and because of the "magical" transformation of one commodity into another, they cause an imbalance in the Accounting Equation. This shows up as a non-zero grand total in balance reports like hledger bse. For most hledger users, this doesn't matter in practice and can safely be ignored ! But if you'd like to learn more, keep reading. Conventional DEB uses an extra pair of equity postings to balance the transaction. Of course you can do this in hledger as well: Variant 4 2022-01-01 assets:dollars $-135 assets:euros 100 equity:conversion $135 equity:conversion -100 Now the transaction is perfectly balanced according to standard DEB, and hledger bse's total will not be disrupted. And, hledger can still infer the cost for cost reporting, but it's not done by default - you must add the --infer-costs flag like so: $ hledger print --infer-costs 2022-01-01 one hundred euros purchased at $1.35 each assets:dollars $-135 @@ 100 assets:euros 100 equity:conversion $135 equity:conversion -100 $ hledger bal --infer-costs -B -100 assets:dollars 100 assets:euros -------------------- 0 Here are some downsides of this kind of entry: o The per-unit cost basis is not easy to read. o Instead of -B you must remember to type -B --infer-costs. o --infer-costs works only where hledger can identify the two eq- uity:conversion postings and match them up with the two non-equity postings. So writing the journal entry in a particular format be- comes more important. More on this below. Inferring equity conversion postings Can we go in the other direction ? Yes, if you have transactions writ- ten with the @/@@ cost notation, hledger can infer the missing equity postings, if you add the --infer-equity flag. Eg: 2022-01-01 assets:dollars -$135 assets:euros 100 @ $1.35 $ hledger print --infer-equity 2022-01-01 assets:dollars $-135 assets:euros 100 @ $1.35 equity:conversion:$-: -100 equity:conversion:$-:$ $135.00 The equity account names will be "equity:conversion:A-B:A" and "eq- uity:conversion:A-B:B" where A is the alphabetically first commodity symbol. You can customise the "equity:conversion" part by declaring an account with the V/Conversion account type. Combining costs and equity conversion postings Finally, you can use both the @/@@ cost notation and equity postings at the same time. This in theory gives the best of all worlds - preserv- ing the accounting equation, revealing the per-unit cost basis, and providing more flexibility in how you write the entry: Variant 5 2022-01-01 one hundred euros purchased at $1.35 each assets:dollars $-135 equity:conversion $135 equity:conversion -100 assets:euros 100 @ $1.35 All the other variants above can (usually) be rewritten to this final form with: $ hledger print -x --infer-costs --infer-equity Downsides: o This was added in hledger-1.29 and is still somewhat experimental. o The precise format of the journal entry becomes more important. If hledger can't detect and match up the cost and equity postings, it will give a transaction balancing error. o The add command does not yet accept this kind of entry (#2056). o This is the most verbose form. Requirements for detecting equity conversion postings --infer-costs has certain requirements (unlike --infer-equity, which always works). It will infer costs only in transactions with: o Two non-equity postings, in different commodities. Their order is significant: the cost will be added to the first of them. o Two postings to equity conversion accounts, next to one another, which balance the two non-equity postings. This balancing is checked to the same precision (number of decimal places) used in the conver- sion posting's amount. Equity conversion accounts are: o any accounts declared with account type V/Conversion, or their sub- accounts o otherwise, accounts named equity:conversion, equity:trade, or eq- uity:trading, or their subaccounts. And multiple such four-posting groups can coexist within a single transaction. When --infer-costs fails, it does not infer a cost in that transaction, and does not raise an error (ie, it infers costs where it can). Reading variant 5 journal entries, combining cost notation and equity postings, has all the same requirements. When reading such an entry fails, hledger raises an "unbalanced transaction" error. Infer cost and equity by default ? Should --infer-costs and --infer-equity be enabled by default ? Try using them always, eg with a shell alias: alias h="hledger --infer-equity --infer-costs" and let us know what problems you find. Value reporting Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), and/or to market value (using some market price on a certain date). This is controlled by the --value=TYPE[,COMMODITY] op- tion, which will be described below. We also provide the simpler -V and -X COMMODITY options, and often one of these is all you need: -V: Value The -V/--market flag converts amounts to market value in their default valuation commodity, using the market prices in effect on the valuation date(s), if any. More on these in a minute. -X: Value in specified commodity The -X/--exchange=COMM option is like -V, except you tell it which cur- rency you want to convert to, and it tries to convert everything to that. Valuation date Market prices can change from day to day. hledger will use the prices on a particular valuation date (or on more than one date). By default hledger uses "end" dates for valuation. More specifically: o For single period reports (including normal print and register re- ports): o If an explicit report end date is specified, that is used o Otherwise the latest transaction date or P directive date is used (even if it's in the future) o For multiperiod reports, each period is valued on its last day. This can be customised with the --value option described below, which can select either "then", "end", "now", or "custom" dates. (Note, this has a bug in hledger-ui <=1.31: turning on valuation with the V key al- ways resets it to "end".) Finding market price To convert a commodity A to its market value in another commodity B, hledger looks for a suitable market price (exchange rate) as follows, in this order of preference: 1. A declared market price or inferred market price: A's latest market price in B on or before the valuation date as declared by a P direc- tive, or (with the --infer-market-prices flag) inferred from costs. 2. A reverse market price: the inverse of a declared or inferred market price from B to A. 3. A forward chain of market prices: a synthetic price formed by com- bining the shortest chain of "forward" (only 1 above) market prices, leading from A to B. 4. Any chain of market prices: a chain of any market prices, including both forward and reverse prices (1 and 2 above), leading from A to B. There is a limit to the length of these price chains; if hledger reaches that length without finding a complete chain or exhausting all possibilities, it will give up (with a "gave up" message visible in --debug=2 output). That limit is currently 1000. Amounts for which no suitable market price can be found, are not con- verted. --infer-market-prices: market prices from transactions Normally, market value in hledger is fully controlled by, and requires, P directives in your journal. Since adding and updating those can be a chore, and since transactions usually take place at close to market value, why not use the recorded costs as additional market prices (as Ledger does) ? Adding the --infer-market-prices flag to -V, -X or --value enables this. So for example, hledger bs -V --infer-market-prices will get market prices both from P directives and from transactions. If both occur on the same day, the P directive takes precedence. There is a downside: value reports can sometimes be affected in confus- ing/undesired ways by your journal entries. If this happens to you, read all of this Value reporting section carefully, and try adding --debug or --debug=2 to troubleshoot. --infer-market-prices can infer market prices from: o multicommodity transactions with explicit prices (@/@@) o multicommodity transactions with implicit prices (no @, two commodi- ties, unbalanced). (With these, the order of postings matters. hledger print -x can be useful for troubleshooting.) o multicommodity transactions with equity postings, if cost is inferred with --infer-costs. There is a limitation (bug) currently: when a valuation commodity is not specified, prices inferred with --infer-market-prices do not help select a default valuation commodity, as P prices would. So conversion might not happen because no valuation commodity was detected (--debug=2 will show this). To be safe, specify the valuation commmodity, eg: o -X EUR --infer-market-prices, not -V --infer-market-prices o --value=then,EUR --infer-market-prices, not --value=then --infer-mar- ket-prices Signed costs and market prices can be confusing. For reference, here is the current behaviour, since hledger 1.25. (If you think it should work differently, see #1870.) 2022-01-01 Positive Unit prices a A 1 b B -1 @ A 1 2022-01-01 Positive Total prices a A 1 b B -1 @@ A 1 2022-01-02 Negative unit prices a A 1 b B 1 @ A -1 2022-01-02 Negative total prices a A 1 b B 1 @@ A -1 2022-01-03 Double Negative unit prices a A -1 b B -1 @ A -1 2022-01-03 Double Negative total prices a A -1 b B -1 @@ A -1 All of the transactions above are considered balanced (and on each day, the two transactions are considered equivalent). Here are the market prices inferred for B: $ hledger -f- --infer-market-prices prices P 2022-01-01 B A 1 P 2022-01-01 B A 1.0 P 2022-01-02 B A -1 P 2022-01-02 B A -1.0 P 2022-01-03 B A -1 P 2022-01-03 B A -1.0 Valuation commodity When you specify a valuation commodity (-X COMM or --value TYPE,COMM): hledger will convert all amounts to COMM, wherever it can find a suit- able market price (including by reversing or chaining prices). When you leave the valuation commodity unspecified (-V or --value TYPE): For each commodity A, hledger picks a default valuation commodity as follows, in this order of preference: 1. The price commodity from the latest P-declared market price for A on or before valuation date. 2. The price commodity from the latest P-declared market price for A on any date. (Allows conversion to proceed when there are inferred prices before the valuation date.) 3. If there are no P directives at all (any commodity or date) and the --infer-market-prices flag is used: the price commodity from the latest transaction-inferred price for A on or before valuation date. This means: o If you have P directives, they determine which commodities -V will convert, and to what. o If you have no P directives, and use the --infer-market-prices flag, costs determine it. Amounts for which no valuation commodity can be found are not con- verted. Simple valuation examples Here are some quick examples of -V: ; one euro is worth this many dollars from nov 1 P 2016/11/01 $1.10 ; purchase some euros on nov 3 2016/11/3 assets:euros 100 assets:checking ; the euro is worth fewer dollars by dec 21 P 2016/12/21 $1.03 How many euros do I have ? $ hledger -f t.j bal -N euros 100 assets:euros What are they worth at end of nov 3 ? $ hledger -f t.j bal -N euros -V -e 2016/11/4 $110.00 assets:euros What are they worth after 2016/12/21 ? (no report end date specified, defaults to today) $ hledger -f t.j bal -N euros -V $103.00 assets:euros --value: Flexible valuation -V and -X are special cases of the more general --value option: --value=TYPE[,COMM] TYPE is then, end, now or YYYY-MM-DD. COMM is an optional commodity symbol. Shows amounts converted to: - default valuation commodity (or COMM) using market prices at posting dates - default valuation commodity (or COMM) using market prices at period end(s) - default valuation commodity (or COMM) using current market prices - default valuation commodity (or COMM) using market prices at some date The TYPE part selects cost or value and valuation date: --value=then Convert amounts to their value in the default valuation commod- ity, using market prices on each posting's date. --value=end Convert amounts to their value in the default valuation commod- ity, using market prices on the last day of the report period (or if unspecified, the journal's end date); or in multiperiod reports, market prices on the last day of each subperiod. --value=now Convert amounts to their value in the default valuation commod- ity using current market prices (as of when report is gener- ated). --value=YYYY-MM-DD Convert amounts to their value in the default valuation commod- ity using market prices on this date. To select a different valuation commodity, add the optional ,COMM part: a comma, then the target commodity's symbol. Eg: --value=now,EUR. hledger will do its best to convert amounts to this commodity, deducing market prices as described above. More valuation examples Here are some examples showing the effect of --value, as seen with print: P 2000-01-01 A 1 B P 2000-02-01 A 2 B P 2000-03-01 A 3 B P 2000-04-01 A 4 B 2000-01-01 (a) 1 A @ 5 B 2000-02-01 (a) 1 A @ 6 B 2000-03-01 (a) 1 A @ 7 B Show the cost of each posting: $ hledger -f- print --cost 2000-01-01 (a) 5 B 2000-02-01 (a) 6 B 2000-03-01 (a) 7 B Show the value as of the last day of the report period (2000-02-29): $ hledger -f- print --value=end date:2000/01-2000/03 2000-01-01 (a) 2 B 2000-02-01 (a) 2 B With no report period specified, that shows the value as of the last day of the journal (2000-03-01): $ hledger -f- print --value=end 2000-01-01 (a) 3 B 2000-02-01 (a) 3 B 2000-03-01 (a) 3 B Show the current value (the 2000-04-01 price is still in effect today): $ hledger -f- print --value=now 2000-01-01 (a) 4 B 2000-02-01 (a) 4 B 2000-03-01 (a) 4 B Show the value on 2000/01/15: $ hledger -f- print --value=2000-01-15 2000-01-01 (a) 1 B 2000-02-01 (a) 1 B 2000-03-01 (a) 1 B Interaction of valuation and queries When matching postings based on queries in the presence of valuation, the following happens. 1. The query is separated into two parts: 1. the currency (cur:) or amount (amt:). 2. all other parts. 2. The postings are matched to the currency and amount queries based on pre-valued amounts. 3. Valuation is applied to the postings. 4. The postings are matched to the other parts of the query based on post-valued amounts. See: 1625 Effect of valuation on reports Here is a reference for how valuation is supposed to affect each part of hledger's reports (and a glossary). (It's wide, you'll have to scroll sideways.) It may be useful when troubleshooting. If you find problems, please report them, ideally with a reproducible example. Re- lated: #329, #1083. Report -B, --cost -V, -X --value=then --value=end --value=DATE, type --value=now -------------------------------------------------------------------------------------------- print posting cost value at re- value at posting value at re- value at amounts port end or date port or DATE/today today journal end balance unchanged unchanged unchanged unchanged unchanged asser- tions/as- signments register starting cost value at re- valued at day value at re- value at balance port or each historical port or DATE/today (-H) journal end posting was made journal end starting cost value at day valued at day value at day value at balance before re- each historical before re- DATE/today (-H) with port or posting was made port or report journal journal interval start start posting cost value at re- value at posting value at re- value at amounts port or date port or DATE/today journal end journal end summary summarised value at pe- sum of postings value at pe- value at posting cost riod ends in interval, val- riod ends DATE/today amounts ued at interval with re- start port in- terval running sum/average sum/average sum/average of sum/average sum/average total/av- of displayed of displayed displayed values of displayed of displayed erage values values values values balance (bs, bse, cf, is) balance sums of value at re- value at posting value at re- value at changes costs port end or date port or DATE/today of today of journal end sums of post- sums of of sums of ings postings postings budget like balance like balance like balance like bal- like balance amounts changes changes changes ances changes (--bud- get) grand to- sum of dis- sum of dis- sum of displayed sum of dis- sum of dis- tal played val- played val- valued played val- played values ues ues ues balance (bs, bse, cf, is) with re- port in- terval starting sums of value at re- sums of values of value at re- sums of post- balances costs of port start postings before port start ings before (-H) postings be- of sums of report start at of sums of report start fore report all postings respective post- all postings start before re- ing dates before re- port start port start balance sums of same as sums of values of balance value at changes costs of --value=end postings in pe- change in DATE/today of (bal, is, postings in riod at respec- each period, sums of post- bs period tive posting valued at ings --change, dates period ends cf --change) end bal- sums of same as sums of values of period end value at ances costs of --value=end postings from be- balances, DATE/today of (bal -H, postings fore period start valued at sums of post- is --H, from before to period end at period ends ings bs, cf) report start respective post- to period ing dates end budget like balance like balance like balance like bal- like balance amounts changes/end changes/end changes/end bal- ances changes/end (--bud- balances balances ances balances get) row to- sums, aver- sums, aver- sums, averages of sums, aver- sums, aver- tals, row ages of dis- ages of dis- displayed values ages of dis- ages of dis- averages played val- played val- played val- played values (-T, -A) ues ues ues column sums of dis- sums of dis- sums of displayed sums of dis- sums of dis- totals played val- played val- values played val- played values ues ues ues grand to- sum, average sum, average sum, average of sum, average sum, average tal, of column of column column totals of column of column to- grand av- totals totals totals tals erage --cumulative is omitted to save space, it works like -H but with a zero starting balance. Glossary: cost calculated using price(s) recorded in the transaction(s). value market value using available market price declarations, or the unchanged amount if no conversion rate can be found. report start the first day of the report period specified with -b or -p or date:, otherwise today. report or journal start the first day of the report period specified with -b or -p or date:, otherwise the earliest transaction date in the journal, otherwise today. report end the last day of the report period specified with -e or -p or date:, otherwise today. report or journal end the last day of the report period specified with -e or -p or date:, otherwise the latest transaction date in the journal, otherwise today. report interval a flag (-D/-W/-M/-Q/-Y) or period expression that activates the report's multi-period mode (whether showing one or many subperi- ods). PART 4: COMMANDS Commands overview Here are the built-in commands: DATA ENTRY These data entry commands are the only ones which can modify your jour- nal file. o add - add transactions using terminal prompts o import - add new transactions from other files, eg CSV files DATA CREATION o close - generate balance-zeroing/restoring transactions o rewrite - generate auto postings, like print --auto DATA MANAGEMENT o check - check for various kinds of error in the data o diff - compare account transactions in two journal files REPORTS, FINANCIAL o aregister (areg) - show transactions in a particular account o balancesheet (bs) - show assets, liabilities and net worth o balancesheetequity (bse) - show assets, liabilities and equity o cashflow (cf) - show changes in liquid assets o incomestatement (is) - show revenues and expenses REPORTS, VERSATILE o balance (bal) - show balance changes, end balances, budgets, gains.. o print - show transactions or export journal data o register (reg) - show postings in one or more accounts & running to- tal o roi - show return on investments REPORTS, BASIC o accounts - show account names o activity - show bar charts of posting counts per period o codes - show transaction codes o commodities - show commodity/currency symbols o descriptions - show transaction descriptions o files - show input file paths o notes - show note parts of transaction descriptions o payees - show payee parts of transaction descriptions o prices - show market prices o stats - show journal statistics o tags - show tag names o test - run self tests HELP o help - show the hledger manual with info/man/pager o demo - show small hledger demos in the terminal ADD-ONS And here are some typical add-on commands. Some of these are installed by the hledger-install script. If installed, they will appear in hledger's commands list: o ui - run hledger's terminal UI o web - run hledger's web UI o iadd - add transactions using a TUI (currently hard to build) o interest - generate interest transactions o stockquotes - download market prices from AlphaVantage o Scripts and add-ons - check-fancyassertions, edit, fifo, git, move, pijul, plot, and more.. Next, each command is described in detail, in alphabetical order. accounts Show account names. This command lists account names. By default it shows all known ac- counts, either used in transactions or declared with account direc- tives. With query arguments, only matched account names and account names ref- erenced by matched postings are shown. Or it can show just the used accounts (--used/-u), the declared ac- counts (--declared/-d), the accounts declared but not used (--unused), the accounts used but not declared (--undeclared), or the first account matched by an account name pattern, if any (--find). It shows a flat list by default. With --tree, it uses indentation to show the account hierarchy. In flat mode you can add --drop N to omit the first few account name components. Account names can be depth-clipped with depth:N or --depth N or -N. With --types, it also shows each account's type, if it's known. (See Declaring accounts > Account types.) With --positions, it also shows the file and line number of each ac- count's declaration, if any, and the account's overall declaration or- der; these may be useful when troubleshooting account display order. With --directives, it adds the account keyword, showing valid account directives which can be pasted into a journal file. This is useful to- gether with --undeclared when updating your account declarations to satisfy hledger check accounts. The --find flag can be used to look up a single account name, in the same way that the aregister command does. It returns the alphanumeri- cally-first matched account name, or if none can be found, it fails with a non-zero exit code. Examples: $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts $ hledger accounts --undeclared --directives >> $LEDGER_FILE $ hledger check accounts activity Show an ascii barchart of posting counts per interval. The activity command displays an ascii histogram showing transaction counts by day, week, month or other reporting interval (by day is the default). With query arguments, it counts only matched transactions. Examples: $ hledger activity --quarterly 2008-01-01 ** 2008-04-01 ******* 2008-07-01 2008-10-01 ** add Prompt for transactions and add them to the journal. Any arguments will be used as default inputs for the first N prompts. Many hledger users edit their journals directly with a text editor, or generate them from CSV. For more interactive data entry, there is the add command, which prompts interactively on the console for new trans- actions, and appends them to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also import). To use it, just run hledger add and follow the prompts. You can add as many transactions as you like; when you are finished, enter . or press control-d or control-c to exit. Features: o add tries to provide useful defaults, using the most similar (by de- scription) recent transaction (filtered by the query, if any) as a template. o You can also set the initial defaults with command line arguments. o Readline-style edit keys can be used during data entry. o The tab key will auto-complete whenever possible - accounts, pay- ees/descriptions, dates (yesterday, today, tomorrow). If the input area is empty, it will insert the default value. o If the journal defines a default commodity, it will be added to any bare numbers entered. o A parenthesised transaction code may be entered following a date. o Comments and tags may be entered following a description or amount. o If you make a mistake, enter < at any prompt to go one step backward. o Input prompts are displayed in a different colour when the terminal supports it. Example (see https://hledger.org/add.html for a detailed tutorial): $ hledger add Adding transactions to journal file /src/hledger/examples/sample.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control-d or control-c. Date [2015/05/22]: Description: supermarket Account 1: expenses:food Amount 1: $10 Account 2: assets:checking Amount 2 [$-10.0]: Account 3 (or . or enter to finish this transaction): . 2015/05/22 supermarket expenses:food $10 assets:checking $-10.0 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl-D/ctrl-C to quit) Date [2015/05/22]: $ On Microsoft Windows, the add command makes sure that no part of the file path ends with a period, as that would cause problems (#1056). aregister (areg) Show the transactions and running historical balance of a single ac- count, with each transaction displayed as one line. aregister shows the overall transactions affecting a particular account (and any subaccounts). Each report line represents one transaction in this account. Transactions before the report start date are always in- cluded in the running balance (--historical mode is always on). This is a more "real world", bank-like view than the register command (which shows individual postings, possibly from multiple accounts, not necessarily in historical mode). As a quick rule of thumb: - use areg- ister for reviewing and reconciling real-world asset/liability accounts - use register for reviewing detailed revenues/expenses. aregister requires one argument: the account to report on. You can write either the full account name, or a case-insensitive regular ex- pression which will select the alphabetically first matched account. When there are multiple matches, the alphabetically-first choice can be surprising; eg if you have assets:per:checking 1 and assets:biz:check- ing 2 accounts, hledger areg checking would select assets:biz:checking 2. It's just a convenience to save typing, so if in doubt, write the full account name, or a distinctive substring that matches uniquely. Transactions involving subaccounts of this account will also be shown. aregister ignores depth limits, so its final total will always match a balance report with similar arguments. Any additional arguments form a query which will filter the transac- tions shown. Note some queries will disturb the running balance, caus- ing it to be different from the account's real-world running balance. An example: this shows the transactions and historical running balance during july, in the first account whose name contains "checking": $ hledger areg checking date:jul Each aregister line item shows: o the transaction's date (or the relevant posting's date if different, see below) o the names of all the other account(s) involved in this transaction (probably abbreviated) o the total change to this account's balance from this transaction o the account's historical running balance after this transaction. Transactions making a net change of zero are not shown by default; add the -E/--empty flag to show them. For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the --align-all flag. This command also supports the output destination and output format op- tions. The output formats supported are txt, csv, tsv, and json. aregister and posting dates aregister always shows one line (and date and amount) per transaction. But sometimes transactions have postings with different dates. Also, not all of a transaction's postings may be within the report period. To resolve this, aregister shows the earliest of the transaction's date and posting dates that is in-period, and the sum of the in-period post- ings. In other words it will show a combined line item with just the earliest date, and the running balance will (temporarily, until the transaction's last posting) be inaccurate. Use register -H if you need to see the individual postings. There is also a --txn-dates flag, which filters strictly by transaction date, ignoring posting dates. This too can cause an inaccurate running balance. balance (bal) Show accounts and their balances. balance is one of hledger's oldest and most versatile commands, for listing account balances, balance changes, values, value changes and more, during one time period or many. Generally it shows a table, with rows representing accounts, and columns representing periods. Note there are some higher-level variants of the balance command with convenient defaults, which can be simpler to use: balancesheet, bal- ancesheetequity, cashflow and incomestatement. When you need more con- trol, then use balance. balance features Here's a quick overview of the balance command's features, followed by more detailed descriptions and examples. Many of these work with the higher-level commands as well. balance can show.. o accounts as a list (-l) or a tree (-t) o optionally depth-limited (-[1-9]) o sorted by declaration order and name, or by amount ..and their.. o balance changes (the default) o or actual and planned balance changes (--budget) o or value of balance changes (-V) o or change of balance values (--valuechange) o or unrealised capital gain/loss (--gain) o or postings count (--count) ..in.. o one time period (the whole journal period by default) o or multiple periods (-D, -W, -M, -Q, -Y, -p INTERVAL) ..either.. o per period (the default) o or accumulated since report start date (--cumulative) o or accumulated since account creation (--historical/-H) ..possibly converted to.. o cost (--value=cost[,COMM]/--cost/-B) o or market value, as of transaction dates (--value=then[,COMM]) o or at period ends (--value=end[,COMM]) o or now (--value=now) o or at some other date (--value=YYYY-MM-DD) ..with.. o totals (-T), averages (-A), percentages (-%), inverted sign (--in- vert) o rows and columns swapped (--transpose) o another field used as account name (--pivot) o custom-formatted line items (single-period reports only) (--format) o commodities displayed on the same line or multiple lines (--layout) This command supports the output destination and output format options, with output formats txt, csv, tsv, json, and (multi-period reports only:) html. In txt output in a colour-supporting terminal, negative amounts are shown in red. The --related/-r flag shows the balance of the other postings in the transactions of the postings which would normally be shown. Simple balance report With no arguments, balance shows a list of all accounts and their change of balance - ie, the sum of posting amounts, both inflows and outflows - during the entire period of the journal. ("Simple" here means just one column of numbers, covering a single period. You can also have multi-period reports, described later.) For real-world accounts, these numbers will normally be their end bal- ance at the end of the journal period; more on this below. Accounts are sorted by declaration order if any, and then alphabeti- cally by account name. For instance (using examples/sample.journal): $ hledger -f examples/sample.journal bal $1 assets:bank:saving $-2 assets:cash $1 expenses:food $1 expenses:supplies $-1 income:gifts $-1 income:salary $1 liabilities:debts -------------------- 0 Accounts with a zero balance (and no non-zero subaccounts, in tree mode - see below) are hidden by default. Use -E/--empty to show them (re- vealing assets:bank:checking here): $ hledger -f examples/sample.journal bal -E 0 assets:bank:checking $1 assets:bank:saving $-2 assets:cash $1 expenses:food $1 expenses:supplies $-1 income:gifts $-1 income:salary $1 liabilities:debts -------------------- 0 The total of the amounts displayed is shown as the last line, unless -N/--no-total is used. Balance report line format For single-period balance reports displayed in the terminal (only), you can use --format FMT to customise the format and content of each line. Eg: $ hledger -f examples/sample.journal balance --format "%20(account) %12(total)" assets $-1 bank:saving $1 cash $-2 expenses $2 food $1 supplies $1 income $-2 gifts $-1 salary $-1 liabilities:debts $1 --------------------------------- 0 The FMT format string specifies the formatting applied to each ac- count/balance pair. It may contain any suitable text, with data fields interpolated like so: %[MIN][.MAX](FIELDNAME) o MIN pads with spaces to at least this width (optional) o MAX truncates at this width (optional) o FIELDNAME must be enclosed in parentheses, and can be one of: o depth_spacer - a number of spaces equal to the account's depth, or if MIN is specified, MIN * depth spaces. o account - the account's name o total - the account's balance/posted total, right justified Also, FMT can begin with an optional prefix to control how multi-com- modity amounts are rendered: o %_ - render on multiple lines, bottom-aligned (the default) o %^ - render on multiple lines, top-aligned o %, - render on one line, comma-separated There are some quirks. Eg in one-line mode, %(depth_spacer) has no ef- fect, instead %(account) has indentation built in. Experimentation may be needed to get pleasing results. Some example formats: o %(total) - the account's total o %-20.20(account) - the account's name, left justified, padded to 20 characters and clipped at 20 characters o %,%-50(account) %25(total) - account name padded to 50 characters, total padded to 20 characters, with multiple commodities rendered on one line o %20(total) %2(depth_spacer)%-(account) - the default format for the single-column balance report Filtered balance report You can show fewer accounts, a different time period, totals from cleared transactions only, etc. by using query arguments or options to limit the postings being matched. Eg: $ hledger -f examples/sample.journal bal --cleared assets date:200806 $-2 assets:cash -------------------- $-2 List or tree mode By default, or with -l/--flat, accounts are shown as a flat list with their full names visible, as in the examples above. With -t/--tree, the account hierarchy is shown, with subaccounts' "leaf" names indented below their parent: $ hledger -f examples/sample.journal balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 Notes: o "Boring" accounts are combined with their subaccount for more compact output, unless --no-elide is used. Boring accounts have no balance of their own and just one subaccount (eg assets:bank and liabilities above). o All balances shown are "inclusive", ie including the balances from all subaccounts. Note this means some repetition in the output, which requires explanation when sharing reports with non-plaintextac- counting-users. A tree mode report's final total is the sum of the top-level balances shown, not of all the balances shown. o Each group of sibling accounts (ie, under a common parent) is sorted separately. Depth limiting With a depth:NUM query, or --depth NUM option, or just -NUM (eg: -3) balance reports will show accounts only to the specified depth, hiding the deeper subaccounts. This can be useful for getting an overview without too much detail. Account balances at the depth limit always include the balances from any deeper subaccounts (even in list mode). Eg, limiting to depth 1: $ hledger -f examples/sample.journal balance -1 $-1 assets $2 expenses $-2 income $1 liabilities -------------------- 0 Dropping top-level accounts You can also hide one or more top-level account name parts, using --drop NUM. This can be useful for hiding repetitive top-level account names: $ hledger -f examples/sample.journal bal expenses --drop 1 $1 food $1 supplies -------------------- $2 Showing declared accounts With --declared, accounts which have been declared with an account di- rective will be included in the balance report, even if they have no transactions. (Since they will have a zero balance, you will also need -E/--empty to see them.) More precisely, leaf declared accounts (with no subaccounts) will be included, since those are usually the more useful in reports. The idea of this is to be able to see a useful "complete" balance re- port, even when you don't have transactions in all of your declared ac- counts yet. Sorting by amount With -S/--sort-amount, accounts with the largest (most positive) bal- ances are shown first. Eg: hledger bal expenses -MAS shows your biggest averaged monthly expenses first. When more than one commodity is present, they will be sorted by the alphabetically earliest commod- ity first, and then by subsequent commodities (if an amount is missing a commodity, it is treated as 0). Revenues and liability balances are typically negative, however, so -S shows these in reverse order. To work around this, you can add --in- vert to flip the signs. (Or, use one of the higher-level reports, which flip the sign automatically. Eg: hledger incomestatement -MAS). Percentages With -%/--percent, balance reports show each account's value expressed as a percentage of the (column) total. Note it is not useful to calculate percentages if the amounts in a col- umn have mixed signs. In this case, make a separate report for each sign, eg: $ hledger bal -% amt:`>0` $ hledger bal -% amt:`<0` Similarly, if the amounts in a column have mixed commodities, convert them to one commodity with -B, -V, -X or --value, or make a separate report for each commodity: $ hledger bal -% cur:\\$ $ hledger bal -% cur: Multi-period balance report With a report interval (set by the -D/--daily, -W/--weekly, -M/--monthly, -Q/--quarterly, -Y/--yearly, or -p/--period flag), bal- ance shows a tabular report, with columns representing successive time periods (and a title): $ hledger -f examples/sample.journal bal --quarterly income expenses -E Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 ===================++================================= expenses:food || 0 $1 0 0 expenses:supplies || 0 $1 0 0 income:gifts || 0 $-1 0 0 income:salary || $-1 0 0 0 -------------------++--------------------------------- || $-1 $1 0 0 Notes: o The report's start/end dates will be expanded, if necessary, to fully encompass the displayed subperiods (so that the first and last subpe- riods have the same duration as the others). o Leading and trailing periods (columns) containing all zeroes are not shown, unless -E/--empty is used. o Accounts (rows) containing all zeroes are not shown, unless -E/--empty is used. o Amounts with many commodities are shown in abbreviated form, unless --no-elide is used. (experimental) o Average and/or total columns can be added with the -A/--average and -T/--row-total flags. o The --transpose flag can be used to exchange rows and columns. o The --pivot FIELD option causes a different transaction field to be used as "account name". See PIVOTING. Multi-period reports with many periods can be too wide for easy viewing in the terminal. Here are some ways to handle that: o Hide the totals row with -N/--no-total o Convert to a single currency with -V o Maximize the terminal window o Reduce the terminal's font size o View with a pager like less, eg: hledger bal -D --color=yes | less -RS o Output as CSV and use a CSV viewer like visidata (hledger bal -D -O csv | vd -f csv), Emacs' csv-mode (M-x csv-mode, C-c C-a), or a spreadsheet (hledger bal -D -o a.csv && open a.csv) o Output as HTML and view with a browser: hledger bal -D -o a.html && open a.html Balance change, end balance It's important to be clear on the meaning of the numbers shown in bal- ance reports. Here is some terminology we use: A balance change is the net amount added to, or removed from, an ac- count during some period. An end balance is the amount accumulated in an account as of some date (and some time, but hledger doesn't store that; assume end of day in your timezone). It is the sum of previous balance changes. We call it a historical end balance if it includes all balance changes since the account was created. For a real world account, this means it will match the "historical record", eg the balances reported in your bank statements or bank web UI. (If they are correct!) In general, balance changes are what you want to see when reviewing revenues and expenses, and historical end balances are what you want to see when reviewing or reconciling asset, liability and equity accounts. balance shows balance changes by default. To see accurate historical end balances: 1. Initialise account starting balances with an "opening balances" transaction (a transfer from equity to the account), unless the journal covers the account's full lifetime. 2. Include all of of the account's prior postings in the report, by not specifying a report start date, or by using the -H/--historical flag. (-H causes report start date to be ignored when summing post- ings.) Balance report types The balance command is quite flexible; here is the full detail on how to control what it reports. If the following seems complicated, don't worry - this is for advanced reporting, and it does take time and ex- perimentation to get familiar with all the report modes. There are three important option groups: hledger balance [CALCULATIONTYPE] [ACCUMULATIONTYPE] [VALUATIONTYPE] ... Calculation type The basic calculation to perform for each table cell. It is one of: o --sum : sum the posting amounts (default) o --budget : sum the amounts, but also show the budget goal amount (for each account/period) o --valuechange : show the change in period-end historical balance val- ues (caused by deposits, withdrawals, and/or market price fluctua- tions) o --gain : show the unrealised capital gain/loss, (the current valued balance minus each amount's original cost) o --count : show the count of postings Accumulation type How amounts should accumulate across report periods. Another way to say it: which time period's postings should contribute to each cell's calculation. It is one of: o --change : calculate with postings from column start to column end, ie "just this column". Typically used to see revenues/expenses. (default for balance, incomestatement) o --cumulative : calculate with postings from report start to column end, ie "previous columns plus this column". Typically used to show changes accumulated since the report's start date. Not often used. o --historical/-H : calculate with postings from journal start to col- umn end, ie "all postings from before report start date until this column's end". Typically used to see historical end balances of as- sets/liabilities/equity. (default for balancesheet, balancesheete- quity, cashflow) Valuation type Which kind of value or cost conversion should be applied, if any, be- fore displaying the report. It is one of: o no valuation type : don't convert to cost or value (default) o --value=cost[,COMM] : convert amounts to cost (then optionally to some other commodity) o --value=then[,COMM] : convert amounts to market value on transaction dates o --value=end[,COMM] : convert amounts to market value on period end date(s) (default with --valuechange, --gain) o --value=now[,COMM] : convert amounts to market value on today's date o --value=YYYY-MM-DD[,COMM] : convert amounts to market value on an- other date or one of the equivalent simpler flags: o -B/--cost : like --value=cost (though, note --cost and --value are independent options which can both be used at once) o -V/--market : like --value=end o -X COMM/--exchange COMM : like --value=end,COMM See Cost reporting and Value reporting for more about these. Combining balance report types Most combinations of these options should produce reasonable reports, but if you find any that seem wrong or misleading, let us know. The following restrictions are applied: o --valuechange implies --value=end o --valuechange makes --change the default when used with the bal- ancesheet/balancesheetequity commands o --cumulative or --historical disables --row-total/-T For reference, here is what the combinations of accumulation and valua- tion show: Valua- no valuation --value= then --value= end --value= tion:> YYYY-MM-DD Accumu- /now lation:v ----------------------------------------------------------------------------------- --change change in period sum of post- period-end DATE-value of ing-date market value of change change in pe- values in period in period riod --cumu- change from re- sum of post- period-end DATE-value of lative port start to ing-date market value of change change from period end values from re- from report report start port start to pe- start to period to period end riod end end --his- change from sum of post- period-end DATE-value of torical journal start to ing-date market value of change change from /-H period end (his- values from jour- from journal journal start torical end bal- nal start to pe- start to period to period end ance) riod end end Budget report The --budget report type is like a regular balance report, but with two main differences: o Budget goals and performance percentages are also shown, in brackets o Accounts which don't have budget goals are hidden by default. This is useful for comparing planned and actual income, expenses, time usage, etc. Periodic transaction rules are used to define budget goals. For exam- ple, here's a periodic rule defining monthly goals for bus travel and food expenses: ;; Budget ~ monthly (expenses:bus) $30 (expenses:food) $400 After recording some actual expenses, ;; Two months worth of expenses 2017-11-01 income $-1950 expenses:bus $35 expenses:food:groceries $310 expenses:food:dining $42 expenses:movies $38 assets:bank:checking 2017-12-01 income $-2100 expenses:bus $53 expenses:food:groceries $380 expenses:food:dining $32 expenses:gifts $100 assets:bank:checking we can see a budget report like this: $ hledger bal -M --budget Budget performance in 2017-11-01..2017-12-31: || Nov Dec ===============++============================================ || $-425 $-565 expenses || $425 [ 99% of $430] $565 [131% of $430] expenses:bus || $35 [117% of $30] $53 [177% of $30] expenses:food || $352 [ 88% of $400] $412 [103% of $400] ---------------++-------------------------------------------- || 0 [ 0% of $430] 0 [ 0% of $430] This is "goal-based budgeting"; you define goals for accounts and peri- ods, often recurring, and hledger shows performance relative to the goals. This contrasts with "envelope budgeting", which is more de- tailed and strict - useful when cash is tight, but also quite a bit more work. https://plaintextaccounting.org/Budgeting has more on this topic. Using the budget report Historically this report has been confusing and fragile. hledger's version should be relatively robust and intuitive, but you may still find surprises. Here are more notes to help with learning and trou- bleshooting. o In the above example, expenses:bus and expenses:food are shown be- cause they have budget goals during the report period. o Their parent expenses is also shown, with budget goals aggregated from the children. o The subaccounts expenses:food:groceries and expenses:food:dining are not shown since they have no budget goal of their own, but they con- tribute to expenses:food's actual amount. o Unbudgeted accounts expenses:movies and expenses:gifts are also not shown, but they contribute to expenses's actual amount. o The other unbudgeted accounts income and assets:bank:checking are grouped as . o --depth or depth: can be used to limit report depth in the usual way (but will not reveal unbudgeted subaccounts). o Amounts are always inclusive of subaccounts (even in -l/--list mode). o Numbers displayed in a --budget report will not always agree with the totals, because of hidden unbudgeted accounts; this is normal. -E/--empty can be used to reveal the hidden accounts. o In the periodic rules used for setting budget goals, unbalanced post- ings are convenient. o You can filter budget reports with the usual queries, eg to focus on particular accounts. It's common to restrict them to just expenses. (The account is occasionally hard to exclude; this is because of date surprises, discussed below.) o When you have multiple currencies, you may want to convert them to one (-X COMM --infer-market-prices) and/or show just one at a time (cur:COMM). If you do need to show multiple currencies at once, --layout bare can be helpful. o You can "roll over" amounts (actual and budgeted) to the next period with --cumulative. See also: https://hledger.org/budgeting.html. Budget date surprises With small data, or when starting out, some of the generated budget goal transaction dates might fall outside the report periods. Eg with the following journal and report, the first period appears to have no expenses:food budget. (Also the account should be ex- cluded by the expenses query, but isn't.): ~ monthly in 2020 (expenses:food) $500 2020-01-15 expenses:food $400 assets:checking $ hledger bal --budget expenses Budget performance in 2020-01-15: || 2020-01-15 ===============++==================== || $400 expenses:food || 0 [ 0% of $500] ---------------++-------------------- || $400 [80% of $500] In this case, the budget goal transactions are generated on first days of of month (this can be seen with hledger print --forecast tag:gener- ated expenses). Whereas the report period defaults to just the 15th day of january (this can be seen from the report table's column head- ings). To fix this kind of thing, be more explicit about the report period (and/or the periodic rules' dates). In this case, adding -b 2020 does the trick. Selecting budget goals By default, the budget report uses all available periodic transaction rules to generate goals. This includes rules with a different report interval from your report. Eg if you have daily, weekly and monthly periodic rules, all of these will contribute to the goals in a monthly budget report. You can select a subset of periodic rules by providing an argument to the --budget flag. --budget=DESCPAT will match all periodic rules whose description contains DESCPAT, a case-insensitive substring (not a regular expression or query). This means you can give your periodic rules descriptions (remember that two spaces are needed between period expression and description), and then select from multiple budgets de- fined in your journal. Budgeting vs forecasting --budget and --forecast both use the periodic transaction rules in the journal to generate temporary transactions for reporting purposes. However they are separate features - though you can use both at the same time if you want. Here are some differences between them: 1. --budget is a command-specific option; it selects the budget report. --forecast is a general option; forecasting works with all reports. 2. --budget uses all periodic rules; --budget=DESCPAT uses just the rules matched by DESCPAT. --forecast uses all periodic rules. 3. --budget's budget goal transactions are invisible, except that they produce goal amounts. --forecast's forecast transactions are visible, and appear in re- ports. 4. --budget generates budget goal transactions throughout the report period, optionally restricted by periods specified in the periodic transaction rules. --forecast generates forecast transactions from after the last reg- ular transaction, to the end of the report period; while --fore- cast=PERIODEXPR generates them throughout the specified period; both optionally restricted by periods specified in the periodic transaction rules. Balance report layout The --layout option affects how balance reports show multi-commodity amounts and commodity symbols, which can improve readability. It can also normalise the data for easy consumption by other programs. It has four possible values: o --layout=wide[,WIDTH]: commodities are shown on a single line, op- tionally elided to WIDTH o --layout=tall: each commodity is shown on a separate line o --layout=bare: commodity symbols are in their own column, amounts are bare numbers o --layout=tidy: data is normalised to easily-consumed "tidy" form, with one row per data value Here are the --layout modes supported by each output format; note only CSV output supports all of them: - txt csv html json sql ------------------------------------- wide Y Y Y tall Y Y Y bare Y Y Y tidy Y Examples: o Wide layout. With many commodities, reports can be very wide: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=wide Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++==================================================================================================================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, -98.12 USD, 10.00 VEA, 18.00 VHT -11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT ------------------++-------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------- || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, -98.12 USD, 10.00 VEA, 18.00 VHT -11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT o Limited wide layout. A width limit reduces the width, but some com- modities will be hidden: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=wide,32 Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++=========================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. -11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. ------------------++--------------------------------------------------------------------------------------------------------------------------- || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. -11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. o Tall layout. Each commodity gets a new line (may be different in each column), and account names are repeated: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=tall Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++================================================== Assets:US:ETrade || 10.00 ITOT 70.00 GLD -11.00 ITOT 70.00 GLD Assets:US:ETrade || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT Assets:US:ETrade || 12.00 VEA -98.12 USD 14.00 VEA 5120.50 USD Assets:US:ETrade || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA Assets:US:ETrade || 18.00 VHT 294.00 VHT ------------------++-------------------------------------------------- || 10.00 ITOT 70.00 GLD -11.00 ITOT 70.00 GLD || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT || 12.00 VEA -98.12 USD 14.00 VEA 5120.50 USD || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA || 18.00 VHT 294.00 VHT o Bare layout. Commodity symbols are kept in one column, each commod- ity gets its own report row, account names are repeated: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=bare Balance changes in 2012-01-01..2014-12-31: || Commodity 2012 2013 2014 Total ==================++============================================= Assets:US:ETrade || GLD 0 70.00 0 70.00 Assets:US:ETrade || ITOT 10.00 18.00 -11.00 17.00 Assets:US:ETrade || USD 337.18 -98.12 4881.44 5120.50 Assets:US:ETrade || VEA 12.00 10.00 14.00 36.00 Assets:US:ETrade || VHT 106.00 18.00 170.00 294.00 ------------------++--------------------------------------------- || GLD 0 70.00 0 70.00 || ITOT 10.00 18.00 -11.00 17.00 || USD 337.18 -98.12 4881.44 5120.50 || VEA 12.00 10.00 14.00 36.00 || VHT 106.00 18.00 170.00 294.00 o Bare layout also affects CSV output, which is useful for producing data that is easier to consume, eg for making charts: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -O csv --layout=bare "account","commodity","balance" "Assets:US:ETrade","GLD","70.00" "Assets:US:ETrade","ITOT","17.00" "Assets:US:ETrade","USD","5120.50" "Assets:US:ETrade","VEA","36.00" "Assets:US:ETrade","VHT","294.00" "total","GLD","70.00" "total","ITOT","17.00" "total","USD","5120.50" "total","VEA","36.00" "total","VHT","294.00" o Note: bare layout will sometimes display an extra row for the no-sym- bol commodity, because of zero amounts (hledger treats zeroes as com- modity-less, usually). This can break hledger-bar confusingly (workaround: add a cur: query to exclude the no-symbol row). o Tidy layout produces normalised "tidy data", where every variable has its own column and each row represents a single data point. See https://cran.r-project.org/web/packages/tidyr/vi- gnettes/tidy-data.html for more. This is the easiest kind of data for other software to consume. Here's how it looks: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -Y -O csv --layout=tidy "account","period","start_date","end_date","commodity","value" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","GLD","0" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","ITOT","10.00" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","USD","337.18" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","VEA","12.00" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","VHT","106.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","GLD","70.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","ITOT","18.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","USD","-98.12" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","VEA","10.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","VHT","18.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","GLD","0" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","ITOT","-11.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","USD","4881.44" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","VEA","14.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","VHT","170.00" Useful balance reports Some frequently used balance options/reports are: o bal -M revenues expenses Show revenues/expenses in each month. Also available as the incomes- tatement command. o bal -M -H assets liabilities Show historical asset/liability balances at each month end. Also available as the balancesheet command. o bal -M -H assets liabilities equity Show historical asset/liability/equity balances at each month end. Also available as the balancesheetequity command. o bal -M assets not:receivable Show changes to liquid assets in each month. Also available as the cashflow command. Also: o bal -M expenses -2 -SA Show monthly expenses summarised to depth 2 and sorted by average amount. o bal -M --budget expenses Show monthly expenses and budget goals. o bal -M --valuechange investments Show monthly change in market value of investment assets. o bal investments --valuechange -D date:lastweek amt:'>1000' -STA [--invert] Show top gainers [or losers] last week balancesheet (bs) This command displays a balance sheet, showing historical ending bal- ances of asset and liability accounts. (To see equity as well, use the balancesheetequity command.) Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the Asset, Cash or Liability type (see account types). Or if no such accounts are declared, it shows top-level accounts named asset or liability (case insensitive, plurals allowed) and their subaccounts. Example: $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 This command is a higher-level variant of the balance command, and sup- ports many of that command's features, such as multi-period reports. It is similar to hledger balance -H assets liabilities, but with smarter account detection, and liabilities displayed with their sign flipped. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, tsv, html, and (exper- imental) json. balancesheetequity (bse) This command displays a balance sheet, showing historical ending bal- ances of asset, liability and equity accounts. Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the Asset, Cash, Liability or Equity type (see account types). Or if no such accounts are declared, it shows top-level accounts named asset, liability or equity (case in- sensitive, plurals allowed) and their subaccounts. Example: $ hledger balancesheetequity Balance Sheet With Equity Assets: $-2 assets $1 bank:saving $-3 cash -------------------- $-2 Liabilities: $1 liabilities:debts -------------------- $1 Equity: $1 equity:owner -------------------- $1 Total: -------------------- 0 This command is a higher-level variant of the balance command, and sup- ports many of that command's features, such as multi-period reports. It is similar to hledger balance -H assets liabilities equity, but with smarter account detection, and liabilities/equity displayed with their sign flipped. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, tsv, html, and (exper- imental) json. cashflow (cf) This command displays a cashflow statement, showing the inflows and outflows affecting "cash" (ie, liquid, easily convertible) assets. Amounts are shown with normal positive sign, as in conventional finan- cial statements. This report shows accounts declared with the Cash type (see account types). Or if no such accounts are declared, it shows accounts o under a top-level account named asset (case insensitive, plural al- lowed) o whose name contains some variation of cash, bank, checking or saving. More precisely: all accounts matching this case insensitive regular ex- pression: ^assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|currentcash)(:|$) and their subaccounts. An example cashflow report: $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 This command is a higher-level variant of the balance command, and sup- ports many of that command's features, such as multi-period reports. It is similar to hledger balance assets not:fixed not:investment not:receivable, but with smarter account detection. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, tsv, html, and (exper- imental) json. check Check for various kinds of errors in your data. hledger provides a number of built-in error checks to help prevent problems in your data. Some of these are run automatically; or, you can use this check command to run them on demand, with no output and a zero exit code if all is well. Specify their names (or a prefix) as argument(s). Some examples: hledger check # basic checks hledger check -s # basic + strict checks hledger check ordereddates payees # basic + two other checks If you are an Emacs user, you can also configure flycheck-hledger to run these checks, providing instant feedback as you edit the journal. Here are the checks currently available: Default checks These checks are run automatically by (almost) all hledger commands: o parseable - data files are in a supported format, with no syntax er- rors and no invalid include directives. o autobalanced - all transactions are balanced, after converting to cost. Missing amounts and missing costs are inferred automatically where possible. o assertions - all balance assertions in the journal are passing. (This check can be disabled with -I/--ignore-assertions.) Strict checks These additional checks are run when the -s/--strict (strict mode) flag is used. Or, they can be run by giving their names as arguments to check: o balanced - all transactions are balanced after converting to cost, without inferring missing costs. If conversion costs are required, they must be explicit. o accounts - all account names used by transactions have been declared o commodities - all commodity symbols used have been declared Other checks These checks can be run only by giving their names as arguments to check. They are more specialised and not desirable for everyone: o ordereddates - transactions are ordered by date within each file o payees - all payees used by transactions have been declared o recentassertions - all accounts with balance assertions have a bal- ance assertion within 7 days of their latest posting o tags - all tags used by transactions have been declared o uniqueleafnames - all account leaf names are unique Custom checks A few more checks are are available as separate add-on commands, in https://github.com/simonmichael/hledger/tree/master/bin: o hledger-check-tagfiles - all tag values containing / (a forward slash) exist as file paths o hledger-check-fancyassertions - more complex balance assertions are passing You could make similar scripts to perform your own custom checks. See: Cookbook -> Scripting. More about specific checks hledger check recentassertions will complain if any balance-asserted account has postings more than 7 days after its latest balance asser- tion. This aims to prevent the situation where you are regularly up- dating your journal, but forgetting to check your balances against the real world, then one day must dig back through months of data to find an error. It assumes that adding a balance assertion requires/reminds you to check the real-world balance. (That may not be true if you auto-generate balance assertions from bank data; in that case, I recom- mend to import transactions uncleared, and when you manually review and clear them, also check the latest assertion against the real-world bal- ance.) close (equity) Generate transactions which transfer account balances to and/or from another account (typically equity). This can be useful for migrating balances to a new journal file, or for merging earnings into equity at end of accounting period. By default, it prints a transaction that zeroes out ALE accounts (as- set, liability, equity accounts; this requires account types to be con- figured); or if ACCTQUERY is provided, the accounts matched by that. (experimental) This command has four main modes, corresponding to the most common use cases: 1. With --close (default), it prints a "closing balances" transaction that zeroes out ALE (asset, liability, equity) accounts by default (this requires account types to be inferred or declared); or, the accounts matched by the provided ACCTQUERY arguments. 2. With --open, it prints an opposite "opening balances" transaction that restores those balances from zero. This is similar to Ledger's equity command. 3. With --migrate, it prints both the closing and opening transactions. This is the preferred way to migrate balances to a new file: run hledger close --migrate, add the closing transaction at the end of the old file, and add the opening transaction at the start of the new file. The matching closing/opening transactions cancel each other out, preserving correct balances during multi-file reporting. 4. With --retain, it prints a "retain earnings" transaction that trans- fers RX (revenue and expense) balances to equity:retained earnings. Businesses traditionally do this at the end of each accounting pe- riod; it is less necessary with computer-based accounting, but it could still be useful if you want to see the accounting equation (A=L+E) satisfied. In all modes, the defaults can be overridden: o the transaction descriptions can be changed with --close-desc=DESC and --open-desc=DESC o the account to transfer to/from can be changed with --close-acct=ACCT and --open-acct=ACCT o the accounts to be closed/opened can be changed with ACCTQUERY (ac- count query arguments). o the closing/opening dates can be changed with -e DATE (a report end date) By default just one destination/source posting will be used, with its amount left implicit. With --x/--explicit, the amount will be shown explicitly, and if it involves multiple commodities, a separate posting will be generated for each of them (similar to print -x). With --show-costs, any amount costs are shown, with separate postings for each cost. This is currently the best way to view investment lots. If you have many currency conversion or investment transactions, it can generate very large journal entries. With --interleaved, each individual transfer is shown with source and destination postings next to each other. This could be useful for troubleshooting. The default closing date is yesterday, or the journal's end date, whichever is later. You can change this by specifying a report end date with -e. The last day of the report period will be the closing date, eg -e 2024 means "close on 2023-12-31". The opening date is al- ways the day after the closing date. close and balance assertions Balance assertions will be generated, verifying that the accounts have been reset to zero (and then restored to their previous balances, if there is an opening transaction). These provide useful error checking, but you can ignore them temporar- ily with -I, or remove them if you prefer. You probably should avoid filtering transactions by status or realness (-C, -R, status:), or generating postings (--auto), with this command, since the balance assertions would depend on these. Note custom posting dates spanning the file boundary will disrupt the balance assertions: 2023-12-30 a purchase made in december, cleared in january expenses:food 5 assets:bank:checking -5 ; date: 2023-01-02 To solve that you can transfer the money to and from a temporary ac- count, in effect splitting the multi-day transaction into two sin- gle-day transactions: ; in 2022.journal: 2022-12-30 a purchase made in december, cleared in january expenses:food 5 equity:pending -5 ; in 2023.journal: 2023-01-02 last year's transaction cleared equity:pending 5 = 0 assets:bank:checking -5 Example: retain earnings Record 2022's revenues/expenses as retained earnings on 2022-12-31, ap- pending the generated transaction to the journal: $ hledger close --retain -f 2022.journal -p 2022 >> 2022.journal Note 2022's income statement will now show only zeroes, because rev- enues and expenses have been moved entirely to equity. To see them again, you could exclude the retain transaction: $ hledger -f 2022.journal is not:desc:'retain earnings' Example: migrate balances to a new file Close assets/liabilities/equity on 2022-12-31 and re-open them on 2023-01-01: $ hledger close --migrate -f 2022.journal -p 2022 # copy/paste the closing transaction to the end of 2022.journal # copy/paste the opening transaction to the start of 2023.journal Now 2022's balance sheet will show only zeroes, indicating a balanced accounting equation. (Unless you are using @/@@ notation - in that case, try adding --infer-equity.) To see the end-of-year balances again, you could exclude the closing transaction: $ hledger -f 2022.journal bs not:desc:'closing balances' Example: excluding closing/opening transactions When combining many files for multi-year reports, the closing/opening transactions cause some noise in transaction-oriented reports like print and register. You can exclude them as shown above, but not:desc:... is not ideal as it depends on consistent descriptions; also you will want to avoid excluding the very first opening transac- tion, which could be awkward. Here is one alternative, using tags: Add clopen: tags to all opening/closing balances transactions except the first, like this: ; 2021.journal 2021-06-01 first opening balances ... 2021-12-31 closing balances ; clopen:2022 ... ; 2022.journal 2022-01-01 opening balances ; clopen:2022 ... 2022-12-31 closing balances ; clopen:2023 ... ; 2023.journal 2023-01-01 opening balances ; clopen:2023 ... Now, assuming a combined journal like: ; all.journal include 2021.journal include 2022.journal include 2023.journal The clopen: tag can exclude all but the first opening transaction. To show a clean multi-year checking register: $ hledger -f all.journal areg checking not:tag:clopen And the year values allow more precision. To show 2022's year-end bal- ance sheet: $ hledger -f all.journal bs -e2023 not:tag:clopen=2023 codes List the codes seen in transactions, in the order parsed. This command prints the value of each transaction's code field, in the order transactions were parsed. The transaction code is an optional value written in parentheses between the date and description, often used to store a cheque number, order number or similar. Transactions aren't required to have a code, and missing or empty codes will not be shown by default. With the -E/--empty flag, they will be printed as blank lines. You can add a query to select a subset of transactions. Examples: 2022/1/1 (123) Supermarket Food $5.00 Checking 2022/1/2 (124) Post Office Postage $8.32 Checking 2022/1/3 Supermarket Food $11.23 Checking 2022/1/4 (126) Post Office Postage $3.21 Checking $ hledger codes 123 124 126 $ hledger codes -E 123 124 126 commodities List all commodity/currency symbols used or declared in the journal. demo Play demos of hledger usage in the terminal, if asciinema is installed. Run this command with no argument to list the demos. To play a demo, write its number or a prefix or substring of its title. Tips: Make your terminal window large enough to see the demo clearly. Use the -s/--speed SPEED option to set your preferred playback speed, eg -s4 to play at 4x original speed or -s.5 to play at half speed. The default speed is 2x. Other asciinema options can be added following a double dash, eg -- -i.1 to limit pauses or -- -h to list asciinema's other options. During playback, several keys are available: SPACE to pause/unpause, . to step forward (while paused), CTRL-c quit. Examples: $ hledger demo # list available demos $ hledger demo 1 # play the first demo at default speed (2x) $ hledger demo install -s4 # play the "install" demo at 4x speed descriptions List the unique descriptions that appear in transactions. This command lists the unique descriptions that appear in transactions, in alphabetic order. You can add a query to select a subset of trans- actions. Example: $ hledger descriptions Store Name Gas Station | Petrol Person A diff Compares a particular account's transactions in two input files. It shows any transactions to this account which are in one file but not in the other. More precisely, for each posting affecting this account in either file, it looks for a corresponding posting in the other file which posts the same amount to the same account (ignoring date, description, etc.) Since postings not transactions are compared, this also works when mul- tiple bank transactions have been combined into a single journal entry. This is useful eg if you have downloaded an account's transactions from your bank (eg as CSV data). When hledger and your bank disagree about the account balance, you can compare the bank data with your journal to find out the cause. Examples: $ hledger diff -f $LEDGER_FILE -f bank.csv assets:bank:giro These transactions are in the first file only: 2014/01/01 Opening Balances assets:bank:giro EUR ... ... equity:opening balances EUR -... These transactions are in the second file only: files List all files included in the journal. With a REGEX argument, only file names matching the regular expression (case sensitive) are shown. help Show the hledger user manual in the terminal, with info, man, or a pager. With a TOPIC argument, open it at that topic if possible. TOPIC can be any heading in the manual, or a heading prefix, case in- sensitive. Eg: commands, print, forecast, journal, amount, "auto post- ings". This command shows the hledger manual built in to your hledger version. It can be useful when offline, or when you prefer the terminal to a web browser, or when the appropriate hledger manual or viewing tools are not installed on your system. By default it chooses the best viewer found in $PATH, trying (in this order): info, man, $PAGER, less, more. You can force the use of info, man, or a pager with the -i, -m, or -p flags, If no viewer can be found, or the command is run non-interactively, it just prints the man- ual to stdout. If using info, note that version 6 or greater is needed for TOPIC lookup. If you are on mac you will likely have info 4.8, and should consider installing a newer version, eg with brew install texinfo (#1770). Examples $ hledger help --help # show how the help command works $ hledger help # show the hledger manual with info, man or $PAGER $ hledger help journal # show the journal topic in the hledger manual $ hledger help -m journal # show it with man, even if info is installed import Read new transactions added to each FILE provided as arguments since last run, and add them to the journal. Or with --dry-run, just print the transactions that would be added. Or with --catchup, just mark all of the FILEs' current transactions as imported, without importing them. This command may append new transactions to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also add). Unlike other hledger commands, with import the journal file is an out- put file, and will be modified, though only by appending (existing data will not be changed). The input files are specified as arguments, so to import one or more CSV files to your main journal, you will run hledger import bank.csv or perhaps hledger import *.csv. Note you can import from any file format, though CSV files are the most common import source, and these docs focus on that case. Deduplication import does time-based deduplication, to detect only the new transac- tions since the last successful import. (This does not mean "ignore transactions that look the same", but rather "ignore transactions that have been seen before".) This is intended for when you are periodi- cally importing downloaded data, which may overlap with previous down- loads. Eg if every week (or every day) you download a bank's last three months of CSV data, you can safely run hledger import thebank.csv each time and only new transactions will be imported. Since the items being read (CSV records, eg) often do not come with unique identifiers, hledger detects new transactions by date, assuming that: 1. new items always have the newest dates 2. item dates do not change across reads 3. and items with the same date remain in the same relative order across reads. These are often true of CSV files representing transactions, or true enough so that it works pretty well in practice. 1 is important, but violations of 2 and 3 amongst the old transactions won't matter (and if you import often, the new transactions will be few, so less likely to be the ones affected). hledger remembers the latest date processed in each input file by sav- ing a hidden ".latest.FILE" file in FILE's directory (after a succesful import). Eg when reading finance/bank.csv, it will look for and update the fi- nance/.latest.bank.csv state file. The format is simple: one or more lines containing the same ISO-format date (YYYY-MM-DD), meaning "I have processed transactions up to this date, and this many of them on that date." Normally you won't see or manipulate these state files yourself. But if needed, you can delete them to reset the state (making all transactions "new"), or you can construct them to "catch up" to a cer- tain date. Note deduplication (and updating of state files) can also be done by print --new, but this is less often used. Related: CSV > Working with CSV > Deduplicating, importing. Import testing With --dry-run, the transactions that will be imported are printed to the terminal, without updating your journal or state files. The output is valid journal format, like the print command, so you can re-parse it. Eg, to see any importable transactions which CSV rules have not categorised: $ hledger import --dry bank.csv | hledger -f- -I print unknown or (live updating): $ ls bank.csv* | entr bash -c 'echo ====; hledger import --dry bank.csv | hledger -f- -I print unknown' Note: when importing from multiple files at once, it's currently possi- ble for some .latest files to be updated successfully, while the actual import fails because of a problem in one of the files, leaving them out of sync (and causing some transactions to be missed). To prevent this, do a --dry-run first and fix any problems before the real import. Importing balance assignments Entries added by import will have their posting amounts made explicit (like hledger print -x). This means that any balance assignments in imported files must be evaluated; but, imported files don't get to see the main file's account balances. As a result, importing entries with balance assignments (eg from an institution that provides only balances and not posting amounts) will probably generate incorrect posting amounts. To avoid this problem, use print instead of import: $ hledger print IMPORTFILE [--new] >> $LEDGER_FILE (If you think import should leave amounts implicit like print does, please test it and send a pull request.) Commodity display styles Imported amounts will be formatted according to the canonical commodity styles (declared or inferred) in the main journal file. incomestatement (is) This command displays an income statement, showing revenues and ex- penses during one or more periods. Amounts are shown with normal posi- tive sign, as in conventional financial statements. This report shows accounts declared with the Revenue or Expense type (see account types). Or if no such accounts are declared, it shows top-level accounts named revenue or income or expense (case insensi- tive, plurals allowed) and their subaccounts. Example: $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 This command is a higher-level variant of the balance command, and sup- ports many of that command's features, such as multi-period reports. It is similar to hledger balance '(revenues|income)' expenses, but with smarter account detection, and revenues/income displayed with their sign flipped. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, tsv, html, and (exper- imental) json. notes List the unique notes that appear in transactions. This command lists the unique notes that appear in transactions, in al- phabetic order. You can add a query to select a subset of transac- tions. The note is the part of the transaction description after a | character (or if there is no |, the whole description). Example: $ hledger notes Petrol Snacks payees List the unique payee/payer names that appear in transactions. This command lists unique payee/payer names which have been declared with payee directives (--declared), used in transaction descriptions (--used), or both (the default). The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). You can add query arguments to select a subset of transactions. This implies --used. Example: $ hledger payees Store Name Gas Station Person A prices Print the market prices declared with P directives. With --infer-mar- ket-prices, also show any additional prices inferred from costs. With --show-reverse, also show additional prices inferred by reversing known prices. Price amounts are always displayed with their full precision, except for reverse prices which are limited to 8 decimal digits. Prices can be filtered by a date:, cur: or amt: query. Generally if you run this command with --infer-market-prices --show-re- verse, it will show the same prices used internally to calculate value reports. But if in doubt, you can inspect those directly by running the value report with --debug=2. print Show transaction journal entries, sorted by date. The print command displays full journal entries (transactions) from the journal file, sorted by date (or with --date2, by secondary date). Directives and inter-transaction comments are not shown, currently. This means the print command is somewhat lossy, and if you are using it to reformat/regenerate your journal you should take care to also copy over the directives and inter-transaction comments. Eg: $ hledger print -f examples/sample.journal date:200806 2008/06/01 gift assets:bank:checking $1 income:gifts $-1 2008/06/02 save assets:bank:saving $1 assets:bank:checking $-1 2008/06/03 * eat & shop expenses:food $1 expenses:supplies $1 assets:cash $-2 print explicitness Normally, whether posting amounts are implicit or explicit is pre- served. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, if a conversion cost is implied but not written, it will not appear in the output. You can use the -x/--explicit flag to force explicit display of all amounts and costs. This can be useful for troubleshooting or for mak- ing your journal more readable and robust against data entry errors. -x is also implied by using any of -B,-V,-X,--value. The -x/--explicit flag will cause any postings with a multi-commodity amount (which can arise when a multi-commodity transaction has an im- plicit amount) to be split into multiple single-commodity postings, keeping the output parseable. print amount style Amounts are shown right-aligned within each transaction (but not aligned across all transactions; you can do that with ledger-mode in Emacs). Amounts will be (mostly) normalised to their commodity display style: their symbol placement, decimal mark, and digit group marks will be made consistent. By default, decimal digits are shown as they are written in the journal. With the --round option, print will try increasingly hard to display decimal digits according to the commodity display styles: o --round=none show amounts with original precisions (default) o --round=soft add/remove decimal zeros in amounts (except costs) o --round=hard round amounts (except costs), possibly hiding signifi- cant digits o --round=all round all amounts and costs soft is good for non-lossy cleanup, formatting amounts more consis- tently where it's safe to do so. hard and all can cause print to show invalid unbalanced journal en- tries; they may be useful eg for stronger cleanup, with manual fixups when needed. print parseability print's output is usually a valid hledger journal, and you can process it again with a second hledger command. This can be useful for certain kinds of search (though the same can be achieved with expr: queries now): # Show running total of food expenses paid from cash. # -f- reads from stdin. -I/--ignore-assertions is sometimes needed. $ hledger print assets:cash | hledger -f- -I reg expenses:food There are some situations where print's output can become unparseable: o Value reporting affects posting amounts but not balance assertion or balance assignment amounts, potentially causing those to fail. o Auto postings can generate postings with too many missing amounts. o Account aliases can generate bad account names. print, other features With -B/--cost, amounts with costs are shown converted to cost. With --new, print shows only transactions it has not seen on a previous run. This uses the same deduplication system as the import command. (See import's docs for details.) With -m DESC/--match=DESC, print shows one recent transaction whose de- scription is most similar to DESC. DESC should contain at least two characters. If there is no similar-enough match, no transaction will be shown and the program exit code will be non-zero. print output format This command also supports the output destination and output format op- tions The output formats supported are txt, beancount, csv, tsv, json and sql. Experimental: The beancount format tries to produce Beancount-compati- ble output, as follows: o Transaction and postings with unmarked status are converted to cleared (*) status. o Transactions' payee and note are backslash-escaped and dou- ble-quote-escaped and wrapped in double quotes. o Transaction tags are copied to Beancount #tag format. o Commodity symbols are converted to upper case, and a small number of currency symbols like $ are converted to the corresponding currency names. o Account name parts are capitalised and unsupported characters are re- placed with -. If an account name part does not begin with a letter, or if the first part is not Assets, Liabilities, Equity, Income, or Expenses, an error is raised. (Use --alias options to bring your ac- counts into compliance.) o An open directive is generated for each account used, on the earliest transaction date. Some limitations: o Balance assertions are removed. o Balance assignments become missing amounts. o Virtual and balanced virtual postings become regular postings. o Directives are not converted. Here's an example of print's CSV output: $ hledger print -Ocsv "txnidx","date","date2","status","code","description","comment","account","amount","commodity","credit","debit","posting-status","posting-comment" "1","2008/01/01","","","","income","","assets:bank:checking","1","$","","1","","" "1","2008/01/01","","","","income","","income:salary","-1","$","1","","","" "2","2008/06/01","","","","gift","","assets:bank:checking","1","$","","1","","" "2","2008/06/01","","","","gift","","income:gifts","-1","$","1","","","" "3","2008/06/02","","","","save","","assets:bank:saving","1","$","","1","","" "3","2008/06/02","","","","save","","assets:bank:checking","-1","$","1","","","" "4","2008/06/03","","*","","eat & shop","","expenses:food","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","expenses:supplies","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","assets:cash","-2","$","2","","","" "5","2008/12/31","","*","","pay off","","liabilities:debts","1","$","","1","","" "5","2008/12/31","","*","","pay off","","assets:bank:checking","-1","$","1","","","" o There is one CSV record per posting, with the parent transaction's fields repeated. o The "txnidx" (transaction index) field shows which postings belong to the same transaction. (This number might change if transactions are reordered within the file, files are parsed/included in a different order, etc.) o The amount is separated into "commodity" (the symbol) and "amount" (numeric quantity) fields. o The numeric amount is repeated in either the "credit" or "debit" col- umn, for convenience. (Those names are not accurate in the account- ing sense; it just puts negative amounts under credit and zero or greater amounts under debit.) register (reg) Show postings and their running total. The register command displays matched postings, across all accounts, in date order, with their running total or running historical balance. (See also the aregister command, which shows matched transactions in a specific account.) register normally shows line per posting, but note that multi-commodity amounts will occupy multiple lines (one line per commodity). It is typically used with a query selecting a particular account, to see that account's activity: $ hledger register checking 2008/01/01 income assets:bank:checking $1 $1 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $-1 $1 2008/12/31 pay off assets:bank:checking $-1 0 With --date2, it shows and sorts by secondary date instead. For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the --align-all flag. The --historical/-H flag adds the balance from any undisplayed prior postings to the running total. This is useful when you want to see only recent activity, with a historically accurate running balance: $ hledger register checking -b 2008/6 --historical 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $-1 $1 2008/12/31 pay off assets:bank:checking $-1 0 The --depth option limits the amount of sub-account detail displayed. The --average/-A flag shows the running average posting amount instead of the running total (so, the final number displayed is the average for the whole report period). This flag implies --empty (see below). It is affected by --historical. It works best when showing just one ac- count and one commodity. The --related/-r flag shows the other postings in the transactions of the postings which would normally be shown. The --invert flag negates all amounts. For example, it can be used on an income account where amounts are normally displayed as negative num- bers. It's also useful to show postings on the checking account to- gether with the related account: $ hledger register --related --invert assets:checking With a reporting interval, register shows summary postings, one per in- terval, aggregating the postings to each account: $ hledger register --monthly income 2008/01 income:salary $-1 $-1 2008/06 income:gifts $-1 $-2 Periods with no activity, and summary postings with a zero amount, are not shown by default; use the --empty/-E flag to see them: $ hledger register --monthly income -E 2008/01 income:salary $-1 $-1 2008/02 0 $-1 2008/03 0 $-1 2008/04 0 $-1 2008/05 0 $-1 2008/06 income:gifts $-1 $-2 2008/07 0 $-2 2008/08 0 $-2 2008/09 0 $-2 2008/10 0 $-2 2008/11 0 $-2 2008/12 0 $-2 Often, you'll want to see just one line per interval. The --depth op- tion helps with this, causing subaccounts to be aggregated: $ hledger register --monthly assets --depth 1h 2008/01 assets $1 $1 2008/06 assets $-1 0 2008/12 assets $-1 $-1 Note when using report intervals, if you specify start/end dates these will be adjusted outward if necessary to contain a whole number of in- tervals. This ensures that the first and last intervals are full length and comparable to the others in the report. With -m DESC/--match=DESC, register does a fuzzy search for one recent posting whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar-enough match, no post- ing will be shown and the program exit code will be non-zero. Custom register output register uses the full terminal width by default, except on windows. You can override this by setting the COLUMNS environment variable (not a bash shell variable) or by using the --width/-w option. The description and account columns normally share the space equally (about half of (width - 40) each). You can adjust this by adding a de- scription width as part of --width's argument, comma-separated: --width W,D . Here's a diagram (won't display correctly in --help): <--------------------------------- width (W) ----------------------------------> date (10) description (D) account (W-41-D) amount (12) balance (12) DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA and some examples: $ hledger reg # use terminal width (or 80 on windows) $ hledger reg -w 100 # use width 100 $ COLUMNS=100 hledger reg # set with one-time environment variable $ export COLUMNS=100; hledger reg # set till session end (or window resize) $ hledger reg -w 100,40 # set overall width 100, description width 40 $ hledger reg -w $COLUMNS,40 # use terminal width, & description width 40 This command also supports the output destination and output format op- tions The output formats supported are txt, csv, tsv, and (experimen- tal) json. rewrite Print all transactions, rewriting the postings of matched transactions. For now the only rewrite available is adding new postings, like print --auto. This is a start at a generic rewriter of transaction entries. It reads the default journal and prints the transactions, like print, but adds one or more specified postings to any transactions matching QUERY. The posting amounts can be fixed, or a multiplier of the existing transac- tion's first posting amount. Examples: $ hledger-rewrite.hs ^income --add-posting '(liabilities:tax) *.33 ; income tax' --add-posting '(reserve:gifts) $100' $ hledger-rewrite.hs expenses:gifts --add-posting '(reserve:gifts) *-1"' $ hledger-rewrite.hs -f rewrites.hledger rewrites.hledger may consist of entries like: = ^income amt:<0 date:2017 (liabilities:tax) *0.33 ; tax on income (reserve:grocery) *0.25 ; reserve 25% for grocery (reserve:) *0.25 ; reserve 25% for grocery Note the single quotes to protect the dollar sign from bash, and the two spaces between account and amount. More: $ hledger rewrite -- [QUERY] --add-posting "ACCT AMTEXPR" ... $ hledger rewrite -- ^income --add-posting '(liabilities:tax) *.33' $ hledger rewrite -- expenses:gifts --add-posting '(budget:gifts) *-1"' $ hledger rewrite -- ^income --add-posting '(budget:foreign currency) *0.25 JPY; diversify' Argument for --add-posting option is a usual posting of transaction with an exception for amount specification. More precisely, you can use '*' (star symbol) before the amount to indicate that that this is a factor for an amount of original matched posting. If the amount in- cludes a commodity name, the new posting amount will be in the new com- modity; otherwise, it will be in the matched posting amount's commod- ity. Re-write rules in a file During the run this tool will execute so called "Automated Transac- tions" found in any journal it process. I.e instead of specifying this operations in command line you can put them in a journal file. $ rewrite-rules.journal Make contents look like this: = ^income (liabilities:tax) *.33 = expenses:gifts budget:gifts *-1 assets:budget *1 Note that '=' (equality symbol) that is used instead of date in trans- actions you usually write. It indicates the query by which you want to match the posting to add new ones. $ hledger rewrite -- -f input.journal -f rewrite-rules.journal > rewritten-tidy-output.journal This is something similar to the commands pipeline: $ hledger rewrite -- -f input.journal '^income' --add-posting '(liabilities:tax) *.33' \ | hledger rewrite -- -f - expenses:gifts --add-posting 'budget:gifts *-1' \ --add-posting 'assets:budget *1' \ > rewritten-tidy-output.journal It is important to understand that relative order of such entries in journal is important. You can re-use result of previously added post- ings. Diff output format To use this tool for batch modification of your journal files you may find useful output in form of unified diff. $ hledger rewrite -- --diff -f examples/sample.journal '^income' --add-posting '(liabilities:tax) *.33' Output might look like: --- /tmp/examples/sample.journal +++ /tmp/examples/sample.journal @@ -18,3 +18,4 @@ 2008/01/01 income - assets:bank:checking $1 + assets:bank:checking $1 income:salary + (liabilities:tax) 0 @@ -22,3 +23,4 @@ 2008/06/01 gift - assets:bank:checking $1 + assets:bank:checking $1 income:gifts + (liabilities:tax) 0 If you'll pass this through patch tool you'll get transactions contain- ing the posting that matches your query be updated. Note that multiple files might be update according to list of input files specified via --file options and include directives inside of these files. Be careful. Whole transaction being re-formatted in a style of output from hledger print. See also: https://github.com/simonmichael/hledger/issues/99 rewrite vs. print --auto This command predates print --auto, and currently does much the same thing, but with these differences: o with multiple files, rewrite lets rules in any file affect all other files. print --auto uses standard directive scoping; rules affect only child files. o rewrite's query limits which transactions can be rewritten; all are printed. print --auto's query limits which transactions are printed. o rewrite applies rules specified on command line or in the journal. print --auto applies rules specified in the journal. roi Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. At a minimum, you need to supply a query (which could be just an ac- count name) to select your investment(s) with --inv, and another query to identify your profit and loss transactions with --pnl. If you do not record changes in the value of your investment manually, or do not require computation of time-weighted return (TWR), --pnl could be an empty query (--pnl "" or --pnl STR where STR does not match any of your accounts). This command will compute and display the internalized rate of return (IRR, also known as money-weighted rate of return) and time-weighted rate of return (TWR) for your investments for the time period re- quested. IRR is always annualized due to the way it is computed, but TWR is reported both as a rate over the chosen reporting period and as an annual rate. Price directives will be taken into account if you supply appropriate --cost or --value flags (see VALUATION). Note, in some cases this report can fail, for these reasons: o Error (NotBracketed): No solution for Internal Rate of Return (IRR). Possible causes: IRR is huge (>1000000%), balance of investment be- comes negative at some point in time. o Error (SearchFailed): Failed to find solution for Internal Rate of Return (IRR). Either search does not converge to a solution, or con- verges too slowly. Examples: o Using roi to compute total return of investment in stocks: https://github.com/simonmichael/hledger/blob/master/examples/invest- ing/roi-unrealised.ledger o Cookbook > Return on Investment: https://hledger.org/roi.html Spaces and special characters in --inv and --pnl Note that --inv and --pnl's argument is a query, and queries could have several space-separated terms (see QUERIES). To indicate that all search terms form single command-line argument, you will need to put them in quotes (see Special characters): $ hledger roi --inv 'term1 term2 term3 ...' If any query terms contain spaces themselves, you will need an extra level of nested quoting, eg: $ hledger roi --inv="'Assets:Test 1'" --pnl="'Equity:Unrealized Profit and Loss'" Semantics of --inv and --pnl Query supplied to --inv has to match all transactions that are related to your investment. Transactions not matching --inv will be ignored. In these transactions, ROI will conside postings that match --inv to be "investment postings" and other postings (not matching --inv) will be sorted into two categories: "cash flow" and "profit and loss", as ROI needs to know which part of the investment value is your contributions and which is due to the return on investment. o "Cash flow" is depositing or withdrawing money, buying or selling as- sets, or otherwise converting between your investment commodity and any other commodity. Example: 2019-01-01 Investing in Snake Oil assets:cash -$100 investment:snake oil 2020-01-01 Selling my Snake Oil assets:cash $10 investment:snake oil = 0 o "Profit and loss" is change in the value of your investment: 2019-06-01 Snake Oil falls in value investment:snake oil = $57 equity:unrealized profit or loss All non-investment postings are assumed to be "cash flow", unless they match --pnl query. Changes in value of your investment due to "profit and loss" postings will be considered as part of your investment re- turn. Example: if you use --inv snake --pnl equity:unrealized, then postings in the example below would be classifed as: 2019-01-01 Snake Oil #1 assets:cash -$100 ; cash flow posting investment:snake oil ; investment posting 2019-03-01 Snake Oil #2 equity:unrealized pnl -$100 ; profit and loss posting snake oil ; investment posting 2019-07-01 Snake Oil #3 equity:unrealized pnl ; profit and loss posting cash -$100 ; cash flow posting snake oil $50 ; investment posting IRR and TWR explained "ROI" stands for "return on investment". Traditionally this was com- puted as a difference between current value of investment and its ini- tial value, expressed in percentage of the initial value. However, this approach is only practical in simple cases, where invest- ments receives no in-flows or out-flows of money, and where rate of growth is fixed over time. For more complex scenarios you need differ- ent ways to compute rate of return, and this command implements two of them: IRR and TWR. Internal rate of return, or "IRR" (also called "money-weighted rate of return") takes into account effects of in-flows and out-flows, and the time between them. Investment at a particular fixed interest rate is going to give you more interest than the same amount invested at the same interest rate, but made later in time. If you are withdrawing from your investment, your future gains would be smaller (in absolute numbers), and will be a smaller percentage of your initial investment, so your IRR will be smaller. And if you are adding to your investment, you will receive bigger absolute gains, which will be a bigger percent- age of your initial investment, so your IRR will be larger. As mentioned before, in-flows and out-flows would be any cash that you personally put in or withdraw, and for the "roi" command, these are the postings that match the query in the--inv argument and NOT match the query in the--pnl argument. If you manually record changes in the value of your investment as transactions that balance them against "profit and loss" (or "unreal- ized gains") account or use price directives, then in order for IRR to compute the precise effect of your in-flows and out-flows on the rate of return, you will need to record the value of your investement on or close to the days when in- or out-flows occur. In technical terms, IRR uses the same approach as computation of net present value, and tries to find a discount rate that makes net present value of all the cash flows of your investment to add up to zero. This could be hard to wrap your head around, especially if you haven't done discounted cash flow analysis before. Implementation of IRR in hledger should produce results that match the =XIRR formula in Excel. Second way to compute rate of return that roi command implements is called "time-weighted rate of return" or "TWR". Like IRR, it will ac- count for the effect of your in-flows and out-flows, but unlike IRR it will try to compute the true rate of return of the underlying asset, compensating for the effect that deposits and withdrawas have on the apparent rate of growth of your investment. TWR represents your investment as an imaginary "unit fund" where in-flows/ out-flows lead to buying or selling "units" of your invest- ment and changes in its value change the value of "investment unit". Change in "unit price" over the reporting period gives you rate of re- turn of your investment, and make TWR less sensitive than IRR to the effects of cash in-flows and out-flows. References: o Explanation of rate of return o Explanation of IRR o Explanation of TWR o IRR vs TWR o Examples of computing IRR and TWR and discussion of the limitations of both metrics stats Show journal and performance statistics. The stats command displays summary information for the whole journal, or a matched part of it. With a reporting interval, it shows a report for each report period. At the end, it shows (in the terminal) the overall run time and number of transactions processed per second. Note these are approximate and will vary based on machine, current load, data size, hledger version, haskell lib versions, GHC version.. but they may be of interest. The stats command's run time is similar to that of a single-column balance report. Example: $ hledger stats -f examples/1000x1000x10.journal Main file : /Users/simon/src/hledger/examples/1000x1000x10.journal Included files : Transactions span : 2000-01-01 to 2002-09-27 (1000 days) Last transaction : 2002-09-26 (6995 days ago) Transactions : 1000 (1.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 1000 Accounts : 1000 (depth 10) Commodities : 26 (A, B, C, D, E, F, G, H, I, J, K, L, M, N, O, P, Q, R, S, T, U, V, W, X, Y, Z) Market prices : 1000 (A) Run time : 0.12 s Throughput : 8342 txns/s This command supports the -o/--output-file option (but not -O/--out- put-format selection). tags List the tags used in the journal, or their values. This command lists the tag names used in the journal, whether on trans- actions, postings, or account declarations. With a TAGREGEX argument, only tag names matching this regular expres- sion (case insensitive, infix matched) are shown. With QUERY arguments, only transactions and accounts matching this query are considered. If the query involves transaction fields (date:, desc:, amt:, ...), the search is restricted to the matched transactions and their accounts. With the --values flag, the tags' unique non-empty values are listed instead. With -E/--empty, blank/empty values are also shown. With --parsed, tags or values are shown in the order they were parsed, with duplicates included. (Except, tags from account declarations are always shown first.) Tip: remember, accounts also acquire tags from their parents, postings also acquire tags from their account and transaction, transactions also acquire tags from their postings. test Run built-in unit tests. This command runs the unit tests built in to hledger and hledger-lib, printing the results on stdout. If any test fails, the exit code will be non-zero. This is mainly used by hledger developers, but you can also use it to sanity-check the installed hledger executable on your platform. All tests are expected to pass - if you ever see a failure, please report as a bug! This command also accepts tasty test runner options, written after a -- (double hyphen). Eg to run only the tests in Hledger.Data.Amount, with ANSI colour codes disabled: $ hledger test -- -pData.Amount --color=never For help on these, see https://github.com/feuerbach/tasty#options (-- --help currently doesn't show them). PART 5: COMMON TASKS Here are some quick examples of how to do some basic tasks with hledger. Getting help Here's how to list commands and view options and command docs: $ hledger # show available commands $ hledger --help # show common options $ hledger CMD --help # show CMD's options, common options and CMD's documentation You can also view your hledger version's manual in several formats by using the help command. Eg: $ hledger help # show the hledger manual with info, man or $PAGER (best available) $ hledger help journal # show the journal topic in the hledger manual $ hledger help --help # find out more about the help command To view manuals and introductory docs on the web, visit https://hledger.org. Chat and mail list support and discussion archives can be found at https://hledger.org/support. Constructing command lines hledger has a flexible command line interface. We strive to keep it simple and ergonomic, but if you run into one of the sharp edges de- scribed in OPTIONS, here are some tips that might help: o command-specific options must go after the command (it's fine to put common options there too: hledger CMD OPTS ARGS) o running add-on executables directly simplifies command line parsing (hledger-ui OPTS ARGS) o enclose "problematic" args in single quotes o if needed, also add a backslash to hide regular expression metachar- acters from the shell o to see how a misbehaving command line is being parsed, add --debug=2. Starting a journal file hledger looks for your accounting data in a journal file, $HOME/.hledger.journal by default: $ hledger stats The hledger journal file "/Users/simon/.hledger.journal" was not found. Please create it first, eg with "hledger add" or a text editor. Or, specify an existing journal file with -f or LEDGER_FILE. You can override this by setting the LEDGER_FILE environment variable (see below). It's a good practice to keep this important file under version control, and to start a new file each year. So you could do something like this: $ mkdir ~/finance $ cd ~/finance $ git init Initialized empty Git repository in /Users/simon/finance/.git/ $ touch 2023.journal $ echo "export LEDGER_FILE=$HOME/finance/2023.journal" >> ~/.profile $ source ~/.profile $ hledger stats Main file : /Users/simon/finance/2023.journal Included files : Transactions span : to (0 days) Last transaction : none Transactions : 0 (0.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 0 Accounts : 0 (depth 0) Commodities : 0 () Market prices : 0 () Setting LEDGER_FILE How to set LEDGER_FILE permanently depends on your setup: On unix and mac, running these commands in the terminal will work for many people; adapt as needed: $ echo 'export LEDGER_FILE=~/finance/2023.journal' >> ~/.profile $ source ~/.profile When correctly configured, in a new terminal window env | grep LEDGER_FILE will show your file, and so will hledger files. On mac, this additional step might be helpful for GUI applications (like Emacs started from the dock): add an entry to ~/.MacOSX/environ- ment.plist like { "LEDGER_FILE" : "~/finance/2023.journal" } and then run killall Dock in a terminal window (or restart the ma- chine). On Windows, see https://www.java.com/en/download/help/path.html, or try running these commands in a powershell window (let us know if it per- sists across a reboot, and if you need to be an Administrator): > CD > MKDIR finance > SETX LEDGER_FILE "C:\Users\USERNAME\finance\2023.journal" Setting opening balances Pick a starting date for which you can look up the balances of some real-world assets (bank accounts, wallet..) and liabilities (credit cards..). To avoid a lot of data entry, you may want to start with just one or two accounts, like your checking account or cash wallet; and pick a re- cent starting date, like today or the start of the week. You can al- ways come back later and add more accounts and older transactions, eg going back to january 1st. Add an opening balances transaction to the journal, declaring the bal- ances on this date. Here are two ways to do it: o The first way: open the journal in any text editor and save an entry like this: 2023-01-01 * opening balances assets:bank:checking $1000 = $1000 assets:bank:savings $2000 = $2000 assets:cash $100 = $100 liabilities:creditcard $-50 = $-50 equity:opening/closing balances These are start-of-day balances, ie whatever was in the account at the end of the previous day. The * after the date is an optional status flag. Here it means "cleared & confirmed". The currency symbols are optional, but usually a good idea as you'll be dealing with multiple currencies sooner or later. The = amounts are optional balance assertions, providing extra error checking. o The second way: run hledger add and follow the prompts to record a similar transaction: $ hledger add Adding transactions to journal file /Users/simon/finance/2023.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control-d or control-c. Date [2023-02-07]: 2023-01-01 Description: * opening balances Account 1: assets:bank:checking Amount 1: $1000 Account 2: assets:bank:savings Amount 2 [$-1000]: $2000 Account 3: assets:cash Amount 3 [$-3000]: $100 Account 4: liabilities:creditcard Amount 4 [$-3100]: $-50 Account 5: equity:opening/closing balances Amount 5 [$-3050]: Account 6 (or . or enter to finish this transaction): . 2023-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl-D/ctrl-C to quit) Date [2023-01-01]: . If you're using version control, this could be a good time to commit the journal. Eg: $ git commit -m 'initial balances' 2023.journal Recording transactions As you spend or receive money, you can record these transactions using one of the methods above (text editor, hledger add) or by using the hledger-iadd or hledger-web add-ons, or by using the import command to convert CSV data downloaded from your bank. Here are some simple transactions, see the hledger_journal(5) manual and hledger.org for more ideas: 2023/1/10 * gift received assets:cash $20 income:gifts 2023.1.12 * farmers market expenses:food $13 assets:cash 2023-01-15 paycheck income:salary assets:bank:checking $1000 Reconciling Periodically you should reconcile - compare your hledger-reported bal- ances against external sources of truth, like bank statements or your bank's website - to be sure that your ledger accurately represents the real-world balances (and, that the real-world institutions have not made a mistake!). This gets easy and fast with (1) practice and (2) frequency. If you do it daily, it can take 2-10 minutes. If you let it pile up, expect it to take longer as you hunt down errors and dis- crepancies. A typical workflow: 1. Reconcile cash. Count what's in your wallet. Compare with what hledger reports (hledger bal cash). If they are different, try to remember the missing transaction, or look for the error in the al- ready-recorded transactions. A register report can be helpful (hledger reg cash). If you can't find the error, add an adjustment transaction. Eg if you have $105 after the above, and can't explain the missing $2, it could be: 2023-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc 2. Reconcile checking. Log in to your bank's website. Compare today's (cleared) balance with hledger's cleared balance (hledger bal check- ing -C). If they are different, track down the error or record the missing transaction(s) or add an adjustment transaction, similar to the above. Unlike the cash case, you can usually compare the trans- action history and running balance from your bank with the one re- ported by hledger reg checking -C. This will be easier if you gen- erally record transaction dates quite similar to your bank's clear- ing dates. 3. Repeat for other asset/liability accounts. Tip: instead of the register command, use hledger-ui to see a live-up- dating register while you edit the journal: hledger-ui --watch --regis- ter checking -C After reconciling, it could be a good time to mark the reconciled transactions' status as "cleared and confirmed", if you want to track that, by adding the * marker. Eg in the paycheck transaction above, insert * between 2023-01-15 and paycheck If you're using version control, this can be another good time to com- mit: $ git commit -m 'txns' 2023.journal Reporting Here are some basic reports. Show all transactions: $ hledger print 2023-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 2023-01-10 * gift received assets:cash $20 income:gifts 2023-01-12 * farmers market expenses:food $13 assets:cash 2023-01-15 * paycheck income:salary assets:bank:checking $1000 2023-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc Show account names, and their hierarchy: $ hledger accounts --tree assets bank checking savings cash equity opening/closing balances expenses food misc income gifts salary liabilities creditcard Show all account totals: $ hledger balance $4105 assets $4000 bank $2000 checking $2000 savings $105 cash $-3050 equity:opening/closing balances $15 expenses $13 food $2 misc $-1020 income $-20 gifts $-1000 salary $-50 liabilities:creditcard -------------------- 0 Show only asset and liability balances, as a flat list, limited to depth 2: $ hledger bal assets liabilities -2 $4000 assets:bank $105 assets:cash $-50 liabilities:creditcard -------------------- $4055 Show the same thing without negative numbers, formatted as a simple balance sheet: $ hledger bs -2 Balance Sheet 2023-01-16 || 2023-01-16 ========================++============ Assets || ------------------------++------------ assets:bank || $4000 assets:cash || $105 ------------------------++------------ || $4105 ========================++============ Liabilities || ------------------------++------------ liabilities:creditcard || $50 ------------------------++------------ || $50 ========================++============ Net: || $4055 The final total is your "net worth" on the end date. (Or use bse for a full balance sheet with equity.) Show income and expense totals, formatted as an income statement: hledger is Income Statement 2023-01-01-2023-01-16 || 2023-01-01-2023-01-16 ===============++======================= Revenues || ---------------++----------------------- income:gifts || $20 income:salary || $1000 ---------------++----------------------- || $1020 ===============++======================= Expenses || ---------------++----------------------- expenses:food || $13 expenses:misc || $2 ---------------++----------------------- || $15 ===============++======================= Net: || $1005 The final total is your net income during this period. Show transactions affecting your wallet, with running total: $ hledger register cash 2023-01-01 opening balances assets:cash $100 $100 2023-01-10 gift received assets:cash $20 $120 2023-01-12 farmers market assets:cash $-13 $107 2023-01-16 adjust cash assets:cash $-2 $105 Show weekly posting counts as a bar chart: $ hledger activity -W 2019-12-30 ***** 2023-01-06 **** 2023-01-13 **** Migrating to a new file At the end of the year, you may want to continue your journal in a new file, so that old transactions don't slow down or clutter your reports, and to help ensure the integrity of your accounting history. See the close command. If using version control, don't forget to git add the new file. BUGS We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). Some known issues and limitations: The need to precede add-on command options with -- when invoked from hledger is awkward. (See Command options, Constructing command lines.) A UTF-8-aware system locale must be configured to work with non-ascii data. (See Unicode characters, Troubleshooting.) On Microsoft Windows, depending whether you are running in a CMD window or a Cygwin/MSYS/Mintty window and how you installed hledger, non-ascii characters and colours may not be supported, and the tab key may not be supported by hledger add. (Running in a WSL window should resolve these.) When processing large data files, hledger uses more memory than Ledger. Troubleshooting Here are some common issues you might encounter when you run hledger, and how to resolve them (and remember also you can usually get quick Support): PATH issues: I get an error like "No command 'hledger' found" Depending how you installed hledger, the executables may not be in your shell's PATH. Eg on unix systems, stack installs hledger in ~/.lo- cal/bin and cabal installs it in ~/.cabal/bin. You may need to add one of these directories to your shell's PATH, and/or open a new terminal window. LEDGER_FILE issues: I configured LEDGER_FILE but hledger is not using it o LEDGER_FILE should be a real environment variable, not just a shell variable. Eg on unix, the command env | grep LEDGER_FILE should show it. You may need to use export (see https://stackover- flow.com/a/7411509). o You may need to force your shell to see the new configuration. A simple way is to close your terminal window and open a new one. LANG issues: I get errors like "Illegal byte sequence" or "Invalid or incomplete multibyte or wide character" or "commitAndReleaseBuffer: in- valid argument (invalid character)" Programs compiled with GHC (hledger, haskell build tools, etc.) need the system locale to be UTF-8-aware, or they will fail when they en- counter non-ascii characters. To fix it, set the LANG environment variable to a locale which supports UTF-8 and which is installed on your system. On unix, locale -a lists the installed locales. Look for one which mentions utf8, UTF-8 or similar. Some examples: C.UTF-8, en_US.utf-8, fr_FR.utf8. If necessary, use your system package manager to install one. Then select it by setting the LANG environment variable. Note, exact spelling and capitalisation of the locale name may be important: Here's one common way to configure this permanently for your shell: $ echo "export LANG=en_US.utf8" >>~/.profile # close and re-open terminal window If you are using Nix (not NixOS) for GHC and Hledger, you might need to set the LOCALE_ARCHIVE variable: $ echo "export LOCALE_ARCHIVE=${glibcLocales}/lib/locale/locale-archive" >>~/.profile # close and re-open terminal window COMPATIBILITY ISSUES: hledger gives an error with my Ledger file Not all of Ledger's journal file syntax or feature set is supported. See hledger and Ledger for full details. AUTHORS Simon Michael and contributors. See http://hledger.org/CREDITS.html COPYRIGHT Copyright 2007-2023 Simon Michael and contributors. LICENSE Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), ledger(1) hledger-1.32.3 January 2024 HLEDGER(1) hledger-1.32.3/hledger.info0000644000000000000000000144755314555433336013725 0ustar0000000000000000This is hledger.info, produced by makeinfo version 7.1 from stdin. INFO-DIR-SECTION User Applications START-INFO-DIR-ENTRY * hledger: (hledger). Command-line plain text accounting tool. END-INFO-DIR-ENTRY  File: hledger.info, Node: Top, Next: PART 1 USER INTERFACE, Up: (dir) hledger(1) ********** hledger - robust, friendly plain text accounting (CLI version) 'hledger' 'hledger COMMAND [OPTS] [ARGS]' 'hledger ADDONCMD -- [OPTS] [ARGS]' hledger is a robust, user-friendly, cross-platform set of programs for tracking money, time, or any other commodity, using double-entry accounting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). This manual is for hledger's command line interface, version 1.32.3. It also describes the common options, file formats and concepts used by all hledger programs. It might accidentally teach you some bookkeeping/accounting as well! You don't need to know everything in here to use hledger productively, but when you have a question about functionality, this doc should answer it. It is detailed, so do skip ahead or skim when needed. You can read it on hledger.org, or as an info manual or man page on your system. You can also get it from hledger itself with 'hledger --man', 'hledger --info' or 'hledger help [TOPIC]'. The main function of the hledger CLI is to read plain text files describing financial transactions, crunch the numbers, and print a useful report on the terminal (or save it as HTML, CSV, JSON or SQL). Many reports are available, as subcommands. hledger will also detect other 'hledger-*' executables as extra subcommands. hledger usually reads from (and appends to) a journal file specified by the 'LEDGER_FILE' environment variable (defaulting to '$HOME/.hledger.journal'); or you can specify files with '-f' options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. Here is a small journal file describing one transaction: 2015-10-16 bought food expenses:food $10 assets:cash Transactions are dated movements of money (etc.) between two or more _accounts_: bank accounts, your wallet, revenue/expense categories, people, etc. You can choose any account names you wish, using ':' to indicate subaccounts. There must be at least two spaces between account name and amount. Positive amounts are inflow to that account (_debit_), negatives are outflow from it (_credit_). (Some reports show revenue, liability and equity account balances as negative numbers as a result; this is normal.) hledger's add command can help you add transactions, or you can install other data entry UIs like hledger-web or hledger-iadd. For more extensive/efficient changes, use a text editor: Emacs + ledger-mode, VIM + vim-ledger, or VS Code + hledger-vscode are some good choices (see https://hledger.org/editors.html). To get started, run 'hledger add' and follow the prompts, or save some entries like the above in '$HOME/.hledger.journal', then try commands like: 'hledger print -x' 'hledger aregister assets' 'hledger balance' 'hledger balancesheet' 'hledger incomestatement'. Run 'hledger' to list the commands. See also the "Starting a journal file" and "Setting opening balances" sections in PART 5: COMMON TASKS. * Menu: * PART 1 USER INTERFACE:: * Input:: * Commands:: * Options:: * Command line tips:: * Output:: * Environment:: * PART 2 DATA FORMATS:: * Journal:: * CSV:: * Timeclock:: * Timedot:: * PART 3 REPORTING CONCEPTS:: * Amount formatting parseability:: * Time periods:: * Depth:: * Queries:: * Pivoting:: * Generating data:: * Forecasting:: * Budgeting:: * Cost reporting:: * Value reporting:: * PART 4 COMMANDS:: * PART 5 COMMON TASKS:: * BUGS::  File: hledger.info, Node: PART 1 USER INTERFACE, Next: Input, Prev: Top, Up: Top 1 PART 1: USER INTERFACE ************************  File: hledger.info, Node: Input, Next: Commands, Prev: PART 1 USER INTERFACE, Up: Top 2 Input ******* hledger reads one or more data files, each time you run it. You can specify a file with '-f', like so $ hledger -f FILE print Files are most often in hledger's journal format, with the '.journal' file extension ('.hledger' or '.j' also work); these files describe transactions, like an accounting general journal. When no file is specified, hledger looks for '.hledger.journal' in your home directory. But most people prefer to keep financial files in a dedicated folder, perhaps with version control. Also, starting a new journal file each year is common (it's not required, but helps keep things fast and organised). So we usually configure a different journal file, by setting the 'LEDGER_FILE' environment variable, to something like '~/finance/2023.journal'. For more about how to do that on your system, see Common tasks > Setting LEDGER_FILE. * Menu: * Data formats:: * Standard input:: * Multiple files:: * Strict mode::  File: hledger.info, Node: Data formats, Next: Standard input, Up: Input 2.1 Data formats ================ Usually the data file is in hledger's journal format, but it can be in any of the supported file formats, which currently are: Reader: Reads: Used for file extensions: ---------------------------------------------------------------------------- 'journal' hledger journal files and '.journal' '.j' '.hledger' some Ledger journals, for '.ledger' transactions 'timeclock' timeclock files, for precise '.timeclock' time logging 'timedot' timedot files, for '.timedot' approximate time logging 'csv' CSV/SSV/TSV/character-separated '.csv' '.ssv' '.tsv' values, for data import '.csv.rules' '.ssv.rules' '.tsv.rules' These formats are described in more detail below. hledger detects the format automatically based on the file extensions shown above. If it can't recognise the file extension, it assumes 'journal' format. So for non-journal files, it's important to use a recognised file extension, so as to either read successfully or to show relevant error messages. You can also force a specific reader/format by prefixing the file path with the format and a colon. Eg, to read a .dat file as csv format: $ hledger -f csv:/some/csv-file.dat stats  File: hledger.info, Node: Standard input, Next: Multiple files, Prev: Data formats, Up: Input 2.2 Standard input ================== The file name '-' means standard input: $ cat FILE | hledger -f- print If reading non-journal data in this way, you'll need to add a file format prefix, like: $ echo 'i 2009/13/1 08:00:00' | hledger print -f timeclock:-  File: hledger.info, Node: Multiple files, Next: Strict mode, Prev: Standard input, Up: Input 2.3 Multiple files ================== You can specify multiple '-f' options, to read multiple files as one big journal. When doing this, note that certain features (described below) will be affected: * Balance assertions will not see the effect of transactions in previous files. (Usually this doesn't matter as each file will set the corresponding opening balances.) * Some directives will not affect previous or subsequent files. If needed, you can work around these by using a single parent file which includes the others, or concatenating the files into one, eg: 'cat a.journal b.journal | hledger -f- CMD'.  File: hledger.info, Node: Strict mode, Prev: Multiple files, Up: Input 2.4 Strict mode =============== hledger checks input files for valid data. By default, the most important errors are detected, while still accepting easy journal files without a lot of declarations: * Are the input files parseable, with valid syntax ? * Are all transactions balanced ? * Do all balance assertions pass ? With the '-s'/'--strict' flag, additional checks are performed: * Are all accounts posted to, declared with an 'account' directive ? (Account error checking) * Are all commodities declared with a 'commodity' directive ? (Commodity error checking) * Are all commodity conversions declared explicitly ? You can use the check command to run individual checks - the ones listed above and some more.  File: hledger.info, Node: Commands, Next: Options, Prev: Input, Up: Top 3 Commands ********** hledger provides various subcommands for getting things done. Most of these commands do not change the journal file; they just read it and output a report. A few commands assist with adding data and file management. To show the commands list, run 'hledger' with no arguments. The commands are described in detail in PART 4: COMMANDS, below. To use a particular command, run 'hledger CMD [CMDOPTS] [CMDARGS]', * CMD is the full command name, or its standard abbreviation shown in the commands list, or any unambiguous prefix of the name. * CMDOPTS are command-specific options, if any. Command-specific options must be written after the command name. Eg: 'hledger print -x'. * CMDARGS are additional arguments to the command, if any. Most hledger commands accept arguments representing a query, to limit the data in some way. Eg: 'hledger reg assets:checking'. To list a command's options, arguments, and documentation in the terminal, run 'hledger CMD -h'. Eg: 'hledger bal -h'. * Menu: * Add-on commands::  File: hledger.info, Node: Add-on commands, Up: Commands 3.1 Add-on commands =================== In addition to the built-in commands, you can install _add-on commands_: programs or scripts named "hledger-SOMETHING", which will also appear in hledger's commands list. If you used the hledger-install script, you will have several add-ons installed already. Some more can be found in hledger's bin/ directory, documented at https://hledger.org/scripts.html. More precisely, add-on commands are programs or scripts in your shell's PATH, whose name starts with "hledger-" and ends with no extension or a recognised extension (".bat", ".com", ".exe", ".hs", ".js", ".lhs", ".lua", ".php", ".pl", ".py", ".rb", ".rkt", or ".sh"), and (on unix and mac) which has executable permission for the current user. You can run add-on commands using hledger, much like built-in commands: 'hledger ADDONCMD [-- ADDONCMDOPTS] [ADDONCMDARGS]'. But note the double hyphen argument, required before add-on-specific options. Eg: 'hledger ui -- --watch' or 'hledger web -- --serve'. If this causes difficulty, you can always run the add-on directly, without using 'hledger': 'hledger-ui --watch' or 'hledger-web --serve'.  File: hledger.info, Node: Options, Next: Command line tips, Prev: Commands, Up: Top 4 Options ********* Run 'hledger -h' to see general command line help, and general options which are common to most hledger commands. These options can be written anywhere on the command line. They can be grouped into help, input, and reporting options: * Menu: * General help options:: * General input options:: * General reporting options::  File: hledger.info, Node: General help options, Next: General input options, Up: Options 4.1 General help options ======================== '-h --help' show general or COMMAND help '--man' show general or COMMAND user manual with man '--info' show general or COMMAND user manual with info '--version' show general or ADDONCMD version '--debug[=N]' show debug output (levels 1-9, default: 1)  File: hledger.info, Node: General input options, Next: General reporting options, Prev: General help options, Up: Options 4.2 General input options ========================= '-f FILE --file=FILE' use a different input file. For stdin, use - (default: '$LEDGER_FILE' or '$HOME/.hledger.journal') '--rules-file=RULESFILE' Conversion rules file to use when reading CSV (default: FILE.rules) '--separator=CHAR' Field separator to expect when reading CSV (default: ',') '--alias=OLD=NEW' rename accounts named OLD to NEW '--pivot FIELDNAME' use some other field or tag for the account name '-I --ignore-assertions' disable balance assertion checks (note: does not disable balance assignments) '-s --strict' do extra error checking (check that all posted accounts are declared)  File: hledger.info, Node: General reporting options, Prev: General input options, Up: Options 4.3 General reporting options ============================= '-b --begin=DATE' include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) '-e --end=DATE' include postings/txns before this date (will be adjusted to following subperiod end when using a report interval) '-D --daily' multiperiod/multicolumn report by day '-W --weekly' multiperiod/multicolumn report by week '-M --monthly' multiperiod/multicolumn report by month '-Q --quarterly' multiperiod/multicolumn report by quarter '-Y --yearly' multiperiod/multicolumn report by year '-p --period=PERIODEXP' set start date, end date, and/or reporting interval all at once using period expressions syntax '--date2' match the secondary date instead (see command help for other effects) '--today=DATE' override today's date (affects relative smart dates, for tests/examples) '-U --unmarked' include only unmarked postings/txns (can combine with -P or -C) '-P --pending' include only pending postings/txns '-C --cleared' include only cleared postings/txns '-R --real' include only non-virtual postings '-NUM --depth=NUM' hide/aggregate accounts or postings more than NUM levels deep '-E --empty' show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) '-B --cost' convert amounts to their cost/selling amount at transaction time '-V --market' convert amounts to their market value in default valuation commodities '-X --exchange=COMM' convert amounts to their market value in commodity COMM '--value' convert amounts to cost or market value, more flexibly than -B/-V/-X '--infer-equity' infer conversion equity postings from costs '--infer-costs' infer costs from conversion equity postings '--infer-market-prices' use costs as additional market prices, as if they were P directives '--forecast' generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger-ui make future-dated transactions visible. '--auto' generate extra postings by applying auto posting rules to all txns (not just forecast txns) '--verbose-tags' add visible tags indicating transactions or postings which have been generated/modified '--commodity-style' Override the commodity style in the output for the specified commodity. For example 'EUR1.000,00'. '--color=WHEN (or --colour=WHEN)' Should color-supporting commands use ANSI color codes in text output. 'auto' (default): whenever stdout seems to be a color-supporting terminal. 'always' or 'yes': always, useful eg when piping output into 'less -R'. 'never' or 'no': never. A NO_COLOR environment variable overrides this. '--pretty[=WHEN]' Show prettier output, e.g. using unicode box-drawing characters. Accepts 'yes' (the default) or 'no' ('y', 'n', 'always', 'never' also work). If you provide an argument you must use '=', e.g. '-pretty=yes'. When a reporting option appears more than once in the command line, the last one takes precedence. Some reporting options can also be written as query arguments.  File: hledger.info, Node: Command line tips, Next: Output, Prev: Options, Up: Top 5 Command line tips ******************* Here are some details useful to know about for hledger command lines (and elsewhere). Feel free to skip this section until you need it. * Menu: * Option repetition:: * Special characters:: * Unicode characters:: * Regular expressions:: * Argument files::  File: hledger.info, Node: Option repetition, Next: Special characters, Up: Command line tips 5.1 Option repetition ===================== If options are repeated in a command line, hledger will generally use the last (right-most) occurence.  File: hledger.info, Node: Special characters, Next: Unicode characters, Prev: Option repetition, Up: Command line tips 5.2 Special characters ====================== * Menu: * Single escaping shell metacharacters:: * Double escaping regular expression metacharacters:: * Triple escaping for add-on commands:: * Less escaping::  File: hledger.info, Node: Single escaping shell metacharacters, Next: Double escaping regular expression metacharacters, Up: Special characters 5.2.1 Single escaping (shell metacharacters) -------------------------------------------- In shell command lines, characters significant to your shell - such as spaces, '<', '>', '(', ')', '|', '$' and '\' - should be "shell-escaped" if you want hledger to see them. This is done by enclosing them in single or double quotes, or by writing a backslash before them. Eg to match an account name containing a space: $ hledger register 'credit card' or: $ hledger register credit\ card Windows users should keep in mind that 'cmd' treats single quote as a regular character, so you should be using double quotes exclusively. PowerShell treats both single and double quotes as quotes.  File: hledger.info, Node: Double escaping regular expression metacharacters, Next: Triple escaping for add-on commands, Prev: Single escaping shell metacharacters, Up: Special characters 5.2.2 Double escaping (regular expression metacharacters) --------------------------------------------------------- Characters significant in regular expressions (described below) - such as '.', '^', '$', '[', ']', '(', ')', '|', and '\' - may need to be "regex-escaped" if you don't want them to be interpreted by hledger's regular expression engine. This is done by writing backslashes before them, but since backslash is typically also a shell metacharacter, both shell-escaping and regex-escaping will be needed. Eg to match a literal '$' sign while using the bash shell: $ hledger balance cur:'\$' or: $ hledger balance cur:\\$  File: hledger.info, Node: Triple escaping for add-on commands, Next: Less escaping, Prev: Double escaping regular expression metacharacters, Up: Special characters 5.2.3 Triple escaping (for add-on commands) ------------------------------------------- When you use hledger to run an external add-on command (described below), one level of shell-escaping is lost from any options or arguments intended for by the add-on command, so those need an extra level of shell-escaping. Eg to match a literal '$' sign while using the bash shell and running an add-on command ('ui'): $ hledger ui cur:'\\$' or: $ hledger ui cur:\\\\$ If you wondered why _four_ backslashes, perhaps this helps: unescaped: '$' escaped: '\$' double-escaped: '\\$' triple-escaped: '\\\\$' Or, you can avoid the extra escaping by running the add-on executable directly: $ hledger-ui cur:\\$  File: hledger.info, Node: Less escaping, Prev: Triple escaping for add-on commands, Up: Special characters 5.2.4 Less escaping ------------------- Options and arguments are sometimes used in places other than the shell command line, where shell-escaping is not needed, so there you should use one less level of escaping. Those places include: * an @argumentfile * hledger-ui's filter field * hledger-web's search form * GHCI's prompt (used by developers).  File: hledger.info, Node: Unicode characters, Next: Regular expressions, Prev: Special characters, Up: Command line tips 5.3 Unicode characters ====================== hledger is expected to handle non-ascii characters correctly: * they should be parsed correctly in input files and on the command line, by all hledger tools (add, iadd, hledger-web's search/add/edit forms, etc.) * they should be displayed correctly by all hledger tools, and on-screen alignment should be preserved. This requires a well-configured environment. Here are some tips: * A system locale must be configured, and it must be one that can decode the characters being used. In bash, you can set a locale like this: 'export LANG=en_US.UTF-8'. There are some more details in Troubleshooting. This step is essential - without it, hledger will quit on encountering a non-ascii character (as with all GHC-compiled programs). * your terminal software (eg Terminal.app, iTerm, CMD.exe, xterm..) must support unicode * the terminal must be using a font which includes the required unicode glyphs * the terminal should be configured to display wide characters as double width (for report alignment) * on Windows, for best results you should run hledger in the same kind of environment in which it was built. Eg hledger built in the standard CMD.EXE environment (like the binaries on our download page) might show display problems when run in a cygwin or msys terminal, and vice versa. (See eg #961).  File: hledger.info, Node: Regular expressions, Next: Argument files, Prev: Unicode characters, Up: Command line tips 5.4 Regular expressions ======================= A regular expression (regexp) is a small piece of text where certain characters (like '.', '^', '$', '+', '*', '()', '|', '[]', '\') have special meanings, forming a tiny language for matching text precisely - very useful in hledger and elsewhere. To learn all about them, visit regular-expressions.info. hledger supports regexps whenever you are entering a pattern to match something, eg in query arguments, account aliases, CSV if rules, hledger-web's search form, hledger-ui's '/' search, etc. You may need to wrap them in quotes, especially at the command line (see Special characters above). Here are some examples: Account name queries (quoted for command line use): Regular expression: Matches: ------------------- ------------------------------------------------------------ bank assets:bank, assets:bank:savings, expenses:art:banksy, ... :bank assets:bank:savings, expenses:art:banksy :bank: assets:bank:savings '^bank' none of those ( ^ matches beginning of text ) 'bank$' assets:bank ( $ matches end of text ) 'big \$ bank' big $ bank ( \ disables following character's special meaning ) '\bbank\b' assets:bank, assets:bank:savings ( \b matches word boundaries ) '(sav|check)ing' saving or checking ( (|) matches either alternative ) 'saving|checking' saving or checking ( outer parentheses are not needed ) 'savings?' saving or savings ( ? matches 0 or 1 of the preceding thing ) 'my +bank' my bank, my bank, ... ( + matches 1 or more of the preceding thing ) 'my *bank' mybank, my bank, my bank, ... ( * matches 0 or more of the preceding thing ) 'b.nk' bank, bonk, b nk, ... ( . matches any character ) Some other queries: desc:'amazon|amzn|audible' Amazon transactions cur:EUR amounts with commodity symbol containing EUR cur:'\$' amounts with commodity symbol containing $ cur:'^\$$' only $ amounts, not eg AU$ or CA$ cur:....? amounts with 4-or-more-character symbols tag:.=202[1-3] things with any tag whose value contains 2021, 2022 or 2023 Account name aliases: accept '.' instead of ':' as account separator: alias /\./=: replaces all periods in account names with colons Show multiple top-level accounts combined as one: --alias='/^[^:]+/=combined' ( [^:] matches any character other than : ) Show accounts with the second-level part removed: --alias '/^([^:]+):[^:]+/ = \1' match a top-level account and a second-level account and replace those with just the top-level account ( \1 in the replacement text means "whatever was matched by the first parenthesised part of the regexp" CSV rules: match CSV records containing dining-related MCC codes: if \?MCC581[124] Match CSV records with a specific amount around the end/start of month: if %amount \b3\.99 & %date (29|30|31|01|02|03)$ * Menu: * hledger's regular expressions::  File: hledger.info, Node: hledger's regular expressions, Up: Regular expressions 5.4.1 hledger's regular expressions ----------------------------------- hledger's regular expressions come from the regex-tdfa library. If they're not doing what you expect, it's important to know exactly what they support: 1. they are case insensitive 2. they are infix matching (they do not need to match the entire thing being matched) 3. they are POSIX ERE (extended regular expressions) 4. they also support GNU word boundaries ('\b', '\B', '\<', '\>') 5. backreferences are supported when doing text replacement in account aliases or CSV rules, where backreferences can be used in the replacement string to reference capturing groups in the search regexp. Otherwise, if you write '\1', it will match the digit '1'. 6. they do not support mode modifiers ('(?s)'), character classes ('\w', '\d'), or anything else not mentioned above. Some things to note: * In the 'alias' directive and '--alias' option, regular expressions must be enclosed in forward slashes ('/REGEX/'). Elsewhere in hledger, these are not required. * In queries, to match a regular expression metacharacter like '$' as a literal character, prepend a backslash. Eg to search for amounts with the dollar sign in hledger-web, write 'cur:\$'. * On the command line, some metacharacters like '$' have a special meaning to the shell and so must be escaped at least once more. See Special characters.  File: hledger.info, Node: Argument files, Prev: Regular expressions, Up: Command line tips 5.5 Argument files ================== You can save a set of command line options and arguments in a file, and then reuse them by writing '@FILENAME' as a command line argument. Eg: 'hledger bal @foo.args'. Inside the argument file, each line should contain just one option or argument. Don't use spaces except inside quotes (or you'll see a confusing error); write '=' (or nothing) between a flag and its argument. For the special characters mentioned above, use one less level of quoting than you would at the command prompt.  File: hledger.info, Node: Output, Next: Environment, Prev: Command line tips, Up: Top 6 Output ******** * Menu: * Output destination:: * Output format:: * Commodity styles:: * Colour:: * Box-drawing:: * Paging:: * Debug output::  File: hledger.info, Node: Output destination, Next: Output format, Up: Output 6.1 Output destination ====================== hledger commands send their output to the terminal by default. You can of course redirect this, eg into a file, using standard shell syntax: $ hledger print > foo.txt Some commands (print, register, stats, the balance commands) also provide the '-o/--output-file' option, which does the same thing without needing the shell. Eg: $ hledger print -o foo.txt $ hledger print -o - # write to stdout (the default)  File: hledger.info, Node: Output format, Next: Commodity styles, Prev: Output destination, Up: Output 6.2 Output format ================= Some commands offer other kinds of output, not just text on the terminal. Here are those commands and the formats currently supported: - txt csv/tsv html json sql ------------------------------------------------------------------------------- aregister Y Y Y Y balance Y _1_ Y _1_ Y _1,2_ Y balancesheet Y _1_ Y _1_ Y _1_ Y balancesheetequityY _1_ Y _1_ Y _1_ Y cashflow Y _1_ Y _1_ Y _1_ Y incomestatement Y _1_ Y _1_ Y _1_ Y print Y Y Y Y register Y Y Y * _1 Also affected by the balance commands' '--layout' option._ * _2 'balance' does not support html output without a report interval or with '--budget'._ The output format is selected by the '-O/--output-format=FMT' option: $ hledger print -O csv # print CSV on stdout or by the filename extension of an output file specified with the '-o/--output-file=FILE.FMT' option: $ hledger balancesheet -o foo.csv # write CSV to foo.csv The '-O' option can be combined with '-o' to override the file extension, if needed: $ hledger balancesheet -o foo.txt -O csv # write CSV to foo.txt Some notes about the various output formats: * Menu: * CSV output:: * HTML output:: * JSON output:: * SQL output::  File: hledger.info, Node: CSV output, Next: HTML output, Up: Output format 6.2.1 CSV output ---------------- * In CSV output, digit group marks (such as thousands separators) are disabled automatically.  File: hledger.info, Node: HTML output, Next: JSON output, Prev: CSV output, Up: Output format 6.2.2 HTML output ----------------- * HTML output can be styled by an optional 'hledger.css' file in the same directory.  File: hledger.info, Node: JSON output, Next: SQL output, Prev: HTML output, Up: Output format 6.2.3 JSON output ----------------- * This is not yet much used; real-world feedback is welcome. * Our JSON is rather large and verbose, since it is a faithful representation of hledger's internal data types. To understand the JSON, read the Haskell type definitions, which are mostly in https://github.com/simonmichael/hledger/blob/master/hledger-lib/Hledger/Data/Types.hs. * hledger represents quantities as Decimal values storing up to 255 significant digits, eg for repeating decimals. Such numbers can arise in practice (from automatically-calculated transaction prices), and would break most JSON consumers. So in JSON, we show quantities as simple Numbers with at most 10 decimal places. We don't limit the number of integer digits, but that part is under your control. We hope this approach will not cause problems in practice; if you find otherwise, please let us know. (Cf #1195)  File: hledger.info, Node: SQL output, Prev: JSON output, Up: Output format 6.2.4 SQL output ---------------- * This is not yet much used; real-world feedback is welcome. * SQL output is expected to work at least with SQLite, MySQL and Postgres. * For SQLite, it will be more useful if you modify the generated 'id' field to be a PRIMARY KEY. Eg: $ hledger print -O sql | sed 's/id serial/id INTEGER PRIMARY KEY AUTOINCREMENT NOT NULL/g' | ... * SQL output is structured with the expectations that statements will be executed in the empty database. If you already have tables created via SQL output of hledger, you would probably want to either clear tables of existing data (via 'delete' or 'truncate' SQL statements) or drop tables completely as otherwise your postings will be duped.  File: hledger.info, Node: Commodity styles, Next: Colour, Prev: Output format, Up: Output 6.3 Commodity styles ==================== When displaying amounts, hledger infers a standard display style for each commodity/currency, as described below in Commodity display style. If needed, this can be overridden by a '-c/--commodity-style' option (except for cost amounts and amounts displayed by the 'print' command, which are always displayed with all decimal digits). For example, the following will force dollar amounts to be displayed as shown: $ hledger print -c '$1.000,0' This option can repeated to set the display style for multiple commodities/currencies. Its argument is as described in the commodity directive.  File: hledger.info, Node: Colour, Next: Box-drawing, Prev: Commodity styles, Up: Output 6.4 Colour ========== In terminal output, some commands can produce colour when the terminal supports it: * if the '--color/--colour' option is given a value of 'yes' or 'always' (or 'no' or 'never'), colour will (or will not) be used; * otherwise, if the 'NO_COLOR' environment variable is set, colour will not be used; * otherwise, colour will be used if the output (terminal or file) supports it.  File: hledger.info, Node: Box-drawing, Next: Paging, Prev: Colour, Up: Output 6.5 Box-drawing =============== In terminal output, you can enable unicode box-drawing characters to render prettier tables: * if the '--pretty' option is given a value of 'yes' or 'always' (or 'no' or 'never'), unicode characters will (or will not) be used; * otherwise, unicode characters will not be used.  File: hledger.info, Node: Paging, Next: Debug output, Prev: Box-drawing, Up: Output 6.6 Paging ========== When showing long output in the terminal, hledger will try to use the pager specified by the 'PAGER' environment variable, or 'less', or 'more'. (A pager is a helper program that shows one page at a time rather than scrolling everything off screen). Currently it does this only for help output, not for reports; specifically, * when listing commands, with 'hledger' * when showing help with 'hledger [CMD] --help', * when viewing manuals with 'hledger help' or 'hledger --man'. Note the pager is expected to handle ANSI codes, which hledger uses eg for bold emphasis. For the common pager 'less' (and its 'more' compatibility mode), we add 'R' to the 'LESS' and 'MORE' environment variables to make this work. If you use a different pager, you might need to configure it similarly, to avoid seeing junk on screen (let us know). Otherwise, you can set the 'NO_COLOR' environment variable to 1 to disable all ANSI output (see Colour).  File: hledger.info, Node: Debug output, Prev: Paging, Up: Output 6.7 Debug output ================ We intend hledger to be relatively easy to troubleshoot, introspect and develop. You can add '--debug[=N]' to any hledger command line to see additional debug output. N ranges from 1 (least output, the default) to 9 (maximum output). Typically you would start with 1 and increase until you are seeing enough. Debug output goes to stderr, and is not affected by '-o/--output-file' (unless you redirect stderr to stdout, eg: '2>&1'). It will be interleaved with normal output, which can help reveal when parts of the code are evaluated. To capture debug output in a log file instead, you can usually redirect stderr, eg: hledger bal --debug=3 2>hledger.log  File: hledger.info, Node: Environment, Next: PART 2 DATA FORMATS, Prev: Output, Up: Top 7 Environment ************* These environment variables affect hledger: *COLUMNS* This is normally set by your terminal; some hledger commands ('register') will format their output to this width. If not set, they will try to use the available terminal width. *LEDGER_FILE* The main journal file to use when not specified with '-f/--file'. Default: '$HOME/.hledger.journal'. *NO_COLOR* If this environment variable is set (with any value), hledger will not use ANSI color codes in terminal output, unless overridden by an explicit '--color/--colour' option.  File: hledger.info, Node: PART 2 DATA FORMATS, Next: Journal, Prev: Environment, Up: Top 8 PART 2: DATA FORMATS **********************  File: hledger.info, Node: Journal, Next: CSV, Prev: PART 2 DATA FORMATS, Up: Top 9 Journal ********* hledger's default file format, representing a General Journal. Here's a cheatsheet/mini-tutorial, or you can skip ahead to About journal format. * Menu: * Journal cheatsheet:: * About journal format:: * Comments:: * Transactions:: * Dates:: * Status:: * Code:: * Description:: * Transaction comments:: * Postings:: * Account names:: * Amounts:: * Costs:: * Balance assertions:: * Posting comments:: * Tags:: * Directives:: * account directive:: * alias directive:: * commodity directive:: * decimal-mark directive:: * include directive:: * P directive:: * payee directive:: * tag directive:: * Periodic transactions:: * Auto postings:: * Other syntax::  File: hledger.info, Node: Journal cheatsheet, Next: About journal format, Up: Journal 9.1 Journal cheatsheet ====================== # Here is the main syntax of hledger's journal format # (omitting extra Ledger compatibility syntax). # hledger journals contain comments, directives, and transactions, in any order: ############################################################################### # 1. Comment lines are for notes or temporarily disabling things. # They begin with #, ;, or a line containing the word "comment". # hash comment line ; semicolon comment line comment These lines are commented. end comment # Some but not all hledger entries can have same-line comments attached to them, # from ; (semicolon) to end of line. ############################################################################### # 2. Directives modify parsing or reports in some way. # They begin with a word or letter (or symbol). account actifs ; type:A, declare an account that is an Asset. 2+ spaces before ;. account passifs ; type:L, declare an account that is a Liability, and so on.. (ALERX) alias chkg = assets:checking commodity $0.00 decimal-mark . include /dev/null payee Whole Foods P 2022-01-01 AAAA $1.40 ~ monthly budget goals ; <- 2+ spaces between period expression and description expenses:food $400 expenses:home $1000 budgeted ############################################################################### # 3. Transactions are what it's all about; they are dated events, # usually describing movements of money. # They begin with a date. # DATE DESCRIPTION ; This is a transaction comment. # ACCOUNT NAME 1 AMOUNT1 ; <- posting 1. This is a posting comment. # ACCOUNT NAME 2 AMOUNT2 ; <- posting 2. Postings must be indented. # ; ^^ At least 2 spaces between account and amount. # ... ; Any number of postings is allowed. The amounts must balance (sum to 0). 2022-01-01 opening balances are declared this way assets:checking $1000 ; Account names can be anything. lower case is easy to type. assets:savings $1000 ; assets, liabilities, equity, revenues, expenses are common. assets:cash:wallet $100 ; : indicates subaccounts. liabilities:credit card $-200 ; liabilities, equity, revenues balances are usually negative. equity ; One amount can be left blank; $-1900 is inferred here. 2022-04-15 * (#12345) pay taxes ; There can be a ! or * after the date meaning "pending" or "cleared". ; There can be a transaction code (text in parentheses) after the date/status. ; Amounts' sign represents direction of flow, or credit/debit: assets:checking $-500 ; minus means removed from this account (credit) expenses:tax:us:2021 $500 ; plus means added to this account (debit) ; revenue/expense categories are also "accounts" 2022-01-01 ; The description is optional. ; Any currency/commodity symbols are allowed, on either side. assets:cash:wallet GBP -10 expenses:clothing GBP 10 assets:gringotts -10 gold assets:pouch 10 gold revenues:gifts -2 "Liquorice Wands" ; Complex symbols assets:bag 2 "Liquorice Wands" ; must be double-quoted. 2022-01-01 Cost in another commodity can be noted with @ or @@ assets:investments 2.0 AAAA @ $1.50 ; @ means per-unit cost assets:investments 3.0 AAAA @@ $4 ; @@ means total cost assets:checking $-7.00 2022-01-02 assert balances ; Balances can be asserted for extra error checking, in any transaction. assets:investments 0 AAAA = 5.0 AAAA assets:pouch 0 gold = 10 gold assets:savings $0 = $1000 1999-12-31 Ordering transactions by date is recommended but not required. ; Postings are not required. 2022.01.01 These date 2022/1/1 formats are 12/31 also allowed (but consistent YYYY-MM-DD is recommended).  File: hledger.info, Node: About journal format, Next: Comments, Prev: Journal cheatsheet, Up: Journal 9.2 About journal format ======================== hledger's usual data source is a plain text file containing journal entries in hledger journal format. This file represents a standard accounting general journal. I use file names ending in '.journal', but that's not required. The journal file contains a number of transaction entries, each describing a transfer of money (or any commodity) between two or more named accounts, in a simple format readable by both hledger and humans. hledger's journal format is compatible with most of Ledger's journal format, but not all of it. The differences and interoperation tips are described at hledger and Ledger. With some care, and by avoiding incompatible features, you can keep your hledger journal readable by Ledger and vice versa. This can useful eg for comparing the behaviour of one app against the other. You can use hledger without learning any more about this file; just use the add or web or import commands to create and update it. Many users, though, edit the journal file with a text editor, and track changes with a version control system such as git. Editor addons such as ledger-mode or hledger-mode for Emacs, vim-ledger for Vim, and hledger-vscode for Visual Studio Code, make this easier, adding colour, formatting, tab completion, and useful commands. See Editor configuration at hledger.org for the full list. Here's a description of each part of the file format (and hledger's data model). A hledger journal file can contain three kinds of thing: file comments, transactions, and/or directives (counting periodic transaction rules and auto posting rules as directives).  File: hledger.info, Node: Comments, Next: Transactions, Prev: About journal format, Up: Journal 9.3 Comments ============ Lines in the journal will be ignored if they begin with a hash ('#') or a semicolon (';'). (See also Other syntax.) hledger will also ignore regions beginning with a 'comment' line and ending with an 'end comment' line (or file end). Here's a suggestion for choosing between them: * '#' for top-level notes * ';' for commenting out things temporarily * 'comment' for quickly commenting large regions (remember it's there, or you might get confused) Eg: # a comment line ; another commentline comment A multi-line comment block, continuing until "end comment" directive or the end of the current file. end comment Some hledger entries can have same-line comments attached to them, from ; (semicolon) to end of line. See Transaction comments, Posting comments, and Account comments below.  File: hledger.info, Node: Transactions, Next: Dates, Prev: Comments, Up: Journal 9.4 Transactions ================ Transactions are the main unit of information in a journal file. They represent events, typically a movement of some quantity of commodities between two or more named accounts. Each transaction is recorded as a journal entry, beginning with a simple date in column 0. This can be followed by any of the following optional fields, separated by spaces: * a status character (empty, '!', or '*') * a code (any short number or text, enclosed in parentheses) * a description (any remaining text until end of line or a semicolon) * a comment (any remaining text following a semicolon until end of line, and any following indented lines beginning with a semicolon) * 0 or more indented _posting_ lines, describing what was transferred and the accounts involved (indented comment lines are also allowed, but not blank lines or non-indented lines). Here's a simple journal file containing one transaction: 2008/01/01 income assets:bank:checking $1 income:salary $-1  File: hledger.info, Node: Dates, Next: Status, Prev: Transactions, Up: Journal 9.5 Dates ========= * Menu: * Simple dates:: * Posting dates::  File: hledger.info, Node: Simple dates, Next: Posting dates, Up: Dates 9.5.1 Simple dates ------------------ Dates in the journal file use _simple dates_ format: 'YYYY-MM-DD' or 'YYYY/MM/DD' or 'YYYY.MM.DD', with leading zeros optional. The year may be omitted, in which case it will be inferred from the context: the current transaction, the default year set with a 'Y' directive, or the current date when the command is run. Some examples: '2010-01-31', '2010/01/31', '2010.1.31', '1/31'. (The UI also accepts simple dates, as well as the more flexible smart dates documented in the hledger manual.)  File: hledger.info, Node: Posting dates, Prev: Simple dates, Up: Dates 9.5.2 Posting dates ------------------- You can give individual postings a different date from their parent transaction, by adding a posting comment containing a tag (see below) like 'date:DATE'. This is probably the best way to control posting dates precisely. Eg in this example the expense should appear in May reports, and the deduction from checking should be reported on 6/1 for easy bank reconciliation: 2015/5/30 expenses:food $10 ; food purchased on saturday 5/30 assets:checking ; bank cleared it on monday, date:6/1 $ hledger -f t.j register food 2015-05-30 expenses:food $10 $10 $ hledger -f t.j register checking 2015-06-01 assets:checking $-10 $-10 DATE should be a simple date; if the year is not specified it will use the year of the transaction's date. The 'date:' tag must have a valid simple date value if it is present, eg a 'date:' tag with no value is not allowed.  File: hledger.info, Node: Status, Next: Code, Prev: Dates, Up: Journal 9.6 Status ========== Transactions, or individual postings within a transaction, can have a status mark, which is a single character before the transaction description or posting account name, separated from it by a space, indicating one of three statuses: mark status ----------------- unmarked '!' pending '*' cleared When reporting, you can filter by status with the '-U/--unmarked', '-P/--pending', and '-C/--cleared' flags; or the 'status:', 'status:!', and 'status:*' queries; or the U, P, C keys in hledger-ui. Note, in Ledger and in older versions of hledger, the "unmarked" state is called "uncleared". As of hledger 1.3 we have renamed it to unmarked for clarity. To replicate Ledger and old hledger's behaviour of also matching pending, combine -U and -P. Status marks are optional, but can be helpful eg for reconciling with real-world accounts. Some editor modes provide highlighting and shortcuts for working with status. Eg in Emacs ledger-mode, you can toggle transaction status with C-c C-e, or posting status with C-c C-c. What "uncleared", "pending", and "cleared" actually mean is up to you. Here's one suggestion: status meaning -------------------------------------------------------------------------- uncleared recorded but not yet reconciled; needs review pending tentatively reconciled (if needed, eg during a big reconciliation) cleared complete, reconciled as far as possible, and considered correct With this scheme, you would use '-PC' to see the current balance at your bank, '-U' to see things which will probably hit your bank soon (like uncashed checks), and no flags to see the most up-to-date state of your finances.  File: hledger.info, Node: Code, Next: Description, Prev: Status, Up: Journal 9.7 Code ======== After the status mark, but before the description, you can optionally write a transaction "code", enclosed in parentheses. This is a good place to record a check number, or some other important transaction id or reference number.  File: hledger.info, Node: Description, Next: Transaction comments, Prev: Code, Up: Journal 9.8 Description =============== A transaction's description is the rest of the line following the date and status mark (or until a comment begins). Sometimes called the "narration" in traditional bookkeeping, it can be used for whatever you wish, or left blank. Transaction descriptions can be queried, unlike comments. * Menu: * Payee and note::  File: hledger.info, Node: Payee and note, Up: Description 9.8.1 Payee and note -------------------- You can optionally include a '|' (pipe) character in descriptions to subdivide the description into separate fields for payee/payer name on the left (up to the first '|') and an additional note field on the right (after the first '|'). This may be worthwhile if you need to do more precise querying and pivoting by payee or by note.  File: hledger.info, Node: Transaction comments, Next: Postings, Prev: Description, Up: Journal 9.9 Transaction comments ======================== Text following ';', after a transaction description, and/or on indented lines immediately below it, form comments for that transaction. They are reproduced by 'print' but otherwise ignored, except they may contain tags, which are not ignored. 2012-01-01 something ; a transaction comment ; a second line of transaction comment expenses 1 assets  File: hledger.info, Node: Postings, Next: Account names, Prev: Transaction comments, Up: Journal 9.10 Postings ============= A posting is an addition of some amount to, or removal of some amount from, an account. Each posting line begins with at least one space or tab (2 or 4 spaces is common), followed by: * (optional) a status character (empty, '!', or '*'), followed by a space * (required) an account name (any text, optionally containing *single spaces*, until end of line or a double space) * (optional) *two or more spaces* or tabs followed by an amount. Positive amounts are being added to the account, negative amounts are being removed. The amounts within a transaction must always sum up to zero. As a convenience, one amount may be left blank; it will be inferred so as to balance the transaction. Be sure to note the unusual two-space delimiter between account name and amount. This makes it easy to write account names containing spaces. But if you accidentally leave only one space (or tab) before the amount, the amount will be considered part of the account name.  File: hledger.info, Node: Account names, Next: Amounts, Prev: Postings, Up: Journal 9.11 Account names ================== Accounts are the main way of categorising things in hledger. As in Double Entry Bookkeeping, they can represent real world accounts (such as a bank account), or more abstract categories such as "money borrowed from Frank" or "money spent on electricity". You can use any account names you like, but we usually start with the traditional accounting categories, which in english are 'assets', 'liabilities', 'equity', 'revenues', 'expenses'. (You might see these referred to as A, L, E, R, X for short.) For more precise reporting, we usually divide the top level accounts into more detailed subaccounts, by writing a full colon between account name parts. For example, from the account names 'assets:bank:checking' and 'expenses:food', hledger will infer this hierarchy of five accounts: assets assets:bank assets:bank:checking expenses expenses:food Shown as an outline, the hierarchical tree structure is more clear: assets bank checking expenses food hledger reports can summarise the account tree to any depth, so you can go as deep as you like with subcategories, but keeping your account names relatively simple may be best when starting out. Account names may be capitalised or not; they may contain letters, numbers, symbols, or single spaces. Note, when an account name and an amount are written on the same line, they must be separated by *two or more spaces* (or tabs). Parentheses or brackets enclosing the full account name indicate virtual postings, described below. Parentheses or brackets internal to the account name have no special meaning. Account names can be altered temporarily or permanently by account aliases.  File: hledger.info, Node: Amounts, Next: Costs, Prev: Account names, Up: Journal 9.12 Amounts ============ After the account name, there is usually an amount. (Important: between account name and amount, there must be *two or more spaces*.) hledger's amount format is flexible, supporting several international formats. Here are some examples. Amounts have a number (the "quantity"): 1 ..and usually a currency symbol or commodity name (more on this below), to the left or right of the quantity, with or without a separating space: $1 4000 AAPL 3 "green apples" Amounts can be preceded by a minus sign (or a plus sign, though plus is the default), The sign can be written before or after a left-side commodity symbol: -$1 $-1 One or more spaces between the sign and the number are acceptable when parsing (but they won't be displayed in output): + $1 $- 1 Scientific E notation is allowed: 1E-6 EUR 1E3 * Menu: * Decimal marks digit group marks:: * Commodity:: * Directives influencing number parsing and display:: * Commodity display style:: * Rounding::  File: hledger.info, Node: Decimal marks digit group marks, Next: Commodity, Up: Amounts 9.12.1 Decimal marks, digit group marks --------------------------------------- A _decimal mark_ can be written as a period or a comma: 1.23 1,23 In the integer part of the quantity (left of the decimal mark), groups of digits can optionally be separated by a _digit group mark_ - a space, comma, or period (different from the decimal mark): $1,000,000.00 EUR 2.000.000,00 INR 9,99,99,999.00 1 000 000.9455 hledger is not biased towards period or comma decimal marks, so a number containing just one period or comma, like '1,000' or '1.000', is ambiguous. In such cases hledger assumes it is a decimal mark, parsing both of these as 1. To disambiguate these and ensure accurate number parsing, especially if you use digit group marks, we recommend declaring the decimal mark. You can declare it for each file with 'decimal-mark' directives, or for each commodity with 'commodity' directives (described below).  File: hledger.info, Node: Commodity, Next: Directives influencing number parsing and display, Prev: Decimal marks digit group marks, Up: Amounts 9.12.2 Commodity ---------------- Amounts in hledger have both a "quantity", which is a signed decimal number, and a "commodity", which is a currency symbol, stock ticker, or any word or phrase describing something you are tracking. If the commodity name contains non-letters (spaces, numbers, or punctuation), you must always write it inside double quotes ('"green apples"', '"ABC123"'). If you write just a bare number, that too will have a commodity, with name '""'; we call that the "no-symbol commodity". Actually, hledger combines these single-commodity amounts into more powerful multi-commodity amounts, which are what it works with most of the time. A multi-commodity amount could be, eg: '1 USD, 2 EUR, 3.456 TSLA'. In practice, you will only see multi-commodity amounts in hledger's output; you can't write them directly in the journal file. (If you are writing scripts or working with hledger's internals, these are the 'Amount' and 'MixedAmount' types.)  File: hledger.info, Node: Directives influencing number parsing and display, Next: Commodity display style, Prev: Commodity, Up: Amounts 9.12.3 Directives influencing number parsing and display -------------------------------------------------------- You can add 'decimal-mark' and 'commodity' directives to the journal, to declare and control these things more explicitly and precisely. These are described below, but here's a quick example: # the decimal mark character used by all amounts in this file (all commodities) decimal-mark . # display styles for the $, EUR, INR and no-symbol commodities: commodity $1,000.00 commodity EUR 1.000,00 commodity INR 9,99,99,999.00 commodity 1 000 000.9455  File: hledger.info, Node: Commodity display style, Next: Rounding, Prev: Directives influencing number parsing and display, Up: Amounts 9.12.4 Commodity display style ------------------------------ For the amounts in each commodity, hledger chooses a consistent display style (symbol placement, decimal mark and digit group marks, number of decimal digits) to use in most reports. This is inferred as follows: First, if there's a 'D' directive declaring a default commodity, that commodity symbol and amount format is applied to all no-symbol amounts in the journal. Then each commodity's display style is determined from its 'commodity' directive. We recommend always declaring commodities with 'commodity' directives, since they help ensure consistent display styles and precisions, and bring other benefits such as error checking for commodity symbols. But if a 'commodity' directive is not present, hledger infers a commodity's display styles from its amounts as they are written in the journal (excluding cost amounts and amounts in periodic transaction rules or auto posting rules). It uses * the symbol placement and decimal mark of the first amount seen * the digit group marks of the first amount with digit group marks * and the maximum number of decimal digits seen across all amounts. And as fallback if no applicable amounts are found, it would use a default style, like '$1000.00' (symbol on the left with no space, period as decimal mark, and two decimal digits). Finally, commodity styles can be overridden by the '-c/--commodity-style' command line option.  File: hledger.info, Node: Rounding, Prev: Commodity display style, Up: Amounts 9.12.5 Rounding --------------- Amounts are stored internally as decimal numbers with up to 255 decimal places. They are displayed with their original journal precisions by print and print-like reports, and rounded to their display precision (the number of decimal digits specified by the commodity display style) by other reports. When rounding, hledger uses banker's rounding (it rounds to the nearest even digit). So eg 0.5 displayed with zero decimal digits appears as "0".  File: hledger.info, Node: Costs, Next: Balance assertions, Prev: Amounts, Up: Journal 9.13 Costs ========== After a posting amount, you can note its cost (when buying) or selling price (when selling) in another commodity, by writing either '@ UNITPRICE' or '@@ TOTALPRICE' after it. This indicates a conversion transaction, where one commodity is exchanged for another. (You might also see this called "transaction price" in hledger docs, discussions, or code; that term was directionally neutral and reminded that it is a price specific to a transaction, but we now just call it "cost", with the understanding that the transaction could be a purchase or a sale.) Costs are usually written explicitly with '@' or '@@', but can also be inferred automatically for simple multi-commodity transactions. Note, if costs are inferred, the order of postings is significant; the first posting will have a cost attached, in the commodity of the second. As an example, here are several ways to record purchases of a foreign currency in hledger, using the cost notation either explicitly or implicitly: 1. Write the price per unit, as '@ UNITPRICE' after the amount: 2009/1/1 assets:euros €100 @ $1.35 ; one hundred euros purchased at $1.35 each assets:dollars ; balancing amount is -$135.00 2. Write the total price, as '@@ TOTALPRICE' after the amount: 2009/1/1 assets:euros €100 @@ $135 ; one hundred euros purchased at $135 for the lot assets:dollars 3. Specify amounts for all postings, using exactly two commodities, and let hledger infer the price that balances the transaction. Note the effect of posting order: the price is added to first posting, making it '€100 @@ $135', as in example 2: 2009/1/1 assets:euros €100 ; one hundred euros purchased assets:dollars $-135 ; for $135 Amounts can be converted to cost at report time using the '-B/--cost' flag; this is discussed more in the Cost reporting section. Note that the cost normally should be a positive amount, though it's not required to be. This can be a little confusing, see discussion at -infer-market-prices: market prices from transactions. * Menu: * Other cost/lot notations::  File: hledger.info, Node: Other cost/lot notations, Up: Costs 9.13.1 Other cost/lot notations ------------------------------- A slight digression for Ledger and Beancount users. Ledger has a number of cost/lot-related notations: * '@ UNITCOST' and '@@ TOTALCOST' * expresses a conversion rate, as in hledger * when buying, also creates a lot than can be selected at selling time * '(@) UNITCOST' and '(@@) TOTALCOST' (virtual cost) * like the above, but also means "this cost was exceptional, don't use it when inferring market prices". Currently, hledger treats the above like '@' and '@@'; the parentheses are ignored. * '{=FIXEDUNITCOST}' and '{{=FIXEDTOTALCOST}}' (fixed price) * when buying, means "this cost is also the fixed price, don't let it fluctuate in value reports" * '{UNITCOST}' and '{{TOTALCOST}}' (lot price) * can be used identically to '@ UNITCOST' and '@@ TOTALCOST', also creates a lot * when selling, combined with '@ ...', specifies an investment lot by its cost basis; does not check if that lot is present * and related: '[YYYY/MM/DD]' (lot date) * when buying, attaches this acquisition date to the lot * when selling, selects a lot by its acquisition date * '(SOME TEXT)' (lot note) * when buying, attaches this note to the lot * when selling, selects a lot by its note Currently, hledger accepts any or all of the above in any order after the posting amount, but ignores them. (This can break transaction balancing.) For Beancount users, the notation and behaviour is different: * '@ UNITCOST' and '@@ TOTALCOST' * expresses a cost without creating a lot, as in hledger * when buying (augmenting) or selling (reducing) a lot, combined with '{...}': documents the cost/selling price (not used for transaction balancing) * '{UNITCOST}' and '{{TOTALCOST}}' * when buying (augmenting), expresses the cost for transaction balancing, and also creates a lot with this cost basis attached * when selling (reducing), * selects a lot by its cost basis * raises an error if that lot is not present or can not be selected unambiguously (depending on booking method configured) * expresses the selling price for transaction balancing Currently, hledger accepts the '{UNITCOST}'/'{{TOTALCOST}}' notation but ignores it. * variations: '{}', '{YYYY-MM-DD}', '{"LABEL"}', '{UNITCOST, "LABEL"}', '{UNITCOST, YYYY-MM-DD, "LABEL"}' etc. Currently, hledger rejects these.  File: hledger.info, Node: Balance assertions, Next: Posting comments, Prev: Costs, Up: Journal 9.14 Balance assertions ======================= hledger supports Ledger-style balance assertions in journal files. These look like, for example, '= EXPECTEDBALANCE' following a posting's amount. Eg here we assert the expected dollar balance in accounts a and b after each posting: 2013/1/1 a $1 =$1 b =$-1 2013/1/2 a $1 =$2 b $-1 =$-2 After reading a journal file, hledger will check all balance assertions and report an error if any of them fail. Balance assertions can protect you from, eg, inadvertently disrupting reconciled balances while cleaning up old entries. You can disable them temporarily with the '-I/--ignore-assertions' flag, which can be useful for troubleshooting or for reading Ledger files. (Note: this flag currently does not disable balance assignments, described below). * Menu: * Assertions and ordering:: * Assertions and multiple included files:: * Assertions and multiple -f files:: * Assertions and commodities:: * Assertions and costs:: * Assertions and subaccounts:: * Assertions and virtual postings:: * Assertions and auto postings:: * Assertions and precision::  File: hledger.info, Node: Assertions and ordering, Next: Assertions and multiple included files, Up: Balance assertions 9.14.1 Assertions and ordering ------------------------------ hledger sorts an account's postings and assertions first by date and then (for postings on the same day) by parse order. Note this is different from Ledger, which sorts assertions only by parse order. (Also, Ledger assertions do not see the accumulated effect of repeated postings to the same account within a transaction.) So, hledger balance assertions keep working if you reorder differently-dated transactions within the journal. But if you reorder same-dated transactions or postings, assertions might break and require updating. This order dependence does bring an advantage: precise control over the order of postings and assertions within a day, so you can assert intra-day balances.  File: hledger.info, Node: Assertions and multiple included files, Next: Assertions and multiple -f files, Prev: Assertions and ordering, Up: Balance assertions 9.14.2 Assertions and multiple included files --------------------------------------------- Multiple files included with the 'include' directive are processed as if concatenated into one file, preserving their order and the posting order within each file. It means that balance assertions in later files will see balance from earlier files. And if you have multiple postings to an account on the same day, split across multiple files, and you want to assert the account's balance on that day, you'll need to put the assertion in the right file - the last one in the sequence, probably.  File: hledger.info, Node: Assertions and multiple -f files, Next: Assertions and commodities, Prev: Assertions and multiple included files, Up: Balance assertions 9.14.3 Assertions and multiple -f files --------------------------------------- Unlike 'include', when multiple files are specified on the command line with multiple '-f/--file' options, balance assertions will not see balance from earlier files. This can be useful when you do not want problems in earlier files to disrupt valid assertions in later files. If you do want assertions to see balance from earlier files, use 'include', or concatenate the files temporarily.  File: hledger.info, Node: Assertions and commodities, Next: Assertions and costs, Prev: Assertions and multiple -f files, Up: Balance assertions 9.14.4 Assertions and commodities --------------------------------- The asserted balance must be a simple single-commodity amount, and in fact the assertion checks only this commodity's balance within the (possibly multi-commodity) account balance. This is how assertions work in Ledger also. We could call this a "partial" balance assertion. To assert the balance of more than one commodity in an account, you can write multiple postings, each asserting one commodity's balance. You can make a stronger "total" balance assertion by writing a double equals sign ('== EXPECTEDBALANCE'). This asserts that there are no other commodities in the account besides the asserted one (or at least, that their balance is 0). 2013/1/1 a $1 a 1€ b $-1 c -1€ 2013/1/2 ; These assertions succeed a 0 = $1 a 0 = 1€ b 0 == $-1 c 0 == -1€ 2013/1/3 ; This assertion fails as 'a' also contains 1€ a 0 == $1 It's not yet possible to make a complete assertion about a balance that has multiple commodities. One workaround is to isolate each commodity into its own subaccount: 2013/1/1 a:usd $1 a:euro 1€ b 2013/1/2 a 0 == 0 a:usd 0 == $1 a:euro 0 == 1€  File: hledger.info, Node: Assertions and costs, Next: Assertions and subaccounts, Prev: Assertions and commodities, Up: Balance assertions 9.14.5 Assertions and costs --------------------------- Balance assertions ignore costs, and should normally be written without one: 2019/1/1 (a) $1 @ €1 = $1 We do allow costs to be written in balance assertion amounts, however, and print shows them, but they don't affect whether the assertion passes or fails. This is for backward compatibility (hledger's close command used to generate balance assertions with costs), and because balance _assignments_ do use costs (see below).  File: hledger.info, Node: Assertions and subaccounts, Next: Assertions and virtual postings, Prev: Assertions and costs, Up: Balance assertions 9.14.6 Assertions and subaccounts --------------------------------- The balance assertions above ('=' and '==') do not count the balance from subaccounts; they check the account's exclusive balance only. You can assert the balance including subaccounts by writing '=*' or '==*', eg: 2019/1/1 equity:opening balances checking:a 5 checking:b 5 checking 1 ==* 11  File: hledger.info, Node: Assertions and virtual postings, Next: Assertions and auto postings, Prev: Assertions and subaccounts, Up: Balance assertions 9.14.7 Assertions and virtual postings -------------------------------------- Balance assertions always consider both real and virtual postings; they are not affected by the '--real/-R' flag or 'real:' query.  File: hledger.info, Node: Assertions and auto postings, Next: Assertions and precision, Prev: Assertions and virtual postings, Up: Balance assertions 9.14.8 Assertions and auto postings ----------------------------------- Balance assertions _are_ affected by the '--auto' flag, which generates auto postings, which can alter account balances. Because auto postings are optional in hledger, accounts affected by them effectively have two balances. But balance assertions can only test one or the other of these. So to avoid making fragile assertions, either: * assert the balance calculated with '--auto', and always use '--auto' with that file * or assert the balance calculated without '--auto', and never use '--auto' with that file * or avoid balance assertions on accounts affected by auto postings (or avoid auto postings entirely).  File: hledger.info, Node: Assertions and precision, Prev: Assertions and auto postings, Up: Balance assertions 9.14.9 Assertions and precision ------------------------------- Balance assertions compare the exactly calculated amounts, which are not always what is shown by reports. Eg a commodity directive may limit the display precision, but this will not affect balance assertions. Balance assertion failure messages show exact amounts.  File: hledger.info, Node: Posting comments, Next: Tags, Prev: Balance assertions, Up: Journal 9.15 Posting comments ===================== Text following ';', at the end of a posting line, and/or on indented lines immediately below it, form comments for that posting. They are reproduced by 'print' but otherwise ignored, except they may contain tags, which are not ignored. 2012-01-01 expenses 1 ; a comment for posting 1 assets ; a comment for posting 2 ; a second comment line for posting 2  File: hledger.info, Node: Tags, Next: Directives, Prev: Posting comments, Up: Journal 9.16 Tags ========= Tags are a way to add extra labels or labelled data to transactions, postings, or accounts, which you can then search or pivot on. They are written as a word (optionally hyphenated) immediately followed by a full colon, in a transaction or posting or account directive's comment. (This is an exception to the usual rule that things in comments are ignored.) Eg, here four different tags are recorded: one on the checking account, two on the transaction, and one on the expenses posting: account assets:checking ; accounttag: 2017/1/16 bought groceries ; transactiontag-1: ; transactiontag-2: assets:checking $-1 expenses:food $1 ; postingtag: Postings also inherit tags from their transaction and their account. And transactions also acquire tags from their postings (and postings' accounts). So in the example above, the expenses posting effectively has all four tags (by inheriting from account and transaction), and the transaction also has all four tags (by acquiring from the expenses posting). You can list tag names with 'hledger tags [NAMEREGEX]', or match by tag name with a 'tag:NAMEREGEX' query. * Menu: * Tag values::  File: hledger.info, Node: Tag values, Up: Tags 9.16.1 Tag values ----------------- Tags can have a value, which is any text after the colon up until a comma or end of line (with surrounding whitespace removed). Note this means that hledger tag values can not contain commas. Eg in the following posting, the three tags' values are "value 1", "value 2", and "" (empty) respectively: expenses:food $10 ; foo, tag1: value 1 , tag2:value 2, bar tag3: , baz Note that tags can be repeated, and are additive rather than overriding: when the same tag name is seen again with a new value, the new name:value pair is added to the tags. (It is not possible to override a tag's value or remove a tag.) You can list a tag's values with 'hledger tags TAGNAME --values', or match by tag value with a 'tag:NAMEREGEX=VALUEREGEX' query.  File: hledger.info, Node: Directives, Next: account directive, Prev: Tags, Up: Journal 9.17 Directives =============== Besides transactions, there is something else you can put in a 'journal' file: directives. These are declarations, beginning with a keyword, that modify hledger's behaviour. Some directives can have more specific subdirectives, indented below them. hledger's directives are similar to Ledger's in many cases, but there are also many differences. Directives are not required, but can be useful. Here are the main directives: purpose directive -------------------------------------------------------------------------- *READING DATA:* Rewrite account names 'alias' Comment out sections of the file 'comment' Declare file's decimal mark, to help 'decimal-mark' parse amounts accurately Include other data files 'include' *GENERATING DATA:* Generate recurring transactions or '~' budget goals Generate extra postings on existing '=' transactions *CHECKING FOR ERRORS:* Define valid entities to provide more 'account', 'commodity', error checking 'payee', 'tag' *REPORTING:* Declare accounts' type and display 'account' order Declare commodity display styles 'commodity' Declare market prices 'P' * Menu: * Directives and multiple files:: * Directive effects::  File: hledger.info, Node: Directives and multiple files, Next: Directive effects, Up: Directives 9.17.1 Directives and multiple files ------------------------------------ Directives vary in their scope, ie which journal entries and which input files they affect. Most often, a directive will affect the following entries and included files if any, until the end of the current file - and no further. You might find this inconvenient! For example, 'alias' directives do not affect parent or sibling files. But there are usually workarounds; for example, put 'alias' directives in your top-most file, before including other files. The restriction, though it may be annoying at first, is in a good cause; it allows reports to be stable and deterministic, independent of the order of input. Without it, reports could show different numbers depending on the order of -f options, or the positions of include directives in your files.  File: hledger.info, Node: Directive effects, Prev: Directives and multiple files, Up: Directives 9.17.2 Directive effects ------------------------ Here are all hledger's directives, with their effects and scope summarised - nine main directives, plus four others which we consider non-essential: directivewhat it does ends at file end? --------------------------------------------------------------------------- *'account'*Declares an account, for checking all entries in all files; andN its display order and type. Subdirectives: any text, ignored. *'alias'*Rewrites account names, in following entries until end of Y current file or 'end aliases'. Command line equivalent: '--alias' *'comment'*Ignores part of the journal file, until end of current file orY 'end comment'. *'commodity'*Declares up to four things: 1. a commodity symbol, for checkingN,Y,N,N all amounts in all files 2. the decimal mark for parsing amounts of this commodity, in the following entries until end of current file (if there is no 'decimal-mark' directive) 3. and the display style for amounts of this commodity 4. which is also the precision to use for balanced-transaction checking in this commodity. Takes precedence over 'D'. Subdirectives: 'format' (Ledger-compatible syntax). Command line equivalent: '-c/--commodity-style' *'decimal-mark'*Declares the decimal mark, for parsing amounts of all Y commodities in following entries until next 'decimal-mark' or end of current file. Included files can override. Takes precedence over 'commodity' and 'D'. *'include'*Includes entries and directives from another file, as if theyN were written inline. Command line alternative: multiple '-f/--file' *'payee'*Declares a payee name, for checking all entries in all files. N *'P'*Declares the market price of a commodity on some date, for value N reports. *'~'*Declares a periodic transaction rule that generates future N (tilde)transactions with '--forecast' and budget goals with 'balance --budget'. Other syntax: *'applyPrepends a common parent account to all account names, in Y account'*following entries until end of current file or 'end apply account'. *'D'*Sets a default commodity to use for no-symbol amounts;and, if Y,Y,N,N there is no 'commodity' directive for this commodity: its decimal mark, balancing precision, and display style, as above. *'Y'*Sets a default year to use for any yearless dates, in following Y entries until end of current file. *'='*Declares an auto posting rule that generates extra postings on partly (equals)matched transactions with '--auto', in current, parent, and child files (but not sibling files, see #1212). *OtherOther directives from Ledger's file format are accepted but Ledgerignored. directives*  File: hledger.info, Node: account directive, Next: alias directive, Prev: Directives, Up: Journal 9.18 'account' directive ======================== 'account' directives can be used to declare accounts (ie, the places that amounts are transferred from and to). Though not required, these declarations can provide several benefits: * They can document your intended chart of accounts, providing a reference. * In strict mode, they restrict which accounts may be posted to by transactions, which helps detect typos. * They control account display order in reports, allowing non-alphabetic sorting (eg Revenues to appear above Expenses). * They help with account name completion (in hledger add, hledger-web, hledger-iadd, ledger-mode, etc.) * They can store additional account information as comments, or as tags which can be used to filter or pivot reports. * They can help hledger know your accounts' types (asset, liability, equity, revenue, expense), affecting reports like balancesheet and incomestatement. They are written as the word 'account' followed by a hledger-style account name, eg: account assets:bank:checking Note, however, that accounts declared in account directives are not allowed to have surrounding brackets and parentheses, unlike accounts used in postings. So the following journal will not parse: account (assets:bank:checking) * Menu: * Account comments:: * Account subdirectives:: * Account error checking:: * Account display order:: * Account types::  File: hledger.info, Node: Account comments, Next: Account subdirectives, Up: account directive 9.18.1 Account comments ----------------------- Text following *two or more spaces* and ';' at the end of an account directive line, and/or following ';' on indented lines immediately below it, form comments for that account. They are ignored except they may contain tags, which are not ignored. The two-space requirement for same-line account comments is because ';' is allowed in account names. account assets:bank:checking ; same-line comment, at least 2 spaces before the semicolon ; next-line comment ; some tags - type:A, acctnum:12345  File: hledger.info, Node: Account subdirectives, Next: Account error checking, Prev: Account comments, Up: account directive 9.18.2 Account subdirectives ---------------------------- Ledger-style indented subdirectives are also accepted, but currently ignored: account assets:bank:checking format subdirective is ignored  File: hledger.info, Node: Account error checking, Next: Account display order, Prev: Account subdirectives, Up: account directive 9.18.3 Account error checking ----------------------------- By default, accounts need not be declared; they come into existence when a posting references them. This is convenient, but it means hledger can't warn you when you mis-spell an account name in the journal. Usually you'll find that error later, as an extra account in balance reports, or an incorrect balance when reconciling. In strict mode, enabled with the '-s'/'--strict' flag, hledger will report an error if any transaction uses an account name that has not been declared by an account directive. Some notes: * The declaration is case-sensitive; transactions must use the correct account name capitalisation. * The account directive's scope is "whole file and below" (see directives). This means it affects all of the current file, and any files it includes, but not parent or sibling files. The position of account directives within the file does not matter, though it's usual to put them at the top. * Accounts can only be declared in 'journal' files, but will affect included files of all types. * It's currently not possible to declare "all possible subaccounts" with a wildcard; every account posted to must be declared.  File: hledger.info, Node: Account display order, Next: Account types, Prev: Account error checking, Up: account directive 9.18.4 Account display order ---------------------------- The order in which account directives are written influences the order in which accounts appear in reports, hledger-ui, hledger-web etc. By default accounts appear in alphabetical order, but if you add these account directives to the journal file: account assets account liabilities account equity account revenues account expenses those accounts will be displayed in declaration order: $ hledger accounts -1 assets liabilities equity revenues expenses Any undeclared accounts are displayed last, in alphabetical order. Sorting is done at each level of the account tree, within each group of sibling accounts under the same parent. And currently, this directive: account other:zoo would influence the position of 'zoo' among 'other''s subaccounts, but not the position of 'other' among the top-level accounts. This means: * you will sometimes declare parent accounts (eg 'account other' above) that you don't intend to post to, just to customize their display order * sibling accounts stay together (you couldn't display 'x:y' in between 'a:b' and 'a:c').  File: hledger.info, Node: Account types, Prev: Account display order, Up: account directive 9.18.5 Account types -------------------- hledger knows that accounts come in several types: assets, liabilities, expenses and so on. This enables easy reports like balancesheet and incomestatement, and filtering by account type with the 'type:' query. As a convenience, hledger will detect these account types automatically if you are using common english-language top-level account names (described below). But generally we recommend you declare types explicitly, by adding a 'type:' tag to your top-level account directives. Subaccounts will inherit the type of their parent. The tag's value should be one of the five main account types: * 'A' or 'Asset' (things you own) * 'L' or 'Liability' (things you owe) * 'E' or 'Equity' (investment/ownership; balanced counterpart of assets & liabilities) * 'R' or 'Revenue' (what you received money from, AKA income; technically part of Equity) * 'X' or 'Expense' (what you spend money on; technically part of Equity) or, it can be (these are used less often): * 'C' or 'Cash' (a subtype of Asset, indicating liquid assets for the cashflow report) * 'V' or 'Conversion' (a subtype of Equity, for conversions (see Cost reporting).) Here is a typical set of account type declarations: account assets ; type: A account liabilities ; type: L account equity ; type: E account revenues ; type: R account expenses ; type: X account assets:bank ; type: C account assets:cash ; type: C account equity:conversion ; type: V Here are some tips for working with account types. * The rules for inferring types from account names are as follows. These are just a convenience that sometimes help new users get going; if they don't work for you, just ignore them and declare your account types. See also Regular expressions. If account's name contains this (CI) regular expression: | its type is: --------------------------------------------------------------------|------------- ^assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|current)(:|$) | Cash ^assets?(:|$) | Asset ^(debts?|liabilit(y|ies))(:|$) | Liability ^equity:(trad(e|ing)|conversion)s?(:|$) | Conversion ^equity(:|$) | Equity ^(income|revenue)s?(:|$) | Revenue ^expenses?(:|$) | Expense * If you declare any account types, it's a good idea to declare an account for all of the account types, because a mixture of declared and name-inferred types can disrupt certain reports. * Certain uses of account aliases can disrupt account types. See Rewriting accounts > Aliases and account types. * As mentioned above, subaccounts will inherit a type from their parent account. More precisely, an account's type is decided by the first of these that exists: 1. A 'type:' declaration for this account. 2. A 'type:' declaration in the parent accounts above it, preferring the nearest. 3. An account type inferred from this account's name. 4. An account type inferred from a parent account's name, preferring the nearest parent. 5. Otherwise, it will have no type. * For troubleshooting, you can list accounts and their types with: $ hledger accounts --types [ACCTPAT] [-DEPTH] [type:TYPECODES]  File: hledger.info, Node: alias directive, Next: commodity directive, Prev: account directive, Up: Journal 9.19 'alias' directive ====================== You can define account alias rules which rewrite your account names, or parts of them, before generating reports. This can be useful for: * expanding shorthand account names to their full form, allowing easier data entry and a less verbose journal * adapting old journals to your current chart of accounts * experimenting with new account organisations, like a new hierarchy * combining two accounts into one, eg to see their sum or difference on one line * customising reports Account aliases also rewrite account names in account directives. They do not affect account names being entered via hledger add or hledger-web. Account aliases are very powerful. They are generally easy to use correctly, but you can also generate invalid account names with them; more on this below. See also Rewrite account names. * Menu: * Basic aliases:: * Regex aliases:: * Combining aliases:: * Aliases and multiple files:: * end aliases directive:: * Aliases can generate bad account names:: * Aliases and account types::  File: hledger.info, Node: Basic aliases, Next: Regex aliases, Up: alias directive 9.19.1 Basic aliases -------------------- To set an account alias, use the 'alias' directive in your journal file. This affects all subsequent journal entries in the current file or its included files (but note: not sibling or parent files). The spaces around the = are optional: alias OLD = NEW Or, you can use the '--alias 'OLD=NEW'' option on the command line. This affects all entries. It's useful for trying out aliases interactively. OLD and NEW are case sensitive full account names. hledger will replace any occurrence of the old account name with the new one. Subaccounts are also affected. Eg: alias checking = assets:bank:wells fargo:checking ; rewrites "checking" to "assets:bank:wells fargo:checking", or "checking:a" to "assets:bank:wells fargo:checking:a"  File: hledger.info, Node: Regex aliases, Next: Combining aliases, Prev: Basic aliases, Up: alias directive 9.19.2 Regex aliases -------------------- There is also a more powerful variant that uses a regular expression, indicated by wrapping the pattern in forward slashes. (This is the only place where hledger requires forward slashes around a regular expression.) Eg: alias /REGEX/ = REPLACEMENT or: $ hledger --alias '/REGEX/=REPLACEMENT' ... Any part of an account name matched by REGEX will be replaced by REPLACEMENT. REGEX is case-insensitive as usual. If you need to match a forward slash, escape it with a backslash, eg '/\/=:'. If REGEX contains parenthesised match groups, these can be referenced by the usual backslash and number in REPLACEMENT: alias /^(.+):bank:([^:]+):(.*)/ = \1:\2 \3 ; rewrites "assets:bank:wells fargo:checking" to "assets:wells fargo checking" REPLACEMENT continues to the end of line (or on command line, to end of option argument), so it can contain trailing whitespace.  File: hledger.info, Node: Combining aliases, Next: Aliases and multiple files, Prev: Regex aliases, Up: alias directive 9.19.3 Combining aliases ------------------------ You can define as many aliases as you like, using journal directives and/or command line options. Recursive aliases - where an account name is rewritten by one alias, then by another alias, and so on - are allowed. Each alias sees the effect of previously applied aliases. In such cases it can be important to understand which aliases will be applied and in which order. For (each account name in) each journal entry, we apply: 1. 'alias' directives preceding the journal entry, most recently parsed first (ie, reading upward from the journal entry, bottom to top) 2. '--alias' options, in the order they appeared on the command line (left to right). In other words, for (an account name in) a given journal entry: * the nearest alias declaration before/above the entry is applied first * the next alias before/above that will be be applied next, and so on * aliases defined after/below the entry do not affect it. This gives nearby aliases precedence over distant ones, and helps provide semantic stability - aliases will keep working the same way independent of which files are being read and in which order. In case of trouble, adding '--debug=6' to the command line will show which aliases are being applied when.  File: hledger.info, Node: Aliases and multiple files, Next: end aliases directive, Prev: Combining aliases, Up: alias directive 9.19.4 Aliases and multiple files --------------------------------- As explained at Directives and multiple files, 'alias' directives do not affect parent or sibling files. Eg in this command, hledger -f a.aliases -f b.journal account aliases defined in a.aliases will not affect b.journal. Including the aliases doesn't work either: include a.aliases 2023-01-01 ; not affected by a.aliases foo 1 bar This means that account aliases should usually be declared at the start of your top-most file, like this: alias foo=Foo alias bar=Bar 2023-01-01 ; affected by aliases above foo 1 bar include c.journal ; also affected  File: hledger.info, Node: end aliases directive, Next: Aliases can generate bad account names, Prev: Aliases and multiple files, Up: alias directive 9.19.5 'end aliases' directive ------------------------------ You can clear (forget) all currently defined aliases (seen in the journal so far, or defined on the command line) with this directive: end aliases  File: hledger.info, Node: Aliases can generate bad account names, Next: Aliases and account types, Prev: end aliases directive, Up: alias directive 9.19.6 Aliases can generate bad account names --------------------------------------------- Be aware that account aliases can produce malformed account names, which could cause confusing reports or invalid 'print' output. For example, you could erase all account names: 2021-01-01 a:aa 1 b $ hledger print --alias '/.*/=' 2021-01-01 1 The above 'print' output is not a valid journal. Or you could insert an illegal double space, causing 'print' output that would give a different journal when reparsed: 2021-01-01 old 1 other $ hledger print --alias old="new USD" | hledger -f- print 2021-01-01 new USD 1 other  File: hledger.info, Node: Aliases and account types, Prev: Aliases can generate bad account names, Up: alias directive 9.19.7 Aliases and account types -------------------------------- If an account with a type declaration (see Declaring accounts > Account types) is renamed by an alias, normally the account type remains in effect. However, renaming in a way that reshapes the account tree (eg renaming parent accounts but not their children, or vice versa) could prevent child accounts from inheriting the account type of their parents. Secondly, if an account's type is being inferred from its name, renaming it by an alias could prevent or alter that. If you are using account aliases and the 'type:' query is not matching accounts as you expect, try troubleshooting with the accounts command, eg something like: $ hledger accounts --alias assets=bassetts type:a  File: hledger.info, Node: commodity directive, Next: decimal-mark directive, Prev: alias directive, Up: Journal 9.20 'commodity' directive ========================== The 'commodity' directive performs several functions: 1. It declares which commodity symbols may be used in the journal, enabling useful error checking with strict mode or the check command. (See Commodity error checking below.) 2. It declares the precision with which this commodity's amounts should be compared when checking for balanced transactions. 3. It declares how this commodity's amounts should be displayed, eg their symbol placement, digit group mark if any, digit group sizes, decimal mark (period or comma), and the number of decimal places. (See Commodity display style above.) 4. It sets which decimal mark (period or comma) to expect when parsing subsequent amounts in this commodity (if there is no 'decimal-mark' directive in effect. See Decimal marks, digit group marks above. For related dev discussion, see #793.) Declaring commodities solves several common parsing/display problems, so we recommend it. Generally you should put 'commodity' directives at the top of your journal file (because function 4 is position-sensitive). * Menu: * Commodity directive syntax:: * Commodity error checking::  File: hledger.info, Node: Commodity directive syntax, Next: Commodity error checking, Up: commodity directive 9.20.1 Commodity directive syntax --------------------------------- A commodity directive is normally the word 'commodity' followed by a sample amount (and optionally a comment). Only the amount's symbol and format is significant. Eg: commodity $1000.00 commodity 1.000,00 EUR commodity 1 000 000.0000 ; the no-symbol commodity Commodities do not have tags (tags in the comment will be ignored). A commodity directive's sample amount must always include a period or comma decimal mark (this rule helps disambiguate decimal marks and digit group marks). If you don't want to show any decimal digits, write the decimal mark at the end: commodity 1000. AAAA ; show AAAA with no decimals Commodity symbols containing spaces, numbers, or punctuation must be enclosed in double quotes, as usual: commodity 1.0000 "AAAA 2023" Commodity directives normally include a sample amount, but can declare only a symbol (ie, just function 1 above): commodity $ commodity INR commodity "AAAA 2023" commodity "" ; the no-symbol commodity Commodity directives may also be written with an indented 'format' subdirective, as in Ledger. The symbol is repeated and must be the same in both places. Other subdirectives are currently ignored: ; display indian rupees with currency name on the left, ; thousands, lakhs and crores comma-separated, ; period as decimal point, and two decimal places. commodity INR format INR 1,00,00,000.00 an unsupported subdirective ; ignored by hledger  File: hledger.info, Node: Commodity error checking, Prev: Commodity directive syntax, Up: commodity directive 9.20.2 Commodity error checking ------------------------------- In strict mode ('-s'/'--strict') (or when you run 'hledger check commodities'), hledger will report an error if an undeclared commodity symbol is used. (With one exception: zero amounts are always allowed to have no commodity symbol.) It works like account error checking (described above).  File: hledger.info, Node: decimal-mark directive, Next: include directive, Prev: commodity directive, Up: Journal 9.21 'decimal-mark' directive ============================= You can use a 'decimal-mark' directive - usually one per file, at the top of the file - to declare which character represents a decimal mark when parsing amounts in this file. It can look like decimal-mark . or decimal-mark , This prevents any ambiguity when parsing numbers in the file, so we recommend it, especially if the file contains digit group marks (eg thousands separators).  File: hledger.info, Node: include directive, Next: P directive, Prev: decimal-mark directive, Up: Journal 9.22 'include' directive ======================== You can pull in the content of additional files by writing an include directive, like this: include FILEPATH Only journal files can include, and only journal, timeclock or timedot files can be included (not CSV files, currently). If the file path does not begin with a slash, it is relative to the current file's folder. A tilde means home directory, eg: 'include ~/main.journal'. The path may contain glob patterns to match multiple files, eg: 'include *.journal'. There is limited support for recursive wildcards: '**/' (the slash is required) matches 0 or more subdirectories. It's not super convenient since you have to avoid include cycles and including directories, but this can be done, eg: 'include */**/*.journal'. The path may also be prefixed to force a specific file format, overriding the file extension (as described in Data formats): 'include timedot:~/notes/2023*.md'.  File: hledger.info, Node: P directive, Next: payee directive, Prev: include directive, Up: Journal 9.23 'P' directive ================== The 'P' directive declares a market price, which is a conversion rate between two commodities on a certain date. This allows value reports to convert amounts of one commodity to their value in another, on or after that date. These prices are often obtained from a stock exchange, cryptocurrency exchange, the or foreign exchange market. The format is: P DATE COMMODITY1SYMBOL COMMODITY2AMOUNT DATE is a simple date, COMMODITY1SYMBOL is the symbol of the commodity being priced, and COMMODITY2AMOUNT is the amount (symbol and quantity) of commodity 2 that one unit of commodity 1 is worth on this date. Examples: # one euro was worth $1.35 from 2009-01-01 onward: P 2009-01-01 € $1.35 # and $1.40 from 2010-01-01 onward: P 2010-01-01 € $1.40 The '-V', '-X' and '--value' flags use these market prices to show amount values in another commodity. See Value reporting.  File: hledger.info, Node: payee directive, Next: tag directive, Prev: P directive, Up: Journal 9.24 'payee' directive ====================== 'payee PAYEE NAME' This directive can be used to declare a limited set of payees which may appear in transaction descriptions. The "payees" check will report an error if any transaction refers to a payee that has not been declared. Eg: payee Whole Foods ; a comment Payees do not have tags (tags in the comment will be ignored). To declare the empty payee name, use '""'. payee "" Ledger-style indented subdirectives, if any, are currently ignored.  File: hledger.info, Node: tag directive, Next: Periodic transactions, Prev: payee directive, Up: Journal 9.25 'tag' directive ==================== 'tag TAGNAME' This directive can be used to declare a limited set of tag names allowed in tags. TAGNAME should be a valid tag name (no spaces). Eg: tag item-id Any indented subdirectives are currently ignored. The "tags" check will report an error if any undeclared tag name is used. It is quite easy to accidentally create a tag through normal use of colons in comments(#comments]; if you want to prevent this, you can declare and check your tags .  File: hledger.info, Node: Periodic transactions, Next: Auto postings, Prev: tag directive, Up: Journal 9.26 Periodic transactions ========================== The '~' directive declares a "periodic rule" which generates temporary extra transactions, usually recurring at some interval, when hledger is run with the '--forecast' flag. These "forecast transactions" are useful for forecasting future activity. They exist only for the duration of the report, and only when '--forecast' is used; they are not saved in the journal file by hledger. Periodic rules also have a second use: with the '--budget' flag they set budget goals for budgeting. Periodic rules can be a little tricky, so before you use them, read this whole section, or at least the following tips: 1. Two spaces accidentally added or omitted will cause you trouble - read about this below. 2. For troubleshooting, show the generated transactions with 'hledger print --forecast tag:generated' or 'hledger register --forecast tag:generated'. 3. Forecasted transactions will begin only after the last non-forecasted transaction's date. 4. Forecasted transactions will end 6 months from today, by default. See below for the exact start/end rules. 5. period expressions can be tricky. Their documentation needs improvement, but is worth studying. 6. Some period expressions with a repeating interval must begin on a natural boundary of that interval. Eg in 'weekly from DATE', DATE must be a monday. '~ weekly from 2019/10/1' (a tuesday) will give an error. 7. Other period expressions with an interval are automatically expanded to cover a whole number of that interval. (This is done to improve reports, but it also affects periodic transactions. Yes, it's a bit inconsistent with the above.) Eg: '~ every 10th day of month from 2023/01', which is equivalent to '~ every 10th day of month from 2023/01/01', will be adjusted to start on 2019/12/10. * Menu: * Periodic rule syntax:: * Periodic rules and relative dates:: * Two spaces between period expression and description!::  File: hledger.info, Node: Periodic rule syntax, Next: Periodic rules and relative dates, Up: Periodic transactions 9.26.1 Periodic rule syntax --------------------------- A periodic transaction rule looks like a normal journal entry, with the date replaced by a tilde ('~') followed by a period expression (mnemonic: '~' looks like a recurring sine wave.): # every first of month ~ monthly expenses:rent $2000 assets:bank:checking # every 15th of month in 2023's first quarter: ~ monthly from 2023-04-15 to 2023-06-16 expenses:utilities $400 assets:bank:checking The period expression is the same syntax used for specifying multi-period reports, just interpreted differently; there, it specifies report periods; here it specifies recurrence dates (the periods' start dates).  File: hledger.info, Node: Periodic rules and relative dates, Next: Two spaces between period expression and description!, Prev: Periodic rule syntax, Up: Periodic transactions 9.26.2 Periodic rules and relative dates ---------------------------------------- Partial or relative dates (like '12/31', '25', 'tomorrow', 'last week', 'next quarter') are usually not recommended in periodic rules, since the results will change as time passes. If used, they will be interpreted relative to, in order of preference: 1. the first day of the default year specified by a recent 'Y' directive 2. or the date specified with '--today' 3. or the date on which you are running the report. They will not be affected at all by report period or forecast period dates.  File: hledger.info, Node: Two spaces between period expression and description!, Prev: Periodic rules and relative dates, Up: Periodic transactions 9.26.3 Two spaces between period expression and description! ------------------------------------------------------------ If the period expression is followed by a transaction description, these must be separated by *two or more spaces*. This helps hledger know where the period expression ends, so that descriptions can not accidentally alter their meaning, as in this example: ; 2 or more spaces needed here, so the period is not understood as "every 2 months in 2023" ; || ; vv ~ every 2 months in 2023, we will review assets:bank:checking $1500 income:acme inc So, * Do write two spaces between your period expression and your transaction description, if any. * Don't accidentally write two spaces in the middle of your period expression.  File: hledger.info, Node: Auto postings, Next: Other syntax, Prev: Periodic transactions, Up: Journal 9.27 Auto postings ================== The '=' directive declares an "auto posting rule" which generates temporary extra postings on existing transactions, when hledger is run with the '--auto' flag. (Remember, postings are the account name & amount lines.) The rule contains a query and one or more posting templates. Wherever the query matches an existing posting, the new posting(s) will be generated and added below that one. Optionally the generated amount(s) can depend on the matched posting's amount. These auto postings can be useful for, eg, adding tax postings with a standard percentage. They exist only for the duration of the report, and only when '--auto' is used; they are not saved in the journal file by hledger. Note that depending fully on generated data such as this has some drawbacks - it's less portable, less future-proof, less auditable by others, and less robust (eg your balance assertions will depend on whether you use or don't use '--auto'). An alternative is to use auto postings in "one time" fashion - use them to help build a complex journal entry, view it with 'hledger print --auto', and then copy that output into the journal file to make it permanent. Here's the journal file syntax. An auto posting rule looks a bit like a transaction: = QUERY ACCOUNT AMOUNT ... ACCOUNT [AMOUNT] except the first line is an equals sign (mnemonic: '=' suggests matching), followed by a query (which matches existing postings), and each "posting" line describes a posting to be generated, and the posting amounts can be: * a normal amount with a commodity symbol, eg '$2'. This will be used as-is. * a number, eg '2'. The commodity symbol (if any) from the matched posting will be added to this. * a numeric multiplier, eg '*2' (a star followed by a number N). The matched posting's amount (and total price, if any) will be multiplied by N. * a multiplier with a commodity symbol, eg '*$2' (a star, number N, and symbol S). The matched posting's amount will be multiplied by N, and its commodity symbol will be replaced with S. Any query term containing spaces must be enclosed in single or double quotes, as on the command line. Eg, note the quotes around the second query term below: = expenses:groceries 'expenses:dining out' (budget:funds:dining out) *-1 Some examples: ; every time I buy food, schedule a dollar donation = expenses:food (liabilities:charity) $-1 ; when I buy a gift, also deduct that amount from a budget envelope subaccount = expenses:gifts assets:checking:gifts *-1 assets:checking *1 2017/12/1 expenses:food $10 assets:checking 2017/12/14 expenses:gifts $20 assets:checking $ hledger print --auto 2017-12-01 expenses:food $10 assets:checking (liabilities:charity) $-1 2017-12-14 expenses:gifts $20 assets:checking assets:checking:gifts -$20 assets:checking $20 * Menu: * Auto postings and multiple files::  File: hledger.info, Node: Auto postings and multiple files, Up: Auto postings 9.27.1 Auto postings and multiple files --------------------------------------- An auto posting rule can affect any transaction in the current file, or in any parent file or child file. Note, currently it will not affect sibling files (when multiple '-f'/'--file' are used - see #1212). * Menu: * Auto postings and dates:: * Auto postings and transaction balancing / inferred amounts / balance assertions:: * Auto posting tags:: * Auto postings on forecast transactions only::  File: hledger.info, Node: Auto postings and dates, Next: Auto postings and transaction balancing / inferred amounts / balance assertions, Up: Auto postings and multiple files 9.27.1.1 Auto postings and dates ................................ A posting date (or secondary date) in the matched posting, or (taking precedence) a posting date in the auto posting rule itself, will also be used in the generated posting.  File: hledger.info, Node: Auto postings and transaction balancing / inferred amounts / balance assertions, Next: Auto posting tags, Prev: Auto postings and dates, Up: Auto postings and multiple files 9.27.1.2 Auto postings and transaction balancing / inferred ........................................................... amounts / balance assertions Currently, auto postings are added: * after missing amounts are inferred, and transactions are checked for balancedness, * but before balance assertions are checked. Note this means that journal entries must be balanced both before and after auto postings are added. This changed in hledger 1.12+; see #893 for background. This also means that you cannot have more than one auto-posting with a missing amount applied to a given transaction, as it will be unable to infer amounts.  File: hledger.info, Node: Auto posting tags, Next: Auto postings on forecast transactions only, Prev: Auto postings and transaction balancing / inferred amounts / balance assertions, Up: Auto postings and multiple files 9.27.1.3 Auto posting tags .......................... Automated postings will have some extra tags: * 'generated-posting:= QUERY' - shows this was generated by an auto posting rule, and the query * '_generated-posting:= QUERY' - a hidden tag, which does not appear in hledger's output. This can be used to match postings generated "just now", rather than generated in the past and saved to the journal. Also, any transaction that has been changed by auto posting rules will have these tags added: * 'modified:' - this transaction was modified * '_modified:' - a hidden tag not appearing in the comment; this transaction was modified "just now".  File: hledger.info, Node: Auto postings on forecast transactions only, Prev: Auto posting tags, Up: Auto postings and multiple files 9.27.1.4 Auto postings on forecast transactions only .................................................... Tip: you can can make auto postings that will apply to forecast transactions but not recorded transactions, by adding 'tag:_generated-transaction' to their QUERY. This can be useful when generating new journal entries to be saved in the journal.  File: hledger.info, Node: Other syntax, Prev: Auto postings, Up: Journal 9.28 Other syntax ================= hledger journal format supports quite a few other features, mainly to make interoperating with or converting from Ledger easier. Note some of the features below are powerful and can be useful in special cases, but in general, features in this section are considered less important or even not recommended for most users. Downsides are mentioned to help you decide if you want to use them. * Menu: * Balance assignments:: * Bracketed posting dates:: * D directive:: * apply account directive:: * Y directive:: * Secondary dates:: * Star comments:: * Valuation expressions:: * Virtual postings:: * Other Ledger directives::  File: hledger.info, Node: Balance assignments, Next: Bracketed posting dates, Up: Other syntax 9.28.1 Balance assignments -------------------------- Ledger-style balance assignments are also supported. These are like balance assertions, but with no posting amount on the left side of the equals sign; instead it is calculated automatically so as to satisfy the assertion. This can be a convenience during data entry, eg when setting opening balances: ; starting a new journal, set asset account balances 2016/1/1 opening balances assets:checking = $409.32 assets:savings = $735.24 assets:cash = $42 equity:opening balances or when adjusting a balance to reality: ; no cash left; update balance, record any untracked spending as a generic expense 2016/1/15 assets:cash = $0 expenses:misc The calculated amount depends on the account's balance in the commodity at that point (which depends on the previously-dated postings of the commodity to that account since the last balance assertion or assignment). Downsides: using balance assignments makes your journal less explicit; to know the exact amount posted, you have to run hledger or do the calculations yourself, instead of just reading it. Also balance assignments' forcing of balances can hide errors. These things make your financial data less portable, less future-proof, and less trustworthy in an audit. * Menu: * Balance assignments and prices:: * Balance assignments and multiple files::  File: hledger.info, Node: Balance assignments and prices, Next: Balance assignments and multiple files, Up: Balance assignments 9.28.1.1 Balance assignments and prices ....................................... A cost in a balance assignment will cause the calculated amount to have that price attached: 2019/1/1 (a) = $1 @ €2 $ hledger print --explicit 2019-01-01 (a) $1 @ €2 = $1 @ €2  File: hledger.info, Node: Balance assignments and multiple files, Prev: Balance assignments and prices, Up: Balance assignments 9.28.1.2 Balance assignments and multiple files ............................................... Balance assignments handle multiple files like balance assertions. They see balance from other files previously included from the current file, but not from previous sibling or parent files.  File: hledger.info, Node: Bracketed posting dates, Next: D directive, Prev: Balance assignments, Up: Other syntax 9.28.2 Bracketed posting dates ------------------------------ For setting posting dates and secondary posting dates, Ledger's bracketed date syntax is also supported: '[DATE]', '[DATE=DATE2]' or '[=DATE2]' in posting comments. hledger will attempt to parse any square-bracketed sequence of the '0123456789/-.=' characters in this way. With this syntax, DATE infers its year from the transaction and DATE2 infers its year from DATE. Downsides: another syntax to learn, redundant with hledger's 'date:'/'date2:' tags, and confusingly similar to Ledger's lot date syntax.  File: hledger.info, Node: D directive, Next: apply account directive, Prev: Bracketed posting dates, Up: Other syntax 9.28.3 'D' directive -------------------- 'D AMOUNT' This directive sets a default commodity, to be used for any subsequent commodityless amounts (ie, plain numbers) seen while parsing the journal. This effect lasts until the next 'D' directive, or the end of the journal. For compatibility/historical reasons, 'D' also acts like a 'commodity' directive (setting the commodity's decimal mark for parsing and display style for output). So its argument is not just a commodity symbol, but a full amount demonstrating the style. The amount must include a decimal mark (either period or comma). Eg: ; commodity-less amounts should be treated as dollars ; (and displayed with the dollar sign on the left, thousands separators and two decimal places) D $1,000.00 1/1 a 5 ; <- commodity-less amount, parsed as $5 and displayed as $5.00 b Interactions with other directives: For setting a commodity's display style, a 'commodity' directive has highest priority, then a 'D' directive. For detecting a commodity's decimal mark during parsing, 'decimal-mark' has highest priority, then 'commodity', then 'D'. For checking commodity symbols with the check command, a 'commodity' directive is required ('hledger check commodities' ignores 'D' directives). Downsides: omitting commodity symbols makes your financial data less explicit, less portable, and less trustworthy in an audit. It is usually an unsustainable shortcut; sooner or later you will want to track multiple commodities. D is overloaded with functions redundant with 'commodity' and 'decimal-mark'. And it works differently from Ledger's 'D'.  File: hledger.info, Node: apply account directive, Next: Y directive, Prev: D directive, Up: Other syntax 9.28.4 'apply account' directive -------------------------------- This directive sets a default parent account, which will be prepended to all accounts in following entries, until an 'end apply account' directive or end of current file. Eg: apply account home 2010/1/1 food $10 cash end apply account is equivalent to: 2010/01/01 home:food $10 home:cash $-10 'account' directives are also affected, and so is any 'include'd content. Account names entered via hledger add or hledger-web are not affected. Account aliases, if any, are applied after the parent account is prepended. Downsides: this can make your financial data less explicit, less portable, and less trustworthy in an audit.  File: hledger.info, Node: Y directive, Next: Secondary dates, Prev: apply account directive, Up: Other syntax 9.28.5 'Y' directive -------------------- 'Y YEAR' or (deprecated backward-compatible forms): 'year YEAR' 'apply year YEAR' The space is optional. This sets a default year to be used for subsequent dates which don't specify a year. Eg: Y2009 ; set default year to 2009 12/15 ; equivalent to 2009/12/15 expenses 1 assets year 2010 ; change default year to 2010 2009/1/30 ; specifies the year, not affected expenses 1 assets 1/31 ; equivalent to 2010/1/31 expenses 1 assets Downsides: omitting the year (from primary transaction dates, at least) makes your financial data less explicit, less portable, and less trustworthy in an audit. Such dates can get separated from their corresponding Y directive, eg when evaluating a region of the journal in your editor. A missing Y directive makes reports dependent on today's date.  File: hledger.info, Node: Secondary dates, Next: Star comments, Prev: Y directive, Up: Other syntax 9.28.6 Secondary dates ---------------------- A secondary date is written after the primary date, following an equals sign. If the year is omitted, the primary date's year is assumed. When running reports, the primary (left) date is used by default, but with the '--date2' flag (or '--aux-date' or '--effective'), the secondary (right) date will be used instead. The meaning of secondary dates is up to you, but it's best to follow a consistent rule. Eg "primary = the bank's clearing date, secondary = date the transaction was initiated, if different". Downsides: makes your financial data more complicated, less portable, and less trustworthy in an audit. Keeping the meaning of the two dates consistent requires discipline, and you have to remember which reporting mode is appropriate for a given report. Posting dates are simpler and better.  File: hledger.info, Node: Star comments, Next: Valuation expressions, Prev: Secondary dates, Up: Other syntax 9.28.7 Star comments -------------------- Lines beginning with '*' (star/asterisk) are also comment lines. This feature allows Emacs users to insert org headings in their journal, allowing them to fold/unfold/navigate it like an outline when viewed with org mode. Downsides: another, unconventional comment syntax to learn. Decreases your journal's portability. And switching to Emacs org mode just for folding/unfolding meant losing the benefits of ledger mode; nowadays you can add outshine mode to ledger mode to get folding without losing ledger mode's features.  File: hledger.info, Node: Valuation expressions, Next: Virtual postings, Prev: Star comments, Up: Other syntax 9.28.8 Valuation expressions ---------------------------- Ledger allows a valuation function or value to be written in double parentheses after an amount. hledger ignores these.  File: hledger.info, Node: Virtual postings, Next: Other Ledger directives, Prev: Valuation expressions, Up: Other syntax 9.28.9 Virtual postings ----------------------- A posting with parentheses around the account name ('(some:account)') is called a _unbalanced virtual posting_. Such postings do not participate in transaction balancing. (And if you write them without an amount, a zero amount is always inferred.) These can occasionally be convenient for special circumstances, but they violate double entry bookkeeping and make your data less portable across applications, so many people avoid using them at all. A posting with brackets around the account name ('[some:account]') is called a _balanced virtual posting_. The balanced virtual postings in a transaction must add up to zero, just like ordinary postings, but separately from them. These are not part of double entry bookkeeping either, but they are at least balanced. An example: 2022-01-01 buy food with cash, update budget envelope subaccounts, & something else assets:cash $-10 ; <- these balance each other expenses:food $7 ; <- expenses:food $3 ; <- [assets:checking:budget:food] $-10 ; <- and these balance each other [assets:checking:available] $10 ; <- (something:else) $5 ; <- this is not required to balance Ordinary postings, whose account names are neither parenthesised nor bracketed, are called _real postings_. You can exclude virtual postings from reports with the '-R/--real' flag or a 'real:1' query.  File: hledger.info, Node: Other Ledger directives, Prev: Virtual postings, Up: Other syntax 9.28.10 Other Ledger directives ------------------------------- These other Ledger directives are currently accepted but ignored. This allows hledger to read more Ledger files, but be aware that hledger's reports may differ from Ledger's if you use these. apply fixed COMM AMT apply tag TAG assert EXPR bucket / A ACCT capture ACCT REGEX check EXPR define VAR=EXPR end apply fixed end apply tag end apply year end tag eval / expr EXPR python PYTHONCODE tag NAME value EXPR --command-line-flags See also https://hledger.org/ledger.html for a detailed hledger/Ledger syntax comparison.  File: hledger.info, Node: CSV, Next: Timeclock, Prev: Journal, Up: Top 10 CSV ****** hledger can read CSV files (Character Separated Value - usually comma, semicolon, or tab) containing dated records, automatically converting each record into a transaction. (To learn about _writing_ CSV, see CSV output.) For best error messages when reading CSV/TSV/SSV files, make sure they have a corresponding '.csv', '.tsv' or '.ssv' file extension or use a hledger file prefix (see File Extension below). Each CSV file must be described by a corresponding _rules file_. This contains rules describing the CSV data (header line, fields layout, date format etc.), how to construct hledger transactions from it, and how to categorise transactions based on description or other attributes. By default hledger looks for a rules file named like the CSV file with an extra '.rules' extension, in the same directory. Eg when asked to read 'foo/FILE.csv', hledger looks for 'foo/FILE.csv.rules'. You can specify a different rules file with the '--rules-file' option. If no rules file is found, hledger will create a sample rules file, which you'll need to adjust. At minimum, the rules file must identify the date and amount fields, and often it also specifies the date format and how many header lines there are. Here's a simple CSV file and a rules file for it: Date, Description, Id, Amount 12/11/2019, Foo, 123, 10.23 # basic.csv.rules skip 1 fields date, description, , amount date-format %d/%m/%Y $ hledger print -f basic.csv 2019-11-12 Foo expenses:unknown 10.23 income:unknown -10.23 There's an introductory Importing CSV data tutorial on hledger.org, and more CSV rules examples below, and a larger collection at https://github.com/simonmichael/hledger/tree/master/examples/csv. * Menu: * CSV rules cheatsheet:: * source:: * separator:: * skip:: * date-format:: * timezone:: * newest-first:: * intra-day-reversed:: * decimal-mark:: * fields list:: * Field assignment:: * Field names:: * if block:: * Matchers:: * if table:: * balance-type:: * include:: * Working with CSV:: * CSV rules examples::  File: hledger.info, Node: CSV rules cheatsheet, Next: source, Up: CSV 10.1 CSV rules cheatsheet ========================= The following kinds of rule can appear in the rules file, in any order. (Blank lines and lines beginning with '#' or ';' or '*' are ignored.) *'source'* optionally declare which file to read data from *'separator'* declare the field separator, instead of relying on file extension *'skip'* skip one or more header lines at start of file *'date-format'* declare how to parse CSV dates/date-times *'timezone'* declare the time zone of ambiguous CSV date-times *'newest-first'* improve txn order when: there are multiple records, newest first, all with the same date *'intra-day-reversed'* improve txn order when: same-day txns are in opposite order to the overall file *'decimal-mark'* declare the decimal mark used in CSV amounts, when ambiguous *'fields' list* name CSV fields for easy reference, and optionally assign their values to hledger fields *Field assignment* assign a CSV value or interpolated text value to a hledger field *'if' block* conditionally assign values to hledger fields, or 'skip' a record or 'end' (skip rest of file) *'if' table* conditionally assign values to hledger fields, using compact syntax *'balance-type'* select which type of balance assertions/assignments to generate *'include'* inline another CSV rules file Working with CSV tips can be found below, including How CSV rules are evaluated.  File: hledger.info, Node: source, Next: separator, Prev: CSV rules cheatsheet, Up: CSV 10.2 'source' ============= If you tell hledger to read a csv file with '-f foo.csv', it will look for rules in 'foo.csv.rules'. Or, you can tell it to read the rules file, with '-f foo.csv.rules', and it will look for data in 'foo.csv' (since 1.30). These are mostly equivalent, but the second method provides some extra features. For one, the data file can be missing, without causing an error; it is just considered empty. And, you can specify a different data file by adding a "source" rule: source ./Checking1.csv If you specify just a file name with no path, hledger will look for it in your system's downloads directory ('~/Downloads', currently): source Checking1.csv And if you specify a glob pattern, hledger will read the most recent of the matched files (useful with repeated downloads): source Checking1*.csv See also "Working with CSV > Reading files specified by rule".  File: hledger.info, Node: separator, Next: skip, Prev: source, Up: CSV 10.3 'separator' ================ You can use the 'separator' rule to read other kinds of character-separated data. The argument is any single separator character, or the words 'tab' or 'space' (case insensitive). Eg, for comma-separated values (CSV): separator , or for semicolon-separated values (SSV): separator ; or for tab-separated values (TSV): separator TAB If the input file has a '.csv', '.ssv' or '.tsv' file extension (or a 'csv:', 'ssv:', 'tsv:' prefix), the appropriate separator will be inferred automatically, and you won't need this rule.  File: hledger.info, Node: skip, Next: date-format, Prev: separator, Up: CSV 10.4 'skip' =========== skip N The word 'skip' followed by a number (or no number, meaning 1) tells hledger to ignore this many non-empty lines at the start of the input data. You'll need this whenever your CSV data contains header lines. Note, empty and blank lines are skipped automatically, so you don't need to count those. 'skip' has a second meaning: it can be used inside if blocks (described below), to skip one or more records whenever the condition is true. Records skipped in this way are ignored, except they are still required to be valid CSV.  File: hledger.info, Node: date-format, Next: timezone, Prev: skip, Up: CSV 10.5 'date-format' ================== date-format DATEFMT This is a helper for the 'date' (and 'date2') fields. If your CSV dates are not formatted like 'YYYY-MM-DD', 'YYYY/MM/DD' or 'YYYY.MM.DD', you'll need to add a date-format rule describing them with a strptime-style date parsing pattern - see https://hackage.haskell.org/package/time/docs/Data-Time-Format.html#v:formatTime. The pattern must parse the CSV date value completely. Some examples: # MM/DD/YY date-format %m/%d/%y # D/M/YYYY # The - makes leading zeros optional. date-format %-d/%-m/%Y # YYYY-Mmm-DD date-format %Y-%h-%d # M/D/YYYY HH:MM AM some other junk # Note the time and junk must be fully parsed, though only the date is used. date-format %-m/%-d/%Y %l:%M %p some other junk  File: hledger.info, Node: timezone, Next: newest-first, Prev: date-format, Up: CSV 10.6 'timezone' =============== timezone TIMEZONE When CSV contains date-times that are implicitly in some time zone other than yours, but containing no explicit time zone information, you can use this rule to declare the CSV's native time zone, which helps prevent off-by-one dates. When the CSV date-times do contain time zone information, you don't need this rule; instead, use '%Z' in 'date-format' (or '%z', '%EZ', '%Ez'; see the formatTime link above). In either of these cases, hledger will do a time-zone-aware conversion, localising the CSV date-times to your current system time zone. If you prefer to localise to some other time zone, eg for reproducibility, you can (on unix at least) set the output timezone with the TZ environment variable, eg: $ TZ=-1000 hledger print -f foo.csv # or TZ=-1000 hledger import foo.csv 'timezone' currently does not understand timezone names, except "UTC", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", "PST", or "PDT". For others, use numeric format: +HHMM or -HHMM.  File: hledger.info, Node: newest-first, Next: intra-day-reversed, Prev: timezone, Up: CSV 10.7 'newest-first' =================== hledger tries to ensure that the generated transactions will be ordered chronologically, including same-day transactions. Usually it can auto-detect how the CSV records are ordered. But if it encounters CSV where all records are on the same date, it assumes that the records are oldest first. If in fact the CSV's records are normally newest first, like: 2022-10-01, txn 3... 2022-10-01, txn 2... 2022-10-01, txn 1... you can add the 'newest-first' rule to help hledger generate the transactions in correct order. # same-day CSV records are newest first newest-first  File: hledger.info, Node: intra-day-reversed, Next: decimal-mark, Prev: newest-first, Up: CSV 10.8 'intra-day-reversed' ========================= If CSV records within a single day are ordered opposite to the overall record order, you can add the 'intra-day-reversed' rule to improve the order of journal entries. Eg, here the overall record order is newest first, but same-day records are oldest first: 2022-10-02, txn 3... 2022-10-02, txn 4... 2022-10-01, txn 1... 2022-10-01, txn 2... # transactions within each day are reversed with respect to the overall date order intra-day-reversed  File: hledger.info, Node: decimal-mark, Next: fields list, Prev: intra-day-reversed, Up: CSV 10.9 'decimal-mark' =================== decimal-mark . or: decimal-mark , hledger automatically accepts either period or comma as a decimal mark when parsing numbers (cf Amounts). However if any numbers in the CSV contain digit group marks, such as thousand-separating commas, you should declare the decimal mark explicitly with this rule, to avoid misparsed numbers.  File: hledger.info, Node: fields list, Next: Field assignment, Prev: decimal-mark, Up: CSV 10.10 'fields' list =================== fields FIELDNAME1, FIELDNAME2, ... A fields list (the word 'fields' followed by comma-separated field names) is optional, but convenient. It does two things: 1. It names the CSV field in each column. This can be convenient if you are referencing them in other rules, so you can say '%SomeField' instead of remembering '%13'. 2. Whenever you use one of the special hledger field names (described below), it assigns the CSV value in this position to that hledger field. This is the quickest way to populate hledger's fields and build a transaction. Here's an example that says "use the 1st, 2nd and 4th fields as the transaction's date, description and amount; name the last two fields for later reference; and ignore the others": fields date, description, , amount, , , somefield, anotherfield In a fields list, the separator is always comma; it is unrelated to the CSV file's separator. Also: * There must be least two items in the list (at least one comma). * Field names may not contain spaces. Spaces before/after field names are optional. * Field names may contain '_' (underscore) or '-' (hyphen). * Fields you don't care about can be given a dummy name or an empty name. If the CSV contains column headings, it's convenient to use these for your field names, suitably modified (eg lower-cased with spaces replaced by underscores). Sometimes you may want to alter a CSV field name to avoid assigning to a hledger field with the same name. Eg you could call the CSV's "balance" field 'balance_' to avoid directly setting hledger's 'balance' field (and generating a balance assertion).  File: hledger.info, Node: Field assignment, Next: Field names, Prev: fields list, Up: CSV 10.11 Field assignment ====================== HLEDGERFIELD FIELDVALUE Field assignments are the more flexible way to assign CSV values to hledger fields. They can be used instead of or in addition to a fields list (see above). To assign a value to a hledger field, write the field name (any of the standard hledger field/pseudo-field names, defined below), a space, followed by a text value on the same line. This text value may interpolate CSV fields, referenced either by their 1-based position in the CSV record ('%N') or by the name they were given in the fields list ('%CSVFIELD'), and regular expression match groups ('\N'). Some examples: # set the amount to the 4th CSV field, with " USD" appended amount %4 USD # combine three fields to make a comment, containing note: and date: tags comment note: %somefield - %anotherfield, date: %1 Tips: * Interpolation strips outer whitespace (so a CSV value like '" 1 "' becomes '1' when interpolated) (#1051). * Interpolations always refer to a CSV field - you can't interpolate a hledger field. (See Referencing other fields below).  File: hledger.info, Node: Field names, Next: if block, Prev: Field assignment, Up: CSV 10.12 Field names ================= Note the two kinds of field names mentioned here, and used only in hledger CSV rules files: 1. *CSV field names* ('CSVFIELD' in these docs): you can optionally name the CSV columns for easy reference (since hledger doesn't yet automatically recognise column headings in a CSV file), by writing arbitrary names in a 'fields' list, eg: fields When, What, Some_Id, Net, Total, Foo, Bar 2. Special *hledger field names* ('HLEDGERFIELD' in these docs): you must set at least some of these to generate the hledger transaction from a CSV record, by writing them as the left hand side of a field assignment, eg: date %When code %Some_Id description %What comment %Foo %Bar amount1 $ %Total or directly in a 'fields' list: fields date, description, code, , amount1, Foo, Bar currency $ comment %Foo %Bar Here are all the special hledger field names available, and what happens when you assign values to them: * Menu: * date field:: * date2 field:: * status field:: * code field:: * description field:: * comment field:: * account field:: * amount field:: * currency field:: * balance field::  File: hledger.info, Node: date field, Next: date2 field, Up: Field names 10.12.1 date field ------------------ Assigning to 'date' sets the transaction date.  File: hledger.info, Node: date2 field, Next: status field, Prev: date field, Up: Field names 10.12.2 date2 field ------------------- 'date2' sets the transaction's secondary date, if any.  File: hledger.info, Node: status field, Next: code field, Prev: date2 field, Up: Field names 10.12.3 status field -------------------- 'status' sets the transaction's status, if any.  File: hledger.info, Node: code field, Next: description field, Prev: status field, Up: Field names 10.12.4 code field ------------------ 'code' sets the transaction's code, if any.  File: hledger.info, Node: description field, Next: comment field, Prev: code field, Up: Field names 10.12.5 description field ------------------------- 'description' sets the transaction's description, if any.  File: hledger.info, Node: comment field, Next: account field, Prev: description field, Up: Field names 10.12.6 comment field --------------------- 'comment' sets the transaction's comment, if any. 'commentN', where N is a number, sets the Nth posting's comment. You can assign multi-line comments by writing literal '\n' in the code. A comment starting with '\n' will begin on a new line. Comments can contain tags, as usual.  File: hledger.info, Node: account field, Next: amount field, Prev: comment field, Up: Field names 10.12.7 account field --------------------- Assigning to 'accountN', where N is 1 to 99, sets the account name of the Nth posting, and causes that posting to be generated. Most often there are two postings, so you'll want to set 'account1' and 'account2'. Typically 'account1' is associated with the CSV file, and is set once with a top-level assignment, while 'account2' is set based on each transaction's description, in conditional rules. If a posting's account name is left unset but its amount is set (see below), a default account name will be chosen (like "expenses:unknown" or "income:unknown").  File: hledger.info, Node: amount field, Next: currency field, Prev: account field, Up: Field names 10.12.8 amount field -------------------- There are several ways to set posting amounts from CSV, useful in different situations. 1. *'amount'* is the oldest and simplest. Assigning to this sets the amount of the first and second postings. In the second posting, the amount will be negated; also, if it has a cost attached, it will be converted to cost. 2. *'amount-in'* and *'amount-out'* work exactly like the above, but should be used when the CSV has two amount fields (such as "Debit" and "Credit", or "Inflow" and "Outflow"). Whichever field has a non-zero value will be used as the amount of the first and second postings. Here are some tips to avoid confusion: * It's not "amount-in for posting 1 and amount-out for posting 2", it is "extract a single amount from the amount-in or amount-out field, and use that for posting 1 and (negated) for posting 2". * Don't use both 'amount' and 'amount-in'/'amount-out' in the same rules file; choose based on whether the amount is in a single CSV field or spread across two fields. * In each record, at most one of the two CSV fields should contain a non-zero amount; the other field must contain a zero or nothing. * hledger assumes both CSV fields contain unsigned numbers, and it automatically negates the amount-out values. * If the data doesn't fit these requirements, you'll probably need an if rule (see below). 3. *'amountN'* (where N is a number from 1 to 99) sets the amount of only a single posting: the Nth posting in the transaction. You'll usually need at least two such assignments to make a balanced transaction. You can also generate more than two postings, to represent more complex transactions. The posting numbers don't have to be consecutive; with if rules, higher posting numbers can be useful to ensure a certain order of postings. 4. *'amountN-in'* and *'amountN-out'* work exactly like the above, but should be used when the CSV has two amount fields. This is analogous to 'amount-in' and 'amount-out', and those tips also apply here. 5. Remember that a 'fields' list can also do assignments. So in a fields list if you name a CSV field "amount", that counts as assigning to 'amount'. (If you don't want that, call it something else in the fields list, like "amount_".) 6. The above don't handle every situation; if you need more flexibility, use an 'if' rule to set amounts conditionally. See "Working with CSV > Setting amounts" below for more on this and on amount-setting generally.  File: hledger.info, Node: currency field, Next: balance field, Prev: amount field, Up: Field names 10.12.9 currency field ---------------------- 'currency' sets a currency symbol, to be prepended to all postings' amounts. You can use this if the CSV amounts do not have a currency symbol, eg if it is in a separate column. 'currencyN' prepends a currency symbol to just the Nth posting's amount.  File: hledger.info, Node: balance field, Prev: currency field, Up: Field names 10.12.10 balance field ---------------------- 'balanceN' sets a balance assertion amount (or if the posting amount is left empty, a balance assignment) on posting N. 'balance' is a compatibility spelling for hledger <1.17; it is equivalent to 'balance1'. You can adjust the type of assertion/assignment with the 'balance-type' rule (see below). See Tips below for more about setting amounts and currency.  File: hledger.info, Node: if block, Next: Matchers, Prev: Field names, Up: CSV 10.13 'if' block ================ Rules can be applied conditionally, depending on patterns in the CSV data. This allows flexibility; in particular, it is how you can categorise transactions, selecting an appropriate account name based on their description (for example). There are two ways to write conditional rules: "if blocks", described here, and "if tables", described below. An if block is the word 'if' and one or more "matcher" expressions (can be a word or phrase), one per line, starting either on the same or next line; followed by one or more indented rules. Eg, if MATCHER RULE or if MATCHER MATCHER MATCHER RULE RULE If any of the matchers succeeds, all of the indented rules will be applied. They are usually field assignments, but the following special rules may also be used within an if block: * 'skip' - skips the matched CSV record (generating no transaction from it) * 'end' - skips the rest of the current CSV file. Some examples: # if the record contains "groceries", set account2 to "expenses:groceries" if groceries account2 expenses:groceries # if the record contains any of these phrases, set account2 and a transaction comment as shown if monthly service fee atm transaction fee banking thru software account2 expenses:business:banking comment XXX deductible ? check it # if an empty record is seen (assuming five fields), ignore the rest of the CSV file if ,,,, end  File: hledger.info, Node: Matchers, Next: if table, Prev: if block, Up: CSV 10.14 Matchers ============== There are two kinds: 1. A record matcher is a word or single-line text fragment or regular expression ('REGEX'), which hledger will try to match case-insensitively anywhere within the CSV record. Eg: 'whole foods' 2. A field matcher is preceded with a percent sign and CSV field name ('%CSVFIELD REGEX'). hledger will try to match these just within the named CSV field. Eg: '%date 2023' The regular expression is (as usual in hledger) a POSIX extended regular expression, that also supports GNU word boundaries ('\b', '\B', '\<', '\>'), and nothing else. If you have trouble, see "Regular expressions" in the hledger manual (https://hledger.org/hledger.html#regular-expressions). * Menu: * What matchers match:: * Combining matchers:: * Match groups::  File: hledger.info, Node: What matchers match, Next: Combining matchers, Up: Matchers 10.14.1 What matchers match --------------------------- With record matchers, it's important to know that the record matched is not the original CSV record, but a modified one: separators will be converted to commas, and enclosing double quotes (but not enclosing whitespace) are removed. So for example, when reading an SSV file, if the original record was: 2023-01-01; "Acme, Inc."; 1,000 the regex would see, and try to match, this modified record text: 2023-01-01,Acme, Inc., 1,000  File: hledger.info, Node: Combining matchers, Next: Match groups, Prev: What matchers match, Up: Matchers 10.14.2 Combining matchers -------------------------- When an if block has multiple matchers, they are combined as follows: * By default they are OR'd (any one of them can match) * When a matcher is preceded by ampersand ('&') it will be AND'ed with the previous matcher (both of them must match) * When a matcher is preceded by an exclamation mark ('!'), the matcher is negated (it may not match). Currently there is a limitation: you can't use both '&' and '!' on the same line (you can't AND a negated matcher).  File: hledger.info, Node: Match groups, Prev: Combining matchers, Up: Matchers 10.14.3 Match groups -------------------- Matchers can define match groups: parenthesised portions of the regular expression which are available for reference in field assignments. Groups are enclosed in regular parentheses ('(' and ')') and can be nested. Each group is available in field assignments using the token '\N', where N is an index into the match groups for this conditional block (e.g. '\1', '\2', etc.). Example: Warp credit card payment postings to the beginning of the billing period (Month start), to match how they are presented in statements, using posting dates: if %date (....-..)-.. comment2 date:\1-01 Another example: Read the expense account from the CSV field, but throw away a prefix: if %account1 liabilities:family:(expenses:.*) account1 \1  File: hledger.info, Node: if table, Next: balance-type, Prev: Matchers, Up: CSV 10.15 'if' table ================ "if tables" are an alternative to if blocks; they can express many matchers and field assignments in a more compact tabular format, like this: if,HLEDGERFIELD1,HLEDGERFIELD2,... MATCHERA,VALUE1,VALUE2,... MATCHERB,VALUE1,VALUE2,... MATCHERC,VALUE1,VALUE2,... The first character after 'if' is taken to be this if table's field separator. It is unrelated to the separator used in the CSV file. It should be a non-alphanumeric character like ',' or '|' that does not appear anywhere else in the table (it should not be used in field names or matchers or values, and it cannot be escaped with a backslash). Each line must contain the same number of separators; empty values are allowed. Whitespace can be used in the matcher lines for readability (but not in the if line, currently). The table must be terminated by an empty line (or end of file). An if table like the above is interpreted as follows: try all of the matchers; whenever a matcher succeeds, assign all of the values on that line to the corresponding hledger fields; later lines can overrider earlier ones. It is equivalent to this sequence of if blocks: if MATCHERA HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERB HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERC HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... Example: if,account2,comment atm transaction fee,expenses:business:banking,deductible? check it %description groceries,expenses:groceries, 2023/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call-out  File: hledger.info, Node: balance-type, Next: include, Prev: if table, Up: CSV 10.16 'balance-type' ==================== Balance assertions generated by assigning to balanceN are of the simple '=' type by default, which is a single-commodity, subaccount-excluding assertion. You may find the subaccount-including variants more useful, eg if you have created some virtual subaccounts of checking to help with budgeting. You can select a different type of assertion with the 'balance-type' rule: # balance assertions will consider all commodities and all subaccounts balance-type ==* Here are the balance assertion types for quick reference: = single commodity, exclude subaccounts =* single commodity, include subaccounts == multi commodity, exclude subaccounts ==* multi commodity, include subaccounts  File: hledger.info, Node: include, Next: Working with CSV, Prev: balance-type, Up: CSV 10.17 'include' =============== include RULESFILE This includes the contents of another CSV rules file at this point. 'RULESFILE' is an absolute file path or a path relative to the current file's directory. This can be useful for sharing common rules between several rules files, eg: # someaccount.csv.rules ## someaccount-specific rules fields date,description,amount account1 assets:someaccount account2 expenses:misc ## common rules include categorisation.rules  File: hledger.info, Node: Working with CSV, Next: CSV rules examples, Prev: include, Up: CSV 10.18 Working with CSV ====================== Some tips: * Menu: * Rapid feedback:: * Valid CSV:: * File Extension:: * Reading CSV from standard input:: * Reading multiple CSV files:: * Reading files specified by rule:: * Valid transactions:: * Deduplicating importing:: * Setting amounts:: * Amount signs:: * Setting currency/commodity:: * Amount decimal places:: * Referencing other fields:: * How CSV rules are evaluated:: * Well factored rules::  File: hledger.info, Node: Rapid feedback, Next: Valid CSV, Up: Working with CSV 10.18.1 Rapid feedback ---------------------- It's a good idea to get rapid feedback while creating/troubleshooting CSV rules. Here's a good way, using entr from eradman.com/entrproject: $ ls foo.csv* | entr bash -c 'echo ----; hledger -f foo.csv print desc:SOMEDESC' A desc: query (eg) is used to select just one, or a few, transactions of interest. "bash -c" is used to run multiple commands, so we can echo a separator each time the command re-runs, making it easier to read the output.  File: hledger.info, Node: Valid CSV, Next: File Extension, Prev: Rapid feedback, Up: Working with CSV 10.18.2 Valid CSV ----------------- Note that hledger will only accept valid CSV conforming to RFC 4180, and equivalent SSV and TSV formats (like RFC 4180 but with semicolon or tab as separators). This means, eg: * Values may be enclosed in double quotes, or not. Enclosing in single quotes is not allowed. (Eg ''A','B'' is rejected.) * When values are enclosed in double quotes, spaces outside the quotes are not allowed. (Eg '"A", "B"' is rejected.) * When values are not enclosed in quotes, they may not contain double quotes. (Eg 'A"A, B' is rejected.) If your CSV/SSV/TSV is not valid in this sense, you'll need to transform it before reading with hledger. Try using sed, or a more permissive CSV parser like python's csv lib.  File: hledger.info, Node: File Extension, Next: Reading CSV from standard input, Prev: Valid CSV, Up: Working with CSV 10.18.3 File Extension ---------------------- To help hledger choose the CSV file reader and show the right error messages (and choose the right field separator character by default), it's best if CSV/SSV/TSV files are named with a '.csv', '.ssv' or '.tsv' filename extension. (More about this at Data formats.) When reading files with the "wrong" extension, you can ensure the CSV reader (and the default field separator) by prefixing the file path with 'csv:', 'ssv:' or 'tsv:': Eg: $ hledger -f ssv:foo.dat print You can also override the default field separator with a separator rule if needed.  File: hledger.info, Node: Reading CSV from standard input, Next: Reading multiple CSV files, Prev: File Extension, Up: Working with CSV 10.18.4 Reading CSV from standard input --------------------------------------- You'll need the file format prefix when reading CSV from stdin also, since hledger assumes journal format by default. Eg: $ cat foo.dat | hledger -f ssv:- print  File: hledger.info, Node: Reading multiple CSV files, Next: Reading files specified by rule, Prev: Reading CSV from standard input, Up: Working with CSV 10.18.5 Reading multiple CSV files ---------------------------------- If you use multiple '-f' options to read multiple CSV files at once, hledger will look for a correspondingly-named rules file for each CSV file. But if you use the '--rules-file' option, that rules file will be used for all the CSV files.  File: hledger.info, Node: Reading files specified by rule, Next: Valid transactions, Prev: Reading multiple CSV files, Up: Working with CSV 10.18.6 Reading files specified by rule --------------------------------------- Instead of specifying a CSV file in the command line, you can specify a rules file, as in 'hledger -f foo.csv.rules CMD'. By default this will read data from foo.csv in the same directory, but you can add a source rule to specify a different data file, perhaps located in your web browser's download directory. This feature was added in hledger 1.30, so you won't see it in most CSV rules examples. But it helps remove some of the busywork of managing CSV downloads. Most of your financial institutions's default CSV filenames are different and can be recognised by a glob pattern. So you can put a rule like 'source Checking1*.csv' in foo-checking.csv.rules, and then periodically follow a workflow like: 1. Download CSV from Foo's website, using your browser's defaults 2. Run 'hledger import foo-checking.csv.rules' to import any new transactions After import, you can: discard the CSV, or leave it where it is for a while, or move it into your archives, as you prefer. If you do nothing, next time your browser will save something like Checking1-2.csv, and hledger will use that because of the '*' wild card and because it is the most recent.  File: hledger.info, Node: Valid transactions, Next: Deduplicating importing, Prev: Reading files specified by rule, Up: Working with CSV 10.18.7 Valid transactions -------------------------- After reading a CSV file, hledger post-processes and validates the generated journal entries as it would for a journal file - balancing them, applying balance assignments, and canonicalising amount styles. Any errors at this stage will be reported in the usual way, displaying the problem entry. There is one exception: balance assertions, if you have generated them, will not be checked, since normally these will work only when the CSV data is part of the main journal. If you do need to check balance assertions generated from CSV right away, pipe into another hledger: $ hledger -f file.csv print | hledger -f- print  File: hledger.info, Node: Deduplicating importing, Next: Setting amounts, Prev: Valid transactions, Up: Working with CSV 10.18.8 Deduplicating, importing -------------------------------- When you download a CSV file periodically, eg to get your latest bank transactions, the new file may overlap with the old one, containing some of the same records. The import command will (a) detect the new transactions, and (b) append just those transactions to your main journal. It is idempotent, so you don't have to remember how many times you ran it or with which version of the CSV. (It keeps state in a hidden '.latest.FILE.csv' file.) This is the easiest way to import CSV data. Eg: # download the latest CSV files, then run this command. # Note, no -f flags needed here. $ hledger import *.csv [--dry] This method works for most CSV files. (Where records have a stable chronological order, and new records appear only at the new end.) A number of other tools and workflows, hledger-specific and otherwise, exist for converting, deduplicating, classifying and managing CSV data. See: * https://hledger.org/cookbook.html#setups-and-workflows * https://plaintextaccounting.org -> data import/conversion  File: hledger.info, Node: Setting amounts, Next: Amount signs, Prev: Deduplicating importing, Up: Working with CSV 10.18.9 Setting amounts ----------------------- Continuing from amount field above, here are more tips for amount-setting: 1. *If the amount is in a single CSV field:* a. *If its sign indicates direction of flow:* Assign it to 'amountN', to set the Nth posting's amount. N is usually 1 or 2 but can go up to 99. b. *If another field indicates direction of flow:* Use one or more conditional rules to set the appropriate amount sign. Eg: # assume a withdrawal unless Type contains "deposit": amount1 -%Amount if %Type deposit amount1 %Amount 2. *If the amount is in two CSV fields (such as Debit and Credit, or In and Out):* a. *If both fields are unsigned:* Assign one field to 'amountN-in' and the other to 'amountN-out'. hledger will automatically negate the "out" field, and will use whichever field value is non-zero as posting N's amount. b. *If either field is signed:* You will probably need to override hledger's sign for one or the other field, as in the following example: # Negate the -out value, but only if it is not empty: fields date, description, amount1-in, amount1-out if %amount1-out [1-9] amount1-out -%amount1-out c. *If both fields can contain a non-zero value (or both can be empty):* The -in/-out rules normally choose the value which is non-zero/non-empty. Some value pairs can be ambiguous, such as '1' and 'none'. For such cases, use conditional rules to help select the amount. Eg, to handle the above you could select the value containing non-zero digits: fields date, description, in, out if %in [1-9] amount1 %in if %out [1-9] amount1 %out 3. *If you want posting 2's amount converted to cost:* Use the unnumbered 'amount' (or 'amount-in' and 'amount-out') syntax. 4. *If the CSV has only balance amounts, not transaction amounts:* Assign to 'balanceN', to set a balance assignment on the Nth posting, causing the posting's amount to be calculated automatically. 'balance' with no number is equivalent to 'balance1'. In this situation hledger is more likely to guess the wrong default account name, so you may need to set that explicitly.  File: hledger.info, Node: Amount signs, Next: Setting currency/commodity, Prev: Setting amounts, Up: Working with CSV 10.18.10 Amount signs --------------------- There is some special handling making it easier to parse and to reverse amount signs. (This only works for whole amounts, not for cost amounts such as COST in 'amount1 AMT @ COST'): * *If an amount value begins with a plus sign:* that will be removed: '+AMT' becomes 'AMT' * *If an amount value is parenthesised:* it will be de-parenthesised and sign-flipped: '(AMT)' becomes '-AMT' * *If an amount value has two minus signs (or two sets of parentheses, or a minus sign and parentheses):* they cancel out and will be removed: '--AMT' or '-(AMT)' becomes 'AMT' * *If an amount value contains just a sign (or just a set of parentheses):* that is removed, making it an empty value. '"+"' or '"-"' or '"()"' becomes '""'. It's not possible (without preprocessing the CSV) to set an amount to its absolute value, ie discard its sign.  File: hledger.info, Node: Setting currency/commodity, Next: Amount decimal places, Prev: Amount signs, Up: Working with CSV 10.18.11 Setting currency/commodity ----------------------------------- If the currency/commodity symbol is included in the CSV's amount field(s): 2023-01-01,foo,$123.00 you don't have to do anything special for the commodity symbol, it will be assigned as part of the amount. Eg: fields date,description,amount 2023-01-01 foo expenses:unknown $123.00 income:unknown $-123.00 If the currency is provided as a separate CSV field: 2023-01-01,foo,USD,123.00 You can assign that to the 'currency' pseudo-field, which has the special effect of prepending itself to every amount in the transaction (on the left, with no separating space): fields date,description,currency,amount 2023-01-01 foo expenses:unknown USD123.00 income:unknown USD-123.00 Or, you can use a field assignment to construct the amount yourself, with more control. Eg to put the symbol on the right, and separated by a space: fields date,description,cur,amt amount %amt %cur 2023-01-01 foo expenses:unknown 123.00 USD income:unknown -123.00 USD Note we used a temporary field name ('cur') that is not 'currency' - that would trigger the prepending effect, which we don't want here.  File: hledger.info, Node: Amount decimal places, Next: Referencing other fields, Prev: Setting currency/commodity, Up: Working with CSV 10.18.12 Amount decimal places ------------------------------ Like amounts in a journal file, the amounts generated by CSV rules like 'amount1' influence commodity display styles, such as the number of decimal places displayed in reports. The original amounts as written in the CSV file do not affect display style (because we don't yet reliably know their commodity).  File: hledger.info, Node: Referencing other fields, Next: How CSV rules are evaluated, Prev: Amount decimal places, Up: Working with CSV 10.18.13 Referencing other fields --------------------------------- In field assignments, you can interpolate only CSV fields, not hledger fields. In the example below, there's both a CSV field and a hledger field named amount1, but %amount1 always means the CSV field, not the hledger field: # Name the third CSV field "amount1" fields date,description,amount1 # Set hledger's amount1 to the CSV amount1 field followed by USD amount1 %amount1 USD # Set comment to the CSV amount1 (not the amount1 assigned above) comment %amount1 Here, since there's no CSV amount1 field, %amount1 will produce a literal "amount1": fields date,description,csvamount amount1 %csvamount USD # Can't interpolate amount1 here comment %amount1 When there are multiple field assignments to the same hledger field, only the last one takes effect. Here, comment's value will be be B, or C if "something" is matched, but never A: comment A comment B if something comment C  File: hledger.info, Node: How CSV rules are evaluated, Next: Well factored rules, Prev: Referencing other fields, Up: Working with CSV 10.18.14 How CSV rules are evaluated ------------------------------------ Here's how to think of CSV rules being evaluated (if you really need to). First, * 'include' - all includes are inlined, from top to bottom, depth first. (At each include point the file is inlined and scanned for further includes, recursively, before proceeding.) Then "global" rules are evaluated, top to bottom. If a rule is repeated, the last one wins: * 'skip' (at top level) * 'date-format' * 'newest-first' * 'fields' - names the CSV fields, optionally sets up initial assignments to hledger fields Then for each CSV record in turn: * test all 'if' blocks. If any of them contain a 'end' rule, skip all remaining CSV records. Otherwise if any of them contain a 'skip' rule, skip that many CSV records. If there are multiple matched 'skip' rules, the first one wins. * collect all field assignments at top level and in matched 'if' blocks. When there are multiple assignments for a field, keep only the last one. * compute a value for each hledger field - either the one that was assigned to it (and interpolate the %CSVFIELD references), or a default * generate a hledger transaction (journal entry) from these values. This is all part of the CSV reader, one of several readers hledger can use to parse input files. When all files have been read successfully, the transactions are passed as input to whichever hledger command the user specified.  File: hledger.info, Node: Well factored rules, Prev: How CSV rules are evaluated, Up: Working with CSV 10.18.15 Well factored rules ---------------------------- Some things than can help reduce duplication and complexity in rules files: * Extracting common rules usable with multiple CSV files into a 'common.rules', and adding 'include common.rules' to each CSV's rules file. * Splitting if blocks into smaller if blocks, extracting the frequently used parts.  File: hledger.info, Node: CSV rules examples, Prev: Working with CSV, Up: CSV 10.19 CSV rules examples ======================== * Menu: * Bank of Ireland:: * Coinbase:: * Amazon:: * Paypal::  File: hledger.info, Node: Bank of Ireland, Next: Coinbase, Up: CSV rules examples 10.19.1 Bank of Ireland ----------------------- Here's a CSV with two amount fields (Debit and Credit), and a balance field, which we can use to add balance assertions, which is not necessary but provides extra error checking: Date,Details,Debit,Credit,Balance 07/12/2012,LODGMENT 529898,,10.0,131.21 07/12/2012,PAYMENT,5,,126 # bankofireland-checking.csv.rules # skip the header line skip # name the csv fields, and assign some of them as journal entry fields fields date, description, amount-out, amount-in, balance # We generate balance assertions by assigning to "balance" # above, but you may sometimes need to remove these because: # # - the CSV balance differs from the true balance, # by up to 0.0000000000005 in my experience # # - it is sometimes calculated based on non-chronological ordering, # eg when multiple transactions clear on the same day # date is in UK/Ireland format date-format %d/%m/%Y # set the currency currency EUR # set the base account for all txns account1 assets:bank:boi:checking $ hledger -f bankofireland-checking.csv print 2012-12-07 LODGMENT 529898 assets:bank:boi:checking EUR10.0 = EUR131.2 income:unknown EUR-10.0 2012-12-07 PAYMENT assets:bank:boi:checking EUR-5.0 = EUR126.0 expenses:unknown EUR5.0 The balance assertions don't raise an error above, because we're reading directly from CSV, but they will be checked if these entries are imported into a journal file.  File: hledger.info, Node: Coinbase, Next: Amazon, Prev: Bank of Ireland, Up: CSV rules examples 10.19.2 Coinbase ---------------- A simple example with some CSV from Coinbase. The spot price is recorded using cost notation. The legacy 'amount' field name conveniently sets amount 2 (posting 2's amount) to the total cost. # Timestamp,Transaction Type,Asset,Quantity Transacted,Spot Price Currency,Spot Price at Transaction,Subtotal,Total (inclusive of fees and/or spread),Fees and/or Spread,Notes # 2021-12-30T06:57:59Z,Receive,USDC,100,GBP,0.740000,"","","","Received 100.00 USDC from an external account" # coinbase.csv.rules skip 1 fields Timestamp,Transaction_Type,Asset,Quantity_Transacted,Spot_Price_Currency,Spot_Price_at_Transaction,Subtotal,Total,Fees_Spread,Notes date %Timestamp date-format %Y-%m-%dT%T%Z description %Notes account1 assets:coinbase:cc amount %Quantity_Transacted %Asset @ %Spot_Price_at_Transaction %Spot_Price_Currency $ hledger print -f coinbase.csv 2021-12-30 Received 100.00 USDC from an external account assets:coinbase:cc 100 USDC @ 0.740000 GBP income:unknown -74.000000 GBP  File: hledger.info, Node: Amazon, Next: Paypal, Prev: Coinbase, Up: CSV rules examples 10.19.3 Amazon -------------- Here we convert amazon.com order history, and use an if block to generate a third posting if there's a fee. (In practice you'd probably get this data from your bank instead, but it's an example.) "Date","Type","To/From","Name","Status","Amount","Fees","Transaction ID" "Jul 29, 2012","Payment","To","Foo.","Completed","$20.00","$0.00","16000000000000DGLNJPI1P9B8DKPVHL" "Jul 30, 2012","Payment","To","Adapteva, Inc.","Completed","$25.00","$1.00","17LA58JSKRD4HDGLNJPI1P9B8DKPVHL" # amazon-orders.csv.rules # skip one header line skip 1 # name the csv fields, and assign the transaction's date, amount and code. # Avoided the "status" and "amount" hledger field names to prevent confusion. fields date, _, toorfrom, name, amzstatus, amzamount, fees, code # how to parse the date date-format %b %-d, %Y # combine two fields to make the description description %toorfrom %name # save the status as a tag comment status:%amzstatus # set the base account for all transactions account1 assets:amazon # leave amount1 blank so it can balance the other(s). # I'm assuming amzamount excludes the fees, don't remember # set a generic account2 account2 expenses:misc amount2 %amzamount # and maybe refine it further: #include categorisation.rules # add a third posting for fees, but only if they are non-zero. if %fees [1-9] account3 expenses:fees amount3 %fees $ hledger -f amazon-orders.csv print 2012-07-29 (16000000000000DGLNJPI1P9B8DKPVHL) To Foo. ; status:Completed assets:amazon expenses:misc $20.00 2012-07-30 (17LA58JSKRD4HDGLNJPI1P9B8DKPVHL) To Adapteva, Inc. ; status:Completed assets:amazon expenses:misc $25.00 expenses:fees $1.00  File: hledger.info, Node: Paypal, Prev: Amazon, Up: CSV rules examples 10.19.4 Paypal -------------- Here's a real-world rules file for (customised) Paypal CSV, with some Paypal-specific rules, and a second rules file included: "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" "10/01/2019","03:46:20","PDT","Calm Radio","Subscription Payment","Completed","USD","-6.99","0.00","-6.99","simon@joyful.com","memberships@calmradio.com","60P57143A8206782E","MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month","","I-R8YLY094FJYR","","-6.99","" "10/01/2019","03:46:20","PDT","","Bank Deposit to PP Account ","Pending","USD","6.99","0.00","6.99","","simon@joyful.com","0TU1544T080463733","","","60P57143A8206782E","","0.00","" "10/01/2019","08:57:01","PDT","Patreon","PreApproved Payment Bill User Payment","Completed","USD","-7.00","0.00","-7.00","simon@joyful.com","support@patreon.com","2722394R5F586712G","Patreon* Membership","","B-0PG93074E7M86381M","","-7.00","" "10/01/2019","08:57:01","PDT","","Bank Deposit to PP Account ","Pending","USD","7.00","0.00","7.00","","simon@joyful.com","71854087RG994194F","Patreon* Membership","","2722394R5F586712G","","0.00","" "10/19/2019","03:02:12","PDT","Wikimedia Foundation, Inc.","Subscription Payment","Completed","USD","-2.00","0.00","-2.00","simon@joyful.com","tle@wikimedia.org","K9U43044RY432050M","Monthly donation to the Wikimedia Foundation","","I-R5C3YUS3285L","","-2.00","" "10/19/2019","03:02:12","PDT","","Bank Deposit to PP Account ","Pending","USD","2.00","0.00","2.00","","simon@joyful.com","3XJ107139A851061F","","","K9U43044RY432050M","","0.00","" "10/22/2019","05:07:06","PDT","Noble Benefactor","Subscription Payment","Completed","USD","10.00","-0.59","9.41","noble@bene.fac.tor","simon@joyful.com","6L8L1662YP1334033","Joyful Systems","","I-KC9VBGY2GWDB","","9.41","" # paypal-custom.csv.rules # Tips: # Export from Activity -> Statements -> Custom -> Activity download # Suggested transaction type: "Balance affecting" # Paypal's default fields in 2018 were: # "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Shipping Address","Address Status","Item Title","Item ID","Shipping and Handling Amount","Insurance Amount","Sales Tax","Option 1 Name","Option 1 Value","Option 2 Name","Option 2 Value","Reference Txn ID","Invoice Number","Custom Number","Quantity","Receipt ID","Balance","Address Line 1","Address Line 2/District/Neighborhood","Town/City","State/Province/Region/County/Territory/Prefecture/Republic","Zip/Postal Code","Country","Contact Phone Number","Subject","Note","Country Code","Balance Impact" # This rules file assumes the following more detailed fields, configured in "Customize report fields": # "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" fields date, time, timezone, description_, type, status_, currency, grossamount, feeamount, netamount, fromemail, toemail, code, itemtitle, itemid, referencetxnid, receiptid, balance, note skip 1 date-format %-m/%-d/%Y # ignore some paypal events if In Progress Temporary Hold Update to skip # add more fields to the description description %description_ %itemtitle # save some other fields as tags comment itemid:%itemid, fromemail:%fromemail, toemail:%toemail, time:%time, type:%type, status:%status_ # convert to short currency symbols if %currency USD currency $ if %currency EUR currency E if %currency GBP currency P # generate postings # the first posting will be the money leaving/entering my paypal account # (negative means leaving my account, in all amount fields) account1 assets:online:paypal amount1 %netamount # the second posting will be money sent to/received from other party # (account2 is set below) amount2 -%grossamount # if there's a fee, add a third posting for the money taken by paypal. if %feeamount [1-9] account3 expenses:banking:paypal amount3 -%feeamount comment3 business: # choose an account for the second posting # override the default account names: # if the amount is positive, it's income (a debit) if %grossamount ^[^-] account2 income:unknown # if negative, it's an expense (a credit) if %grossamount ^- account2 expenses:unknown # apply common rules for setting account2 & other tweaks include common.rules # apply some overrides specific to this csv # Transfers from/to bank. These are usually marked Pending, # which can be disregarded in this case. if Bank Account Bank Deposit to PP Account description %type for %referencetxnid %itemtitle account2 assets:bank:wf:pchecking account1 assets:online:paypal # Currency conversions if Currency Conversion account2 equity:currency conversion # common.rules if darcs noble benefactor account2 revenues:foss donations:darcshub comment2 business: if Calm Radio account2 expenses:online:apps if electronic frontier foundation Patreon wikimedia Advent of Code account2 expenses:dues if Google account2 expenses:online:apps description google | music $ hledger -f paypal-custom.csv print 2019-10-01 (60P57143A8206782E) Calm Radio MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month ; itemid:, fromemail:simon@joyful.com, toemail:memberships@calmradio.com, time:03:46:20, type:Subscription Payment, status:Completed assets:online:paypal $-6.99 = $-6.99 expenses:online:apps $6.99 2019-10-01 (0TU1544T080463733) Bank Deposit to PP Account for 60P57143A8206782E ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:46:20, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $6.99 = $0.00 assets:bank:wf:pchecking $-6.99 2019-10-01 (2722394R5F586712G) Patreon Patreon* Membership ; itemid:, fromemail:simon@joyful.com, toemail:support@patreon.com, time:08:57:01, type:PreApproved Payment Bill User Payment, status:Completed assets:online:paypal $-7.00 = $-7.00 expenses:dues $7.00 2019-10-01 (71854087RG994194F) Bank Deposit to PP Account for 2722394R5F586712G Patreon* Membership ; itemid:, fromemail:, toemail:simon@joyful.com, time:08:57:01, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $7.00 = $0.00 assets:bank:wf:pchecking $-7.00 2019-10-19 (K9U43044RY432050M) Wikimedia Foundation, Inc. Monthly donation to the Wikimedia Foundation ; itemid:, fromemail:simon@joyful.com, toemail:tle@wikimedia.org, time:03:02:12, type:Subscription Payment, status:Completed assets:online:paypal $-2.00 = $-2.00 expenses:dues $2.00 expenses:banking:paypal ; business: 2019-10-19 (3XJ107139A851061F) Bank Deposit to PP Account for K9U43044RY432050M ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:02:12, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $2.00 = $0.00 assets:bank:wf:pchecking $-2.00 2019-10-22 (6L8L1662YP1334033) Noble Benefactor Joyful Systems ; itemid:, fromemail:noble@bene.fac.tor, toemail:simon@joyful.com, time:05:07:06, type:Subscription Payment, status:Completed assets:online:paypal $9.41 = $9.41 revenues:foss donations:darcshub $-10.00 ; business: expenses:banking:paypal $0.59 ; business:  File: hledger.info, Node: Timeclock, Next: Timedot, Prev: CSV, Up: Top 11 Timeclock ************ The time logging format of timeclock.el, as read by hledger. hledger can read time logs in timeclock format. As with Ledger, these are (a subset of) timeclock.el's format, containing clock-in and clock-out entries as in the example below. The date is a simple date. The time format is HH:MM[:SS][+-ZZZZ]. Seconds and timezone are optional. The timezone, if present, must be four digits and is ignored (currently the time is always interpreted as a local time). Lines beginning with '#' or ';' or '*', and blank lines, are ignored. i 2015/03/30 09:00:00 some account optional description after 2 spaces ; optional comment, tags: o 2015/03/30 09:20:00 i 2015/03/31 22:21:45 another:account o 2015/04/01 02:00:34 hledger treats each clock-in/clock-out pair as a transaction posting some number of hours to an account. Or if the session spans more than one day, it is split into several transactions, one for each day. For the above time log, 'hledger print' generates these journal entries: $ hledger -f t.timeclock print 2015-03-30 * optional description after 2 spaces ; optional comment, tags: (some account) 0.33h 2015-03-31 * 22:21-23:59 (another:account) 1.64h 2015-04-01 * 00:00-02:00 (another:account) 2.01h Here is a sample.timeclock to download and some queries to try: $ hledger -f sample.timeclock balance # current time balances $ hledger -f sample.timeclock register -p 2009/3 # sessions in march 2009 $ hledger -f sample.timeclock register -p weekly --depth 1 --empty # time summary by week To generate time logs, ie to clock in and clock out, you could: * use emacs and the built-in timeclock.el, or the extended timeclock-x.el and perhaps the extras in ledgerutils.el * at the command line, use these bash aliases: 'shell alias ti="echo i `date '+%Y-%m-%d %H:%M:%S'` \$* >>$TIMELOG" alias to="echo o `date '+%Y-%m-%d %H:%M:%S'` >>$TIMELOG"' * or use the old 'ti' and 'to' scripts in the ledger 2.x repository. These rely on a "timeclock" executable which I think is just the ledger 2 executable renamed.  File: hledger.info, Node: Timedot, Next: PART 3 REPORTING CONCEPTS, Prev: Timeclock, Up: Top 12 Timedot ********** 'timedot' format is hledger's human-friendly time logging format. Compared to 'timeclock' format, it is more convenient for quick, approximate, and retroactive time logging, and more human-readable (you can see at a glance where time was spent). A quick example: 2023-05-01 hom:errands .... .... ; two hours; the space is ignored fos:hledger:timedot .. ; half an hour per:admin:finance ; no time spent yet hledger reads this as a transaction on this day with three (unbalanced) postings, where each dot represents "0.25". No commodity symbol is assumed, but we typically interpret it as hours. $ hledger -f a.timedot print # .timedot file extension (or timedot: prefix) is required 2023-05-01 * (hom:errands) 2.00 ; two hours (fos:hledger:timedot) 0.50 ; half an hour (per:admin:finance) 0 A timedot file contains a series of transactions (usually one per day). Each begins with a *simple date* (Y-M-D, Y/M/D, or Y.M.D), optionally be followed on the same line by a transaction description, and/or a transaction comment following a semicolon. After the date line are zero or more time postings, consisting of: * *An account name* - any hledger-style account name, optionally indented. * *Two or more spaces* - required if there is an amount (as in journal format). * *A timedot amount*, which can be * empty (representing zero) * a number, optionally followed by a unit 's', 'm', 'h', 'd', 'w', 'mo', or 'y', representing a precise number of seconds, minutes, hours, days weeks, months or years (hours is assumed by default), which will be converted to hours according to 60s = 1m, 60m = 1h, 24h = 1d, 7d = 1w, 30d = 1mo, 365d = 1y. * one or more dots (period characters), each representing 0.25. These are the dots in "timedot". Spaces are ignored and can be used for grouping/alignment. * one or more letters. These are like dots but they also generate a tag 't:' (short for "type") with the letter as its value, and a separate posting for each of the values. This provides a second dimension of categorisation, viewable in reports with '--pivot t'. * *An optional comment* following a semicolon (a hledger-style posting comment). There is some flexibility to help with keeping time log data and notes in the same file: * Blank lines and lines beginning with '#' or ';' are ignored. * After the first date line, lines which do not contain a double space are parsed as postings with zero amount. (hledger's register reports will show these if you add -E). * Before the first date line, lines beginning with '*' (eg org headings) are ignored. And from the first date line onward, Emacs org mode heading prefixes at the start of lines (one or more '*''s followed by a space) will be ignored. This means the time log can also be a org outline. * Menu: * Timedot examples::  File: hledger.info, Node: Timedot examples, Up: Timedot 12.1 Timedot examples ===================== Numbers: 2016/2/3 inc:client1 4 fos:hledger 3h biz:research 60m Dots: # on this day, 6h was spent on client work, 1.5h on haskell FOSS work, etc. 2016/2/1 inc:client1 .... .... .... .... .... .... fos:haskell .... .. biz:research . 2016/2/2 inc:client1 .... .... biz:research . $ hledger -f a.timedot print date:2016/2/2 2016-02-02 * (inc:client1) 2.00 2016-02-02 * (biz:research) 0.25 $ hledger -f a.timedot bal --daily --tree Balance changes in 2016-02-01-2016-02-03: || 2016-02-01d 2016-02-02d 2016-02-03d ============++======================================== biz || 0.25 0.25 1.00 research || 0.25 0.25 1.00 fos || 1.50 0 3.00 haskell || 1.50 0 0 hledger || 0 0 3.00 inc || 6.00 2.00 4.00 client1 || 6.00 2.00 4.00 ------------++---------------------------------------- || 7.75 2.25 8.00 Letters: # Activity types: # c cleanup/catchup/repair # e enhancement # s support # l learning/research 2023-11-01 work:adm ccecces $ hledger -f a.timedot print 2023-11-01 (work:adm) 1 ; t:c (work:adm) 0.5 ; t:e (work:adm) 0.25 ; t:s $ hledger -f a.timedot bal 1.75 work:adm -------------------- 1.75 $ hledger -f a.timedot bal --pivot t 1.00 c 0.50 e 0.25 s -------------------- 1.75 Org: * 2023 Work Diary ** Q1 *** 2023-02-29 **** DONE 0700 yoga **** UNPLANNED **** BEGUN hom:chores cleaning ... water plants outdoor - one full watering can indoor - light watering **** TODO adm:planning: trip *** LATER Using '.' as account name separator: 2016/2/4 fos.hledger.timedot 4h fos.ledger .. $ hledger -f a.timedot --alias '/\./=:' bal -t 4.50 fos 4.00 hledger:timedot 0.50 ledger -------------------- 4.50  File: hledger.info, Node: PART 3 REPORTING CONCEPTS, Next: Amount formatting parseability, Prev: Timedot, Up: Top 13 PART 3: REPORTING CONCEPTS *****************************  File: hledger.info, Node: Amount formatting parseability, Next: Time periods, Prev: PART 3 REPORTING CONCEPTS, Up: Top 14 Amount formatting, parseability ********************************** If you're wondering why your 'print' report sometimes shows trailing decimal marks, with no decimal digits; it does this when showing amounts that have digit group marks but no decimal digits, to disambiguate them and allow them to be re-parsed reliably (see also Decimal marks, digit group marks. Eg: commodity $1,000.00 2023-01-02 (a) $1000 $ hledger print 2023-01-02 (a) $1,000. If this is a problem (eg when exporting to Ledger), you can avoid it by disabling digit group marks, eg with -c/-commodity (for each affected commodity): $ hledger print -c '$1000.00' 2023-01-02 (a) $1000 or by forcing print to always show decimal digits, with -round: $ hledger print -c '$1,000.00' --round=soft 2023-01-02 (a) $1,000.00 More generally: hledger output falls into three rough categories, which format amounts a little bit differently to suit different consumers: *1. "hledger-readable output" - should be readable by hledger (and by humans)* * This is produced by reports that show full journal entries: 'print', 'import', 'close', 'rewrite' etc. * It shows amounts with their original journal precisions, which may not be consistent. * It adds a trailing decimal mark when needed to avoid showing ambiguous amounts. * It can be parsed reliably (by hledger and ledger2beancount at least, but perhaps not by Ledger..) *2. "human-readable output" - usually for humans* * This is produced by all other reports. * It shows amounts with standard display precisions, which will be consistent within each commodity. * It shows ambiguous amounts unmodified. * It can be parsed reliably in the context of a known report (when you know decimals are consistently not being shown, you can assume a single mark is a digit group mark). *3. "machine-readable output" - usually for other software* * This is produced by all reports when an output format like 'csv', 'tsv', 'json', or 'sql' is selected. * It shows amounts as 1 or 2 do, but without digit group marks. * It can be parsed reliably (if needed, the decimal mark can be changed with -c/-commodity-style).  File: hledger.info, Node: Time periods, Next: Depth, Prev: Amount formatting parseability, Up: Top 15 Time periods *************** * Menu: * Report start & end date:: * Smart dates:: * Report intervals:: * Date adjustment:: * Period expressions::  File: hledger.info, Node: Report start & end date, Next: Smart dates, Up: Time periods 15.1 Report start & end date ============================ By default, most hledger reports will show the full span of time represented by the journal. The report start date will be the earliest transaction or posting date, and the report end date will be the latest transaction, posting, or market price date. Often you will want to see a shorter time span, such as the current month. You can specify a start and/or end date using '-b/--begin', '-e/--end', '-p/--period' or a 'date:' query (described below). All of these accept the smart date syntax (below). Some notes: * End dates are exclusive, as in Ledger, so you should write the date _after_ the last day you want to see in the report. * As noted in reporting options: among start/end dates specified with _options_, the last (i.e. right-most) option takes precedence. * The effective report start and end dates are the intersection of the start/end dates from options and that from 'date:' queries. That is, 'date:2019-01 date:2019 -p'2000 to 2030'' yields January 2019, the smallest common time span. * In some cases a report interval will adjust start/end dates to fall on interval boundaries (see below). Examples: '-b begin on St. Patrick's day 2016 2016/3/17' '-e 12/1' end at the start of december 1st of the current year (11/30 will be the last date included) '-b all transactions on or after the 1st of the current month thismonth' '-p all transactions in the current month thismonth' 'date:2016/3/17..'the above written as queries instead ('..' can also be replaced with '-') 'date:..12/1' 'date:thismonth..' 'date:thismonth'  File: hledger.info, Node: Smart dates, Next: Report intervals, Prev: Report start & end date, Up: Time periods 15.2 Smart dates ================ hledger's user interfaces accept a "smart date" syntax for added convenience. Smart dates optionally can be relative to today's date, be written with english words, and have less-significant parts omitted (missing parts are inferred as 1). Some examples: '2004/10/1', exact date, several separators allowed. Year '2004-01-01', is 4+ digits, month is 1-12, day is 1-31 '2004.9.1' '2004' start of year '2004/10' start of month '10/1' month and day in current year '21' day in current month 'october, oct' start of month in current year 'yesterday, today, -1, 0, 1 days from today tomorrow' 'last/this/next -1, 0, 1 periods from the current period day/week/month/quarter/year' 'in n n periods from the current period days/weeks/months/quarters/years' 'n n periods from the current period days/weeks/months/quarters/years ahead' 'n -n periods from the current period days/weeks/months/quarters/years ago' '20181201' 8 digit YYYYMMDD with valid year month and day '201812' 6 digit YYYYMM with valid year and month Some counterexamples - malformed digit sequences might give surprising results: '201813' 6 digits with an invalid month is parsed as start of 6-digit year '20181301' 8 digits with an invalid month is parsed as start of 8-digit year '20181232' 8 digits with an invalid day gives an error '201801012' 9+ digits beginning with a valid YYYYMMDD gives an error "Today's date" can be overridden with the '--today' option, in case it's needed for testing or for recreating old reports. (Except for periodic transaction rules, which are not affected by '--today'.)  File: hledger.info, Node: Report intervals, Next: Date adjustment, Prev: Smart dates, Up: Time periods 15.3 Report intervals ===================== A report interval can be specified so that reports like register, balance or activity become multi-period, showing each subperiod as a separate row or column. The following standard intervals can be enabled with command-line flags: * '-D/--daily' * '-W/--weekly' * '-M/--monthly' * '-Q/--quarterly' * '-Y/--yearly' More complex intervals can be specified using '-p/--period', described below.  File: hledger.info, Node: Date adjustment, Next: Period expressions, Prev: Report intervals, Up: Time periods 15.4 Date adjustment ==================== When there is a report interval (other than daily), report start/end dates which have been inferred, eg from the journal, are automatically adjusted to natural period boundaries. This is convenient for producing simple periodic reports. More precisely: * an inferred start date will be adjusted earlier if needed to fall on a natural period boundary * an inferred end date will be adjusted later if needed to make the last period the same length as the others. By contrast, start/end dates which have been specified explicitly, with '-b', '-e', '-p' or 'date:', will not be adjusted (since hledger 1.29). This makes it possible to specify non-standard report periods, but it also means that if you are specifying a start date, you should pick one that's on a period boundary if you want to see simple report period headings.  File: hledger.info, Node: Period expressions, Prev: Date adjustment, Up: Time periods 15.5 Period expressions ======================= The '-p/--period' option specifies a period expression, which is a compact way of expressing a start date, end date, and/or report interval. Here's a period expression with a start and end date (specifying the first quarter of 2009): '-p "from 2009/1/1 to 2009/4/1"' Several keywords like "from" and "to" are supported for readability; these are optional. "to" can also be written as ".." or "-". The spaces are also optional, as long as you don't run two dates together. So the following are equivalent to the above: '-p "2009/1/1 2009/4/1"' '-p2009/1/1to2009/4/1' '-p2009/1/1..2009/4/1' Dates are smart dates, so if the current year is 2009, these are also equivalent to the above: '-p "1/1 4/1"' '-p "jan-apr"' '-p "this year to 4/1"' If you specify only one date, the missing start or end date will be the earliest or latest transaction date in the journal: '-p "from 2009/1/1"' everything after january 1, 2009 '-p "since 2009/1"' the same, since is a synonym '-p "from 2009"' the same '-p "to 2009"' everything before january 1, 2009 You can also specify a period by writing a single partial or full date: '-p "2009"' the year 2009; equivalent to “2009/1/1 to 2010/1/1” '-p "2009/1"' the month of january 2009; equivalent to “2009/1/1 to 2009/2/1” '-p the first day of 2009; equivalent to “2009/1/1 to "2009/1/1"' 2009/1/2” or by using the "Q" quarter-year syntax (case insensitive): '-p "2009Q1"' first quarter of 2009, equivalent to “2009/1/1 to 2009/4/1” '-p "q4"' fourth quarter of the current year * Menu: * Period expressions with a report interval:: * More complex report intervals:: * Multiple weekday intervals::  File: hledger.info, Node: Period expressions with a report interval, Next: More complex report intervals, Up: Period expressions 15.5.1 Period expressions with a report interval ------------------------------------------------ A period expression can also begin with a report interval, separated from the start/end dates (if any) by a space or the word 'in': '-p "weekly from 2009/1/1 to 2009/4/1"' '-p "monthly in 2008"' '-p "quarterly"'  File: hledger.info, Node: More complex report intervals, Next: Multiple weekday intervals, Prev: Period expressions with a report interval, Up: Period expressions 15.5.2 More complex report intervals ------------------------------------ Some more complex intervals can be specified within period expressions, such as: * 'biweekly' (every two weeks) * 'fortnightly' * 'bimonthly' (every two months) * 'every day|week|month|quarter|year' * 'every N days|weeks|months|quarters|years' Weekly on a custom day: * 'every Nth day of week' ('th', 'nd', 'rd', or 'st' are all accepted after the number) * 'every WEEKDAYNAME' (full or three-letter english weekday name, case insensitive) Monthly on a custom day: * 'every Nth day [of month]' * 'every Nth WEEKDAYNAME [of month]' Yearly on a custom day: * 'every MM/DD [of year]' (month number and day of month number) * 'every MONTHNAME DDth [of year]' (full or three-letter english month name, case insensitive, and day of month number) * 'every DDth MONTHNAME [of year]' (equivalent to the above) Examples: '-p "bimonthly from 2008"' '-p "every 2 weeks"' '-p "every 5 months from 2009/03"' '-p "every 2nd day of periods will go from Tue to Tue week"' '-p "every Tue"' same '-p "every 15th day"' period boundaries will be on 15th of each month '-p "every 2nd Monday"' period boundaries will be on second Monday of each month '-p "every 11/05"' yearly periods with boundaries on 5th of November '-p "every 5th November"' same '-p "every Nov 5th"' same Show historical balances at end of the 15th day of each month (N is an end date, exclusive as always): $ hledger balance -H -p "every 16th day" Group postings from the start of wednesday to end of the following tuesday (N is both (inclusive) start date and (exclusive) end date): $ hledger register checking -p "every 3rd day of week"  File: hledger.info, Node: Multiple weekday intervals, Prev: More complex report intervals, Up: Period expressions 15.5.3 Multiple weekday intervals --------------------------------- This special form is also supported: * 'every WEEKDAYNAME,WEEKDAYNAME,...' (full or three-letter english weekday names, case insensitive) Also, 'weekday' and 'weekendday' are shorthand for 'mon,tue,wed,thu,fri' and 'sat,sun'. This is mainly intended for use with '--forecast', to generate periodic transactions on arbitrary days of the week. It may be less useful with '-p', since it divides each week into subperiods of unequal length, which is unusual. (Related: #1632) Examples: '-p "every dates will be Mon, Wed, Fri; periods will be mon,wed,fri"' Mon-Tue, Wed-Thu, Fri-Sun '-p "every dates will be Mon, Tue, Wed, Thu, Fri; periods will weekday"' be Mon, Tue, Wed, Thu, Fri-Sun '-p "every dates will be Sat, Sun; periods will be Sat, Sun-Fri weekendday"'  File: hledger.info, Node: Depth, Next: Queries, Prev: Time periods, Up: Top 16 Depth ******** With the '--depth NUM' option (short form: '-NUM'), reports will show accounts only to the specified depth, hiding deeper subaccounts. Use this when you want a summary with less detail. This flag has the same effect as a 'depth:' query argument: 'depth:2', '--depth=2' or '-2' are equivalent.  File: hledger.info, Node: Queries, Next: Pivoting, Prev: Depth, Up: Top 17 Queries ********** One of hledger's strengths is being able to quickly report on a precise subset of your data. Most hledger commands accept query arguments, to restrict their scope. Multiple query terms can be provided to build up a more complex query. * By default, a query term is interpreted as a case-insensitive substring pattern for matching account names: 'car:fuel' 'dining groceries' * Patterns containing spaces or other special characters must be enclosed in single or double quotes: ''personal care'' * These patterns are actually regular expressions, so you can add regexp metacharacters for more precision (see "Regular expressions" above for details): ''^expenses\b'' ''food$'' ''fuel|repair'' ''accounts (payable|receivable)'' * To match something other than account name, add one of the query type prefixes described in "Query types" below: 'date:202312-' 'status:' 'desc:amazon' 'cur:USD' 'cur:\\$' 'amt:'>0'' * Add a 'not:' prefix to negate a term: 'not:status:'*'' 'not:desc:'opening|closing'' 'not:cur:USD' * Terms with different types are AND-ed, terms with the same type are OR-ed (mostly; see "Combining query terms" below). The following query: 'date:2022 desc:amazon desc:amzn' is interpreted as: _date is in 2022 AND ( transaction description contains "amazon" OR "amzn" )_ * Menu: * Query types:: * Combining query terms:: * Queries and command options:: * Queries and valuation:: * Querying with account aliases:: * Querying with cost or value::  File: hledger.info, Node: Query types, Next: Combining query terms, Up: Queries 17.1 Query types ================ Here are the types of query term available. Remember these can also be prefixed with *'not:'* to convert them into a negative match. *'acct:REGEX'* or *'REGEX'* Match account names containing this case insensitive regular expression. This is the default query type, so we usually don't bother writing the "acct:" prefix. *'amt:N, amt:N, amt:>=N'* Match postings with a single-commodity amount equal to, less than, or greater than N. (Postings with multi-commodity amounts are not tested and will always match.) The comparison has two modes: if N is preceded by a + or - sign (or is 0), the two signed numbers are compared. Otherwise, the absolute magnitudes are compared, ignoring sign. *'code:REGEX'* Match by transaction code (eg check number). *'cur:REGEX'* Match postings or transactions including any amounts whose currency/commodity symbol is fully matched by REGEX. (For a partial match, use '.*REGEX.*'). Note, to match special characters which are regex-significant, you need to escape them with '\'. And for characters which are significant to your shell you may need one more level of escaping. So eg to match the dollar sign: 'hledger print cur:\\$'. *'desc:REGEX'* Match transaction descriptions. *'date:PERIODEXPR'* Match dates (or with the '--date2' flag, secondary dates) within the specified period. PERIODEXPR is a period expression with no report interval. Examples: 'date:2016', 'date:thismonth', 'date:2/1-2/15', 'date:2021-07-27..nextquarter'. *'date2:PERIODEXPR'* Match secondary dates within the specified period (independent of the '--date2' flag). *'depth:N'* Match (or display, depending on command) accounts at or above this depth. *'expr:"TERM AND NOT (TERM OR TERM)"'* (eg) Match with a boolean combination of queries (which must be enclosed in quotes). See Combining query terms below. *'note:REGEX'* Match transaction notes (the part of the description right of '|', or the whole description if there's no '|'). *'payee:REGEX'* Match transaction payee/payer names (the part of the description left of '|', or the whole description if there's no '|'). *'real:, real:0'* Match real or virtual postings respectively. *'status:, status:!, status:*'* Match unmarked, pending, or cleared transactions respectively. *'type:TYPECODES'* Match by account type (see Declaring accounts > Account types). 'TYPECODES' is one or more of the single-letter account type codes 'ALERXCV', case insensitive. Note 'type:A' and 'type:E' will also match their respective subtypes 'C' (Cash) and 'V' (Conversion). Certain kinds of account alias can disrupt account types, see Rewriting accounts > Aliases and account types. *'tag:REGEX[=REGEX]'* Match by tag name, and optionally also by tag value. (To match only by value, use 'tag:.=REGEX'.) When querying by tag, note that: * Accounts also inherit the tags of their parent accounts * Postings also inherit the tags of their account and their transaction * Transactions also acquire the tags of their postings. (*'inacct:ACCTNAME'* A special query term used automatically in hledger-web only: tells hledger-web to show the transaction register for an account.)  File: hledger.info, Node: Combining query terms, Next: Queries and command options, Prev: Query types, Up: Queries 17.2 Combining query terms ========================== When given multiple space-separated query terms, most commands select things which match: * any of the description terms AND * any of the account terms AND * any of the status terms AND * all the other terms. The print command is a little different, showing transactions which: * match any of the description terms AND * have any postings matching any of the positive account terms AND * have no postings matching any of the negative account terms AND * match all the other terms. We also support more complex boolean queries with the 'expr:' prefix. This allows one to combine queries using one of three operators: AND, OR, and NOT, where NOT is different syntax for 'not:'. Examples of such queries are: * Match transactions with 'cool' in the description AND with the 'A' tag 'expr:"desc:cool AND tag:A"' * Match transactions NOT to the 'expenses:food' account OR with the 'A' tag 'expr:"NOT expenses:food OR tag:A"' * Match transactions NOT involving the 'expenses:food' account OR with the 'A' tag AND involving the 'expenses:drink' account. (the AND is implicitly added by space-separation, following the rules above) 'expr:"expenses:food OR (tag:A expenses:drink)"'  File: hledger.info, Node: Queries and command options, Next: Queries and valuation, Prev: Combining query terms, Up: Queries 17.3 Queries and command options ================================ Some queries can also be expressed as command-line options: 'depth:2' is equivalent to '--depth 2', 'date:2023' is equivalent to '-p 2023', etc. When you mix command options and query arguments, generally the resulting query is their intersection.  File: hledger.info, Node: Queries and valuation, Next: Querying with account aliases, Prev: Queries and command options, Up: Queries 17.4 Queries and valuation ========================== When amounts are converted to other commodities in cost or value reports, 'cur:' and 'amt:' match the old commodity symbol and the old amount quantity, not the new ones (except in hledger 1.22.0 where it's reversed, see #1625).  File: hledger.info, Node: Querying with account aliases, Next: Querying with cost or value, Prev: Queries and valuation, Up: Queries 17.5 Querying with account aliases ================================== When account names are rewritten with '--alias' or 'alias', note that 'acct:' will match either the old or the new account name.  File: hledger.info, Node: Querying with cost or value, Prev: Querying with account aliases, Up: Queries 17.6 Querying with cost or value ================================ When amounts are converted to other commodities in cost or value reports, note that 'cur:' matches the new commodity symbol, and not the old one, and 'amt:' matches the new quantity, and not the old one. Note: this changed in hledger 1.22, previously it was the reverse, see the discussion at #1625.  File: hledger.info, Node: Pivoting, Next: Generating data, Prev: Queries, Up: Top 18 Pivoting *********** Normally, hledger groups and sums amounts within each account. The '--pivot FIELD' option substitutes some other transaction field for account names, causing amounts to be grouped and summed by that field's value instead. FIELD can be any of the transaction fields 'acct', 'status', 'code', 'desc', 'payee', 'note', or a tag name. When pivoting on a tag and a posting has multiple values of that tag, only the first value is displayed. Values containing 'colon:separated:parts' will be displayed hierarchically, like account names. Multiple, colon-delimited fields can be pivoted simultaneously, generating a hierarchical account name. Some examples: 2016/02/16 Yearly Dues Payment assets:bank account 2 EUR income:dues -2 EUR ; member: John Doe, kind: Lifetime Normal balance report showing account names: $ hledger balance 2 EUR assets:bank account -2 EUR income:dues -------------------- 0 Pivoted balance report, using member: tag values instead: $ hledger balance --pivot member 2 EUR -2 EUR John Doe -------------------- 0 One way to show only amounts with a member: value (using a query): $ hledger balance --pivot member tag:member=. -2 EUR John Doe -------------------- -2 EUR Another way (the acct: query matches against the pivoted "account name"): $ hledger balance --pivot member acct:. -2 EUR John Doe -------------------- -2 EUR Hierarchical reports can be generated with multiple pivots: $ hledger balance Income:Dues --pivot kind:member -2 EUR Lifetime:John Doe -------------------- -2 EUR  File: hledger.info, Node: Generating data, Next: Forecasting, Prev: Pivoting, Up: Top 19 Generating data ****************** hledger has several features for generating data, such as: * Periodic transaction rules can generate single or repeating transactions following a template. These are usually dated in the future, eg to help with forecasting. They are activated by the '--forecast' option. * The balance command's '--budget' option uses these same periodic rules to generate goals for the budget report. * Auto posting rules can generate extra postings on certain matched transactions. They are always applied to forecast transactions; with the '--auto' flag they are applied to transactions recorded in the journal as well. * The '--infer-equity' flag infers missing conversion equity postings from @/@@ costs. And the inverse '--infer-costs' flag infers missing @/@@ costs from conversion equity postings. Generated data of this kind is temporary, existing only at report time. But you can see it in the output of 'hledger print', and you can save that to your journal, in effect converting it from temporary generated data to permanent recorded data. This could be useful as a data entry aid. If you are wondering what data is being generated and why, add the '--verbose-tags' flag. In 'hledger print' output you will see extra tags like 'generated-transaction', 'generated-posting', and 'modified' on generated/modified data. Also, even without '--verbose-tags', generated data always has equivalen hidden tags (with an underscore prefix), so eg you could match generated transactions with 'tag:_generated-transaction'.  File: hledger.info, Node: Forecasting, Next: Budgeting, Prev: Generating data, Up: Top 20 Forecasting ************** Forecasting, or speculative future reporting, can be useful for estimating future balances, or for exploring different future scenarios. The simplest and most flexible way to do it with hledger is to manually record a bunch of future-dated transactions. You could keep these in a separate 'future.journal' and include that with '-f' only when you want to see them. * Menu: * --forecast:: * Inspecting forecast transactions:: * Forecast reports:: * Forecast tags:: * Forecast period in detail:: * Forecast troubleshooting::  File: hledger.info, Node: --forecast, Next: Inspecting forecast transactions, Up: Forecasting 20.1 -forecast ============== There is another way: with the '--forecast' option, hledger can generate temporary "forecast transactions" for reporting purposes, according to periodic transaction rules defined in the journal. Each rule can generate multiple recurring transactions, so by changing one rule you can change many forecasted transactions. Forecast transactions usually start after ordinary transactions end. By default, they begin after your latest-dated ordinary transaction, or today, whichever is later, and they end six months from today. (The exact rules are a little more complicated, and are given below.) This is the "forecast period", which need not be the same as the report period. You can override it - eg to forecast farther into the future, or to force forecast transactions to overlap your ordinary transactions - by giving the -forecast option a period expression argument, like '--forecast=..2099' or '--forecast=2023-02-15..'. Note that the '=' is required.  File: hledger.info, Node: Inspecting forecast transactions, Next: Forecast reports, Prev: --forecast, Up: Forecasting 20.2 Inspecting forecast transactions ===================================== 'print' is the best command for inspecting and troubleshooting forecast transactions. Eg: ~ monthly from 2022-12-20 rent assets:bank:checking expenses:rent $1000 $ hledger print --forecast --today=2023/4/21 2023-05-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-06-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-07-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-08-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-09-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 Here there are no ordinary transactions, so the forecasted transactions begin on the first occurence after today's date. (You won't normally use '--today'; it's just to make these examples reproducible.)  File: hledger.info, Node: Forecast reports, Next: Forecast tags, Prev: Inspecting forecast transactions, Up: Forecasting 20.3 Forecast reports ===================== Forecast transactions affect all reports, as you would expect. Eg: $ hledger areg rent --forecast --today=2023/4/21 Transactions in expenses:rent and subaccounts: 2023-05-20 rent as:ba:checking $1000 $1000 2023-06-20 rent as:ba:checking $1000 $2000 2023-07-20 rent as:ba:checking $1000 $3000 2023-08-20 rent as:ba:checking $1000 $4000 2023-09-20 rent as:ba:checking $1000 $5000 $ hledger bal -M expenses --forecast --today=2023/4/21 Balance changes in 2023-05-01..2023-09-30: || May Jun Jul Aug Sep ===============++=================================== expenses:rent || $1000 $1000 $1000 $1000 $1000 ---------------++----------------------------------- || $1000 $1000 $1000 $1000 $1000  File: hledger.info, Node: Forecast tags, Next: Forecast period in detail, Prev: Forecast reports, Up: Forecasting 20.4 Forecast tags ================== Forecast transactions generated by -forecast have a hidden tag, '_generated-transaction'. So if you ever need to match forecast transactions, you could use 'tag:_generated-transaction' (or just 'tag:generated') in a query. For troubleshooting, you can add the '--verbose-tags' flag. Then, visible 'generated-transaction' tags will be added also, so you can view them with the 'print' command. Their value indicates which periodic rule was responsible.  File: hledger.info, Node: Forecast period in detail, Next: Forecast troubleshooting, Prev: Forecast tags, Up: Forecasting 20.5 Forecast period, in detail =============================== Forecast start/end dates are chosen so as to do something useful by default in almost all situations, while also being flexible. Here are (with luck) the exact rules, to help with troubleshooting: The forecast period starts on: * the later of * the start date in the periodic transaction rule * the start date in '--forecast''s argument * otherwise (if those are not available): the later of * the report start date specified with '-b'/'-p'/'date:' * the day after the latest ordinary transaction in the journal * otherwise (if none of these are available): today. The forecast period ends on: * the earlier of * the end date in the periodic transaction rule * the end date in '--forecast''s argument * otherwise: the report end date specified with '-e'/'-p'/'date:' * otherwise: 180 days (~6 months) from today.  File: hledger.info, Node: Forecast troubleshooting, Prev: Forecast period in detail, Up: Forecasting 20.6 Forecast troubleshooting ============================= When -forecast is not doing what you expect, one of these tips should help: * Remember to use the '--forecast' option. * Remember to have at least one periodic transaction rule in your journal. * Test with 'print --forecast'. * Check for typos or too-restrictive start/end dates in your periodic transaction rule. * Leave at least 2 spaces between the rule's period expression and description fields. * Check for future-dated ordinary transactions suppressing forecasted transactions. * Try setting explicit report start and/or end dates with '-b', '-e', '-p' or 'date:' * Try adding the '-E' flag to encourage display of empty periods/zero transactions. * Try setting explicit forecast start and/or end dates with '--forecast=START..END' * Consult Forecast period, in detail, above. * Check inside the engine: add '--debug=2' (eg).  File: hledger.info, Node: Budgeting, Next: Cost reporting, Prev: Forecasting, Up: Top 21 Budgeting ************ With the balance command's '--budget' report, each periodic transaction rule generates recurring budget goals in specified accounts, and goals and actual performance can be compared. See the balance command's doc below. You can generate budget goals and forecast transactions at the same time, from the same or different periodic transaction rules: 'hledger bal -M --budget --forecast ...' See also: Budgeting and Forecasting.  File: hledger.info, Node: Cost reporting, Next: Value reporting, Prev: Budgeting, Up: Top 22 Cost reporting ***************** In some transactions - for example a currency conversion, or a purchase or sale of stock - one commodity is exchanged for another. In these transactions there is a conversion rate, also called the cost (when buying) or selling price (when selling). In hledger docs we just say "cost", for convenience; feel free to mentally translate to "conversion rate" or "selling price" if helpful. * Menu: * Recording costs:: * Reporting at cost:: * Equity conversion postings:: * Inferring equity conversion postings:: * Combining costs and equity conversion postings:: * Requirements for detecting equity conversion postings:: * Infer cost and equity by default ?::  File: hledger.info, Node: Recording costs, Next: Reporting at cost, Up: Cost reporting 22.1 Recording costs ==================== We'll explore several ways of recording transactions involving costs. These are also summarised at hledger Cookbook > Cost notation. Costs can be recorded explicitly in the journal, using the '@ UNITCOST' or '@@ TOTALCOST' notation described in Journal > Costs: *Variant 1* 2022-01-01 assets:dollars $-135 assets:euros €100 @ $1.35 ; $1.35 per euro (unit cost) *Variant 2* 2022-01-01 assets:dollars $-135 assets:euros €100 @@ $135 ; $135 total cost Typically, writing the unit cost (variant 1) is preferable; it can be more effort, requiring more attention to decimal digits; but it reveals the per-unit cost basis, and makes stock sales easier. Costs can also be left implicit, and hledger will infer the cost that is consistent with a balanced transaction: *Variant 3* 2022-01-01 assets:dollars $-135 assets:euros €100 Here, hledger will attach a '@@ €100' cost to the first amount (you can see it with 'hledger print -x'). This form looks convenient, but there are downsides: * It sacrifices some error checking. For example, if you accidentally wrote €10 instead of €100, hledger would not be able to detect the mistake. * It is sensitive to the order of postings - if they were reversed, a different entry would be inferred and reports would be different. * The per-unit cost basis is not easy to read. So generally this kind of entry is not recommended. You can make sure you have none of these by using '-s' (strict mode), or by running 'hledger check balanced'.  File: hledger.info, Node: Reporting at cost, Next: Equity conversion postings, Prev: Recording costs, Up: Cost reporting 22.2 Reporting at cost ====================== Now when you add the '-B'/'--cost' flag to reports ("B" is from Ledger's -B/-basis/-cost flag), any amounts which have been annotated with costs will be converted to their cost's commodity (in the report output). Ie they will be displayed "at cost" or "at sale price". Some things to note: * Costs are attached to specific posting amounts in specific transactions, and once recorded they do not change. This contrasts with market prices, which are ambient and fluctuating. * Conversion to cost is performed before conversion to market value (described below).  File: hledger.info, Node: Equity conversion postings, Next: Inferring equity conversion postings, Prev: Reporting at cost, Up: Cost reporting 22.3 Equity conversion postings =============================== There is a problem with the entries above - they are not conventional Double Entry Bookkeeping (DEB) notation, and because of the "magical" transformation of one commodity into another, they cause an imbalance in the Accounting Equation. This shows up as a non-zero grand total in balance reports like 'hledger bse'. For most hledger users, this doesn't matter in practice and can safely be ignored ! But if you'd like to learn more, keep reading. Conventional DEB uses an extra pair of equity postings to balance the transaction. Of course you can do this in hledger as well: *Variant 4* 2022-01-01 assets:dollars $-135 assets:euros €100 equity:conversion $135 equity:conversion €-100 Now the transaction is perfectly balanced according to standard DEB, and 'hledger bse''s total will not be disrupted. And, hledger can still infer the cost for cost reporting, but it's not done by default - you must add the '--infer-costs' flag like so: $ hledger print --infer-costs 2022-01-01 one hundred euros purchased at $1.35 each assets:dollars $-135 @@ €100 assets:euros €100 equity:conversion $135 equity:conversion €-100 $ hledger bal --infer-costs -B €-100 assets:dollars €100 assets:euros -------------------- 0 Here are some downsides of this kind of entry: * The per-unit cost basis is not easy to read. * Instead of '-B' you must remember to type '-B --infer-costs'. * '--infer-costs' works only where hledger can identify the two equity:conversion postings and match them up with the two non-equity postings. So writing the journal entry in a particular format becomes more important. More on this below.  File: hledger.info, Node: Inferring equity conversion postings, Next: Combining costs and equity conversion postings, Prev: Equity conversion postings, Up: Cost reporting 22.4 Inferring equity conversion postings ========================================= Can we go in the other direction ? Yes, if you have transactions written with the @/@@ cost notation, hledger can infer the missing equity postings, if you add the '--infer-equity' flag. Eg: 2022-01-01 assets:dollars -$135 assets:euros €100 @ $1.35 $ hledger print --infer-equity 2022-01-01 assets:dollars $-135 assets:euros €100 @ $1.35 equity:conversion:$-€:€ €-100 equity:conversion:$-€:$ $135.00 The equity account names will be "equity:conversion:A-B:A" and "equity:conversion:A-B:B" where A is the alphabetically first commodity symbol. You can customise the "equity:conversion" part by declaring an account with the 'V'/'Conversion' account type.  File: hledger.info, Node: Combining costs and equity conversion postings, Next: Requirements for detecting equity conversion postings, Prev: Inferring equity conversion postings, Up: Cost reporting 22.5 Combining costs and equity conversion postings =================================================== Finally, you can use both the @/@@ cost notation and equity postings at the same time. This in theory gives the best of all worlds - preserving the accounting equation, revealing the per-unit cost basis, and providing more flexibility in how you write the entry: *Variant 5* 2022-01-01 one hundred euros purchased at $1.35 each assets:dollars $-135 equity:conversion $135 equity:conversion €-100 assets:euros €100 @ $1.35 All the other variants above can (usually) be rewritten to this final form with: $ hledger print -x --infer-costs --infer-equity Downsides: * This was added in hledger-1.29 and is still somewhat experimental. * The precise format of the journal entry becomes more important. If hledger can't detect and match up the cost and equity postings, it will give a transaction balancing error. * The add command does not yet accept this kind of entry (#2056). * This is the most verbose form.  File: hledger.info, Node: Requirements for detecting equity conversion postings, Next: Infer cost and equity by default ?, Prev: Combining costs and equity conversion postings, Up: Cost reporting 22.6 Requirements for detecting equity conversion postings ========================================================== '--infer-costs' has certain requirements (unlike '--infer-equity', which always works). It will infer costs only in transactions with: * Two non-equity postings, in different commodities. Their order is significant: the cost will be added to the first of them. * Two postings to equity conversion accounts, next to one another, which balance the two non-equity postings. This balancing is checked to the same precision (number of decimal places) used in the conversion posting's amount. Equity conversion accounts are: * any accounts declared with account type 'V'/'Conversion', or their subaccounts * otherwise, accounts named 'equity:conversion', 'equity:trade', or 'equity:trading', or their subaccounts. And multiple such four-posting groups can coexist within a single transaction. When '--infer-costs' fails, it does not infer a cost in that transaction, and does not raise an error (ie, it infers costs where it can). Reading variant 5 journal entries, combining cost notation and equity postings, has all the same requirements. When reading such an entry fails, hledger raises an "unbalanced transaction" error.  File: hledger.info, Node: Infer cost and equity by default ?, Prev: Requirements for detecting equity conversion postings, Up: Cost reporting 22.7 Infer cost and equity by default ? ======================================= Should '--infer-costs' and '--infer-equity' be enabled by default ? Try using them always, eg with a shell alias: alias h="hledger --infer-equity --infer-costs" and let us know what problems you find.  File: hledger.info, Node: Value reporting, Next: PART 4 COMMANDS, Prev: Cost reporting, Up: Top 23 Value reporting ****************** Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), and/or to market value (using some market price on a certain date). This is controlled by the '--value=TYPE[,COMMODITY]' option, which will be described below. We also provide the simpler '-V' and '-X COMMODITY' options, and often one of these is all you need: * Menu: * -V Value:: * -X Value in specified commodity:: * Valuation date:: * Finding market price:: * --infer-market-prices market prices from transactions:: * Valuation commodity:: * Simple valuation examples:: * --value Flexible valuation:: * More valuation examples:: * Interaction of valuation and queries:: * Effect of valuation on reports::  File: hledger.info, Node: -V Value, Next: -X Value in specified commodity, Up: Value reporting 23.1 -V: Value ============== The '-V/--market' flag converts amounts to market value in their default _valuation commodity_, using the market prices in effect on the _valuation date(s)_, if any. More on these in a minute.  File: hledger.info, Node: -X Value in specified commodity, Next: Valuation date, Prev: -V Value, Up: Value reporting 23.2 -X: Value in specified commodity ===================================== The '-X/--exchange=COMM' option is like '-V', except you tell it which currency you want to convert to, and it tries to convert everything to that.  File: hledger.info, Node: Valuation date, Next: Finding market price, Prev: -X Value in specified commodity, Up: Value reporting 23.3 Valuation date =================== Market prices can change from day to day. hledger will use the prices on a particular valuation date (or on more than one date). By default hledger uses "end" dates for valuation. More specifically: * For single period reports (including normal print and register reports): * If an explicit report end date is specified, that is used * Otherwise the latest transaction date or P directive date is used (even if it's in the future) * For multiperiod reports, each period is valued on its last day. This can be customised with the -value option described below, which can select either "then", "end", "now", or "custom" dates. (Note, this has a bug in hledger-ui <=1.31: turning on valuation with the 'V' key always resets it to "end".)  File: hledger.info, Node: Finding market price, Next: --infer-market-prices market prices from transactions, Prev: Valuation date, Up: Value reporting 23.4 Finding market price ========================= To convert a commodity A to its market value in another commodity B, hledger looks for a suitable market price (exchange rate) as follows, in this order of preference: 1. A _declared market price_ or _inferred market price_: A's latest market price in B on or before the valuation date as declared by a P directive, or (with the '--infer-market-prices' flag) inferred from costs. 2. A _reverse market price_: the inverse of a declared or inferred market price from B to A. 3. A _forward chain of market prices_: a synthetic price formed by combining the shortest chain of "forward" (only 1 above) market prices, leading from A to B. 4. _Any chain of market prices_: a chain of any market prices, including both forward and reverse prices (1 and 2 above), leading from A to B. There is a limit to the length of these price chains; if hledger reaches that length without finding a complete chain or exhausting all possibilities, it will give up (with a "gave up" message visible in '--debug=2' output). That limit is currently 1000. Amounts for which no suitable market price can be found, are not converted.  File: hledger.info, Node: --infer-market-prices market prices from transactions, Next: Valuation commodity, Prev: Finding market price, Up: Value reporting 23.5 -infer-market-prices: market prices from transactions ========================================================== Normally, market value in hledger is fully controlled by, and requires, P directives in your journal. Since adding and updating those can be a chore, and since transactions usually take place at close to market value, why not use the recorded costs as additional market prices (as Ledger does) ? Adding the '--infer-market-prices' flag to '-V', '-X' or '--value' enables this. So for example, 'hledger bs -V --infer-market-prices' will get market prices both from P directives and from transactions. If both occur on the same day, the P directive takes precedence. There is a downside: value reports can sometimes be affected in confusing/undesired ways by your journal entries. If this happens to you, read all of this Value reporting section carefully, and try adding '--debug' or '--debug=2' to troubleshoot. '--infer-market-prices' can infer market prices from: * multicommodity transactions with explicit prices ('@'/'@@') * multicommodity transactions with implicit prices (no '@', two commodities, unbalanced). (With these, the order of postings matters. 'hledger print -x' can be useful for troubleshooting.) * multicommodity transactions with equity postings, if cost is inferred with '--infer-costs'. There is a limitation (bug) currently: when a valuation commodity is not specified, prices inferred with '--infer-market-prices' do not help select a default valuation commodity, as 'P' prices would. So conversion might not happen because no valuation commodity was detected ('--debug=2' will show this). To be safe, specify the valuation commmodity, eg: * '-X EUR --infer-market-prices', not '-V --infer-market-prices' * '--value=then,EUR --infer-market-prices', not '--value=then --infer-market-prices' Signed costs and market prices can be confusing. For reference, here is the current behaviour, since hledger 1.25. (If you think it should work differently, see #1870.) 2022-01-01 Positive Unit prices a A 1 b B -1 @ A 1 2022-01-01 Positive Total prices a A 1 b B -1 @@ A 1 2022-01-02 Negative unit prices a A 1 b B 1 @ A -1 2022-01-02 Negative total prices a A 1 b B 1 @@ A -1 2022-01-03 Double Negative unit prices a A -1 b B -1 @ A -1 2022-01-03 Double Negative total prices a A -1 b B -1 @@ A -1 All of the transactions above are considered balanced (and on each day, the two transactions are considered equivalent). Here are the market prices inferred for B: $ hledger -f- --infer-market-prices prices P 2022-01-01 B A 1 P 2022-01-01 B A 1.0 P 2022-01-02 B A -1 P 2022-01-02 B A -1.0 P 2022-01-03 B A -1 P 2022-01-03 B A -1.0  File: hledger.info, Node: Valuation commodity, Next: Simple valuation examples, Prev: --infer-market-prices market prices from transactions, Up: Value reporting 23.6 Valuation commodity ======================== *When you specify a valuation commodity ('-X COMM' or '--value TYPE,COMM'):* hledger will convert all amounts to COMM, wherever it can find a suitable market price (including by reversing or chaining prices). *When you leave the valuation commodity unspecified ('-V' or '--value TYPE'):* For each commodity A, hledger picks a default valuation commodity as follows, in this order of preference: 1. The price commodity from the latest P-declared market price for A on or before valuation date. 2. The price commodity from the latest P-declared market price for A on any date. (Allows conversion to proceed when there are inferred prices before the valuation date.) 3. If there are no P directives at all (any commodity or date) and the '--infer-market-prices' flag is used: the price commodity from the latest transaction-inferred price for A on or before valuation date. This means: * If you have P directives, they determine which commodities '-V' will convert, and to what. * If you have no P directives, and use the '--infer-market-prices' flag, costs determine it. Amounts for which no valuation commodity can be found are not converted.  File: hledger.info, Node: Simple valuation examples, Next: --value Flexible valuation, Prev: Valuation commodity, Up: Value reporting 23.7 Simple valuation examples ============================== Here are some quick examples of '-V': ; one euro is worth this many dollars from nov 1 P 2016/11/01 € $1.10 ; purchase some euros on nov 3 2016/11/3 assets:euros €100 assets:checking ; the euro is worth fewer dollars by dec 21 P 2016/12/21 € $1.03 How many euros do I have ? $ hledger -f t.j bal -N euros €100 assets:euros What are they worth at end of nov 3 ? $ hledger -f t.j bal -N euros -V -e 2016/11/4 $110.00 assets:euros What are they worth after 2016/12/21 ? (no report end date specified, defaults to today) $ hledger -f t.j bal -N euros -V $103.00 assets:euros  File: hledger.info, Node: --value Flexible valuation, Next: More valuation examples, Prev: Simple valuation examples, Up: Value reporting 23.8 -value: Flexible valuation =============================== '-V' and '-X' are special cases of the more general '--value' option: --value=TYPE[,COMM] TYPE is then, end, now or YYYY-MM-DD. COMM is an optional commodity symbol. Shows amounts converted to: - default valuation commodity (or COMM) using market prices at posting dates - default valuation commodity (or COMM) using market prices at period end(s) - default valuation commodity (or COMM) using current market prices - default valuation commodity (or COMM) using market prices at some date The TYPE part selects cost or value and valuation date: '--value=then' Convert amounts to their value in the default valuation commodity, using market prices on each posting's date. '--value=end' Convert amounts to their value in the default valuation commodity, using market prices on the last day of the report period (or if unspecified, the journal's end date); or in multiperiod reports, market prices on the last day of each subperiod. '--value=now' Convert amounts to their value in the default valuation commodity using current market prices (as of when report is generated). '--value=YYYY-MM-DD' Convert amounts to their value in the default valuation commodity using market prices on this date. To select a different valuation commodity, add the optional ',COMM' part: a comma, then the target commodity's symbol. Eg: *'--value=now,EUR'*. hledger will do its best to convert amounts to this commodity, deducing market prices as described above.  File: hledger.info, Node: More valuation examples, Next: Interaction of valuation and queries, Prev: --value Flexible valuation, Up: Value reporting 23.9 More valuation examples ============================ Here are some examples showing the effect of '--value', as seen with 'print': P 2000-01-01 A 1 B P 2000-02-01 A 2 B P 2000-03-01 A 3 B P 2000-04-01 A 4 B 2000-01-01 (a) 1 A @ 5 B 2000-02-01 (a) 1 A @ 6 B 2000-03-01 (a) 1 A @ 7 B Show the cost of each posting: $ hledger -f- print --cost 2000-01-01 (a) 5 B 2000-02-01 (a) 6 B 2000-03-01 (a) 7 B Show the value as of the last day of the report period (2000-02-29): $ hledger -f- print --value=end date:2000/01-2000/03 2000-01-01 (a) 2 B 2000-02-01 (a) 2 B With no report period specified, that shows the value as of the last day of the journal (2000-03-01): $ hledger -f- print --value=end 2000-01-01 (a) 3 B 2000-02-01 (a) 3 B 2000-03-01 (a) 3 B Show the current value (the 2000-04-01 price is still in effect today): $ hledger -f- print --value=now 2000-01-01 (a) 4 B 2000-02-01 (a) 4 B 2000-03-01 (a) 4 B Show the value on 2000/01/15: $ hledger -f- print --value=2000-01-15 2000-01-01 (a) 1 B 2000-02-01 (a) 1 B 2000-03-01 (a) 1 B  File: hledger.info, Node: Interaction of valuation and queries, Next: Effect of valuation on reports, Prev: More valuation examples, Up: Value reporting 23.10 Interaction of valuation and queries ========================================== When matching postings based on queries in the presence of valuation, the following happens. 1. The query is separated into two parts: 1. the currency ('cur:') or amount ('amt:'). 2. all other parts. 2. The postings are matched to the currency and amount queries based on pre-valued amounts. 3. Valuation is applied to the postings. 4. The postings are matched to the other parts of the query based on post-valued amounts. See: 1625  File: hledger.info, Node: Effect of valuation on reports, Prev: Interaction of valuation and queries, Up: Value reporting 23.11 Effect of valuation on reports ==================================== Here is a reference for how valuation is supposed to affect each part of hledger's reports (and a glossary). (It's wide, you'll have to scroll sideways.) It may be useful when troubleshooting. If you find problems, please report them, ideally with a reproducible example. Related: #329, #1083. Report '-B', '-V', '-X' '--value=then' '--value=end''--value=DATE', type '--cost' '--value=now' ------------------------------------------------------------------------------ *print* posting cost value at value at posting value at value amounts report end date report or at or today journal DATE/today end balance unchanged unchanged unchanged unchanged unchanged assertions/assignments *register* starting cost value at valued at day value at value balance report or each historical report or at (-H) journal posting was made journal DATE/today end end starting cost value at valued at day value at value balance day before each historical day before at (-H) report or posting was made report or DATE/today with journal journal report start start interval posting cost value at value at posting value at value amounts report or date report or at journal journal DATE/today end end summary summarised value at sum of postings value at value posting cost period in interval, period at amounts ends valued at ends DATE/today with interval start report interval running sum/average sum/average sum/average of sum/average sum/average total/averageof of displayed values of of displayed displayed displayed displayed values values values values *balance (bs, bse, cf, is)* balance sums of value at value at posting value at value changes costs report end date report or at or today journal DATE/today of sums of end of of postings sums of sums postings of postings budget like like like balance like like amounts balance balance changes balances balance (-budget) changes changes changes grand sum of sum of sum of displayed sum of sum of total displayed displayed valued displayed displayed values values values values *balance (bs, bse, cf, is) with report interval* starting sums of value at sums of values value at sums balances costs of report of postings report of (-H) postings start of before report start of postings before sums of start at sums of before report all respective all report start postings posting dates postings start before before report report start start balance sums of same as sums of values balance value changes costs of -value=end of postings in change in at (bal, postings period at each DATE/today is, bs in period respective period, of -change, posting dates valued at sums cf period of -change) ends postings end sums of same as sums of values period end value balances costs of -value=end of postings from balances, at (bal -H, postings before period valued at DATE/today is -H, from start to period period of bs, cf) before end at ends sums report respective of start to posting dates postings period end budget like like like balance like like amounts balance balance changes/end balances balance (-budget) changes/end changes/end balances changes/end balances balances balances row sums, sums, sums, averages sums, sums, totals, averages averages of displayed averages averages row of of values of of averages displayed displayed displayed displayed (-T, -A) values values values values column sums of sums of sums of sums of sums totals displayed displayed displayed values displayed of values values values displayed values grand sum, sum, sum, average of sum, sum, total, average of average of column totals average of average grand column column column of average totals totals totals column totals '--cumulative' is omitted to save space, it works like '-H' but with a zero starting balance. *Glossary:* _cost_ calculated using price(s) recorded in the transaction(s). _value_ market value using available market price declarations, or the unchanged amount if no conversion rate can be found. _report start_ the first day of the report period specified with -b or -p or date:, otherwise today. _report or journal start_ the first day of the report period specified with -b or -p or date:, otherwise the earliest transaction date in the journal, otherwise today. _report end_ the last day of the report period specified with -e or -p or date:, otherwise today. _report or journal end_ the last day of the report period specified with -e or -p or date:, otherwise the latest transaction date in the journal, otherwise today. _report interval_ a flag (-D/-W/-M/-Q/-Y) or period expression that activates the report's multi-period mode (whether showing one or many subperiods).  File: hledger.info, Node: PART 4 COMMANDS, Next: PART 5 COMMON TASKS, Prev: Value reporting, Up: Top 24 PART 4: COMMANDS ******************* * Menu: * Commands overview:: * accounts:: * activity:: * add:: * aregister:: * balance:: * balancesheet:: * balancesheetequity:: * cashflow:: * check:: * close:: * codes:: * commodities:: * demo:: * descriptions:: * diff:: * files:: * help:: * import:: * incomestatement:: * notes:: * payees:: * prices:: * print:: * register:: * rewrite:: * roi:: * stats:: * tags:: * test::  File: hledger.info, Node: Commands overview, Next: accounts, Up: PART 4 COMMANDS 24.1 Commands overview ====================== Here are the built-in commands: * Menu: * DATA ENTRY:: * DATA CREATION:: * DATA MANAGEMENT:: * REPORTS FINANCIAL:: * REPORTS VERSATILE:: * REPORTS BASIC:: * HELP:: * ADD-ONS::  File: hledger.info, Node: DATA ENTRY, Next: DATA CREATION, Up: Commands overview 24.1.1 DATA ENTRY ----------------- These data entry commands are the only ones which can modify your journal file. * add - add transactions using terminal prompts * import - add new transactions from other files, eg CSV files  File: hledger.info, Node: DATA CREATION, Next: DATA MANAGEMENT, Prev: DATA ENTRY, Up: Commands overview 24.1.2 DATA CREATION -------------------- * close - generate balance-zeroing/restoring transactions * rewrite - generate auto postings, like print -auto  File: hledger.info, Node: DATA MANAGEMENT, Next: REPORTS FINANCIAL, Prev: DATA CREATION, Up: Commands overview 24.1.3 DATA MANAGEMENT ---------------------- * check - check for various kinds of error in the data * diff - compare account transactions in two journal files  File: hledger.info, Node: REPORTS FINANCIAL, Next: REPORTS VERSATILE, Prev: DATA MANAGEMENT, Up: Commands overview 24.1.4 REPORTS, FINANCIAL ------------------------- * aregister (areg) - show transactions in a particular account * balancesheet (bs) - show assets, liabilities and net worth * balancesheetequity (bse) - show assets, liabilities and equity * cashflow (cf) - show changes in liquid assets * incomestatement (is) - show revenues and expenses  File: hledger.info, Node: REPORTS VERSATILE, Next: REPORTS BASIC, Prev: REPORTS FINANCIAL, Up: Commands overview 24.1.5 REPORTS, VERSATILE ------------------------- * balance (bal) - show balance changes, end balances, budgets, gains.. * print - show transactions or export journal data * register (reg) - show postings in one or more accounts & running total * roi - show return on investments  File: hledger.info, Node: REPORTS BASIC, Next: HELP, Prev: REPORTS VERSATILE, Up: Commands overview 24.1.6 REPORTS, BASIC --------------------- * accounts - show account names * activity - show bar charts of posting counts per period * codes - show transaction codes * commodities - show commodity/currency symbols * descriptions - show transaction descriptions * files - show input file paths * notes - show note parts of transaction descriptions * payees - show payee parts of transaction descriptions * prices - show market prices * stats - show journal statistics * tags - show tag names * test - run self tests  File: hledger.info, Node: HELP, Next: ADD-ONS, Prev: REPORTS BASIC, Up: Commands overview 24.1.7 HELP ----------- * help - show the hledger manual with info/man/pager * demo - show small hledger demos in the terminal  File: hledger.info, Node: ADD-ONS, Prev: HELP, Up: Commands overview 24.1.8 ADD-ONS -------------- And here are some typical add-on commands. Some of these are installed by the hledger-install script. If installed, they will appear in hledger's commands list: * ui - run hledger's terminal UI * web - run hledger's web UI * iadd - add transactions using a TUI (currently hard to build) * interest - generate interest transactions * stockquotes - download market prices from AlphaVantage * Scripts and add-ons - check-fancyassertions, edit, fifo, git, move, pijul, plot, and more.. Next, each command is described in detail, in alphabetical order.  File: hledger.info, Node: accounts, Next: activity, Prev: Commands overview, Up: PART 4 COMMANDS 24.2 accounts ============= Show account names. This command lists account names. By default it shows all known accounts, either used in transactions or declared with account directives. With query arguments, only matched account names and account names referenced by matched postings are shown. Or it can show just the used accounts ('--used'/'-u'), the declared accounts ('--declared'/'-d'), the accounts declared but not used ('--unused'), the accounts used but not declared ('--undeclared'), or the first account matched by an account name pattern, if any ('--find'). It shows a flat list by default. With '--tree', it uses indentation to show the account hierarchy. In flat mode you can add '--drop N' to omit the first few account name components. Account names can be depth-clipped with 'depth:N' or '--depth N' or '-N'. With '--types', it also shows each account's type, if it's known. (See Declaring accounts > Account types.) With '--positions', it also shows the file and line number of each account's declaration, if any, and the account's overall declaration order; these may be useful when troubleshooting account display order. With '--directives', it adds the 'account' keyword, showing valid account directives which can be pasted into a journal file. This is useful together with '--undeclared' when updating your account declarations to satisfy 'hledger check accounts'. The '--find' flag can be used to look up a single account name, in the same way that the 'aregister' command does. It returns the alphanumerically-first matched account name, or if none can be found, it fails with a non-zero exit code. Examples: $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts $ hledger accounts --undeclared --directives >> $LEDGER_FILE $ hledger check accounts  File: hledger.info, Node: activity, Next: add, Prev: accounts, Up: PART 4 COMMANDS 24.3 activity ============= Show an ascii barchart of posting counts per interval. The activity command displays an ascii histogram showing transaction counts by day, week, month or other reporting interval (by day is the default). With query arguments, it counts only matched transactions. Examples: $ hledger activity --quarterly 2008-01-01 ** 2008-04-01 ******* 2008-07-01 2008-10-01 **  File: hledger.info, Node: add, Next: aregister, Prev: activity, Up: PART 4 COMMANDS 24.4 add ======== Prompt for transactions and add them to the journal. Any arguments will be used as default inputs for the first N prompts. Many hledger users edit their journals directly with a text editor, or generate them from CSV. For more interactive data entry, there is the 'add' command, which prompts interactively on the console for new transactions, and appends them to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also 'import'). To use it, just run 'hledger add' and follow the prompts. You can add as many transactions as you like; when you are finished, enter '.' or press control-d or control-c to exit. Features: * add tries to provide useful defaults, using the most similar (by description) recent transaction (filtered by the query, if any) as a template. * You can also set the initial defaults with command line arguments. * Readline-style edit keys can be used during data entry. * The tab key will auto-complete whenever possible - accounts, payees/descriptions, dates ('yesterday', 'today', 'tomorrow'). If the input area is empty, it will insert the default value. * If the journal defines a default commodity, it will be added to any bare numbers entered. * A parenthesised transaction code may be entered following a date. * Comments and tags may be entered following a description or amount. * If you make a mistake, enter '<' at any prompt to go one step backward. * Input prompts are displayed in a different colour when the terminal supports it. Example (see https://hledger.org/add.html for a detailed tutorial): $ hledger add Adding transactions to journal file /src/hledger/examples/sample.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control-d or control-c. Date [2015/05/22]: Description: supermarket Account 1: expenses:food Amount 1: $10 Account 2: assets:checking Amount 2 [$-10.0]: Account 3 (or . or enter to finish this transaction): . 2015/05/22 supermarket expenses:food $10 assets:checking $-10.0 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl-D/ctrl-C to quit) Date [2015/05/22]: $ On Microsoft Windows, the add command makes sure that no part of the file path ends with a period, as that would cause problems (#1056).  File: hledger.info, Node: aregister, Next: balance, Prev: add, Up: PART 4 COMMANDS 24.5 aregister ============== (areg) Show the transactions and running historical balance of a single account, with each transaction displayed as one line. 'aregister' shows the overall transactions affecting a particular account (and any subaccounts). Each report line represents one transaction in this account. Transactions before the report start date are always included in the running balance ('--historical' mode is always on). This is a more "real world", bank-like view than the 'register' command (which shows individual postings, possibly from multiple accounts, not necessarily in historical mode). As a quick rule of thumb: - use 'aregister' for reviewing and reconciling real-world asset/liability accounts - use 'register' for reviewing detailed revenues/expenses. 'aregister' requires one argument: the account to report on. You can write either the full account name, or a case-insensitive regular expression which will select the alphabetically first matched account. When there are multiple matches, the alphabetically-first choice can be surprising; eg if you have 'assets:per:checking 1' and 'assets:biz:checking 2' accounts, 'hledger areg checking' would select 'assets:biz:checking 2'. It's just a convenience to save typing, so if in doubt, write the full account name, or a distinctive substring that matches uniquely. Transactions involving subaccounts of this account will also be shown. 'aregister' ignores depth limits, so its final total will always match a balance report with similar arguments. Any additional arguments form a query which will filter the transactions shown. Note some queries will disturb the running balance, causing it to be different from the account's real-world running balance. An example: this shows the transactions and historical running balance during july, in the first account whose name contains "checking": $ hledger areg checking date:jul Each 'aregister' line item shows: * the transaction's date (or the relevant posting's date if different, see below) * the names of all the other account(s) involved in this transaction (probably abbreviated) * the total change to this account's balance from this transaction * the account's historical running balance after this transaction. Transactions making a net change of zero are not shown by default; add the '-E/--empty' flag to show them. For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the '--align-all' flag. This command also supports the output destination and output format options. The output formats supported are 'txt', 'csv', 'tsv', and 'json'. * Menu: * aregister and posting dates::  File: hledger.info, Node: aregister and posting dates, Up: aregister 24.5.1 aregister and posting dates ---------------------------------- aregister always shows one line (and date and amount) per transaction. But sometimes transactions have postings with different dates. Also, not all of a transaction's postings may be within the report period. To resolve this, aregister shows the earliest of the transaction's date and posting dates that is in-period, and the sum of the in-period postings. In other words it will show a combined line item with just the earliest date, and the running balance will (temporarily, until the transaction's last posting) be inaccurate. Use 'register -H' if you need to see the individual postings. There is also a '--txn-dates' flag, which filters strictly by transaction date, ignoring posting dates. This too can cause an inaccurate running balance.  File: hledger.info, Node: balance, Next: balancesheet, Prev: aregister, Up: PART 4 COMMANDS 24.6 balance ============ (bal) Show accounts and their balances. 'balance' is one of hledger's oldest and most versatile commands, for listing account balances, balance changes, values, value changes and more, during one time period or many. Generally it shows a table, with rows representing accounts, and columns representing periods. Note there are some higher-level variants of the 'balance' command with convenient defaults, which can be simpler to use: 'balancesheet', 'balancesheetequity', 'cashflow' and 'incomestatement'. When you need more control, then use 'balance'. * Menu: * balance features:: * Simple balance report:: * Balance report line format:: * Filtered balance report:: * List or tree mode:: * Depth limiting:: * Dropping top-level accounts:: * Showing declared accounts:: * Sorting by amount:: * Percentages:: * Multi-period balance report:: * Balance change end balance:: * Balance report types:: * Budget report:: * Balance report layout:: * Useful balance reports::  File: hledger.info, Node: balance features, Next: Simple balance report, Up: balance 24.6.1 balance features ----------------------- Here's a quick overview of the 'balance' command's features, followed by more detailed descriptions and examples. Many of these work with the higher-level commands as well. 'balance' can show.. * accounts as a list ('-l') or a tree ('-t') * optionally depth-limited ('-[1-9]') * sorted by declaration order and name, or by amount ..and their.. * balance changes (the default) * or actual and planned balance changes ('--budget') * or value of balance changes ('-V') * or change of balance values ('--valuechange') * or unrealised capital gain/loss ('--gain') * or postings count ('--count') ..in.. * one time period (the whole journal period by default) * or multiple periods ('-D', '-W', '-M', '-Q', '-Y', '-p INTERVAL') ..either.. * per period (the default) * or accumulated since report start date ('--cumulative') * or accumulated since account creation ('--historical/-H') ..possibly converted to.. * cost ('--value=cost[,COMM]'/'--cost'/'-B') * or market value, as of transaction dates ('--value=then[,COMM]') * or at period ends ('--value=end[,COMM]') * or now ('--value=now') * or at some other date ('--value=YYYY-MM-DD') ..with.. * totals ('-T'), averages ('-A'), percentages ('-%'), inverted sign ('--invert') * rows and columns swapped ('--transpose') * another field used as account name ('--pivot') * custom-formatted line items (single-period reports only) ('--format') * commodities displayed on the same line or multiple lines ('--layout') This command supports the output destination and output format options, with output formats 'txt', 'csv', 'tsv', 'json', and (multi-period reports only:) 'html'. In 'txt' output in a colour-supporting terminal, negative amounts are shown in red. The '--related'/'-r' flag shows the balance of the _other_ postings in the transactions of the postings which would normally be shown.  File: hledger.info, Node: Simple balance report, Next: Balance report line format, Prev: balance features, Up: balance 24.6.2 Simple balance report ---------------------------- With no arguments, 'balance' shows a list of all accounts and their change of balance - ie, the sum of posting amounts, both inflows and outflows - during the entire period of the journal. ("Simple" here means just one column of numbers, covering a single period. You can also have multi-period reports, described later.) For real-world accounts, these numbers will normally be their end balance at the end of the journal period; more on this below. Accounts are sorted by declaration order if any, and then alphabetically by account name. For instance (using examples/sample.journal): $ hledger -f examples/sample.journal bal $1 assets:bank:saving $-2 assets:cash $1 expenses:food $1 expenses:supplies $-1 income:gifts $-1 income:salary $1 liabilities:debts -------------------- 0 Accounts with a zero balance (and no non-zero subaccounts, in tree mode - see below) are hidden by default. Use '-E/--empty' to show them (revealing 'assets:bank:checking' here): $ hledger -f examples/sample.journal bal -E 0 assets:bank:checking $1 assets:bank:saving $-2 assets:cash $1 expenses:food $1 expenses:supplies $-1 income:gifts $-1 income:salary $1 liabilities:debts -------------------- 0 The total of the amounts displayed is shown as the last line, unless '-N'/'--no-total' is used.  File: hledger.info, Node: Balance report line format, Next: Filtered balance report, Prev: Simple balance report, Up: balance 24.6.3 Balance report line format --------------------------------- For single-period balance reports displayed in the terminal (only), you can use '--format FMT' to customise the format and content of each line. Eg: $ hledger -f examples/sample.journal balance --format "%20(account) %12(total)" assets $-1 bank:saving $1 cash $-2 expenses $2 food $1 supplies $1 income $-2 gifts $-1 salary $-1 liabilities:debts $1 --------------------------------- 0 The FMT format string specifies the formatting applied to each account/balance pair. It may contain any suitable text, with data fields interpolated like so: '%[MIN][.MAX](FIELDNAME)' * MIN pads with spaces to at least this width (optional) * MAX truncates at this width (optional) * FIELDNAME must be enclosed in parentheses, and can be one of: * 'depth_spacer' - a number of spaces equal to the account's depth, or if MIN is specified, MIN * depth spaces. * 'account' - the account's name * 'total' - the account's balance/posted total, right justified Also, FMT can begin with an optional prefix to control how multi-commodity amounts are rendered: * '%_' - render on multiple lines, bottom-aligned (the default) * '%^' - render on multiple lines, top-aligned * '%,' - render on one line, comma-separated There are some quirks. Eg in one-line mode, '%(depth_spacer)' has no effect, instead '%(account)' has indentation built in. Experimentation may be needed to get pleasing results. Some example formats: * '%(total)' - the account's total * '%-20.20(account)' - the account's name, left justified, padded to 20 characters and clipped at 20 characters * '%,%-50(account) %25(total)' - account name padded to 50 characters, total padded to 20 characters, with multiple commodities rendered on one line * '%20(total) %2(depth_spacer)%-(account)' - the default format for the single-column balance report  File: hledger.info, Node: Filtered balance report, Next: List or tree mode, Prev: Balance report line format, Up: balance 24.6.4 Filtered balance report ------------------------------ You can show fewer accounts, a different time period, totals from cleared transactions only, etc. by using query arguments or options to limit the postings being matched. Eg: $ hledger -f examples/sample.journal bal --cleared assets date:200806 $-2 assets:cash -------------------- $-2  File: hledger.info, Node: List or tree mode, Next: Depth limiting, Prev: Filtered balance report, Up: balance 24.6.5 List or tree mode ------------------------ By default, or with '-l/--flat', accounts are shown as a flat list with their full names visible, as in the examples above. With '-t/--tree', the account hierarchy is shown, with subaccounts' "leaf" names indented below their parent: $ hledger -f examples/sample.journal balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 Notes: * "Boring" accounts are combined with their subaccount for more compact output, unless '--no-elide' is used. Boring accounts have no balance of their own and just one subaccount (eg 'assets:bank' and 'liabilities' above). * All balances shown are "inclusive", ie including the balances from all subaccounts. Note this means some repetition in the output, which requires explanation when sharing reports with non-plaintextaccounting-users. A tree mode report's final total is the sum of the top-level balances shown, not of all the balances shown. * Each group of sibling accounts (ie, under a common parent) is sorted separately.  File: hledger.info, Node: Depth limiting, Next: Dropping top-level accounts, Prev: List or tree mode, Up: balance 24.6.6 Depth limiting --------------------- With a 'depth:NUM' query, or '--depth NUM' option, or just '-NUM' (eg: '-3') balance reports will show accounts only to the specified depth, hiding the deeper subaccounts. This can be useful for getting an overview without too much detail. Account balances at the depth limit always include the balances from any deeper subaccounts (even in list mode). Eg, limiting to depth 1: $ hledger -f examples/sample.journal balance -1 $-1 assets $2 expenses $-2 income $1 liabilities -------------------- 0  File: hledger.info, Node: Dropping top-level accounts, Next: Showing declared accounts, Prev: Depth limiting, Up: balance 24.6.7 Dropping top-level accounts ---------------------------------- You can also hide one or more top-level account name parts, using '--drop NUM'. This can be useful for hiding repetitive top-level account names: $ hledger -f examples/sample.journal bal expenses --drop 1 $1 food $1 supplies -------------------- $2  File: hledger.info, Node: Showing declared accounts, Next: Sorting by amount, Prev: Dropping top-level accounts, Up: balance 24.6.8 Showing declared accounts -------------------------------- With '--declared', accounts which have been declared with an account directive will be included in the balance report, even if they have no transactions. (Since they will have a zero balance, you will also need '-E/--empty' to see them.) More precisely, _leaf_ declared accounts (with no subaccounts) will be included, since those are usually the more useful in reports. The idea of this is to be able to see a useful "complete" balance report, even when you don't have transactions in all of your declared accounts yet.  File: hledger.info, Node: Sorting by amount, Next: Percentages, Prev: Showing declared accounts, Up: balance 24.6.9 Sorting by amount ------------------------ With '-S/--sort-amount', accounts with the largest (most positive) balances are shown first. Eg: 'hledger bal expenses -MAS' shows your biggest averaged monthly expenses first. When more than one commodity is present, they will be sorted by the alphabetically earliest commodity first, and then by subsequent commodities (if an amount is missing a commodity, it is treated as 0). Revenues and liability balances are typically negative, however, so '-S' shows these in reverse order. To work around this, you can add '--invert' to flip the signs. (Or, use one of the higher-level reports, which flip the sign automatically. Eg: 'hledger incomestatement -MAS').  File: hledger.info, Node: Percentages, Next: Multi-period balance report, Prev: Sorting by amount, Up: balance 24.6.10 Percentages ------------------- With '-%/--percent', balance reports show each account's value expressed as a percentage of the (column) total. Note it is not useful to calculate percentages if the amounts in a column have mixed signs. In this case, make a separate report for each sign, eg: $ hledger bal -% amt:`>0` $ hledger bal -% amt:`<0` Similarly, if the amounts in a column have mixed commodities, convert them to one commodity with '-B', '-V', '-X' or '--value', or make a separate report for each commodity: $ hledger bal -% cur:\\$ $ hledger bal -% cur:€  File: hledger.info, Node: Multi-period balance report, Next: Balance change end balance, Prev: Percentages, Up: balance 24.6.11 Multi-period balance report ----------------------------------- With a report interval (set by the '-D/--daily', '-W/--weekly', '-M/--monthly', '-Q/--quarterly', '-Y/--yearly', or '-p/--period' flag), 'balance' shows a tabular report, with columns representing successive time periods (and a title): $ hledger -f examples/sample.journal bal --quarterly income expenses -E Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 ===================++================================= expenses:food || 0 $1 0 0 expenses:supplies || 0 $1 0 0 income:gifts || 0 $-1 0 0 income:salary || $-1 0 0 0 -------------------++--------------------------------- || $-1 $1 0 0 Notes: * The report's start/end dates will be expanded, if necessary, to fully encompass the displayed subperiods (so that the first and last subperiods have the same duration as the others). * Leading and trailing periods (columns) containing all zeroes are not shown, unless '-E/--empty' is used. * Accounts (rows) containing all zeroes are not shown, unless '-E/--empty' is used. * Amounts with many commodities are shown in abbreviated form, unless '--no-elide' is used. _(experimental)_ * Average and/or total columns can be added with the '-A/--average' and '-T/--row-total' flags. * The '--transpose' flag can be used to exchange rows and columns. * The '--pivot FIELD' option causes a different transaction field to be used as "account name". See PIVOTING. Multi-period reports with many periods can be too wide for easy viewing in the terminal. Here are some ways to handle that: * Hide the totals row with '-N/--no-total' * Convert to a single currency with '-V' * Maximize the terminal window * Reduce the terminal's font size * View with a pager like less, eg: 'hledger bal -D --color=yes | less -RS' * Output as CSV and use a CSV viewer like visidata ('hledger bal -D -O csv | vd -f csv'), Emacs' csv-mode ('M-x csv-mode, C-c C-a'), or a spreadsheet ('hledger bal -D -o a.csv && open a.csv') * Output as HTML and view with a browser: 'hledger bal -D -o a.html && open a.html'  File: hledger.info, Node: Balance change end balance, Next: Balance report types, Prev: Multi-period balance report, Up: balance 24.6.12 Balance change, end balance ----------------------------------- It's important to be clear on the meaning of the numbers shown in balance reports. Here is some terminology we use: A *_balance change_* is the net amount added to, or removed from, an account during some period. An *_end balance_* is the amount accumulated in an account as of some date (and some time, but hledger doesn't store that; assume end of day in your timezone). It is the sum of previous balance changes. We call it a *_historical end balance_* if it includes all balance changes since the account was created. For a real world account, this means it will match the "historical record", eg the balances reported in your bank statements or bank web UI. (If they are correct!) In general, balance changes are what you want to see when reviewing revenues and expenses, and historical end balances are what you want to see when reviewing or reconciling asset, liability and equity accounts. 'balance' shows balance changes by default. To see accurate historical end balances: 1. Initialise account starting balances with an "opening balances" transaction (a transfer from equity to the account), unless the journal covers the account's full lifetime. 2. Include all of of the account's prior postings in the report, by not specifying a report start date, or by using the '-H/--historical' flag. ('-H' causes report start date to be ignored when summing postings.)  File: hledger.info, Node: Balance report types, Next: Budget report, Prev: Balance change end balance, Up: balance 24.6.13 Balance report types ---------------------------- The balance command is quite flexible; here is the full detail on how to control what it reports. If the following seems complicated, don't worry - this is for advanced reporting, and it does take time and experimentation to get familiar with all the report modes. There are three important option groups: 'hledger balance [CALCULATIONTYPE] [ACCUMULATIONTYPE] [VALUATIONTYPE] ...' * Menu: * Calculation type:: * Accumulation type:: * Valuation type:: * Combining balance report types::  File: hledger.info, Node: Calculation type, Next: Accumulation type, Up: Balance report types 24.6.13.1 Calculation type .......................... The basic calculation to perform for each table cell. It is one of: * '--sum' : sum the posting amounts (*default*) * '--budget' : sum the amounts, but also show the budget goal amount (for each account/period) * '--valuechange' : show the change in period-end historical balance values (caused by deposits, withdrawals, and/or market price fluctuations) * '--gain' : show the unrealised capital gain/loss, (the current valued balance minus each amount's original cost) * '--count' : show the count of postings  File: hledger.info, Node: Accumulation type, Next: Valuation type, Prev: Calculation type, Up: Balance report types 24.6.13.2 Accumulation type ........................... How amounts should accumulate across report periods. Another way to say it: which time period's postings should contribute to each cell's calculation. It is one of: * '--change' : calculate with postings from column start to column end, ie "just this column". Typically used to see revenues/expenses. (*default for balance, incomestatement*) * '--cumulative' : calculate with postings from report start to column end, ie "previous columns plus this column". Typically used to show changes accumulated since the report's start date. Not often used. * '--historical/-H' : calculate with postings from journal start to column end, ie "all postings from before report start date until this column's end". Typically used to see historical end balances of assets/liabilities/equity. (*default for balancesheet, balancesheetequity, cashflow*)  File: hledger.info, Node: Valuation type, Next: Combining balance report types, Prev: Accumulation type, Up: Balance report types 24.6.13.3 Valuation type ........................ Which kind of value or cost conversion should be applied, if any, before displaying the report. It is one of: * no valuation type : don't convert to cost or value (*default*) * '--value=cost[,COMM]' : convert amounts to cost (then optionally to some other commodity) * '--value=then[,COMM]' : convert amounts to market value on transaction dates * '--value=end[,COMM]' : convert amounts to market value on period end date(s) (*default with '--valuechange', '--gain'*) * '--value=now[,COMM]' : convert amounts to market value on today's date * '--value=YYYY-MM-DD[,COMM]' : convert amounts to market value on another date or one of the equivalent simpler flags: * '-B/--cost' : like -value=cost (though, note -cost and -value are independent options which can both be used at once) * '-V/--market' : like -value=end * '-X COMM/--exchange COMM' : like -value=end,COMM See Cost reporting and Value reporting for more about these.  File: hledger.info, Node: Combining balance report types, Prev: Valuation type, Up: Balance report types 24.6.13.4 Combining balance report types ........................................ Most combinations of these options should produce reasonable reports, but if you find any that seem wrong or misleading, let us know. The following restrictions are applied: * '--valuechange' implies '--value=end' * '--valuechange' makes '--change' the default when used with the 'balancesheet'/'balancesheetequity' commands * '--cumulative' or '--historical' disables '--row-total/-T' For reference, here is what the combinations of accumulation and valuation show: Valuation:>no valuation '--value= then' '--value= end' '--value= Accumulation:v YYYY-MM-DD /now' ----------------------------------------------------------------------------- '--change'change in sum of period-end DATE-value period posting-date value of of change in market values change in period in period period '--cumulative'change from sum of period-end DATE-value report start to posting-date value of of change period end market values change from from report from report report start start to start to period to period end period end end '--historicalchange from sum of period-end DATE-value /-H' journal start posting-date value of of change to period end market values change from from journal (historical end from journal journal start start to balance) start to period to period end period end end  File: hledger.info, Node: Budget report, Next: Balance report layout, Prev: Balance report types, Up: balance 24.6.14 Budget report --------------------- The '--budget' report type is like a regular balance report, but with two main differences: * Budget goals and performance percentages are also shown, in brackets * Accounts which don't have budget goals are hidden by default. This is useful for comparing planned and actual income, expenses, time usage, etc. Periodic transaction rules are used to define budget goals. For example, here's a periodic rule defining monthly goals for bus travel and food expenses: ;; Budget ~ monthly (expenses:bus) $30 (expenses:food) $400 After recording some actual expenses, ;; Two months worth of expenses 2017-11-01 income $-1950 expenses:bus $35 expenses:food:groceries $310 expenses:food:dining $42 expenses:movies $38 assets:bank:checking 2017-12-01 income $-2100 expenses:bus $53 expenses:food:groceries $380 expenses:food:dining $32 expenses:gifts $100 assets:bank:checking we can see a budget report like this: $ hledger bal -M --budget Budget performance in 2017-11-01..2017-12-31: || Nov Dec ===============++============================================ || $-425 $-565 expenses || $425 [ 99% of $430] $565 [131% of $430] expenses:bus || $35 [117% of $30] $53 [177% of $30] expenses:food || $352 [ 88% of $400] $412 [103% of $400] ---------------++-------------------------------------------- || 0 [ 0% of $430] 0 [ 0% of $430] This is "goal-based budgeting"; you define goals for accounts and periods, often recurring, and hledger shows performance relative to the goals. This contrasts with "envelope budgeting", which is more detailed and strict - useful when cash is tight, but also quite a bit more work. https://plaintextaccounting.org/Budgeting has more on this topic. * Menu: * Using the budget report:: * Budget date surprises:: * Selecting budget goals:: * Budgeting vs forecasting::  File: hledger.info, Node: Using the budget report, Next: Budget date surprises, Up: Budget report 24.6.14.1 Using the budget report ................................. Historically this report has been confusing and fragile. hledger's version should be relatively robust and intuitive, but you may still find surprises. Here are more notes to help with learning and troubleshooting. * In the above example, 'expenses:bus' and 'expenses:food' are shown because they have budget goals during the report period. * Their parent 'expenses' is also shown, with budget goals aggregated from the children. * The subaccounts 'expenses:food:groceries' and 'expenses:food:dining' are not shown since they have no budget goal of their own, but they contribute to 'expenses:food''s actual amount. * Unbudgeted accounts 'expenses:movies' and 'expenses:gifts' are also not shown, but they contribute to 'expenses''s actual amount. * The other unbudgeted accounts 'income' and 'assets:bank:checking' are grouped as ''. * '--depth' or 'depth:' can be used to limit report depth in the usual way (but will not reveal unbudgeted subaccounts). * Amounts are always inclusive of subaccounts (even in '-l/--list' mode). * Numbers displayed in a -budget report will not always agree with the totals, because of hidden unbudgeted accounts; this is normal. '-E/--empty' can be used to reveal the hidden accounts. * In the periodic rules used for setting budget goals, unbalanced postings are convenient. * You can filter budget reports with the usual queries, eg to focus on particular accounts. It's common to restrict them to just expenses. (The '' account is occasionally hard to exclude; this is because of date surprises, discussed below.) * When you have multiple currencies, you may want to convert them to one ('-X COMM --infer-market-prices') and/or show just one at a time ('cur:COMM'). If you do need to show multiple currencies at once, '--layout bare' can be helpful. * You can "roll over" amounts (actual and budgeted) to the next period with '--cumulative'. See also: https://hledger.org/budgeting.html.  File: hledger.info, Node: Budget date surprises, Next: Selecting budget goals, Prev: Using the budget report, Up: Budget report 24.6.14.2 Budget date surprises ............................... With small data, or when starting out, some of the generated budget goal transaction dates might fall outside the report periods. Eg with the following journal and report, the first period appears to have no 'expenses:food' budget. (Also the '' account should be excluded by the 'expenses' query, but isn't.): ~ monthly in 2020 (expenses:food) $500 2020-01-15 expenses:food $400 assets:checking $ hledger bal --budget expenses Budget performance in 2020-01-15: || 2020-01-15 ===============++==================== || $400 expenses:food || 0 [ 0% of $500] ---------------++-------------------- || $400 [80% of $500] In this case, the budget goal transactions are generated on first days of of month (this can be seen with 'hledger print --forecast tag:generated expenses'). Whereas the report period defaults to just the 15th day of january (this can be seen from the report table's column headings). To fix this kind of thing, be more explicit about the report period (and/or the periodic rules' dates). In this case, adding '-b 2020' does the trick.  File: hledger.info, Node: Selecting budget goals, Next: Budgeting vs forecasting, Prev: Budget date surprises, Up: Budget report 24.6.14.3 Selecting budget goals ................................ By default, the budget report uses all available periodic transaction rules to generate goals. This includes rules with a different report interval from your report. Eg if you have daily, weekly and monthly periodic rules, all of these will contribute to the goals in a monthly budget report. You can select a subset of periodic rules by providing an argument to the '--budget' flag. '--budget=DESCPAT' will match all periodic rules whose description contains DESCPAT, a case-insensitive substring (not a regular expression or query). This means you can give your periodic rules descriptions (remember that two spaces are needed between period expression and description), and then select from multiple budgets defined in your journal.  File: hledger.info, Node: Budgeting vs forecasting, Prev: Selecting budget goals, Up: Budget report 24.6.14.4 Budgeting vs forecasting .................................. '--budget' and '--forecast' both use the periodic transaction rules in the journal to generate temporary transactions for reporting purposes. However they are separate features - though you can use both at the same time if you want. Here are some differences between them: 1. '--budget' is a command-specific option; it selects the *budget report*. '--forecast' is a general option; *forecasting works with all reports*. 2. '--budget' uses *all periodic rules*; '--budget=DESCPAT' uses *just the rules matched* by DESCPAT. '--forecast' uses *all periodic rules*. 3. '--budget''s budget goal transactions are invisible, except that they produce *goal amounts*. '--forecast''s forecast transactions are visible, and *appear in reports*. 4. '--budget' generates budget goal transactions *throughout the report period*, optionally restricted by periods specified in the periodic transaction rules. '--forecast' generates forecast transactions from *after the last regular transaction*, to the end of the report period; while '--forecast=PERIODEXPR' generates them *throughout the specified period*; both optionally restricted by periods specified in the periodic transaction rules.  File: hledger.info, Node: Balance report layout, Next: Useful balance reports, Prev: Budget report, Up: balance 24.6.15 Balance report layout ----------------------------- The '--layout' option affects how balance reports show multi-commodity amounts and commodity symbols, which can improve readability. It can also normalise the data for easy consumption by other programs. It has four possible values: * '--layout=wide[,WIDTH]': commodities are shown on a single line, optionally elided to WIDTH * '--layout=tall': each commodity is shown on a separate line * '--layout=bare': commodity symbols are in their own column, amounts are bare numbers * '--layout=tidy': data is normalised to easily-consumed "tidy" form, with one row per data value Here are the '--layout' modes supported by each output format; note only CSV output supports all of them: - txt csv html json sql --------------------------------------- wide Y Y Y tall Y Y Y bare Y Y Y tidy Y Examples: * Wide layout. With many commodities, reports can be very wide: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=wide Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++==================================================================================================================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, -98.12 USD, 10.00 VEA, 18.00 VHT -11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT ------------------++-------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------- || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, -98.12 USD, 10.00 VEA, 18.00 VHT -11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT * Limited wide layout. A width limit reduces the width, but some commodities will be hidden: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=wide,32 Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++=========================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. -11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. ------------------++--------------------------------------------------------------------------------------------------------------------------- || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. -11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. * Tall layout. Each commodity gets a new line (may be different in each column), and account names are repeated: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=tall Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++================================================== Assets:US:ETrade || 10.00 ITOT 70.00 GLD -11.00 ITOT 70.00 GLD Assets:US:ETrade || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT Assets:US:ETrade || 12.00 VEA -98.12 USD 14.00 VEA 5120.50 USD Assets:US:ETrade || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA Assets:US:ETrade || 18.00 VHT 294.00 VHT ------------------++-------------------------------------------------- || 10.00 ITOT 70.00 GLD -11.00 ITOT 70.00 GLD || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT || 12.00 VEA -98.12 USD 14.00 VEA 5120.50 USD || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA || 18.00 VHT 294.00 VHT * Bare layout. Commodity symbols are kept in one column, each commodity gets its own report row, account names are repeated: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=bare Balance changes in 2012-01-01..2014-12-31: || Commodity 2012 2013 2014 Total ==================++============================================= Assets:US:ETrade || GLD 0 70.00 0 70.00 Assets:US:ETrade || ITOT 10.00 18.00 -11.00 17.00 Assets:US:ETrade || USD 337.18 -98.12 4881.44 5120.50 Assets:US:ETrade || VEA 12.00 10.00 14.00 36.00 Assets:US:ETrade || VHT 106.00 18.00 170.00 294.00 ------------------++--------------------------------------------- || GLD 0 70.00 0 70.00 || ITOT 10.00 18.00 -11.00 17.00 || USD 337.18 -98.12 4881.44 5120.50 || VEA 12.00 10.00 14.00 36.00 || VHT 106.00 18.00 170.00 294.00 * Bare layout also affects CSV output, which is useful for producing data that is easier to consume, eg for making charts: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -O csv --layout=bare "account","commodity","balance" "Assets:US:ETrade","GLD","70.00" "Assets:US:ETrade","ITOT","17.00" "Assets:US:ETrade","USD","5120.50" "Assets:US:ETrade","VEA","36.00" "Assets:US:ETrade","VHT","294.00" "total","GLD","70.00" "total","ITOT","17.00" "total","USD","5120.50" "total","VEA","36.00" "total","VHT","294.00" * Note: bare layout will sometimes display an extra row for the no-symbol commodity, because of zero amounts (hledger treats zeroes as commodity-less, usually). This can break 'hledger-bar' confusingly (workaround: add a 'cur:' query to exclude the no-symbol row). * Tidy layout produces normalised "tidy data", where every variable has its own column and each row represents a single data point. See https://cran.r-project.org/web/packages/tidyr/vignettes/tidy-data.html for more. This is the easiest kind of data for other software to consume. Here's how it looks: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -Y -O csv --layout=tidy "account","period","start_date","end_date","commodity","value" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","GLD","0" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","ITOT","10.00" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","USD","337.18" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","VEA","12.00" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","VHT","106.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","GLD","70.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","ITOT","18.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","USD","-98.12" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","VEA","10.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","VHT","18.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","GLD","0" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","ITOT","-11.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","USD","4881.44" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","VEA","14.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","VHT","170.00"  File: hledger.info, Node: Useful balance reports, Prev: Balance report layout, Up: balance 24.6.16 Useful balance reports ------------------------------ Some frequently used 'balance' options/reports are: * 'bal -M revenues expenses' Show revenues/expenses in each month. Also available as the 'incomestatement' command. * 'bal -M -H assets liabilities' Show historical asset/liability balances at each month end. Also available as the 'balancesheet' command. * 'bal -M -H assets liabilities equity' Show historical asset/liability/equity balances at each month end. Also available as the 'balancesheetequity' command. * 'bal -M assets not:receivable' Show changes to liquid assets in each month. Also available as the 'cashflow' command. Also: * 'bal -M expenses -2 -SA' Show monthly expenses summarised to depth 2 and sorted by average amount. * 'bal -M --budget expenses' Show monthly expenses and budget goals. * 'bal -M --valuechange investments' Show monthly change in market value of investment assets. * 'bal investments --valuechange -D date:lastweek amt:'>1000' -STA [--invert]' Show top gainers [or losers] last week  File: hledger.info, Node: balancesheet, Next: balancesheetequity, Prev: balance, Up: PART 4 COMMANDS 24.7 balancesheet ================= (bs) This command displays a balance sheet, showing historical ending balances of asset and liability accounts. (To see equity as well, use the balancesheetequity command.) Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the 'Asset', 'Cash' or 'Liability' type (see account types). Or if no such accounts are declared, it shows top-level accounts named 'asset' or 'liability' (case insensitive, plurals allowed) and their subaccounts. Example: $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 This command is a higher-level variant of the 'balance' command, and supports many of that command's features, such as multi-period reports. It is similar to 'hledger balance -H assets liabilities', but with smarter account detection, and liabilities displayed with their sign flipped. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'tsv', 'html', and (experimental) 'json'.  File: hledger.info, Node: balancesheetequity, Next: cashflow, Prev: balancesheet, Up: PART 4 COMMANDS 24.8 balancesheetequity ======================= (bse) This command displays a balance sheet, showing historical ending balances of asset, liability and equity accounts. Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the 'Asset', 'Cash', 'Liability' or 'Equity' type (see account types). Or if no such accounts are declared, it shows top-level accounts named 'asset', 'liability' or 'equity' (case insensitive, plurals allowed) and their subaccounts. Example: $ hledger balancesheetequity Balance Sheet With Equity Assets: $-2 assets $1 bank:saving $-3 cash -------------------- $-2 Liabilities: $1 liabilities:debts -------------------- $1 Equity: $1 equity:owner -------------------- $1 Total: -------------------- 0 This command is a higher-level variant of the 'balance' command, and supports many of that command's features, such as multi-period reports. It is similar to 'hledger balance -H assets liabilities equity', but with smarter account detection, and liabilities/equity displayed with their sign flipped. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'tsv', 'html', and (experimental) 'json'.  File: hledger.info, Node: cashflow, Next: check, Prev: balancesheetequity, Up: PART 4 COMMANDS 24.9 cashflow ============= (cf) This command displays a cashflow statement, showing the inflows and outflows affecting "cash" (ie, liquid, easily convertible) assets. Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the 'Cash' type (see account types). Or if no such accounts are declared, it shows accounts * under a top-level account named 'asset' (case insensitive, plural allowed) * whose name contains some variation of 'cash', 'bank', 'checking' or 'saving'. More precisely: all accounts matching this case insensitive regular expression: '^assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|currentcash)(:|$)' and their subaccounts. An example cashflow report: $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 This command is a higher-level variant of the 'balance' command, and supports many of that command's features, such as multi-period reports. It is similar to 'hledger balance assets not:fixed not:investment not:receivable', but with smarter account detection. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'tsv', 'html', and (experimental) 'json'.  File: hledger.info, Node: check, Next: close, Prev: cashflow, Up: PART 4 COMMANDS 24.10 check =========== Check for various kinds of errors in your data. hledger provides a number of built-in error checks to help prevent problems in your data. Some of these are run automatically; or, you can use this 'check' command to run them on demand, with no output and a zero exit code if all is well. Specify their names (or a prefix) as argument(s). Some examples: hledger check # basic checks hledger check -s # basic + strict checks hledger check ordereddates payees # basic + two other checks If you are an Emacs user, you can also configure flycheck-hledger to run these checks, providing instant feedback as you edit the journal. Here are the checks currently available: * Menu: * Default checks:: * Strict checks:: * Other checks:: * Custom checks:: * More about specific checks::  File: hledger.info, Node: Default checks, Next: Strict checks, Up: check 24.10.1 Default checks ---------------------- These checks are run automatically by (almost) all hledger commands: * *parseable* - data files are in a supported format, with no syntax errors and no invalid include directives. * *autobalanced* - all transactions are balanced, after converting to cost. Missing amounts and missing costs are inferred automatically where possible. * *assertions* - all balance assertions in the journal are passing. (This check can be disabled with '-I'/'--ignore-assertions'.)  File: hledger.info, Node: Strict checks, Next: Other checks, Prev: Default checks, Up: check 24.10.2 Strict checks --------------------- These additional checks are run when the '-s'/'--strict' (strict mode) flag is used. Or, they can be run by giving their names as arguments to 'check': * *balanced* - all transactions are balanced after converting to cost, without inferring missing costs. If conversion costs are required, they must be explicit. * *accounts* - all account names used by transactions have been declared * *commodities* - all commodity symbols used have been declared  File: hledger.info, Node: Other checks, Next: Custom checks, Prev: Strict checks, Up: check 24.10.3 Other checks -------------------- These checks can be run only by giving their names as arguments to 'check'. They are more specialised and not desirable for everyone: * *ordereddates* - transactions are ordered by date within each file * *payees* - all payees used by transactions have been declared * *recentassertions* - all accounts with balance assertions have a balance assertion within 7 days of their latest posting * *tags* - all tags used by transactions have been declared * *uniqueleafnames* - all account leaf names are unique  File: hledger.info, Node: Custom checks, Next: More about specific checks, Prev: Other checks, Up: check 24.10.4 Custom checks --------------------- A few more checks are are available as separate add-on commands, in https://github.com/simonmichael/hledger/tree/master/bin: * *hledger-check-tagfiles* - all tag values containing / (a forward slash) exist as file paths * *hledger-check-fancyassertions* - more complex balance assertions are passing You could make similar scripts to perform your own custom checks. See: Cookbook -> Scripting.  File: hledger.info, Node: More about specific checks, Prev: Custom checks, Up: check 24.10.5 More about specific checks ---------------------------------- 'hledger check recentassertions' will complain if any balance-asserted account has postings more than 7 days after its latest balance assertion. This aims to prevent the situation where you are regularly updating your journal, but forgetting to check your balances against the real world, then one day must dig back through months of data to find an error. It assumes that adding a balance assertion requires/reminds you to check the real-world balance. (That may not be true if you auto-generate balance assertions from bank data; in that case, I recommend to import transactions uncleared, and when you manually review and clear them, also check the latest assertion against the real-world balance.)  File: hledger.info, Node: close, Next: codes, Prev: check, Up: PART 4 COMMANDS 24.11 close =========== (equity) Generate transactions which transfer account balances to and/or from another account (typically equity). This can be useful for migrating balances to a new journal file, or for merging earnings into equity at end of accounting period. By default, it prints a transaction that zeroes out ALE accounts (asset, liability, equity accounts; this requires account types to be configured); or if ACCTQUERY is provided, the accounts matched by that. _(experimental)_ This command has four main modes, corresponding to the most common use cases: 1. With '--close' (default), it prints a "closing balances" transaction that zeroes out ALE (asset, liability, equity) accounts by default (this requires account types to be inferred or declared); or, the accounts matched by the provided ACCTQUERY arguments. 2. With '--open', it prints an opposite "opening balances" transaction that restores those balances from zero. This is similar to Ledger's equity command. 3. With '--migrate', it prints both the closing and opening transactions. This is the preferred way to migrate balances to a new file: run 'hledger close --migrate', add the closing transaction at the end of the old file, and add the opening transaction at the start of the new file. The matching closing/opening transactions cancel each other out, preserving correct balances during multi-file reporting. 4. With '--retain', it prints a "retain earnings" transaction that transfers RX (revenue and expense) balances to 'equity:retained earnings'. Businesses traditionally do this at the end of each accounting period; it is less necessary with computer-based accounting, but it could still be useful if you want to see the accounting equation (A=L+E) satisfied. In all modes, the defaults can be overridden: * the transaction descriptions can be changed with '--close-desc=DESC' and '--open-desc=DESC' * the account to transfer to/from can be changed with '--close-acct=ACCT' and '--open-acct=ACCT' * the accounts to be closed/opened can be changed with 'ACCTQUERY' (account query arguments). * the closing/opening dates can be changed with '-e DATE' (a report end date) By default just one destination/source posting will be used, with its amount left implicit. With '--x/--explicit', the amount will be shown explicitly, and if it involves multiple commodities, a separate posting will be generated for each of them (similar to 'print -x'). With '--show-costs', any amount costs are shown, with separate postings for each cost. This is currently the best way to view investment lots. If you have many currency conversion or investment transactions, it can generate very large journal entries. With '--interleaved', each individual transfer is shown with source and destination postings next to each other. This could be useful for troubleshooting. The default closing date is yesterday, or the journal's end date, whichever is later. You can change this by specifying a report end date with '-e'. The last day of the report period will be the closing date, eg '-e 2024' means "close on 2023-12-31". The opening date is always the day after the closing date. * Menu: * close and balance assertions:: * Example retain earnings:: * Example migrate balances to a new file:: * Example excluding closing/opening transactions::  File: hledger.info, Node: close and balance assertions, Next: Example retain earnings, Up: close 24.11.1 close and balance assertions ------------------------------------ Balance assertions will be generated, verifying that the accounts have been reset to zero (and then restored to their previous balances, if there is an opening transaction). These provide useful error checking, but you can ignore them temporarily with '-I', or remove them if you prefer. You probably should avoid filtering transactions by status or realness ('-C', '-R', 'status:'), or generating postings ('--auto'), with this command, since the balance assertions would depend on these. Note custom posting dates spanning the file boundary will disrupt the balance assertions: 2023-12-30 a purchase made in december, cleared in january expenses:food 5 assets:bank:checking -5 ; date: 2023-01-02 To solve that you can transfer the money to and from a temporary account, in effect splitting the multi-day transaction into two single-day transactions: ; in 2022.journal: 2022-12-30 a purchase made in december, cleared in january expenses:food 5 equity:pending -5 ; in 2023.journal: 2023-01-02 last year's transaction cleared equity:pending 5 = 0 assets:bank:checking -5  File: hledger.info, Node: Example retain earnings, Next: Example migrate balances to a new file, Prev: close and balance assertions, Up: close 24.11.2 Example: retain earnings -------------------------------- Record 2022's revenues/expenses as retained earnings on 2022-12-31, appending the generated transaction to the journal: $ hledger close --retain -f 2022.journal -p 2022 >> 2022.journal Note 2022's income statement will now show only zeroes, because revenues and expenses have been moved entirely to equity. To see them again, you could exclude the retain transaction: $ hledger -f 2022.journal is not:desc:'retain earnings'  File: hledger.info, Node: Example migrate balances to a new file, Next: Example excluding closing/opening transactions, Prev: Example retain earnings, Up: close 24.11.3 Example: migrate balances to a new file ----------------------------------------------- Close assets/liabilities/equity on 2022-12-31 and re-open them on 2023-01-01: $ hledger close --migrate -f 2022.journal -p 2022 # copy/paste the closing transaction to the end of 2022.journal # copy/paste the opening transaction to the start of 2023.journal Now 2022's balance sheet will show only zeroes, indicating a balanced accounting equation. (Unless you are using @/@@ notation - in that case, try adding -infer-equity.) To see the end-of-year balances again, you could exclude the closing transaction: $ hledger -f 2022.journal bs not:desc:'closing balances'  File: hledger.info, Node: Example excluding closing/opening transactions, Prev: Example migrate balances to a new file, Up: close 24.11.4 Example: excluding closing/opening transactions ------------------------------------------------------- When combining many files for multi-year reports, the closing/opening transactions cause some noise in transaction-oriented reports like 'print' and 'register'. You can exclude them as shown above, but 'not:desc:...' is not ideal as it depends on consistent descriptions; also you will want to avoid excluding the very first opening transaction, which could be awkward. Here is one alternative, using tags: Add 'clopen:' tags to all opening/closing balances transactions except the first, like this: ; 2021.journal 2021-06-01 first opening balances ... 2021-12-31 closing balances ; clopen:2022 ... ; 2022.journal 2022-01-01 opening balances ; clopen:2022 ... 2022-12-31 closing balances ; clopen:2023 ... ; 2023.journal 2023-01-01 opening balances ; clopen:2023 ... Now, assuming a combined journal like: ; all.journal include 2021.journal include 2022.journal include 2023.journal The 'clopen:' tag can exclude all but the first opening transaction. To show a clean multi-year checking register: $ hledger -f all.journal areg checking not:tag:clopen And the year values allow more precision. To show 2022's year-end balance sheet: $ hledger -f all.journal bs -e2023 not:tag:clopen=2023  File: hledger.info, Node: codes, Next: commodities, Prev: close, Up: PART 4 COMMANDS 24.12 codes =========== List the codes seen in transactions, in the order parsed. This command prints the value of each transaction's code field, in the order transactions were parsed. The transaction code is an optional value written in parentheses between the date and description, often used to store a cheque number, order number or similar. Transactions aren't required to have a code, and missing or empty codes will not be shown by default. With the '-E'/'--empty' flag, they will be printed as blank lines. You can add a query to select a subset of transactions. Examples: 2022/1/1 (123) Supermarket Food $5.00 Checking 2022/1/2 (124) Post Office Postage $8.32 Checking 2022/1/3 Supermarket Food $11.23 Checking 2022/1/4 (126) Post Office Postage $3.21 Checking $ hledger codes 123 124 126 $ hledger codes -E 123 124 126  File: hledger.info, Node: commodities, Next: demo, Prev: codes, Up: PART 4 COMMANDS 24.13 commodities ================= List all commodity/currency symbols used or declared in the journal.  File: hledger.info, Node: demo, Next: descriptions, Prev: commodities, Up: PART 4 COMMANDS 24.14 demo ========== Play demos of hledger usage in the terminal, if asciinema is installed. Run this command with no argument to list the demos. To play a demo, write its number or a prefix or substring of its title. Tips: Make your terminal window large enough to see the demo clearly. Use the -s/-speed SPEED option to set your preferred playback speed, eg '-s4' to play at 4x original speed or '-s.5' to play at half speed. The default speed is 2x. Other asciinema options can be added following a double dash, eg '-- -i.1' to limit pauses or '-- -h' to list asciinema's other options. During playback, several keys are available: SPACE to pause/unpause, . to step forward (while paused), CTRL-c quit. Examples: $ hledger demo # list available demos $ hledger demo 1 # play the first demo at default speed (2x) $ hledger demo install -s4 # play the "install" demo at 4x speed  File: hledger.info, Node: descriptions, Next: diff, Prev: demo, Up: PART 4 COMMANDS 24.15 descriptions ================== List the unique descriptions that appear in transactions. This command lists the unique descriptions that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. Example: $ hledger descriptions Store Name Gas Station | Petrol Person A  File: hledger.info, Node: diff, Next: files, Prev: descriptions, Up: PART 4 COMMANDS 24.16 diff ========== Compares a particular account's transactions in two input files. It shows any transactions to this account which are in one file but not in the other. More precisely, for each posting affecting this account in either file, it looks for a corresponding posting in the other file which posts the same amount to the same account (ignoring date, description, etc.) Since postings not transactions are compared, this also works when multiple bank transactions have been combined into a single journal entry. This is useful eg if you have downloaded an account's transactions from your bank (eg as CSV data). When hledger and your bank disagree about the account balance, you can compare the bank data with your journal to find out the cause. Examples: $ hledger diff -f $LEDGER_FILE -f bank.csv assets:bank:giro These transactions are in the first file only: 2014/01/01 Opening Balances assets:bank:giro EUR ... ... equity:opening balances EUR -... These transactions are in the second file only:  File: hledger.info, Node: files, Next: help, Prev: diff, Up: PART 4 COMMANDS 24.17 files =========== List all files included in the journal. With a REGEX argument, only file names matching the regular expression (case sensitive) are shown.  File: hledger.info, Node: help, Next: import, Prev: files, Up: PART 4 COMMANDS 24.18 help ========== Show the hledger user manual in the terminal, with 'info', 'man', or a pager. With a TOPIC argument, open it at that topic if possible. TOPIC can be any heading in the manual, or a heading prefix, case insensitive. Eg: 'commands', 'print', 'forecast', 'journal', 'amount', '"auto postings"'. This command shows the hledger manual built in to your hledger version. It can be useful when offline, or when you prefer the terminal to a web browser, or when the appropriate hledger manual or viewing tools are not installed on your system. By default it chooses the best viewer found in $PATH, trying (in this order): 'info', 'man', '$PAGER', 'less', 'more'. You can force the use of info, man, or a pager with the '-i', '-m', or '-p' flags, If no viewer can be found, or the command is run non-interactively, it just prints the manual to stdout. If using 'info', note that version 6 or greater is needed for TOPIC lookup. If you are on mac you will likely have info 4.8, and should consider installing a newer version, eg with 'brew install texinfo' (#1770). Examples $ hledger help --help # show how the help command works $ hledger help # show the hledger manual with info, man or $PAGER $ hledger help journal # show the journal topic in the hledger manual $ hledger help -m journal # show it with man, even if info is installed  File: hledger.info, Node: import, Next: incomestatement, Prev: help, Up: PART 4 COMMANDS 24.19 import ============ Read new transactions added to each FILE provided as arguments since last run, and add them to the journal. Or with -dry-run, just print the transactions that would be added. Or with -catchup, just mark all of the FILEs' current transactions as imported, without importing them. This command may append new transactions to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also 'add'). Unlike other hledger commands, with 'import' the journal file is an output file, and will be modified, though only by appending (existing data will not be changed). The input files are specified as arguments, so to import one or more CSV files to your main journal, you will run 'hledger import bank.csv' or perhaps 'hledger import *.csv'. Note you can import from any file format, though CSV files are the most common import source, and these docs focus on that case. * Menu: * Deduplication:: * Import testing:: * Importing balance assignments:: * Commodity display styles::  File: hledger.info, Node: Deduplication, Next: Import testing, Up: import 24.19.1 Deduplication --------------------- 'import' does _time-based deduplication_, to detect only the new transactions since the last successful import. (This does not mean "ignore transactions that look the same", but rather "ignore transactions that have been seen before".) This is intended for when you are periodically importing downloaded data, which may overlap with previous downloads. Eg if every week (or every day) you download a bank's last three months of CSV data, you can safely run 'hledger import thebank.csv' each time and only new transactions will be imported. Since the items being read (CSV records, eg) often do not come with unique identifiers, hledger detects new transactions by date, assuming that: 1. new items always have the newest dates 2. item dates do not change across reads 3. and items with the same date remain in the same relative order across reads. These are often true of CSV files representing transactions, or true enough so that it works pretty well in practice. 1 is important, but violations of 2 and 3 amongst the old transactions won't matter (and if you import often, the new transactions will be few, so less likely to be the ones affected). hledger remembers the latest date processed in each input file by saving a hidden ".latest.FILE" file in FILE's directory (after a succesful import). Eg when reading 'finance/bank.csv', it will look for and update the 'finance/.latest.bank.csv' state file. The format is simple: one or more lines containing the same ISO-format date (YYYY-MM-DD), meaning "I have processed transactions up to this date, and this many of them on that date." Normally you won't see or manipulate these state files yourself. But if needed, you can delete them to reset the state (making all transactions "new"), or you can construct them to "catch up" to a certain date. Note deduplication (and updating of state files) can also be done by 'print --new', but this is less often used. Related: CSV > Working with CSV > Deduplicating, importing.  File: hledger.info, Node: Import testing, Next: Importing balance assignments, Prev: Deduplication, Up: import 24.19.2 Import testing ---------------------- With '--dry-run', the transactions that will be imported are printed to the terminal, without updating your journal or state files. The output is valid journal format, like the print command, so you can re-parse it. Eg, to see any importable transactions which CSV rules have not categorised: $ hledger import --dry bank.csv | hledger -f- -I print unknown or (live updating): $ ls bank.csv* | entr bash -c 'echo ====; hledger import --dry bank.csv | hledger -f- -I print unknown' Note: when importing from multiple files at once, it's currently possible for some .latest files to be updated successfully, while the actual import fails because of a problem in one of the files, leaving them out of sync (and causing some transactions to be missed). To prevent this, do a -dry-run first and fix any problems before the real import.  File: hledger.info, Node: Importing balance assignments, Next: Commodity display styles, Prev: Import testing, Up: import 24.19.3 Importing balance assignments ------------------------------------- Entries added by import will have their posting amounts made explicit (like 'hledger print -x'). This means that any balance assignments in imported files must be evaluated; but, imported files don't get to see the main file's account balances. As a result, importing entries with balance assignments (eg from an institution that provides only balances and not posting amounts) will probably generate incorrect posting amounts. To avoid this problem, use print instead of import: $ hledger print IMPORTFILE [--new] >> $LEDGER_FILE (If you think import should leave amounts implicit like print does, please test it and send a pull request.)  File: hledger.info, Node: Commodity display styles, Prev: Importing balance assignments, Up: import 24.19.4 Commodity display styles -------------------------------- Imported amounts will be formatted according to the canonical commodity styles (declared or inferred) in the main journal file.  File: hledger.info, Node: incomestatement, Next: notes, Prev: import, Up: PART 4 COMMANDS 24.20 incomestatement ===================== (is) This command displays an income statement, showing revenues and expenses during one or more periods. Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the 'Revenue' or 'Expense' type (see account types). Or if no such accounts are declared, it shows top-level accounts named 'revenue' or 'income' or 'expense' (case insensitive, plurals allowed) and their subaccounts. Example: $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 This command is a higher-level variant of the 'balance' command, and supports many of that command's features, such as multi-period reports. It is similar to 'hledger balance '(revenues|income)' expenses', but with smarter account detection, and revenues/income displayed with their sign flipped. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'tsv', 'html', and (experimental) 'json'.  File: hledger.info, Node: notes, Next: payees, Prev: incomestatement, Up: PART 4 COMMANDS 24.21 notes =========== List the unique notes that appear in transactions. This command lists the unique notes that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. The note is the part of the transaction description after a | character (or if there is no |, the whole description). Example: $ hledger notes Petrol Snacks  File: hledger.info, Node: payees, Next: prices, Prev: notes, Up: PART 4 COMMANDS 24.22 payees ============ List the unique payee/payer names that appear in transactions. This command lists unique payee/payer names which have been declared with payee directives (-declared), used in transaction descriptions (-used), or both (the default). The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). You can add query arguments to select a subset of transactions. This implies -used. Example: $ hledger payees Store Name Gas Station Person A  File: hledger.info, Node: prices, Next: print, Prev: payees, Up: PART 4 COMMANDS 24.23 prices ============ Print the market prices declared with P directives. With -infer-market-prices, also show any additional prices inferred from costs. With -show-reverse, also show additional prices inferred by reversing known prices. Price amounts are always displayed with their full precision, except for reverse prices which are limited to 8 decimal digits. Prices can be filtered by a date:, cur: or amt: query. Generally if you run this command with -infer-market-prices -show-reverse, it will show the same prices used internally to calculate value reports. But if in doubt, you can inspect those directly by running the value report with -debug=2.  File: hledger.info, Node: print, Next: register, Prev: prices, Up: PART 4 COMMANDS 24.24 print =========== Show transaction journal entries, sorted by date. The print command displays full journal entries (transactions) from the journal file, sorted by date (or with '--date2', by secondary date). Directives and inter-transaction comments are not shown, currently. This means the print command is somewhat lossy, and if you are using it to reformat/regenerate your journal you should take care to also copy over the directives and inter-transaction comments. Eg: $ hledger print -f examples/sample.journal date:200806 2008/06/01 gift assets:bank:checking $1 income:gifts $-1 2008/06/02 save assets:bank:saving $1 assets:bank:checking $-1 2008/06/03 * eat & shop expenses:food $1 expenses:supplies $1 assets:cash $-2 * Menu: * print explicitness:: * print amount style:: * print parseability:: * print other features:: * print output format::  File: hledger.info, Node: print explicitness, Next: print amount style, Up: print 24.24.1 print explicitness -------------------------- Normally, whether posting amounts are implicit or explicit is preserved. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, if a conversion cost is implied but not written, it will not appear in the output. You can use the '-x'/'--explicit' flag to force explicit display of all amounts and costs. This can be useful for troubleshooting or for making your journal more readable and robust against data entry errors. '-x' is also implied by using any of '-B','-V','-X','--value'. The '-x'/'--explicit' flag will cause any postings with a multi-commodity amount (which can arise when a multi-commodity transaction has an implicit amount) to be split into multiple single-commodity postings, keeping the output parseable.  File: hledger.info, Node: print amount style, Next: print parseability, Prev: print explicitness, Up: print 24.24.2 print amount style -------------------------- Amounts are shown right-aligned within each transaction (but not aligned across all transactions; you can do that with ledger-mode in Emacs). Amounts will be (mostly) normalised to their commodity display style: their symbol placement, decimal mark, and digit group marks will be made consistent. By default, decimal digits are shown as they are written in the journal. With the '--round' option, 'print' will try increasingly hard to display decimal digits according to the commodity display styles: * '--round=none' show amounts with original precisions (default) * '--round=soft' add/remove decimal zeros in amounts (except costs) * '--round=hard' round amounts (except costs), possibly hiding significant digits * '--round=all' round all amounts and costs 'soft' is good for non-lossy cleanup, formatting amounts more consistently where it's safe to do so. 'hard' and 'all' can cause 'print' to show invalid unbalanced journal entries; they may be useful eg for stronger cleanup, with manual fixups when needed.  File: hledger.info, Node: print parseability, Next: print other features, Prev: print amount style, Up: print 24.24.3 print parseability -------------------------- print's output is usually a valid hledger journal, and you can process it again with a second hledger command. This can be useful for certain kinds of search (though the same can be achieved with 'expr:' queries now): # Show running total of food expenses paid from cash. # -f- reads from stdin. -I/--ignore-assertions is sometimes needed. $ hledger print assets:cash | hledger -f- -I reg expenses:food There are some situations where print's output can become unparseable: * Value reporting affects posting amounts but not balance assertion or balance assignment amounts, potentially causing those to fail. * Auto postings can generate postings with too many missing amounts. * Account aliases can generate bad account names.  File: hledger.info, Node: print other features, Next: print output format, Prev: print parseability, Up: print 24.24.4 print, other features ----------------------------- With '-B'/'--cost', amounts with costs are shown converted to cost. With '--new', print shows only transactions it has not seen on a previous run. This uses the same deduplication system as the 'import' command. (See import's docs for details.) With '-m DESC'/'--match=DESC', print shows one recent transaction whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar-enough match, no transaction will be shown and the program exit code will be non-zero.  File: hledger.info, Node: print output format, Prev: print other features, Up: print 24.24.5 print output format --------------------------- This command also supports the output destination and output format options The output formats supported are 'txt', 'beancount', 'csv', 'tsv', 'json' and 'sql'. _Experimental:_ The 'beancount' format tries to produce Beancount-compatible output, as follows: * Transaction and postings with unmarked status are converted to cleared ('*') status. * Transactions' payee and note are backslash-escaped and double-quote-escaped and wrapped in double quotes. * Transaction tags are copied to Beancount #tag format. * Commodity symbols are converted to upper case, and a small number of currency symbols like '$' are converted to the corresponding currency names. * Account name parts are capitalised and unsupported characters are replaced with '-'. If an account name part does not begin with a letter, or if the first part is not Assets, Liabilities, Equity, Income, or Expenses, an error is raised. (Use '--alias' options to bring your accounts into compliance.) * An 'open' directive is generated for each account used, on the earliest transaction date. Some limitations: * Balance assertions are removed. * Balance assignments become missing amounts. * Virtual and balanced virtual postings become regular postings. * Directives are not converted. Here's an example of print's CSV output: $ hledger print -Ocsv "txnidx","date","date2","status","code","description","comment","account","amount","commodity","credit","debit","posting-status","posting-comment" "1","2008/01/01","","","","income","","assets:bank:checking","1","$","","1","","" "1","2008/01/01","","","","income","","income:salary","-1","$","1","","","" "2","2008/06/01","","","","gift","","assets:bank:checking","1","$","","1","","" "2","2008/06/01","","","","gift","","income:gifts","-1","$","1","","","" "3","2008/06/02","","","","save","","assets:bank:saving","1","$","","1","","" "3","2008/06/02","","","","save","","assets:bank:checking","-1","$","1","","","" "4","2008/06/03","","*","","eat & shop","","expenses:food","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","expenses:supplies","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","assets:cash","-2","$","2","","","" "5","2008/12/31","","*","","pay off","","liabilities:debts","1","$","","1","","" "5","2008/12/31","","*","","pay off","","assets:bank:checking","-1","$","1","","","" * There is one CSV record per posting, with the parent transaction's fields repeated. * The "txnidx" (transaction index) field shows which postings belong to the same transaction. (This number might change if transactions are reordered within the file, files are parsed/included in a different order, etc.) * The amount is separated into "commodity" (the symbol) and "amount" (numeric quantity) fields. * The numeric amount is repeated in either the "credit" or "debit" column, for convenience. (Those names are not accurate in the accounting sense; it just puts negative amounts under credit and zero or greater amounts under debit.)  File: hledger.info, Node: register, Next: rewrite, Prev: print, Up: PART 4 COMMANDS 24.25 register ============== (reg) Show postings and their running total. The register command displays matched postings, across all accounts, in date order, with their running total or running historical balance. (See also the 'aregister' command, which shows matched transactions in a specific account.) register normally shows line per posting, but note that multi-commodity amounts will occupy multiple lines (one line per commodity). It is typically used with a query selecting a particular account, to see that account's activity: $ hledger register checking 2008/01/01 income assets:bank:checking $1 $1 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $-1 $1 2008/12/31 pay off assets:bank:checking $-1 0 With '--date2', it shows and sorts by secondary date instead. For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the '--align-all' flag. The '--historical'/'-H' flag adds the balance from any undisplayed prior postings to the running total. This is useful when you want to see only recent activity, with a historically accurate running balance: $ hledger register checking -b 2008/6 --historical 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $-1 $1 2008/12/31 pay off assets:bank:checking $-1 0 The '--depth' option limits the amount of sub-account detail displayed. The '--average'/'-A' flag shows the running average posting amount instead of the running total (so, the final number displayed is the average for the whole report period). This flag implies '--empty' (see below). It is affected by '--historical'. It works best when showing just one account and one commodity. The '--related'/'-r' flag shows the _other_ postings in the transactions of the postings which would normally be shown. The '--invert' flag negates all amounts. For example, it can be used on an income account where amounts are normally displayed as negative numbers. It's also useful to show postings on the checking account together with the related account: $ hledger register --related --invert assets:checking With a reporting interval, register shows summary postings, one per interval, aggregating the postings to each account: $ hledger register --monthly income 2008/01 income:salary $-1 $-1 2008/06 income:gifts $-1 $-2 Periods with no activity, and summary postings with a zero amount, are not shown by default; use the '--empty'/'-E' flag to see them: $ hledger register --monthly income -E 2008/01 income:salary $-1 $-1 2008/02 0 $-1 2008/03 0 $-1 2008/04 0 $-1 2008/05 0 $-1 2008/06 income:gifts $-1 $-2 2008/07 0 $-2 2008/08 0 $-2 2008/09 0 $-2 2008/10 0 $-2 2008/11 0 $-2 2008/12 0 $-2 Often, you'll want to see just one line per interval. The '--depth' option helps with this, causing subaccounts to be aggregated: $ hledger register --monthly assets --depth 1h 2008/01 assets $1 $1 2008/06 assets $-1 0 2008/12 assets $-1 $-1 Note when using report intervals, if you specify start/end dates these will be adjusted outward if necessary to contain a whole number of intervals. This ensures that the first and last intervals are full length and comparable to the others in the report. With '-m DESC'/'--match=DESC', register does a fuzzy search for one recent posting whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar-enough match, no posting will be shown and the program exit code will be non-zero. * Menu: * Custom register output::  File: hledger.info, Node: Custom register output, Up: register 24.25.1 Custom register output ------------------------------ register uses the full terminal width by default, except on windows. You can override this by setting the 'COLUMNS' environment variable (not a bash shell variable) or by using the '--width'/'-w' option. The description and account columns normally share the space equally (about half of (width - 40) each). You can adjust this by adding a description width as part of -width's argument, comma-separated: '--width W,D' . Here's a diagram (won't display correctly in -help): <--------------------------------- width (W) ----------------------------------> date (10) description (D) account (W-41-D) amount (12) balance (12) DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA and some examples: $ hledger reg # use terminal width (or 80 on windows) $ hledger reg -w 100 # use width 100 $ COLUMNS=100 hledger reg # set with one-time environment variable $ export COLUMNS=100; hledger reg # set till session end (or window resize) $ hledger reg -w 100,40 # set overall width 100, description width 40 $ hledger reg -w $COLUMNS,40 # use terminal width, & description width 40 This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'tsv', and (experimental) 'json'.  File: hledger.info, Node: rewrite, Next: roi, Prev: register, Up: PART 4 COMMANDS 24.26 rewrite ============= Print all transactions, rewriting the postings of matched transactions. For now the only rewrite available is adding new postings, like print -auto. This is a start at a generic rewriter of transaction entries. It reads the default journal and prints the transactions, like print, but adds one or more specified postings to any transactions matching QUERY. The posting amounts can be fixed, or a multiplier of the existing transaction's first posting amount. Examples: $ hledger-rewrite.hs ^income --add-posting '(liabilities:tax) *.33 ; income tax' --add-posting '(reserve:gifts) $100' $ hledger-rewrite.hs expenses:gifts --add-posting '(reserve:gifts) *-1"' $ hledger-rewrite.hs -f rewrites.hledger rewrites.hledger may consist of entries like: = ^income amt:<0 date:2017 (liabilities:tax) *0.33 ; tax on income (reserve:grocery) *0.25 ; reserve 25% for grocery (reserve:) *0.25 ; reserve 25% for grocery Note the single quotes to protect the dollar sign from bash, and the two spaces between account and amount. More: $ hledger rewrite -- [QUERY] --add-posting "ACCT AMTEXPR" ... $ hledger rewrite -- ^income --add-posting '(liabilities:tax) *.33' $ hledger rewrite -- expenses:gifts --add-posting '(budget:gifts) *-1"' $ hledger rewrite -- ^income --add-posting '(budget:foreign currency) *0.25 JPY; diversify' Argument for '--add-posting' option is a usual posting of transaction with an exception for amount specification. More precisely, you can use ''*'' (star symbol) before the amount to indicate that that this is a factor for an amount of original matched posting. If the amount includes a commodity name, the new posting amount will be in the new commodity; otherwise, it will be in the matched posting amount's commodity. * Menu: * Re-write rules in a file:: * Diff output format:: * rewrite vs print --auto::  File: hledger.info, Node: Re-write rules in a file, Next: Diff output format, Up: rewrite 24.26.1 Re-write rules in a file -------------------------------- During the run this tool will execute so called "Automated Transactions" found in any journal it process. I.e instead of specifying this operations in command line you can put them in a journal file. $ rewrite-rules.journal Make contents look like this: = ^income (liabilities:tax) *.33 = expenses:gifts budget:gifts *-1 assets:budget *1 Note that ''='' (equality symbol) that is used instead of date in transactions you usually write. It indicates the query by which you want to match the posting to add new ones. $ hledger rewrite -- -f input.journal -f rewrite-rules.journal > rewritten-tidy-output.journal This is something similar to the commands pipeline: $ hledger rewrite -- -f input.journal '^income' --add-posting '(liabilities:tax) *.33' \ | hledger rewrite -- -f - expenses:gifts --add-posting 'budget:gifts *-1' \ --add-posting 'assets:budget *1' \ > rewritten-tidy-output.journal It is important to understand that relative order of such entries in journal is important. You can re-use result of previously added postings.  File: hledger.info, Node: Diff output format, Next: rewrite vs print --auto, Prev: Re-write rules in a file, Up: rewrite 24.26.2 Diff output format -------------------------- To use this tool for batch modification of your journal files you may find useful output in form of unified diff. $ hledger rewrite -- --diff -f examples/sample.journal '^income' --add-posting '(liabilities:tax) *.33' Output might look like: --- /tmp/examples/sample.journal +++ /tmp/examples/sample.journal @@ -18,3 +18,4 @@ 2008/01/01 income - assets:bank:checking $1 + assets:bank:checking $1 income:salary + (liabilities:tax) 0 @@ -22,3 +23,4 @@ 2008/06/01 gift - assets:bank:checking $1 + assets:bank:checking $1 income:gifts + (liabilities:tax) 0 If you'll pass this through 'patch' tool you'll get transactions containing the posting that matches your query be updated. Note that multiple files might be update according to list of input files specified via '--file' options and 'include' directives inside of these files. Be careful. Whole transaction being re-formatted in a style of output from 'hledger print'. See also: https://github.com/simonmichael/hledger/issues/99  File: hledger.info, Node: rewrite vs print --auto, Prev: Diff output format, Up: rewrite 24.26.3 rewrite vs. print -auto ------------------------------- This command predates print -auto, and currently does much the same thing, but with these differences: * with multiple files, rewrite lets rules in any file affect all other files. print -auto uses standard directive scoping; rules affect only child files. * rewrite's query limits which transactions can be rewritten; all are printed. print -auto's query limits which transactions are printed. * rewrite applies rules specified on command line or in the journal. print -auto applies rules specified in the journal.  File: hledger.info, Node: roi, Next: stats, Prev: rewrite, Up: PART 4 COMMANDS 24.27 roi ========= Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. At a minimum, you need to supply a query (which could be just an account name) to select your investment(s) with '--inv', and another query to identify your profit and loss transactions with '--pnl'. If you do not record changes in the value of your investment manually, or do not require computation of time-weighted return (TWR), '--pnl' could be an empty query ('--pnl ""' or '--pnl STR' where 'STR' does not match any of your accounts). This command will compute and display the internalized rate of return (IRR, also known as money-weighted rate of return) and time-weighted rate of return (TWR) for your investments for the time period requested. IRR is always annualized due to the way it is computed, but TWR is reported both as a rate over the chosen reporting period and as an annual rate. Price directives will be taken into account if you supply appropriate '--cost' or '--value' flags (see VALUATION). Note, in some cases this report can fail, for these reasons: * Error (NotBracketed): No solution for Internal Rate of Return (IRR). Possible causes: IRR is huge (>1000000%), balance of investment becomes negative at some point in time. * Error (SearchFailed): Failed to find solution for Internal Rate of Return (IRR). Either search does not converge to a solution, or converges too slowly. Examples: * Using roi to compute total return of investment in stocks: https://github.com/simonmichael/hledger/blob/master/examples/investing/roi-unrealised.ledger * Cookbook > Return on Investment: https://hledger.org/roi.html * Menu: * Spaces and special characters in --inv and --pnl:: * Semantics of --inv and --pnl:: * IRR and TWR explained::  File: hledger.info, Node: Spaces and special characters in --inv and --pnl, Next: Semantics of --inv and --pnl, Up: roi 24.27.1 Spaces and special characters in '--inv' and ---------------------------------------------------- '--pnl' Note that '--inv' and '--pnl''s argument is a query, and queries could have several space-separated terms (see QUERIES). To indicate that all search terms form single command-line argument, you will need to put them in quotes (see Special characters): $ hledger roi --inv 'term1 term2 term3 ...' If any query terms contain spaces themselves, you will need an extra level of nested quoting, eg: $ hledger roi --inv="'Assets:Test 1'" --pnl="'Equity:Unrealized Profit and Loss'"  File: hledger.info, Node: Semantics of --inv and --pnl, Next: IRR and TWR explained, Prev: Spaces and special characters in --inv and --pnl, Up: roi 24.27.2 Semantics of '--inv' and '--pnl' ---------------------------------------- Query supplied to '--inv' has to match all transactions that are related to your investment. Transactions not matching '--inv' will be ignored. In these transactions, ROI will conside postings that match '--inv' to be "investment postings" and other postings (not matching '--inv') will be sorted into two categories: "cash flow" and "profit and loss", as ROI needs to know which part of the investment value is your contributions and which is due to the return on investment. * "Cash flow" is depositing or withdrawing money, buying or selling assets, or otherwise converting between your investment commodity and any other commodity. Example: 2019-01-01 Investing in Snake Oil assets:cash -$100 investment:snake oil 2020-01-01 Selling my Snake Oil assets:cash $10 investment:snake oil = 0 * "Profit and loss" is change in the value of your investment: 2019-06-01 Snake Oil falls in value investment:snake oil = $57 equity:unrealized profit or loss All non-investment postings are assumed to be "cash flow", unless they match '--pnl' query. Changes in value of your investment due to "profit and loss" postings will be considered as part of your investment return. Example: if you use '--inv snake --pnl equity:unrealized', then postings in the example below would be classifed as: 2019-01-01 Snake Oil #1 assets:cash -$100 ; cash flow posting investment:snake oil ; investment posting 2019-03-01 Snake Oil #2 equity:unrealized pnl -$100 ; profit and loss posting snake oil ; investment posting 2019-07-01 Snake Oil #3 equity:unrealized pnl ; profit and loss posting cash -$100 ; cash flow posting snake oil $50 ; investment posting  File: hledger.info, Node: IRR and TWR explained, Prev: Semantics of --inv and --pnl, Up: roi 24.27.3 IRR and TWR explained ----------------------------- "ROI" stands for "return on investment". Traditionally this was computed as a difference between current value of investment and its initial value, expressed in percentage of the initial value. However, this approach is only practical in simple cases, where investments receives no in-flows or out-flows of money, and where rate of growth is fixed over time. For more complex scenarios you need different ways to compute rate of return, and this command implements two of them: IRR and TWR. Internal rate of return, or "IRR" (also called "money-weighted rate of return") takes into account effects of in-flows and out-flows, and the time between them. Investment at a particular fixed interest rate is going to give you more interest than the same amount invested at the same interest rate, but made later in time. If you are withdrawing from your investment, your future gains would be smaller (in absolute numbers), and will be a smaller percentage of your initial investment, so your IRR will be smaller. And if you are adding to your investment, you will receive bigger absolute gains, which will be a bigger percentage of your initial investment, so your IRR will be larger. As mentioned before, in-flows and out-flows would be any cash that you personally put in or withdraw, and for the "roi" command, these are the postings that match the query in the'--inv' argument and NOT match the query in the'--pnl' argument. If you manually record changes in the value of your investment as transactions that balance them against "profit and loss" (or "unrealized gains") account or use price directives, then in order for IRR to compute the precise effect of your in-flows and out-flows on the rate of return, you will need to record the value of your investement on or close to the days when in- or out-flows occur. In technical terms, IRR uses the same approach as computation of net present value, and tries to find a discount rate that makes net present value of all the cash flows of your investment to add up to zero. This could be hard to wrap your head around, especially if you haven't done discounted cash flow analysis before. Implementation of IRR in hledger should produce results that match the '=XIRR' formula in Excel. Second way to compute rate of return that 'roi' command implements is called "time-weighted rate of return" or "TWR". Like IRR, it will account for the effect of your in-flows and out-flows, but unlike IRR it will try to compute the true rate of return of the underlying asset, compensating for the effect that deposits and withdrawas have on the apparent rate of growth of your investment. TWR represents your investment as an imaginary "unit fund" where in-flows/ out-flows lead to buying or selling "units" of your investment and changes in its value change the value of "investment unit". Change in "unit price" over the reporting period gives you rate of return of your investment, and make TWR less sensitive than IRR to the effects of cash in-flows and out-flows. References: * Explanation of rate of return * Explanation of IRR * Explanation of TWR * IRR vs TWR * Examples of computing IRR and TWR and discussion of the limitations of both metrics  File: hledger.info, Node: stats, Next: tags, Prev: roi, Up: PART 4 COMMANDS 24.28 stats =========== Show journal and performance statistics. The stats command displays summary information for the whole journal, or a matched part of it. With a reporting interval, it shows a report for each report period. At the end, it shows (in the terminal) the overall run time and number of transactions processed per second. Note these are approximate and will vary based on machine, current load, data size, hledger version, haskell lib versions, GHC version.. but they may be of interest. The 'stats' command's run time is similar to that of a single-column balance report. Example: $ hledger stats -f examples/1000x1000x10.journal Main file : /Users/simon/src/hledger/examples/1000x1000x10.journal Included files : Transactions span : 2000-01-01 to 2002-09-27 (1000 days) Last transaction : 2002-09-26 (6995 days ago) Transactions : 1000 (1.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 1000 Accounts : 1000 (depth 10) Commodities : 26 (A, B, C, D, E, F, G, H, I, J, K, L, M, N, O, P, Q, R, S, T, U, V, W, X, Y, Z) Market prices : 1000 (A) Run time : 0.12 s Throughput : 8342 txns/s This command supports the -o/-output-file option (but not -O/-output-format selection).  File: hledger.info, Node: tags, Next: test, Prev: stats, Up: PART 4 COMMANDS 24.29 tags ========== List the tags used in the journal, or their values. This command lists the tag names used in the journal, whether on transactions, postings, or account declarations. With a TAGREGEX argument, only tag names matching this regular expression (case insensitive, infix matched) are shown. With QUERY arguments, only transactions and accounts matching this query are considered. If the query involves transaction fields (date:, desc:, amt:, ...), the search is restricted to the matched transactions and their accounts. With the -values flag, the tags' unique non-empty values are listed instead. With -E/-empty, blank/empty values are also shown. With -parsed, tags or values are shown in the order they were parsed, with duplicates included. (Except, tags from account declarations are always shown first.) Tip: remember, accounts also acquire tags from their parents, postings also acquire tags from their account and transaction, transactions also acquire tags from their postings.  File: hledger.info, Node: test, Prev: tags, Up: PART 4 COMMANDS 24.30 test ========== Run built-in unit tests. This command runs the unit tests built in to hledger and hledger-lib, printing the results on stdout. If any test fails, the exit code will be non-zero. This is mainly used by hledger developers, but you can also use it to sanity-check the installed hledger executable on your platform. All tests are expected to pass - if you ever see a failure, please report as a bug! This command also accepts tasty test runner options, written after a - (double hyphen). Eg to run only the tests in Hledger.Data.Amount, with ANSI colour codes disabled: $ hledger test -- -pData.Amount --color=never For help on these, see https://github.com/feuerbach/tasty#options ('-- --help' currently doesn't show them).  File: hledger.info, Node: PART 5 COMMON TASKS, Next: BUGS, Prev: PART 4 COMMANDS, Up: Top 25 PART 5: COMMON TASKS *********************** Here are some quick examples of how to do some basic tasks with hledger. * Menu: * Getting help:: * Constructing command lines:: * Starting a journal file:: * Setting LEDGER_FILE:: * Setting opening balances:: * Recording transactions:: * Reconciling:: * Reporting:: * Migrating to a new file::  File: hledger.info, Node: Getting help, Next: Constructing command lines, Up: PART 5 COMMON TASKS 25.1 Getting help ================= Here's how to list commands and view options and command docs: $ hledger # show available commands $ hledger --help # show common options $ hledger CMD --help # show CMD's options, common options and CMD's documentation You can also view your hledger version's manual in several formats by using the help command. Eg: $ hledger help # show the hledger manual with info, man or $PAGER (best available) $ hledger help journal # show the journal topic in the hledger manual $ hledger help --help # find out more about the help command To view manuals and introductory docs on the web, visit https://hledger.org. Chat and mail list support and discussion archives can be found at https://hledger.org/support.  File: hledger.info, Node: Constructing command lines, Next: Starting a journal file, Prev: Getting help, Up: PART 5 COMMON TASKS 25.2 Constructing command lines =============================== hledger has a flexible command line interface. We strive to keep it simple and ergonomic, but if you run into one of the sharp edges described in OPTIONS, here are some tips that might help: * command-specific options must go after the command (it's fine to put common options there too: 'hledger CMD OPTS ARGS') * running add-on executables directly simplifies command line parsing ('hledger-ui OPTS ARGS') * enclose "problematic" args in single quotes * if needed, also add a backslash to hide regular expression metacharacters from the shell * to see how a misbehaving command line is being parsed, add '--debug=2'.  File: hledger.info, Node: Starting a journal file, Next: Setting LEDGER_FILE, Prev: Constructing command lines, Up: PART 5 COMMON TASKS 25.3 Starting a journal file ============================ hledger looks for your accounting data in a journal file, '$HOME/.hledger.journal' by default: $ hledger stats The hledger journal file "/Users/simon/.hledger.journal" was not found. Please create it first, eg with "hledger add" or a text editor. Or, specify an existing journal file with -f or LEDGER_FILE. You can override this by setting the 'LEDGER_FILE' environment variable (see below). It's a good practice to keep this important file under version control, and to start a new file each year. So you could do something like this: $ mkdir ~/finance $ cd ~/finance $ git init Initialized empty Git repository in /Users/simon/finance/.git/ $ touch 2023.journal $ echo "export LEDGER_FILE=$HOME/finance/2023.journal" >> ~/.profile $ source ~/.profile $ hledger stats Main file : /Users/simon/finance/2023.journal Included files : Transactions span : to (0 days) Last transaction : none Transactions : 0 (0.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 0 Accounts : 0 (depth 0) Commodities : 0 () Market prices : 0 ()  File: hledger.info, Node: Setting LEDGER_FILE, Next: Setting opening balances, Prev: Starting a journal file, Up: PART 5 COMMON TASKS 25.4 Setting LEDGER_FILE ======================== How to set 'LEDGER_FILE' permanently depends on your setup: On unix and mac, running these commands in the terminal will work for many people; adapt as needed: $ echo 'export LEDGER_FILE=~/finance/2023.journal' >> ~/.profile $ source ~/.profile When correctly configured, in a new terminal window 'env | grep LEDGER_FILE' will show your file, and so will 'hledger files'. On mac, this additional step might be helpful for GUI applications (like Emacs started from the dock): add an entry to '~/.MacOSX/environment.plist' like { "LEDGER_FILE" : "~/finance/2023.journal" } and then run 'killall Dock' in a terminal window (or restart the machine). On Windows, see https://www.java.com/en/download/help/path.html, or try running these commands in a powershell window (let us know if it persists across a reboot, and if you need to be an Administrator): > CD > MKDIR finance > SETX LEDGER_FILE "C:\Users\USERNAME\finance\2023.journal"  File: hledger.info, Node: Setting opening balances, Next: Recording transactions, Prev: Setting LEDGER_FILE, Up: PART 5 COMMON TASKS 25.5 Setting opening balances ============================= Pick a starting date for which you can look up the balances of some real-world assets (bank accounts, wallet..) and liabilities (credit cards..). To avoid a lot of data entry, you may want to start with just one or two accounts, like your checking account or cash wallet; and pick a recent starting date, like today or the start of the week. You can always come back later and add more accounts and older transactions, eg going back to january 1st. Add an opening balances transaction to the journal, declaring the balances on this date. Here are two ways to do it: * The first way: open the journal in any text editor and save an entry like this: 2023-01-01 * opening balances assets:bank:checking $1000 = $1000 assets:bank:savings $2000 = $2000 assets:cash $100 = $100 liabilities:creditcard $-50 = $-50 equity:opening/closing balances These are start-of-day balances, ie whatever was in the account at the end of the previous day. The * after the date is an optional status flag. Here it means "cleared & confirmed". The currency symbols are optional, but usually a good idea as you'll be dealing with multiple currencies sooner or later. The = amounts are optional balance assertions, providing extra error checking. * The second way: run 'hledger add' and follow the prompts to record a similar transaction: $ hledger add Adding transactions to journal file /Users/simon/finance/2023.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control-d or control-c. Date [2023-02-07]: 2023-01-01 Description: * opening balances Account 1: assets:bank:checking Amount 1: $1000 Account 2: assets:bank:savings Amount 2 [$-1000]: $2000 Account 3: assets:cash Amount 3 [$-3000]: $100 Account 4: liabilities:creditcard Amount 4 [$-3100]: $-50 Account 5: equity:opening/closing balances Amount 5 [$-3050]: Account 6 (or . or enter to finish this transaction): . 2023-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl-D/ctrl-C to quit) Date [2023-01-01]: . If you're using version control, this could be a good time to commit the journal. Eg: $ git commit -m 'initial balances' 2023.journal  File: hledger.info, Node: Recording transactions, Next: Reconciling, Prev: Setting opening balances, Up: PART 5 COMMON TASKS 25.6 Recording transactions =========================== As you spend or receive money, you can record these transactions using one of the methods above (text editor, hledger add) or by using the hledger-iadd or hledger-web add-ons, or by using the import command to convert CSV data downloaded from your bank. Here are some simple transactions, see the hledger_journal(5) manual and hledger.org for more ideas: 2023/1/10 * gift received assets:cash $20 income:gifts 2023.1.12 * farmers market expenses:food $13 assets:cash 2023-01-15 paycheck income:salary assets:bank:checking $1000  File: hledger.info, Node: Reconciling, Next: Reporting, Prev: Recording transactions, Up: PART 5 COMMON TASKS 25.7 Reconciling ================ Periodically you should reconcile - compare your hledger-reported balances against external sources of truth, like bank statements or your bank's website - to be sure that your ledger accurately represents the real-world balances (and, that the real-world institutions have not made a mistake!). This gets easy and fast with (1) practice and (2) frequency. If you do it daily, it can take 2-10 minutes. If you let it pile up, expect it to take longer as you hunt down errors and discrepancies. A typical workflow: 1. Reconcile cash. Count what's in your wallet. Compare with what hledger reports ('hledger bal cash'). If they are different, try to remember the missing transaction, or look for the error in the already-recorded transactions. A register report can be helpful ('hledger reg cash'). If you can't find the error, add an adjustment transaction. Eg if you have $105 after the above, and can't explain the missing $2, it could be: 2023-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc 2. Reconcile checking. Log in to your bank's website. Compare today's (cleared) balance with hledger's cleared balance ('hledger bal checking -C'). If they are different, track down the error or record the missing transaction(s) or add an adjustment transaction, similar to the above. Unlike the cash case, you can usually compare the transaction history and running balance from your bank with the one reported by 'hledger reg checking -C'. This will be easier if you generally record transaction dates quite similar to your bank's clearing dates. 3. Repeat for other asset/liability accounts. Tip: instead of the register command, use hledger-ui to see a live-updating register while you edit the journal: 'hledger-ui --watch --register checking -C' After reconciling, it could be a good time to mark the reconciled transactions' status as "cleared and confirmed", if you want to track that, by adding the '*' marker. Eg in the paycheck transaction above, insert '*' between '2023-01-15' and 'paycheck' If you're using version control, this can be another good time to commit: $ git commit -m 'txns' 2023.journal  File: hledger.info, Node: Reporting, Next: Migrating to a new file, Prev: Reconciling, Up: PART 5 COMMON TASKS 25.8 Reporting ============== Here are some basic reports. Show all transactions: $ hledger print 2023-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 2023-01-10 * gift received assets:cash $20 income:gifts 2023-01-12 * farmers market expenses:food $13 assets:cash 2023-01-15 * paycheck income:salary assets:bank:checking $1000 2023-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc Show account names, and their hierarchy: $ hledger accounts --tree assets bank checking savings cash equity opening/closing balances expenses food misc income gifts salary liabilities creditcard Show all account totals: $ hledger balance $4105 assets $4000 bank $2000 checking $2000 savings $105 cash $-3050 equity:opening/closing balances $15 expenses $13 food $2 misc $-1020 income $-20 gifts $-1000 salary $-50 liabilities:creditcard -------------------- 0 Show only asset and liability balances, as a flat list, limited to depth 2: $ hledger bal assets liabilities -2 $4000 assets:bank $105 assets:cash $-50 liabilities:creditcard -------------------- $4055 Show the same thing without negative numbers, formatted as a simple balance sheet: $ hledger bs -2 Balance Sheet 2023-01-16 || 2023-01-16 ========================++============ Assets || ------------------------++------------ assets:bank || $4000 assets:cash || $105 ------------------------++------------ || $4105 ========================++============ Liabilities || ------------------------++------------ liabilities:creditcard || $50 ------------------------++------------ || $50 ========================++============ Net: || $4055 The final total is your "net worth" on the end date. (Or use 'bse' for a full balance sheet with equity.) Show income and expense totals, formatted as an income statement: hledger is Income Statement 2023-01-01-2023-01-16 || 2023-01-01-2023-01-16 ===============++======================= Revenues || ---------------++----------------------- income:gifts || $20 income:salary || $1000 ---------------++----------------------- || $1020 ===============++======================= Expenses || ---------------++----------------------- expenses:food || $13 expenses:misc || $2 ---------------++----------------------- || $15 ===============++======================= Net: || $1005 The final total is your net income during this period. Show transactions affecting your wallet, with running total: $ hledger register cash 2023-01-01 opening balances assets:cash $100 $100 2023-01-10 gift received assets:cash $20 $120 2023-01-12 farmers market assets:cash $-13 $107 2023-01-16 adjust cash assets:cash $-2 $105 Show weekly posting counts as a bar chart: $ hledger activity -W 2019-12-30 ***** 2023-01-06 **** 2023-01-13 ****  File: hledger.info, Node: Migrating to a new file, Prev: Reporting, Up: PART 5 COMMON TASKS 25.9 Migrating to a new file ============================ At the end of the year, you may want to continue your journal in a new file, so that old transactions don't slow down or clutter your reports, and to help ensure the integrity of your accounting history. See the close command. If using version control, don't forget to 'git add' the new file.  File: hledger.info, Node: BUGS, Prev: PART 5 COMMON TASKS, Up: Top 26 BUGS ******* We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). Some known issues and limitations: The need to precede add-on command options with '--' when invoked from hledger is awkward. (See Command options, Constructing command lines.) A UTF-8-aware system locale must be configured to work with non-ascii data. (See Unicode characters, Troubleshooting.) On Microsoft Windows, depending whether you are running in a CMD window or a Cygwin/MSYS/Mintty window and how you installed hledger, non-ascii characters and colours may not be supported, and the tab key may not be supported by 'hledger add'. (Running in a WSL window should resolve these.) When processing large data files, hledger uses more memory than Ledger. * Menu: * Troubleshooting::  File: hledger.info, Node: Troubleshooting, Up: BUGS 26.1 Troubleshooting ==================== Here are some common issues you might encounter when you run hledger, and how to resolve them (and remember also you can usually get quick Support): *PATH issues: I get an error like "No command 'hledger' found"* Depending how you installed hledger, the executables may not be in your shell's PATH. Eg on unix systems, stack installs hledger in '~/.local/bin' and cabal installs it in '~/.cabal/bin'. You may need to add one of these directories to your shell's PATH, and/or open a new terminal window. *LEDGER_FILE issues: I configured LEDGER_FILE but hledger is not using it* * 'LEDGER_FILE' should be a real environment variable, not just a shell variable. Eg on unix, the command 'env | grep LEDGER_FILE' should show it. You may need to use 'export' (see https://stackoverflow.com/a/7411509). * You may need to force your shell to see the new configuration. A simple way is to close your terminal window and open a new one. *LANG issues: I get errors like "Illegal byte sequence" or "Invalid or incomplete multibyte or wide character" or "commitAndReleaseBuffer: invalid argument (invalid character)"* Programs compiled with GHC (hledger, haskell build tools, etc.) need the system locale to be UTF-8-aware, or they will fail when they encounter non-ascii characters. To fix it, set the LANG environment variable to a locale which supports UTF-8 and which is installed on your system. On unix, 'locale -a' lists the installed locales. Look for one which mentions 'utf8', 'UTF-8' or similar. Some examples: 'C.UTF-8', 'en_US.utf-8', 'fr_FR.utf8'. If necessary, use your system package manager to install one. Then select it by setting the 'LANG' environment variable. Note, exact spelling and capitalisation of the locale name may be important: Here's one common way to configure this permanently for your shell: $ echo "export LANG=en_US.utf8" >>~/.profile # close and re-open terminal window If you are using Nix (not NixOS) for GHC and Hledger, you might need to set the 'LOCALE_ARCHIVE' variable: $ echo "export LOCALE_ARCHIVE=${glibcLocales}/lib/locale/locale-archive" >>~/.profile # close and re-open terminal window *COMPATIBILITY ISSUES: hledger gives an error with my Ledger file* Not all of Ledger's journal file syntax or feature set is supported. See hledger and Ledger for full details.  Tag Table: Node: Top208 Node: PART 1 USER INTERFACE3820 Ref: #part-1-user-interface3959 Node: Input3959 Ref: #input4069 Node: Data formats5018 Ref: #data-formats5131 Node: Standard input6493 Ref: #standard-input6633 Node: Multiple files6860 Ref: #multiple-files6999 Node: Strict mode7597 Ref: #strict-mode7707 Node: Commands8431 Ref: #commands8533 Node: Add-on commands9600 Ref: #add-on-commands9702 Node: Options10818 Ref: #options10930 Node: General help options11258 Ref: #general-help-options11404 Node: General input options11686 Ref: #general-input-options11868 Node: General reporting options12525 Ref: #general-reporting-options12686 Node: Command line tips16076 Ref: #command-line-tips16206 Node: Option repetition16465 Ref: #option-repetition16609 Node: Special characters16713 Ref: #special-characters16886 Node: Single escaping shell metacharacters17049 Ref: #single-escaping-shell-metacharacters17290 Node: Double escaping regular expression metacharacters17893 Ref: #double-escaping-regular-expression-metacharacters18204 Node: Triple escaping for add-on commands18730 Ref: #triple-escaping-for-add-on-commands18990 Node: Less escaping19634 Ref: #less-escaping19788 Node: Unicode characters20112 Ref: #unicode-characters20287 Node: Regular expressions21699 Ref: #regular-expressions21872 Node: hledger's regular expressions24968 Ref: #hledgers-regular-expressions25127 Node: Argument files26513 Ref: #argument-files26649 Node: Output27146 Ref: #output27258 Node: Output destination27385 Ref: #output-destination27516 Node: Output format27941 Ref: #output-format28087 Node: CSV output29684 Ref: #csv-output29800 Node: HTML output29903 Ref: #html-output30041 Node: JSON output30135 Ref: #json-output30273 Node: SQL output31195 Ref: #sql-output31311 Node: Commodity styles32046 Ref: #commodity-styles32186 Node: Colour32785 Ref: #colour32903 Node: Box-drawing33307 Ref: #box-drawing33425 Node: Paging33715 Ref: #paging33829 Node: Debug output34782 Ref: #debug-output34888 Node: Environment35551 Ref: #environment35675 Node: PART 2 DATA FORMATS36219 Ref: #part-2-data-formats36362 Node: Journal36362 Ref: #journal36471 Node: Journal cheatsheet37128 Ref: #journal-cheatsheet37267 Node: About journal format41252 Ref: #about-journal-format41412 Node: Comments43028 Ref: #comments43158 Node: Transactions43974 Ref: #transactions44097 Node: Dates45111 Ref: #dates45218 Node: Simple dates45263 Ref: #simple-dates45379 Node: Posting dates45879 Ref: #posting-dates45997 Node: Status46966 Ref: #status47067 Node: Code48775 Ref: #code48878 Node: Description49110 Ref: #description49241 Node: Payee and note49561 Ref: #payee-and-note49667 Node: Transaction comments50002 Ref: #transaction-comments50155 Node: Postings50518 Ref: #postings50651 Node: Account names51646 Ref: #account-names51776 Node: Amounts53450 Ref: #amounts53565 Node: Decimal marks digit group marks54550 Ref: #decimal-marks-digit-group-marks54725 Node: Commodity55584 Ref: #commodity55771 Node: Directives influencing number parsing and display56723 Ref: #directives-influencing-number-parsing-and-display56982 Node: Commodity display style57434 Ref: #commodity-display-style57640 Node: Rounding59050 Ref: #rounding59168 Node: Costs59618 Ref: #costs59734 Node: Other cost/lot notations61930 Ref: #other-costlot-notations62062 Node: Balance assertions64651 Ref: #balance-assertions64802 Node: Assertions and ordering65884 Ref: #assertions-and-ordering66073 Node: Assertions and multiple included files66773 Ref: #assertions-and-multiple-included-files67033 Node: Assertions and multiple -f files67533 Ref: #assertions-and-multiple--f-files67784 Node: Assertions and commodities68181 Ref: #assertions-and-commodities68402 Node: Assertions and costs69582 Ref: #assertions-and-costs69785 Node: Assertions and subaccounts70226 Ref: #assertions-and-subaccounts70446 Node: Assertions and virtual postings70770 Ref: #assertions-and-virtual-postings71008 Node: Assertions and auto postings71140 Ref: #assertions-and-auto-postings71370 Node: Assertions and precision72015 Ref: #assertions-and-precision72197 Node: Posting comments72464 Ref: #posting-comments72610 Node: Tags72987 Ref: #tags73101 Node: Tag values74294 Ref: #tag-values74383 Node: Directives75142 Ref: #directives75269 Node: Directives and multiple files76599 Ref: #directives-and-multiple-files76777 Node: Directive effects77544 Ref: #directive-effects77698 Node: account directive80711 Ref: #account-directive80867 Node: Account comments82265 Ref: #account-comments82415 Node: Account subdirectives82923 Ref: #account-subdirectives83114 Node: Account error checking83256 Ref: #account-error-checking83454 Node: Account display order84643 Ref: #account-display-order84831 Node: Account types85932 Ref: #account-types86073 Node: alias directive89700 Ref: #alias-directive89861 Node: Basic aliases90911 Ref: #basic-aliases91042 Node: Regex aliases91786 Ref: #regex-aliases91943 Node: Combining aliases92833 Ref: #combining-aliases93011 Node: Aliases and multiple files94287 Ref: #aliases-and-multiple-files94491 Node: end aliases directive95070 Ref: #end-aliases-directive95289 Node: Aliases can generate bad account names95438 Ref: #aliases-can-generate-bad-account-names95686 Node: Aliases and account types96271 Ref: #aliases-and-account-types96463 Node: commodity directive97159 Ref: #commodity-directive97333 Node: Commodity directive syntax98518 Ref: #commodity-directive-syntax98703 Node: Commodity error checking100154 Ref: #commodity-error-checking100335 Node: decimal-mark directive100629 Ref: #decimal-mark-directive100811 Node: include directive101208 Ref: #include-directive101372 Node: P directive102284 Ref: #p-directive102429 Node: payee directive103318 Ref: #payee-directive103467 Node: tag directive103940 Ref: #tag-directive104095 Node: Periodic transactions104563 Ref: #periodic-transactions104728 Node: Periodic rule syntax106717 Ref: #periodic-rule-syntax106895 Node: Periodic rules and relative dates107540 Ref: #periodic-rules-and-relative-dates107806 Node: Two spaces between period expression and description!108317 Ref: #two-spaces-between-period-expression-and-description108594 Node: Auto postings109278 Ref: #auto-postings109426 Node: Auto postings and multiple files112471 Ref: #auto-postings-and-multiple-files112635 Node: Auto postings and dates113036 Ref: #auto-postings-and-dates113284 Node: Auto postings and transaction balancing / inferred amounts / balance assertions113459 Ref: #auto-postings-and-transaction-balancing-inferred-amounts-balance-assertions113815 Node: Auto posting tags114318 Ref: #auto-posting-tags114600 Node: Auto postings on forecast transactions only115236 Ref: #auto-postings-on-forecast-transactions-only115482 Node: Other syntax115729 Ref: #other-syntax115845 Node: Balance assignments116472 Ref: #balance-assignments116628 Node: Balance assignments and prices118001 Ref: #balance-assignments-and-prices118216 Node: Balance assignments and multiple files118427 Ref: #balance-assignments-and-multiple-files118658 Node: Bracketed posting dates118851 Ref: #bracketed-posting-dates119035 Node: D directive119549 Ref: #d-directive119717 Node: apply account directive121317 Ref: #apply-account-directive121497 Node: Y directive122184 Ref: #y-directive122344 Node: Secondary dates123172 Ref: #secondary-dates123326 Node: Star comments124140 Ref: #star-comments124300 Node: Valuation expressions124832 Ref: #valuation-expressions125009 Node: Virtual postings125131 Ref: #virtual-postings125308 Node: Other Ledger directives126745 Ref: #other-ledger-directives126908 Node: CSV127474 Ref: #csv127567 Node: CSV rules cheatsheet129647 Ref: #csv-rules-cheatsheet129776 Node: source131574 Ref: #source131697 Node: separator132577 Ref: #separator132690 Node: skip133230 Ref: #skip133338 Node: date-format133882 Ref: #date-format134003 Node: timezone134727 Ref: #timezone134850 Node: newest-first135855 Ref: #newest-first135993 Node: intra-day-reversed136570 Ref: #intra-day-reversed136724 Node: decimal-mark137172 Ref: #decimal-mark137313 Node: fields list137652 Ref: #fields-list137791 Node: Field assignment139462 Ref: #field-assignment139606 Node: Field names140683 Ref: #field-names140814 Node: date field142017 Ref: #date-field142135 Node: date2 field142183 Ref: #date2-field142324 Node: status field142380 Ref: #status-field142523 Node: code field142572 Ref: #code-field142717 Node: description field142762 Ref: #description-field142922 Node: comment field142981 Ref: #comment-field143136 Node: account field143429 Ref: #account-field143579 Node: amount field144149 Ref: #amount-field144298 Node: currency field146990 Ref: #currency-field147143 Node: balance field147400 Ref: #balance-field147532 Node: if block147904 Ref: #if-block148025 Node: Matchers149433 Ref: #matchers149547 Node: What matchers match150344 Ref: #what-matchers-match150493 Node: Combining matchers150933 Ref: #combining-matchers151101 Node: Match groups151587 Ref: #match-groups151715 Node: if table152462 Ref: #if-table152584 Node: balance-type154146 Ref: #balance-type154275 Node: include154975 Ref: #include155102 Node: Working with CSV155546 Ref: #working-with-csv155693 Node: Rapid feedback156100 Ref: #rapid-feedback156233 Node: Valid CSV156685 Ref: #valid-csv156831 Node: File Extension157563 Ref: #file-extension157736 Node: Reading CSV from standard input158300 Ref: #reading-csv-from-standard-input158524 Node: Reading multiple CSV files158688 Ref: #reading-multiple-csv-files158919 Node: Reading files specified by rule159160 Ref: #reading-files-specified-by-rule159388 Node: Valid transactions160559 Ref: #valid-transactions160758 Node: Deduplicating importing161386 Ref: #deduplicating-importing161581 Node: Setting amounts162617 Ref: #setting-amounts162788 Node: Amount signs165146 Ref: #amount-signs165316 Node: Setting currency/commodity166213 Ref: #setting-currencycommodity166417 Node: Amount decimal places167591 Ref: #amount-decimal-places167797 Node: Referencing other fields168109 Ref: #referencing-other-fields168322 Node: How CSV rules are evaluated169219 Ref: #how-csv-rules-are-evaluated169436 Node: Well factored rules170889 Ref: #well-factored-rules171057 Node: CSV rules examples171381 Ref: #csv-rules-examples171516 Node: Bank of Ireland171581 Ref: #bank-of-ireland171718 Node: Coinbase173180 Ref: #coinbase173318 Node: Amazon174365 Ref: #amazon174490 Node: Paypal176209 Ref: #paypal176317 Node: Timeclock183961 Ref: #timeclock184066 Node: Timedot186244 Ref: #timedot186367 Node: Timedot examples189472 Ref: #timedot-examples189578 Node: PART 3 REPORTING CONCEPTS191749 Ref: #part-3-reporting-concepts191931 Node: Amount formatting parseability191931 Ref: #amount-formatting-parseability192128 Node: Time periods194333 Ref: #time-periods194472 Node: Report start & end date194590 Ref: #report-start-end-date194742 Node: Smart dates196401 Ref: #smart-dates196554 Node: Report intervals198422 Ref: #report-intervals198577 Node: Date adjustment198995 Ref: #date-adjustment199155 Node: Period expressions200006 Ref: #period-expressions200147 Node: Period expressions with a report interval201911 Ref: #period-expressions-with-a-report-interval202145 Node: More complex report intervals202359 Ref: #more-complex-report-intervals202604 Node: Multiple weekday intervals204405 Ref: #multiple-weekday-intervals204594 Node: Depth205416 Ref: #depth205518 Node: Queries205814 Ref: #queries205916 Node: Query types207546 Ref: #query-types207667 Node: Combining query terms210901 Ref: #combining-query-terms211078 Node: Queries and command options212346 Ref: #queries-and-command-options212545 Node: Queries and valuation212794 Ref: #queries-and-valuation212989 Node: Querying with account aliases213218 Ref: #querying-with-account-aliases213429 Node: Querying with cost or value213559 Ref: #querying-with-cost-or-value213736 Node: Pivoting214037 Ref: #pivoting214151 Node: Generating data215928 Ref: #generating-data216060 Node: Forecasting217643 Ref: #forecasting217768 Node: --forecast218299 Ref: #forecast218430 Node: Inspecting forecast transactions219400 Ref: #inspecting-forecast-transactions219602 Node: Forecast reports220732 Ref: #forecast-reports220905 Node: Forecast tags221841 Ref: #forecast-tags222001 Node: Forecast period in detail222461 Ref: #forecast-period-in-detail222655 Node: Forecast troubleshooting223549 Ref: #forecast-troubleshooting223717 Node: Budgeting224620 Ref: #budgeting224740 Node: Cost reporting225177 Ref: #cost-reporting225311 Node: Recording costs225972 Ref: #recording-costs226108 Node: Reporting at cost227699 Ref: #reporting-at-cost227874 Node: Equity conversion postings228464 Ref: #equity-conversion-postings228678 Node: Inferring equity conversion postings231109 Ref: #inferring-equity-conversion-postings231372 Node: Combining costs and equity conversion postings232124 Ref: #combining-costs-and-equity-conversion-postings232434 Node: Requirements for detecting equity conversion postings233422 Ref: #requirements-for-detecting-equity-conversion-postings233744 Node: Infer cost and equity by default ?234944 Ref: #infer-cost-and-equity-by-default235173 Node: Value reporting235381 Ref: #value-reporting235523 Node: -V Value236297 Ref: #v-value236429 Node: -X Value in specified commodity236624 Ref: #x-value-in-specified-commodity236825 Node: Valuation date236974 Ref: #valuation-date237151 Node: Finding market price237934 Ref: #finding-market-price238145 Node: --infer-market-prices market prices from transactions239314 Ref: #infer-market-prices-market-prices-from-transactions239596 Node: Valuation commodity242358 Ref: #valuation-commodity242577 Node: Simple valuation examples243790 Ref: #simple-valuation-examples243994 Node: --value Flexible valuation244653 Ref: #value-flexible-valuation244863 Node: More valuation examples246507 Ref: #more-valuation-examples246722 Node: Interaction of valuation and queries247992 Ref: #interaction-of-valuation-and-queries248239 Node: Effect of valuation on reports248711 Ref: #effect-of-valuation-on-reports248914 Node: PART 4 COMMANDS256611 Ref: #part-4-commands256760 Node: Commands overview257139 Ref: #commands-overview257273 Node: DATA ENTRY257452 Ref: #data-entry257576 Node: DATA CREATION257775 Ref: #data-creation257929 Node: DATA MANAGEMENT258047 Ref: #data-management258212 Node: REPORTS FINANCIAL258333 Ref: #reports-financial258508 Node: REPORTS VERSATILE258813 Ref: #reports-versatile258986 Node: REPORTS BASIC259239 Ref: #reports-basic259391 Node: HELP259900 Ref: #help260022 Node: ADD-ONS260132 Ref: #add-ons260238 Node: accounts260817 Ref: #accounts260950 Node: activity262837 Ref: #activity262956 Node: add263330 Ref: #add263440 Node: aregister266251 Ref: #aregister266372 Node: aregister and posting dates269260 Ref: #aregister-and-posting-dates269405 Node: balance270161 Ref: #balance270287 Node: balance features271272 Ref: #balance-features271412 Node: Simple balance report273378 Ref: #simple-balance-report273563 Node: Balance report line format275188 Ref: #balance-report-line-format275390 Node: Filtered balance report277548 Ref: #filtered-balance-report277740 Node: List or tree mode278067 Ref: #list-or-tree-mode278235 Node: Depth limiting279580 Ref: #depth-limiting279746 Node: Dropping top-level accounts280347 Ref: #dropping-top-level-accounts280547 Node: Showing declared accounts280857 Ref: #showing-declared-accounts281056 Node: Sorting by amount281587 Ref: #sorting-by-amount281754 Node: Percentages282424 Ref: #percentages282583 Node: Multi-period balance report283131 Ref: #multi-period-balance-report283331 Node: Balance change end balance285606 Ref: #balance-change-end-balance285815 Node: Balance report types287243 Ref: #balance-report-types287424 Node: Calculation type287922 Ref: #calculation-type288077 Node: Accumulation type288626 Ref: #accumulation-type288806 Node: Valuation type289708 Ref: #valuation-type289896 Node: Combining balance report types290897 Ref: #combining-balance-report-types291091 Node: Budget report292929 Ref: #budget-report293091 Node: Using the budget report295234 Ref: #using-the-budget-report295407 Node: Budget date surprises297510 Ref: #budget-date-surprises297710 Node: Selecting budget goals298874 Ref: #selecting-budget-goals299077 Node: Budgeting vs forecasting299822 Ref: #budgeting-vs-forecasting299999 Node: Balance report layout301270 Ref: #balance-report-layout301450 Node: Useful balance reports309635 Ref: #useful-balance-reports309795 Node: balancesheet310880 Ref: #balancesheet311025 Node: balancesheetequity312352 Ref: #balancesheetequity312510 Node: cashflow313906 Ref: #cashflow314037 Node: check315472 Ref: #check315586 Node: Default checks316390 Ref: #default-checks316516 Node: Strict checks317013 Ref: #strict-checks317158 Node: Other checks317638 Ref: #other-checks317780 Node: Custom checks318313 Ref: #custom-checks318470 Node: More about specific checks318887 Ref: #more-about-specific-checks319049 Node: close319755 Ref: #close319866 Node: close and balance assertions323331 Ref: #close-and-balance-assertions323509 Node: Example retain earnings324660 Ref: #example-retain-earnings324877 Node: Example migrate balances to a new file325309 Ref: #example-migrate-balances-to-a-new-file325574 Node: Example excluding closing/opening transactions326150 Ref: #example-excluding-closingopening-transactions326399 Node: codes327617 Ref: #codes327734 Node: commodities328598 Ref: #commodities328726 Node: demo328796 Ref: #demo328917 Node: descriptions329833 Ref: #descriptions329963 Node: diff330254 Ref: #diff330369 Node: files331411 Ref: #files331520 Node: help331661 Ref: #help-1331770 Node: import333143 Ref: #import333266 Node: Deduplication334374 Ref: #deduplication334499 Node: Import testing336518 Ref: #import-testing336683 Node: Importing balance assignments337526 Ref: #importing-balance-assignments337732 Node: Commodity display styles338381 Ref: #commodity-display-styles338554 Node: incomestatement338683 Ref: #incomestatement338825 Node: notes340153 Ref: #notes340275 Node: payees340637 Ref: #payees340752 Node: prices341271 Ref: #prices341386 Node: print342039 Ref: #print342154 Node: print explicitness343130 Ref: #print-explicitness343273 Node: print amount style344052 Ref: #print-amount-style344222 Node: print parseability345274 Ref: #print-parseability345446 Node: print other features346195 Ref: #print-other-features346374 Node: print output format346895 Ref: #print-output-format347043 Node: register350162 Ref: #register350284 Node: Custom register output355315 Ref: #custom-register-output355446 Node: rewrite356790 Ref: #rewrite356908 Node: Re-write rules in a file358806 Ref: #re-write-rules-in-a-file358969 Node: Diff output format360118 Ref: #diff-output-format360301 Node: rewrite vs print --auto361393 Ref: #rewrite-vs.-print---auto361553 Node: roi362109 Ref: #roi362216 Node: Spaces and special characters in --inv and --pnl364028 Ref: #spaces-and-special-characters-in---inv-and---pnl364268 Node: Semantics of --inv and --pnl364756 Ref: #semantics-of---inv-and---pnl364995 Node: IRR and TWR explained366845 Ref: #irr-and-twr-explained367005 Node: stats370258 Ref: #stats370366 Node: tags371753 Ref: #tags-1371860 Node: test372869 Ref: #test372962 Node: PART 5 COMMON TASKS373704 Ref: #part-5-common-tasks373850 Node: Getting help374148 Ref: #getting-help374289 Node: Constructing command lines375049 Ref: #constructing-command-lines375250 Node: Starting a journal file375907 Ref: #starting-a-journal-file376109 Node: Setting LEDGER_FILE377311 Ref: #setting-ledger_file377503 Node: Setting opening balances378460 Ref: #setting-opening-balances378661 Node: Recording transactions381802 Ref: #recording-transactions381991 Node: Reconciling382547 Ref: #reconciling382699 Node: Reporting384956 Ref: #reporting385105 Node: Migrating to a new file389090 Ref: #migrating-to-a-new-file389247 Node: BUGS389546 Ref: #bugs389636 Node: Troubleshooting390515 Ref: #troubleshooting390615  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.32.3/embeddedfiles/add.cast0000644000000000000000000003341014555053231015564 0ustar0000000000000000{"version": 2, "width": 80, "height": 25, "timestamp": 1678904454, "env": {"SHELL": "/opt/homebrew/bin/bash", "TERM": "xterm-256color"}, "title": "The easiest way to start a journal (add)"} [0.255203, "o", "\u001b[?2004h~$ "] [1.234397, "o", "h"] [1.327242, "o", "l"] [1.370235, "o", "e"] [1.53249, "o", "d"] [1.644623, "o", "g"] [1.819847, "o", "e"] [1.918665, "o", "r"] [2.045801, "o", " "] [2.542267, "o", "f"] [2.64452, "o", "i"] [2.738195, "o", "l"] [2.791383, "o", "e"] [2.874609, "o", "s"] [3.26324, "o", "\r\n\u001b[?2004l\r"] [3.428244, "o", "The hledger journa"] [3.428272, "o", "l file \"/Users/simon/.hledger.journ"] [3.42833, "o", "al\" was not found.\r\nPlease create it first, eg wi"] [3.428339, "o", "th \"hledg"] [3.428343, "o", "er a"] [3.428347, "o", "dd\""] [3.42835, "o", " or"] [3.428353, "o", " a"] [3.428356, "o", " t"] [3.428377, "o", "ext"] [3.42838, "o", " edito"] [3.428508, "o", "r.\r\nOr, specify an existing journal file with -f or LEDGE"] [3.428519, "o", "R_FILE.\r\n"] [3.441928, "o", "\u001b[?2004h~$ "] [4.143164, "o", "#"] [4.300801, "o", " "] [4.567329, "o", "N"] [4.763292, "o", "o"] [4.867708, "o", " "] [5.065003, "o", "h"] [5.123361, "o", "l"] [5.18613, "o", "e"] [5.327324, "o", "d"] [5.418392, "o", "g"] [5.552056, "o", "e"] [5.627632, "o", "r"] [5.735515, "o", " "] [5.834046, "o", "d"] [5.964766, "o", "a"] [6.106152, "o", "t"] [6.226028, "o", "a"] [6.532517, "o", "."] [6.678581, "o", " "] [8.309635, "o", "G"] [8.631756, "o", "o"] [8.735402, "o", "a"] [8.871778, "o", "l"] [9.439375, "o", ":"] [9.515163, "o", " "] [9.997127, "o", "u"] [10.078262, "o", "s"] [10.121507, "o", "e"] [10.251843, "o", " "] [10.349225, "o", "t"] [10.452566, "o", "h"] [10.521314, "o", "e"] [10.609218, "o", " "] [10.683405, "o", "a"] [10.764836, "o", "d"] [10.900257, "o", "d"] [11.012004, "o", " "] [11.128565, "o", "c"] [11.224034, "o", "o"] [11.266054, "o", "m"] [11.426288, "o", "m"] [11.506869, "o", "a"] [11.617359, "o", "n"] [11.693657, "o", "d"] [11.811191, "o", " "] [11.930049, "o", "t"] [12.014447, "o", "o"] [12.08663, "o", " "] [12.28556, "o", "s"] [12.43082, "o", "t"] [12.580679, "o", "a"] [12.662909, "o", "r"] [12.718242, "o", "t"] [12.871033, "o", " "] [12.963237, "o", "a"] [13.064358, "o", " "] [13.236245, "o", "j"] [13.343545, "o", "o"] [13.418653, "o", "u"] [13.526455, "o", "r"] [13.662285, "o", "n"] [13.766545, "o", "a"] [13.878083, "o", "l"] [13.9981, "o", " "] [14.162788, "o", "f"] [14.28061, "o", "i"] [14.364875, "o", "l"] [14.477069, "o", "e"] [16.816326, "o", "\r\n"] [16.816471, "o", "\u001b[?2004l\r"] [16.817073, "o", "\u001b[?2004h~$ "] [17.363334, "o", "#"] [17.870424, "o", " "] [18.801564, "o", "a"] [18.922632, "o", "n"] [18.993035, "o", "d"] [19.099526, "o", " "] [19.215501, "o", "t"] [19.293816, "o", "e"] [19.388051, "o", "l"] [19.545868, "o", "l"] [19.598296, "o", " "] [19.837054, "o", "h"] [19.911172, "o", "l"] [19.99106, "o", "e"] [20.171846, "o", "d"] [20.281177, "o", "g"] [20.427339, "o", "e"] [20.532727, "o", "r"] [20.704936, "o", " "] [20.826309, "o", "a"] [20.945941, "o", "b"] [21.069307, "o", "o"] [21.143202, "o", "u"] [21.247183, "o", "t"] [21.356392, "o", " "] [21.497804, "o", "m"] [21.763716, "o", "y"] [21.845479, "o", " "] [21.936883, "o", "f"] [22.06424, "o", "i"] [22.145905, "o", "r"] [22.287272, "o", "s"] [22.388396, "o", "t"] [22.528249, "o", " "] [22.805059, "o", "a"] [22.857191, "o", "c"] [23.035561, "o", "c"] [23.097684, "o", "o"] [23.144705, "o", "u"] [23.33486, "o", "n"] [23.38399, "o", "t"] [24.02125, "o", ":"] [24.096632, "o", " "] [25.64211, "o", "m"] [25.875169, "o", "y"] [25.960022, "o", " "] [26.056582, "o", "w"] [26.174807, "o", "a"] [26.300508, "o", "l"] [26.434609, "o", "l"] [26.512283, "o", "e"] [26.603068, "o", "t"] [26.733512, "o", "."] [28.063557, "o", "\r\n"] [28.06375, "o", "\u001b[?2004l\r"] [28.064135, "o", "\u001b[?2004h"] [28.064168, "o", "~$ "] [28.804492, "o", "h"] [28.887535, "o", "l"] [28.941199, "o", "e"] [29.096535, "o", "d"] [29.196855, "o", "g"] [29.343033, "o", "e"] [29.423874, "o", "r"] [29.567085, "o", " "] [29.754997, "o", "a"] [29.84447, "o", "d"] [29.964696, "o", "d"] [30.821916, "o", "\r\n"] [30.821956, "o", "\u001b[?2004l\r"] [30.977925, "o", "Creating hledger journal file \"/Users/simon/.hledger.j"] [30.97808, "o", "ournal\".\r\n"] [30.979303, "o", "Add"] [30.979315, "o", "ing tran"] [30.979321, "o", "saction"] [30.979324, "o", "s to "] [30.979336, "o", "jou"] [30.979391, "o", "rnal file /"] [30.979397, "o", "Users/simon/.hledger.journal\r\nAny command line ar"] [30.979401, "o", "gum"] [30.979403, "o", "en"] [30.979521, "o", "ts will be used as defaults.\r\nU"] [30.979556, "o", "se tab key to complete, readline keys to edit, enter to accept defaults.\r\nAn opt"] [30.979597, "o", "ional (CODE) may follow tra"] [30.979629, "o", "nsaction dates.\r\nAn optional ; COMMENT"] [30.979656, "o", " may follow descriptions or amounts.\r\nIf you"] [30.979661, "o", " make "] [30.979664, "o", "a "] [30.979667, "o", "mis"] [30.979674, "o", "ta"] [30.979677, "o", "ke, en"] [30.979733, "o", "te"] [30.979739, "o", "r < at any prompt to go one step backward.\r\nTo end a"] [30.979746, "o", " trans"] [30.979763, "o", "action, enter "] [30.979766, "o", ". w"] [30.979769, "o", "he"] [30.979772, "o", "n p"] [30.979775, "o", "ro"] [30.979778, "o", "mp"] [30.979781, "o", "ted"] [30.979783, "o", ".\r\n"] [30.979789, "o", "To"] [30.979792, "o", " quit"] [30.979795, "o", ", "] [30.979898, "o", "enter . at a date prompt or press control-d or control-c.\r\n"] [30.981349, "o", "\u001b[?1h\u001b="] [30.981828, "o", "\u001b[1;32mDate [2023-03-15]: \u001b[0m"] [32.365693, "o", "E"] [32.500444, "o", "N"] [32.618772, "o", "T"] [32.735942, "o", "E"] [32.846347, "o", "R"] [33.019661, "o", " "] [33.327122, "o", "k"] [33.448324, "o", "e"] [33.604502, "o", "y"] [33.684293, "o", " "] [33.846854, "o", "t"] [33.943511, "o", "o"] [34.037209, "o", " "] [34.184367, "o", "a"] [34.218041, "o", "c"] [34.66764, "o", "e"] [35.057403, "o", "\b\u001b[K"] [35.181887, "o", "c"] [35.255623, "o", "e"] [35.427566, "o", "p"] [35.571436, "o", "t"] [35.675992, "o", " "] [35.818066, "o", "d"] [36.014537, "o", "e"] [36.124485, "o", "f"] [36.220167, "o", "a"] [36.292678, "o", "u"] [36.363166, "o", "l"] [36.64892, "o", "t"] [36.954332, "o", "."] [38.004952, "o", "\u001b[8D\u001b[K"] [38.182813, "o", "\u001b[7D\u001b[K"] [38.372388, "o", "\u001b[3D\u001b[K"] [38.566491, "o", "\u001b[4D\u001b[K"] [38.937339, "o", "\u001b[6D\u001b[K"] [39.366089, "o", "\r\r\n"] [39.366289, "o", "\u001b[?1l\u001b>"] [39.370371, "o", "\u001b[?1h\u001b="] [39.370686, "o", "\u001b[1;32mDescription: \u001b[0m"] [40.438771, "o", "o"] [40.510529, "o", "p"] [40.624829, "o", "e"] [40.790305, "o", "n"] [40.965564, "o", "i"] [41.043854, "o", "n"] [41.153372, "o", "g"] [41.232651, "o", " "] [41.46274, "o", "b"] [41.559769, "o", "a"] [41.688099, "o", "l"] [41.799534, "o", "a"] [41.87038, "o", "n"] [42.013444, "o", "c"] [42.100814, "o", "e"] [42.179245, "o", "s"] [42.672007, "o", "\r\r\n"] [42.672242, "o", "\u001b[?1l\u001b>"] [42.672897, "o", "\u001b[?1h\u001b="] [42.677624, "o", "\u001b[1;32mAccount 1: \u001b[0m"] [44.247752, "o", "I"] [44.451109, "o", "'"] [44.648424, "o", "l"] [44.796114, "o", "l"] [44.887984, "o", " "] [44.978643, "o", "c"] [45.044853, "o", "a"] [45.129135, "o", "l"] [45.276748, "o", "l"] [45.379586, "o", " "] [45.545822, "o", "i"] [45.670209, "o", "t"] [45.763155, "o", " "] [46.076756, "o", "c"] [46.206959, "o", "a"] [46.298797, "o", "s"] [46.40413, "o", "h"] [47.912169, "o", "\u001b[4D\u001b[K"] [48.126171, "o", "\u001b[3D\u001b[K"] [48.333167, "o", "\u001b[5D\u001b[K"] [48.539866, "o", "\u001b[3D\u001b[K"] [48.762142, "o", "\u001b[2D\u001b[K"] [49.06622, "o", "c"] [49.164572, "o", "a"] [49.250997, "o", "s"] [49.327952, "o", "h"] [49.73888, "o", "\r\r\n"] [49.739041, "o", "\u001b[?1l\u001b>"] [49.739718, "o", "\u001b[?1h\u001b="] [49.740062, "o", "\u001b[1;32mAmount 1: \u001b[0m"] [50.952601, "o", "$"] [51.407241, "o", "5"] [51.608231, "o", "0"] [51.926796, "o", "."] [52.089745, "o", "2"] [52.216239, "o", "5"] [53.233036, "o", "\r\r\n"] [53.23324, "o", "\u001b[?1l\u001b>"] [53.235334, "o", "\u001b[?1h\u001b="] [53.235626, "o", "\u001b[1;32mAccount 2: \u001b[0m"] [55.593736, "o", "I"] [55.778761, "o", "n"] [55.846798, "o", " "] [56.100551, "o", "D"] [56.321018, "o", "o"] [56.413207, "o", "u"] [56.470998, "o", "b"] [56.601466, "o", "l"] [56.670964, "o", "e"] [56.796657, "o", " "] [56.955752, "o", "E"] [57.171269, "o", "n"] [57.289458, "o", "t"] [57.339763, "o", "r"] [57.500175, "o", "y"] [57.573121, "o", " "] [57.846171, "o", "B"] [58.087773, "o", "o"] [58.244044, "o", "o"] [58.333501, "o", "k"] [58.836289, "o", "k"] [58.930351, "o", "e"] [59.083618, "o", "e"] [59.199624, "o", "p"] [59.415746, "o", "i"] [59.476424, "o", "n"] [59.570074, "o", "g"] [59.93668, "o", ","] [60.017958, "o", " "] [60.507438, "o", "w"] [60.589713, "o", "e"] [60.711635, "o", " "] [60.911856, "o", "m"] [61.105571, "o", "u"] [61.158489, "o", "s"] [61.250867, "o", "t"] [61.321488, "o", " "] [61.48602, "o", "s"] [61.574183, "o", "a"] [61.753348, "o", "y"] [61.829632, "o", " "] [62.100469, "o", "w"] [62.279986, "o", "h"] [62.393708, "o", "e"] [62.529779, "o", "r"] [62.626381, "o", "e"] [62.79806, "o", " "] [62.926809, "o", "t"] [63.029974, "o", "h"] [63.126396, "o", "e"] [63.136837, "o", " "] [63.336311, "o", "m"] [63.457882, "o", "o"] [63.565931, "o", "n"] [63.71167, "o", "e"] [63.941578, "o", "y"] [64.005898, "o", " "] [64.202506, "o", "c"] [64.299594, "o", "o"] [64.351714, "o", "m"] [64.452243, "o", "e"] [64.545918, "o", "s"] [64.676844, "o", " "] [64.800326, "o", "f"] [64.968768, "o", "r"] [65.000807, "o", "o"] [65.075064, "o", "m"] [65.335673, "o", "."] [65.434415, "o", " \b"] [65.754756, "o", "F"] [66.021373, "o", "o"] [66.105097, "o", "r"] [66.20665, "o", " "] [66.353568, "o", "o"] [66.433295, "o", "p"] [66.547727, "o", "e"] [66.678949, "o", "n"] [66.844279, "o", "i"] [66.929605, "o", "n"] [67.041925, "o", "g"] [67.249947, "o", " "] [67.912057, "o", "b"] [68.023269, "o", "a"] [68.128661, "o", "l"] [68.254994, "o", "a"] [68.33604, "o", "n"] [68.457164, "o", "c"] [68.527258, "o", "e"] [68.612963, "o", "s"] [68.904649, "o", ","] [68.985425, "o", " "] [69.977925, "o", "t"] [70.136536, "o", "h"] [70.219258, "o", "a"] [70.31614, "o", "t"] [70.485621, "o", "'"] [70.617502, "o", "s"] [70.83977, "o", " "] [71.662638, "o", "\""] [72.018456, "o", "e"] [72.221028, "o", "q"] [72.313577, "o", "u"] [72.349719, "o", "i"] [72.468137, "o", "t"] [72.568905, "o", "y"] [72.800114, "o", "\""] [73.188821, "o", "."] [77.548683, "o", "\u001b[8D\u001b[K"] [77.799445, "o", "\u001b[3D\u001b[K"] [77.832655, "o", "\u001b[5D\u001b[K"] [77.866934, "o", "\u001b[10D\u001b[K"] [77.901869, "o", "\u001b[8D\u001b[K"] [77.9349, "o", "\u001b[4D\u001b[K"] [77.97057, "o", "\r\u001b[A\u001b[74C\u001b[K\r\r\n\u001b[K\r\u001b[A\u001b[74C"] [78.001574, "o", "\u001b[6D\u001b[K"] [78.034116, "o", "\u001b[6D\u001b[K"] [78.067545, "o", "\u001b[4D\u001b[K"] [78.10191, "o", "\u001b[6D\u001b[K"] [78.134988, "o", "\u001b[4D\u001b[K"] [78.168896, "o", "\u001b[5D\u001b[K"] [78.201546, "o", "\u001b[3D\u001b[K"] [78.475379, "o", "\u001b[13D\u001b[K"] [78.727091, "o", "\u001b[6D\u001b[K"] [78.759581, "o", "\u001b[7D\u001b[K"] [78.794906, "o", "\u001b[3D\u001b[K"] [79.197513, "o", "e"] [79.388333, "o", "q"] [79.478797, "o", "u"] [79.557333, "o", "i"] [79.646162, "o", "t"] [79.752036, "o", "y"] [80.052548, "o", "\r\r\n"] [80.052709, "o", "\u001b[?1l\u001b>"] [80.053503, "o", "\u001b[?1h\u001b="] [80.053779, "o", "\u001b[1;32mAmount 2 [$-50.25]: \u001b[0m"] [81.514416, "o", "\r\r\n"] [81.514624, "o", "\u001b[?1l\u001b>"] [81.515346, "o", "\u001b[?1h\u001b="] [81.515758, "o", "\u001b[1;32mAccount 3 (or . or enter to finish this transaction): \u001b[0m"] [83.121045, "o", "\r\r\n"] [83.121349, "o", "\u001b[?1l\u001b>"] [83.124682, "o", "2023-03-15 opening balances\r\n cash $50.25\r\n equity $-50.25\r\n\r\n"] [83.124741, "o", "\u001b[?1h\u001b="] [83.125302, "o", "\u001b[1;32mSave this transaction to the journal ? [y]: \u001b[0m"] [84.648814, "o", "\r\r\n"] [84.649125, "o", "\u001b[?1l\u001b>"] [84.650906, "o", "Saved"] [84.650941, "o", ".\r\nStartin"] [84.650952, "o", "g th"] [84.650963, "o", "e "] [84.650973, "o", "nex"] [84.650983, "o", "t t"] [84.650993, "o", "ran"] [84.651004, "o", "sa"] [84.651014, "o", "cti"] [84.651025, "o", "on "] [84.651035, "o", "(."] [84.651045, "o", " or"] [84.651055, "o", " ct"] [84.651065, "o", "rl"] [84.651075, "o", "-D/"] [84.651086, "o", "ct"] [84.651096, "o", "rl-"] [84.651106, "o", "C t"] [84.651116, "o", "o "] [84.651126, "o", "qui"] [84.651136, "o", "t)\r\n"] [84.652027, "o", "\u001b[?1h\u001b="] [84.652505, "o", "\u001b[1;32mDate [2023-03-15]: \u001b[0m"] [86.062566, "o", "."] [86.948614, "o", "\r\r\n"] [86.94891, "o", "\u001b[?1l\u001b>"] [86.961366, "o", "\u001b[?2004h"] [86.961397, "o", "~$ "] [90.08491, "o", "h"] [90.169623, "o", "l"] [90.259761, "o", "e"] [90.393192, "o", "d"] [90.48565, "o", "g"] [90.643033, "o", "e"] [90.731047, "o", "r"] [90.845308, "o", " "] [90.989267, "o", "f"] [91.090677, "o", "i"] [91.155866, "o", "l"] [91.219015, "o", "e"] [91.318928, "o", "s"] [91.846494, "o", "\r\n"] [91.846728, "o", "\u001b[?2004l\r"] [91.89879, "o", "/Users/simon/.hledger.journal\r\n"] [91.905659, "o", "\u001b[?2004h~$ "] [93.218891, "o", "c"] [93.397969, "o", "a"] [93.545225, "o", "t"] [93.677595, "o", " "] [93.891204, "o", "."] [94.181562, "o", "h"] [94.223614, "o", "l"] [94.309628, "o", "e"] [94.451716, "o", "d"] [94.549868, "o", "g"] [94.684816, "o", "e"] [94.792859, "o", "r"] [94.855242, "o", "."] [95.054234, "o", "j"] [95.201191, "o", "o"] [95.260721, "o", "u"] [95.404053, "o", "r"] [95.529899, "o", "n"] [95.655928, "o", "a"] [95.768796, "o", "l"] [97.848002, "o", "\r\n\u001b[?2004l\r"] [97.85161, "o", "; journal created 2023-03-15 by hledger\r\n\r\n2023-03-15 opening balances\r\n cash $50.25\r\n equity $-50.25\r\n"] [100.830158, "o", "\u001b[?2004h"] [100.830201, "o", "~$ "] [105, "o", "\u001b[?2004l\r\r\n"] hledger-1.32.3/embeddedfiles/balance.cast0000644000000000000000000000531614555053231016425 0ustar0000000000000000{"version": 2, "width": 80, "height": 25, "timestamp": 1678904454, "idle_time_limit": 0.5, "env": {"SHELL": "/opt/homebrew/bin/bash", "TERM": "xterm-256color"}, "title": "Show account balances and changes (balance)"} [97.851861, "o", "\u001b[?2004h~$ "] [108.4427, "o", "h"] [108.511571, "o", "l"] [108.563283, "o", "e"] [108.730511, "o", "d"] [108.803014, "o", "g"] [108.958676, "o", "e"] [109.045557, "o", "r"] [109.179193, "o", " "] [109.479806, "o", "b"] [109.579409, "o", "a"] [109.688887, "o", "l"] [109.797373, "o", "a"] [109.91028, "o", "n"] [109.997384, "o", "c"] [110.094392, "o", "e"] [110.502797, "o", " "] [110.689187, "o", " "] [110.861258, "o", " "] [110.983483, "o", "#"] [111.339007, "o", " "] [111.716216, "o", "s"] [111.764379, "o", "h"] [111.834664, "o", "o"] [111.929608, "o", "w"] [112.018977, "o", " "] [112.127754, "o", "a"] [112.222003, "o", "c"] [112.376553, "o", "c"] [112.447519, "o", "o"] [112.508197, "o", "u"] [112.718333, "o", "n"] [112.776805, "o", "t"] [112.882741, "o", " "] [113.097111, "o", "b"] [113.178418, "o", "a"] [113.315295, "o", "l"] [113.375822, "o", "a"] [113.519044, "o", "n"] [113.609534, "o", "c"] [113.696372, "o", "e"] [113.785515, "o", "s"] [115.603503, "o", "\r\n"] [115.603698, "o", "\u001b[?2004l\r"] [115.658566, "o", " $50.25 cash\r\n \u001b[31m$-50.25\u001b[m equity\r\n--------------------\r\n 0 \r\n"] [115.666234, "o", "\u001b[?2004h~$ "] [117.006486, "o", "h"] [117.097537, "o", "l"] [117.154161, "o", "e"] [117.331344, "o", "d"] [117.4488, "o", "g"] [117.596908, "o", "e"] [117.690342, "o", "r"] [117.799646, "o", " "] [118.066348, "o", "b"] [118.131542, "o", "a"] [118.269237, "o", "l"] [118.350699, "o", "a"] [118.45648, "o", "n"] [118.540488, "o", "c"] [118.651362, "o", "e"] [118.751114, "o", " "] [119.039376, "o", "c"] [119.146043, "o", "a"] [119.258617, "o", "s"] [119.41532, "o", "h"] [119.7897, "o", " "] [119.955405, "o", " "] [120.142919, "o", " "] [120.480195, "o", "#"] [120.753113, "o", " "] [120.904346, "o", "s"] [121.013868, "o", "h"] [121.06859, "o", "o"] [121.151587, "o", "w"] [121.241558, "o", " "] [121.408393, "o", "j"] [121.582123, "o", "u"] [121.637329, "o", "s"] [121.731132, "o", "t"] [121.799539, "o", " "] [121.972017, "o", "c"] [122.064462, "o", "a"] [122.157572, "o", "s"] [122.355162, "o", "h"] [122.459994, "o", " "] [122.595849, "o", "a"] [122.697417, "o", "c"] [122.861577, "o", "c"] [122.919021, "o", "o"] [122.953757, "o", "u"] [123.174305, "o", "n"] [123.270113, "o", "t"] [124.685978, "o", "\r\n"] [124.686062, "o", "\u001b[?2004l\r"] [124.827946, "o", " $50.25 cash\r\n--------------------\r\n $50.25 \r\n"] [125, "o", "\u001b[?2004h"] [125, "o", "~$ "] [126, "o", "\u001b[?2004l\r\r\n"] hledger-1.32.3/embeddedfiles/install.cast0000644000000000000000000132331114555053231016505 0ustar0000000000000000{"version": 2, "width": 80, "height": 25, "timestamp": 1679022326, "env": {"SHELL": "/opt/homebrew/bin/bash", "TERM": "xterm-256color"}, "title": "Upgrading hledger tools to latest source release with hledger-install"} [0.176734, "o", "\u001b[?2004h$ "] [1.370668, "o", "#"] [1.638932, "o", " "] [1.902566, "o", "G"] [2.050607, "o", "o"] [2.196438, "o", "a"] [2.321222, "o", "l"] [2.594621, "o", ":"] [2.654595, "o", " "] [3.032902, "o", "u"] [3.119646, "o", "s"] [3.202388, "o", "e"] [3.358939, "o", " "] [3.520646, "o", "t"] [3.602487, "o", "h"] [3.724757, "o", "e"] [3.781112, "o", " "] [3.963303, "o", "h"] [4.038573, "o", "l"] [4.074891, "o", "e"] [4.24445, "o", "d"] [4.381226, "o", "g"] [4.52317, "o", "e"] [4.59591, "o", "r"] [4.673338, "o", "-"] [4.881321, "o", "i"] [4.93948, "o", "n"] [5.025133, "o", "s"] [5.064065, "o", "t"] [5.196402, "o", "a"] [5.336885, "o", "l"] [5.486745, "o", "l"] [5.550249, "o", " "] [5.731842, "o", "b"] [5.847355, "o", "a"] [5.925392, "o", "s"] [6.043606, "o", "h"] [6.116812, "o", " "] [6.252079, "o", "s"] [6.353887, "o", "c"] [6.564841, "o", "r"] [6.656664, "o", "i"] [6.71234, "o", "p"] [6.852646, "o", "t"] [6.950147, "o", " "] [7.11887, "o", "t"] [7.278621, "o", "o"] [7.371103, "o", " "] [7.7892, "o", "u"] [7.859178, "o", "p"] [7.950347, "o", "g"] [8.005077, "o", "r"] [8.148006, "o", "a"] [8.249959, "o", "d"] [8.452416, "o", "e"] [8.641369, "o", " "] [9.607081, "o", "h"] [9.651407, "o", "l"] [9.715114, "o", "e"] [9.894138, "o", "d"] [10.026633, "o", "g"] [10.18316, "o", "e"] [10.243145, "o", "r"] [10.375556, "o", " "] [10.701801, "o", "a"] [10.805391, "o", "n"] [10.889889, "o", "d"] [11.028208, "o", " "] [11.460136, "o", "r"] [11.494157, "o", "e"] [11.585034, "o", "l"] [11.769757, "o", "a"] [11.930786, "o", "t"] [11.998833, "o", "e"] [12.191688, "o", "d"] [12.331504, "o", " "] [12.472755, "o", "t"] [12.5659, "o", "o"] [12.699219, "o", "o \r"] [12.911827, "o", "l"] [13.008721, "o", "s"] [14.076361, "o", "\r\n"] [14.076596, "o", "\u001b[?2004l\r"] [14.076772, "o", "\u001b[?2004h$ "] [17.898143, "o", "\u001b[7mcurl -O https://raw.githubusercontent.com/simonmichael/hledger/master/hledger-\u001b[27m\u001b[7mi\u001b[27m\u001b[7mnstall/hledger-install.sh \u001b[27m"] [20.279622, "o", "\u001b[A\r\u001b[C\u001b[Ccurl -O https://raw.githubusercontent.com/simonmichael/hledger/master/hledger-install/hledger-install.sh "] [21.332271, "o", " "] [21.474465, "o", " "] [21.676089, "o", "#"] [21.838239, "o", " "] [22.010876, "o", "g"] [22.145012, "o", "e"] [22.253908, "o", "t"] [22.348254, "o", " "] [22.441593, "o", "t"] [22.556485, "o", "h"] [22.621661, "o", "e"] [22.736076, "o", " "] [22.866482, "o", "l"] [22.939641, "o", "a"] [23.059433, "o", "t"] [23.143479, "o", "e"] [23.231822, "o", "s"] [23.311578, "o", "t"] [24.015276, "o", "\r\n"] [24.015439, "o", "\u001b[?2004l\r"] [24.032231, "o", " % Total % Received % Xferd Average Speed Time "] [24.032263, "o", " Time Time Current\r\n Dload Upload Total Spent Left "] [24.032409, "o", " Speed\r\n\r 0 0 0 0 0 0 0 0 --:--:-- --:--:-- --:--:-- 0"] [24.780302, "o", "\r100 31183 100 31183 0 0 41224 "] [24.780456, "o", " 0 --:--:-- --:--:-- --:--:-- 41688\r\n"] [24.783804, "o", "\u001b[?2004h$ "] [26.961496, "o", "l"] [27.064797, "o", "e"] [27.139896, "o", "s"] [27.333159, "o", "s"] [27.505476, "o", " "] [28.858202, "o", "h"] [28.915346, "o", "l"] [28.972458, "o", "e"] [29.153008, "o", "d"] [29.252495, "o", "g"] [29.384733, "o", "e"] [29.461821, "o", "r"] [29.537611, "o", "-"] [29.728954, "o", "i"] [29.795565, "o", "n"] [29.82052, "o", "s"] [29.899985, "o", "t"] [30.010507, "o", "s"] [30.016084, "o", "a"] [30.122473, "o", "l"] [30.251287, "o", "l"] [30.453547, "o", "."] [30.603412, "o", "s"] [30.667159, "o", "h"] [31.210044, "o", "\b\u001b[K"] [31.461264, "o", "\b\u001b[K"] [31.49236, "o", "\b\u001b[K"] [31.52637, "o", "\b\u001b[K"] [31.560295, "o", "\b\u001b[K"] [31.593332, "o", "\b\u001b[K"] [31.625685, "o", "\b\u001b[K"] [32.187842, "o", "a"] [32.279734, "o", "l"] [32.417519, "o", "l"] [32.60417, "o", "."] [32.744899, "o", "s"] [32.849145, "o", "h"] [33.067965, "o", " "] [33.200691, "o", " "] [33.41353, "o", "#"] [33.913465, "o", " "] [34.134768, "o", "s"] [34.258318, "o", "a"] [34.421427, "o", "n"] [34.516776, "o", "i"] [34.643727, "o", "t"] [34.786966, "o", "y"] [34.843291, "o", " "] [34.975237, "o", "c"] [35.066835, "o", "h"] [35.163416, "o", "e"] [35.231586, "o", "c"] [35.326834, "o", "k"] [35.401151, "o", " "] [35.553708, "o", "i"] [35.624617, "o", "t"] [35.727053, "o", " "] [35.979997, "o", "f"] [36.066291, "o", "o"] [36.158722, "o", "r"] [36.279483, "o", " "] [36.705012, "o", "s"] [36.782066, "o", "e"] [36.972752, "o", "c"] [37.132775, "o", "u"] [37.231615, "o", "r"] [37.347584, "o", "i"] [37.467899, "o", "t"] [37.590745, "o", "y"] [40.616408, "o", "\b\b\b\b\b\b\b\b\u001b[K"] [40.811557, "o", "\b\b\b\b\u001b[K"] [40.996774, "o", "\b\b\b\u001b[K"] [41.171117, "o", "\b\b\b\b\b\b\u001b[K"] [41.346749, "o", "\b\b\b\b\b\b\b\u001b[K"] [41.525057, "o", "\b\b\b\b\b\b\u001b[K"] [41.702317, "o", "\b\b\b\b\b\b\b\b\u001b[K"] [41.882476, "o", "\b\b\b\b\b\b\b\b\u001b[K"] [42.060761, "o", "\r\u001b[C\u001b[C\u001b[K"] [43.733882, "o", "b"] [43.874113, "o", "a"] [43.918772, "o", "s"] [44.015582, "o", "h"] [44.088499, "o", " "] [44.268316, "o", "h"] [44.332259, "o", "l"] [44.376558, "o", "e"] [44.524447, "o", "d"] [44.639242, "o", "g"] [44.772352, "o", "e"] [44.841668, "o", "r"] [44.926803, "o", "-"] [45.157838, "o", "i"] [45.202148, "o", "n"] [45.283461, "o", "s"] [45.343617, "o", "t"] [45.465177, "o", "a"] [45.60539, "o", "l"] [45.746209, "o", "l"] [45.9551, "o", "."] [46.130441, "o", "s"] [46.240858, "o", "h"] [47.051474, "o", " "] [47.198596, "o", " "] [47.339509, "o", "#"] [47.636693, "o", " "] [47.742026, "o", "a"] [47.852332, "o", "n"] [47.951976, "o", "d"] [48.039539, "o", " "] [48.201027, "o", "r"] [48.3132, "o", "u"] [48.51545, "o", "n"] [49.048946, "o", "\r\n"] [49.049102, "o", "\u001b[?2004l\r"] [49.062342, "o", "Thu Mar 16 17:06:15 HST 2023\r\n"] [49.062586, "o", "Running hledger-install.sh version 20230316 to install hledger 1.29.1 and related tools\r\n"] [49.065782, "o", "on "] [49.067688, "o", "Darwin 21.6.0 Darwin Kernel Version 21.6.0: Sun Nov 6 23:29:57 PST 2022; root:xnu-8020.240.14~1/RELEASE_ARM64_T8101\r\n"] [49.069173, "o", "\r\nCurrent install status:\r\n"] [49.118169, "o", "hledger 1.29 is installed at /Users/simon/.local/bin/hledger\r\n"] [49.163219, "o", "hledger-ui 1.29 is installed at /Users/simon/.local/bin/hledger-ui\r\n"] [49.218934, "o", "hledger-web 1.29 is installed at /Users/simon/.local/bin/hledger-web\r\n"] [49.274654, "o", "hledger-stockquotes 0.1.2.1 is installed at /Users/simon/.local/bin/hledger-stockquotes\r\n"] [50.619726, "o", "hledger-edit 1.13.2 is installed at /opt/homebrew/bin/hledger-edit\r\n"] [51.32363, "o", "hledger-plot 1.13.2 is installed at /opt/homebrew/bin/hledger-plot\r\n"] [51.360783, "o", "hledger-interest 1.6.5 is installed at /Users/simon/.local/bin/hledger-interest\r\n"] [51.409888, "o", "hledger-iadd 1.3.17 is installed at /Users/simon/.cabal/bin/hledger-iadd\r\n"] [51.409911, "o", "\r\nEnsuring a Haskell build tool:\r\n"] [51.464642, "o", "stack 2.9.3 is installed, using stack to install hledger in /Users/simon/.local/bin\r\n"] [51.536206, "o", "Using stack Version 2.9.3, Git revision d0e984f00034552aac7c67675d49ef0807c10c7b (dirty) (112 commits) aarch64\r\nWarning: this is an unsupported build that may use different versions of\r\ndependencies and GHC than the officially released binaries, and therefore may\r\nnot behave identically. If you encounter problems, please try the latest\r\nofficial build by running 'stack upgrade --force-download'.\r\n"] [51.536229, "o", "Updating stack's package db to see latest packages\r\nTrying stack update --verbosity=error\r\n"] [63.303664, "o", "\r\nEnsuring the Python pip install tool:\r\n"] [63.520606, "o", "pip 23.0 from /opt/homebrew/lib/python3.9/site-packages/pip (python 3.9) is installed\r\n\r\nInstalling hledger tools:\r\n"] [63.583691, "o", "Installing hledger\r\n"] [63.583791, "o", "Trying stack install --install-ghc --resolver=lts-20.14 hledger-1.29.1 hledger-lib-1.29.1 brick-1.6 fsnotify-0.4.1.0 --verbosity=error\r\n"] [66.628657, "o", "Progress 0/135"] [66.734469, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [66.734496, "o", "Progress 1/135: Diff, OneTuple, Only, StateVar, base-compat, base-orphans, bimap, blaze-builder"] [66.801372, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [66.801559, "o", "Progress 2/135: OneTuple, Only, StateVar, base-compat, base-orphans, bimap, blaze-builder, cabal-doctest"] [66.870952, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [66.871065, "o", "Progress 3/135: Only, StateVar, base-compat, base-orphans, bimap, blaze-builder, cabal-doctest, call-stack"] [66.938928, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [66.93905, "o", "Progress 4/135: StateVar, base-compat, base-orphans, bimap, blaze-builder, cabal-doctest, call-stack, cereal"] [67.004839, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.004873, "o", "Progress 5/135: base-compat, base-orphans, bimap, blaze-builder, cabal-doctest, call-stack, cereal, clock"] [67.087887, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.088013, "o", "Progress 6/135: base-compat-batteries, base-orphans, bimap, blaze-builder, cabal-doctest, call-stack, cereal, clock"] [67.157264, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.157291, "o", "Progress 7/135: base-compat-batteries, bimap, blaze-builder, cabal-doctest, call-stack, cereal, clock, cmdargs"] [67.226998, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.227106, "o", "Progress 8/135: base-compat-batteries, blaze-builder, cabal-doctest, call-stack, cereal, clock, cmdargs, colour"] [67.294664, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.294683, "o", "Progress 9/135: base-compat-batteries, blaze-markup, cabal-doctest, call-stack, cereal, clock, cmdargs, colour"] [67.364781, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.364901, "o", "Progress 10/135: base-compat-batteries, blaze-markup, call-stack, cereal, clock, cmdargs, colour, contravariant"] [67.434849, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.434945, "o", "Progress 11/135: base-compat-batteries, blaze-markup, cereal, clock, cmdargs, colour, contravariant, control-monad-free"] [67.502403, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.502499, "o", "Progress 12/135: base-compat-batteries, blaze-markup, clock, cmdargs, colour, contravariant, control-monad-free, csv"] [67.571581, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.571664, "o", "Progress 13/135: base-compat-batteries, blaze-markup, cmdargs, colour, contravariant, control-monad-free, csv, data-array-byte"] [67.648921, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.649013, "o", "Progress 14/135: blaze-markup, cmdargs, colour, contravariant, control-monad-free, csv, data-array-byte, data-clist"] [67.716431, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.716457, "o", "Progress 15/135: blaze-markup, colour, contravariant, control-monad-free, csv, data-array-byte, data-clist, data-default-class"] [67.782473, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.782593, "o", "Progress 16/135: ansi-terminal, blaze-markup, contravariant, control-monad-free, csv, data-array-byte, data-clist, data-default-class"] [67.84998, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.850164, "o", "Progress 17/135: ansi-terminal, blaze-html, contravariant, control-monad-free, csv, data-array-byte, data-clist, data-default-class"] [67.917932, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.918099, "o", "Progress 18/135: ansi-terminal, blaze-html, control-monad-free, csv, data-array-byte, data-clist, data-default-class, dlist"] [67.985774, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [67.985872, "o", "Progress 19/135: ansi-terminal, blaze-html, csv, data-array-byte, data-clist, data-default-class, dlist, emojis"] [68.053443, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.053581, "o", "Progress 20/135: ansi-terminal, blaze-html, data-array-byte, data-clist, data-default-class, dlist, emojis, extra"] [68.118894, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.118922, "o", "Progress 21/135: ansi-terminal, blaze-html, data-clist, data-default-class, dlist, emojis, extra, file-embed"] [68.188577, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.188654, "o", "Progress 22/135: ansi-terminal, blaze-html, data-default-class, dlist, emojis, extra, file-embed, hashable"] [68.255757, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.255899, "o", "Progress 23/135: ansi-terminal, blaze-html, data-default-instances-containers, dlist, emojis, extra, file-embed, hashable"] [68.323647, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.323841, "o", "Progress 24/135: ansi-wl-pprint, blaze-html, data-default-instances-containers, dlist, emojis, extra, file-embed, hashable"] [68.393516, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.39354, "o", "Progress 25/135: ansi-wl-pprint, data-default-instances-containers, dlist, emojis, extra, file-embed, hashable, haskeline"] [68.457735, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.457821, "o", "Progress 26/135: ansi-wl-pprint, data-default-instances-containers, data-default-instances-dlist, emojis, extra, file-embed, hashable, haskeline"] [68.523531, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.523556, "o", "Progress 27/135: ansi-wl-pprint, data-default-instances-containers, data-default-instances-dlist, extra, file-embed, hashable, haskeline, hfsevents"] [68.58999, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.59017, "o", "Progress 28/135: ansi-wl-pprint, data-default-instances-containers, data-default-instances-dlist, file-embed, hashable, haskeline, hfsevents, html"] [68.657569, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.657672, "o", "Progress 29/135: ansi-wl-pprint, data-default-instances-containers, data-default-instances-dlist, hashable, haskeline, hfsevents, html, indexed-traversable"] [68.723733, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.723758, "o", "Progress 30/135: ansi-wl-pprint, async, data-default-instances-containers, data-default-instances-dlist, haskeline, hfsevents, html, indexed-traversable"] [68.790493, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.790587, "o", "Progress 31/135: ansi-wl-pprint, async, case-insensitive, data-default-instances-dlist, haskeline, hfsevents, html, indexed-traversable"] [68.854509, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.854652, "o", "Progress 32/135: async, case-insensitive, data-default-instances-dlist, data-fix, haskeline, hfsevents, html, indexed-traversable"] [68.924087, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.924291, "o", "Progress 33/135: async, case-insensitive, data-default-instances-dlist, data-fix, hfsevents, html, indexed-traversable, integer-logarithms"] [68.992299, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [68.992428, "o", "Progress 34/135: async, case-insensitive, data-fix, hfsevents, html, indexed-traversable, integer-logarithms, microlens"] [69.060303, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.060327, "o", "Progress 35/135: async, case-insensitive, data-fix, html, indexed-traversable, integer-logarithms, microlens, network"] [69.135362, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.13558, "o", "Progress 36/135: async, case-insensitive, data-fix, indexed-traversable, integer-logarithms, microlens, network, old-locale"] [69.198866, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.198995, "o", "Progress 37/135: async, case-insensitive, data-fix, integer-logarithms, microlens, network, old-locale, parallel"] [69.266419, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.266578, "o", "Progress 38/135: case-insensitive, data-fix, integer-logarithms, microlens, network, old-locale, parallel, parser-combinators"] [69.331747, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.331772, "o", "Progress 39/135: data-fix, integer-logarithms, microlens, network, old-locale, parallel, parser-combinators, prettyprinter"] [69.398399, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.398528, "o", "Progress 40/135: integer-logarithms, microlens, network, old-locale, parallel, parser-combinators, prettyprinter, primitive"] [69.463617, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.463642, "o", "Progress 41/135: microlens, network, old-locale, parallel, parser-combinators, prettyprinter, primitive, regex-base"] [69.531593, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.531619, "o", "Progress 42/135: network, old-locale, parallel, parser-combinators, prettyprinter, primitive, regex-base, safe"] [69.59901, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.599133, "o", "Progress 43/135: data-default-instances-old-locale, network, parallel, parser-combinators, prettyprinter, primitive, regex-base, safe"] [69.666844, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.666868, "o", "Progress 44/135: data-default-instances-old-locale, network, parser-combinators, prettyprinter, primitive, regex-base, safe, safe-exceptions"] [69.734599, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.734705, "o", "Progress 45/135: data-default-instances-old-locale, network, prettyprinter, primitive, regex-base, safe, safe-exceptions, split"] [69.803643, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.803804, "o", "Progress 46/135: data-default-instances-old-locale, network, prettyprinter-ansi-terminal, primitive, regex-base, safe, safe-exceptions, split"] [69.876169, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.876423, "o", "Progress 47/135: data-default-instances-old-locale, network, prettyprinter-ansi-terminal, regex-base, safe, safe-exceptions, scientific, split"] [69.96197, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [69.962098, "o", "Progress 48/135: data-default-instances-old-locale, network, prettyprinter-ansi-terminal, regex-tdfa, safe, safe-exceptions, scientific, split"] [70.031083, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.031217, "o", "Progress 49/135: data-default-instances-old-locale, doclayout, network, prettyprinter-ansi-terminal, regex-tdfa, safe-exceptions, scientific, split"] [70.102656, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.102785, "o", "Progress 50/135: data-default, doclayout, network, prettyprinter-ansi-terminal, regex-tdfa, safe-exceptions, scientific, split"] [70.184031, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.184197, "o", "Progress 51/135: data-default, doclayout, network, prettyprinter-ansi-terminal, regex-tdfa, scientific, split, splitmix"] [70.265704, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.265892, "o", "Progress 52/135: data-default, doclayout, network, prettyprinter-ansi-terminal, regex-tdfa, scientific, splitmix, tabular"] [70.333181, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.333205, "o", "Progress 53/135: data-default, doclayout, network, regex-tdfa, scientific, splitmix, tabular, tagged"] [70.414374, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.414449, "o", "Progress 54/135: attoparsec, data-default, doclayout, network, regex-tdfa, splitmix, tabular, tagged"] [70.496118, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.496311, "o", "Progress 55/135: attoparsec, data-default, doclayout, megaparsec, network, splitmix, tabular, tagged"] [70.598438, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.598826, "o", "Progress 56/135: attoparsec, data-default, megaparsec, network, splitmix, tabular, tagged, text-short"] [70.693058, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.693163, "o", "Progress 57/135: attoparsec, megaparsec, network, splitmix, tabular, tagged, text-short"] [70.761599, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.761687, "o", "Progress 58/135: attoparsec, megaparsec, network, random, tabular, tagged, text-short, th-abstraction"] [70.83064, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.830749, "o", "Progress 59/135: attoparsec, megaparsec, network, random, tagged, text-short, th-abstraction, th-compat"] [70.8998, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [70.899943, "o", "Progress 60/135: attoparsec, distributive, megaparsec, network, random, text-short, th-abstraction, th-compat"] [71.052999, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.053099, "o", "Progress 61/135: distributive, megaparsec, network, random, text-short, th-abstraction, th-compat, time-compat"] [71.131267, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.131455, "o", "Progress 62/135: distributive, network, random, text-short, th-abstraction, th-compat, time-compat"] [71.20473, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.204874, "o", "Progress 63/135: distributive, network, random, th-abstraction, th-compat, time-compat, timeit"] [71.277562, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.277739, "o", "Progress 64/135: distributive, microlens-th, network, random, th-compat, time-compat, timeit, transformers-compat"] [71.362161, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.362585, "o", "Progress 65/135: QuickCheck, distributive, microlens-th, network, th-compat, time-compat, timeit, transformers-compat"] [71.444863, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.445058, "o", "Progress 66/135: QuickCheck, distributive, githash, microlens-th, network, time-compat, timeit, transformers-compat"] [71.513027, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.513054, "o", "Progress 67/135: QuickCheck, githash, microlens-th, network, temporary, time-compat, timeit, transformers-compat"] [71.579238, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.579368, "o", "Progress 68/135: QuickCheck, githash, microlens-th, network, temporary, th-lift, timeit, transformers-compat"] [71.650516, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.650729, "o", "Progress 69/135: QuickCheck, githash, microlens-th, network, temporary, th-lift, transformers-compat, uglymemo"] [71.716619, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.716868, "o", "Progress 70/135: QuickCheck, githash, microlens-th, network, temporary, th-lift, uglymemo"] [71.798709, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.79885, "o", "Progress 71/135: Glob, QuickCheck, comonad, githash, network, temporary, th-lift, uglymemo"] [71.877181, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.877386, "o", "Progress 72/135: Glob, comonad, githash, microlens-mtl, network, temporary, th-lift, uglymemo"] [71.956409, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [71.956632, "o", "Progress 73/135: Glob, comonad, microlens-mtl, mmorph, network, temporary, th-lift, uglymemo"] [72.036224, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.036407, "o", "Progress 74/135: Glob, comonad, microlens-mtl, mmorph, network, optparse-applicative, th-lift, uglymemo"] [72.11443, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.114529, "o", "Progress 75/135: Glob, comonad, microlens-mtl, mmorph, network, optparse-applicative, transformers-base, uglymemo"] [72.195284, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.195398, "o", "Progress 76/135: Glob, comonad, microlens-mtl, mmorph, network, optparse-applicative, transformers-base, unix-compat"] [72.276523, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.276693, "o", "Progress 77/135: comonad, microlens-mtl, mmorph, network, optparse-applicative, transformers-base, unix-compat, unliftio-core"] [72.357975, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.358124, "o", "Progress 78/135: bifunctors, microlens-mtl, mmorph, network, optparse-applicative, transformers-base, unix-compat, unliftio-core"] [72.435967, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.436122, "o", "Progress 79/135: bifunctors, mmorph, network, optparse-applicative, transformers-base, unix-compat, unliftio-core, unordered-containers"] [72.518475, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.518643, "o", "Progress 80/135: bifunctors, lucid, network, optparse-applicative, transformers-base, unix-compat, unliftio-core, unordered-containers"] [72.598651, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.598771, "o", "Progress 81/135: bifunctors, lucid, network, pretty-simple, transformers-base, unix-compat, unliftio-core, unordered-containers"] [72.681608, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.681657, "o", "Progress 82/135: bifunctors, lucid, network, pretty-simple, tasty, transformers-base, unliftio-core, unordered-containers"] [72.764176, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.764276, "o", "Progress 83/135: bifunctors, lucid, network, pretty-simple, resourcet, tasty, transformers-base, unordered-containers"] [72.845507, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.845599, "o", "Progress 84/135: assoc, lucid, network, pretty-simple, resourcet, tasty, transformers-base, unordered-containers"] [72.926562, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [72.926584, "o", "Progress 85/135: assoc, config-ini, lucid, network, pretty-simple, resourcet, tasty, transformers-base"] [73.008067, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.008212, "o", "Progress 86/135: assoc, config-ini, network, pretty-simple, profunctors, resourcet, tasty, transformers-base"] [73.091174, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.091318, "o", "Progress 87/135: assoc, config-ini, network, profunctors, resourcet, semigroupoids, tasty, transformers-base"] [73.171688, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.171711, "o", "Progress 88/135: assoc, config-ini, network, profunctors, resourcet, semigroupoids, tasty-hunit, transformers-base"] [73.251539, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.251706, "o", "Progress 89/135: assoc, config-ini, network, profunctors, semigroupoids, tasty-hunit, transformers-base, typed-process"] [73.331631, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.331658, "o", "Progress 90/135: config-ini, network, profunctors, semigroupoids, tasty-hunit, these, transformers-base, typed-process"] [73.410026, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.410057, "o", "Progress 91/135: network, profunctors, semigroupoids, tasty-hunit, these, transformers-base, typed-process, utf8-string"] [73.487501, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.487713, "o", "Progress 92/135: network, profunctors, tasty-hunit, these, transformers-base, typed-process, utf8-string, utility-ht"] [73.568477, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.568585, "o", "Progress 93/135: network, profunctors, these, transformers-base, typed-process, utf8-string, utility-ht, uuid-types"] [73.649047, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.649073, "o", "Progress 94/135: network, profunctors, these, transformers-base, utf8-string, utility-ht, uuid-types, vector"] [73.731333, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.731511, "o", "Progress 95/135: network, profunctors, strict, transformers-base, utf8-string, utility-ht, uuid-types, vector"] [73.81237, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.812504, "o", "Progress 96/135: network, profunctors, strict, transformers-base, utility-ht, uuid-types, vector, wizards"] [73.893704, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.893735, "o", "Progress 97/135: network, profunctors, strict, transformers-base, uuid-types, vector, wizards, word-wrap"] [73.973933, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [73.974107, "o", "Progress 98/135: network, profunctors, strict, transformers-base, vector, wizards, word-wrap, zlib"] [74.055498, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.055671, "o", "Progress 99/135: cassava, network, profunctors, strict, transformers-base, wizards, word-wrap, zlib"] [74.137336, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.13748, "o", "Progress 100/135: cassava, hashtables, network, profunctors, transformers-base, wizards, word-wrap, zlib"] [74.218419, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.218649, "o", "Progress 101/135: cassava, hashtables, indexed-traversable-instances, network, profunctors, transformers-base, word-wrap, zlib"] [74.298043, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.298211, "o", "Progress 102/135: cassava, hashtables, indexed-traversable-instances, isomorphism-class, network, profunctors, transformers-base, zlib"] [74.377516, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.377666, "o", "Progress 103/135: cassava, hashtables, indexed-traversable-instances, isomorphism-class, math-functions, network, profunctors, transformers-base"] [74.494776, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.494803, "o", "Progress 104/135: cassava-megaparsec, hashtables, indexed-traversable-instances, isomorphism-class, math-functions, network, profunctors, transformers-base"] [74.575948, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.575983, "o", "Progress 105/135: cassava-megaparsec, indexed-traversable-instances, isomorphism-class, math-functions, network, profunctors, text-zipper, transformers-base"] [74.657861, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.658072, "o", "Progress 106/135: cassava-megaparsec, isomorphism-class, math-functions, network, profunctors, semialign, text-zipper, transformers-base"] [74.739153, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.739407, "o", "Progress 107/135: cassava-megaparsec, math-functions, network, profunctors, semialign, text-zipper, transformers-base, vector-algorithms"] [74.81977, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.819796, "o", "Progress 108/135: cassava-megaparsec, network, profunctors, semialign, text-zipper, transformers-base, vector-algorithms, vty"] [74.90125, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.901382, "o", "Progress 109/135: network, profunctors, semialign, text-zipper, transformers-base, vector-algorithms, vty, witherable"] [74.98241, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [74.982453, "o", "Progress 110/135: network, profunctors, semialign, transformers-base, vector-algorithms, vty, witherable"] [75.064802, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [75.064937, "o", "Progress 111/135: network, profunctors, transformers-base, vector-algorithms, vty, witherable"] [75.145547, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [75.145657, "o", "Progress 112/135: mono-traversable, network, profunctors, transformers-base, vty, witherable"] [75.227361, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [75.227466, "o", "Progress 113/135: brick, mono-traversable, network, profunctors, transformers-base, witherable"] [75.307274, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [75.307411, "o", "Progress 114/135: aeson, brick, mono-traversable, network, profunctors, transformers-base"] [75.387084, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [75.387243, "o", "Progress 115/135: aeson, brick, conduit, network, profunctors, transformers-base"] [75.465978, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 116/135: aeson, conduit, network, profunctors, transformers-base"] [75.546452, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 117/135: aeson-pretty, conduit, network, profunctors, shakespeare, transformers-base"] [75.621012, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [75.621051, "o", "Progress 118/135: aeson-pretty, network, profunctors, shakespeare, transformers-base"] [75.699655, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 119/135: network, profunctors, shakespeare, transformers-base"] [75.777227, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 120/135: network, profunctors, transformers-base"] [77.054756, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [77.05478, "o", "Progress 121/135: monad-control, network, profunctors"] [78.886525, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [78.886608, "o", "Progress 122/135: fsnotify, network, profunctors"] [82.257503, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 123/135: network, profunctors"] [82.728565, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [82.728678, "o", "Progress 124/135: foldl, network"] [87.694345, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 125/135: foldl, streaming-commons"] [88.48506, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 126/135: deferred-folds, streaming-commons"] [91.786806, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [91.786915, "o", "Progress 127/135: streaming-commons, text-builder-dev"] [93.637853, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [93.637965, "o", "Progress 128/135: conduit-extra, text-builder-dev"] [95.3383, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [95.338329, "o", "Progress 129/135: conduit-extra, text-builder"] [97.425921, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [97.426085, "o", "Progress 130/135: conduit-extra, text-ansi"] [98.793653, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [98.79376, "o", "Progress 131/135: pager, text-ansi"] [101.681294, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 132/135: text-ansi"] [105.094767, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [105.094795, "o", "Progress 133/135: hledger-lib"] [124.900153, "o", " "] [125.10379, "o", " "] [125.291966, "o", " "] [125.52379, "o", "#"] [125.811915, "o", " "] [126.086154, "o", "w"] [126.232879, "o", "h"] [126.296292, "o", "i"] [126.356857, "o", "l"] [126.469053, "o", "e"] [126.600857, "o", " "] [126.7246, "o", "w"] [126.821066, "o", "e"] [126.92071, "o", " "] [127.100508, "o", "w"] [127.202095, "o", "a"] [127.36135, "o", "i"] [127.514402, "o", "t"] [127.848334, "o", "."] [128.025137, "o", "."] [128.176967, "o", "."] [128.301749, "o", " "] [128.962672, "o", "t"] [129.065807, "o", "h"] [129.127209, "o", "i"] [129.242853, "o", "s"] [129.354678, "o", " "] [129.485986, "o", "i"] [129.682919, "o", "s"] [129.719141, "o", " "] [132.25637, "o", "t"] [132.447468, "o", "y"] [132.519602, "o", "p"] [132.754644, "o", "i"] [132.909922, "o", "c"] [133.022794, "o", "a"] [133.172551, "o", "l"] [133.239931, "o", " "] [133.47921, "o", "o"] [133.635156, "o", "f"] [133.859473, "o", " "] [134.554253, "o", "a"] [134.675146, "o", "n"] [134.727527, "o", " "] [135.019586, "o", "u"] [135.039525, "o", "p"] [135.183684, "o", "g"] [135.231371, "o", "r"] [135.367296, "o", "a"] [135.475442, "o", "d"] [135.683532, "o", "e"] [138.746489, "o", "^[\b \b\b \b"] [138.934445, "o", "^[\b \b\b \b"] [139.094216, "o", "^[\b \b\b \b"] [139.246407, "o", "^[\b \b\b \b"] [139.760467, "o", "\b \b"] [140.011539, "o", "\b \b"] [140.045528, "o", "\b \b"] [140.079623, "o", "\b \b"] [140.113546, "o", "\b \b"] [140.14639, "o", "\b \b"] [140.180617, "o", "\b \b"] [140.213819, "o", "\b \b"] [140.246522, "o", "\b \b"] [140.280527, "o", "\b \b"] [140.313978, "o", "\b \b"] [140.347237, "o", "\b \b"] [140.380655, "o", "\b \b"] [140.413996, "o", "\b \b"] [140.447289, "o", "\b \b"] [140.480658, "o", "\b \b"] [140.514108, "o", "\b \b"] [140.547243, "o", "\b \b"] [140.580524, "o", "\b \b"] [140.613946, "o", "\b \b"] [140.647146, "o", "\b \b"] [140.680572, "o", "\b \b"] [140.713902, "o", "\b \b"] [140.747334, "o", "\b \b"] [140.779893, "o", "\b \b"] [140.814134, "o", "\b \b"] [140.847331, "o", "\b \b"] [140.881532, "o", "\b \b"] [140.913396, "o", "\b \b"] [140.947008, "o", "\b \b"] [140.980381, "o", "\b \b"] [141.013783, "o", "\b \b"] [141.047946, "o", "\b \b"] [141.081042, "o", "\b \b"] [141.116427, "o", "\b \b"] [141.14786, "o", "\b \b"] [141.181264, "o", "\b \b"] [141.21468, "o", "\b \b"] [141.248057, "o", "\b \b"] [141.281415, "o", "\b \b"] [141.314729, "o", "\b \b"] [141.563137, "o", "\b \b"] [141.745654, "o", "\b \b"] [141.921348, "o", "\b \b"] [142.11468, "o", "\b \b"] [145.659727, "o", "m"] [145.856586, "o", "a"] [145.912839, "o", "n"] [146.205114, "o", "y"] [146.266482, "o", " "] [146.557181, "o", "p"] [146.665137, "o", "a"] [146.728362, "o", "c"] [146.82955, "o", "k"] [146.933884, "o", "a"] [147.085768, "o", "g"] [147.150165, "o", "e"] [147.214058, "o", "s"] [150.416886, "o", " "] [150.721088, "o", "w"] [150.840988, "o", "e"] [150.984826, "o", "r"] [151.15052, "o", "e"] [151.591895, "o", " "] [151.741116, "o", "r"] [151.777834, "o", "e"] [152.299721, "o", "u"] [152.359707, "o", "s"] [152.447583, "o", "e"] [152.631718, "o", "d"] [152.945893, "o", ","] [153.026015, "o", " "] [153.264877, "o", "b"] [153.388912, "o", "u"] [153.488425, "o", "t"] [153.576752, "o", " "] [153.739446, "o", "s"] [153.83178, "o", "o"] [153.875742, "o", "m"] [153.999549, "o", "e"] [154.150705, "o", " "] [154.393811, "o", "m"] [154.620866, "o", "u"] [154.701323, "o", "s"] [154.802695, "o", "t"] [157.481655, "o", " "] [157.674667, "o", "b"] [157.782107, "o", "e"] [157.870761, "o", " "] [158.167673, "o", "r"] [158.210803, "o", "e"] [158.525522, "o", "b"] [158.639369, "o", "u"] [158.695678, "o", "i"] [158.767703, "o", "l"] [158.859281, "o", "t"] [159.730592, "o", ","] [159.798749, "o", " "] [159.993608, "o", "w"] [160.109374, "o", "h"] [160.162186, "o", "i"] [160.28634, "o", "c"] [160.447356, "o", "h"] [160.515476, "o", " "] [160.67146, "o", "i"] [160.771515, "o", "s"] [160.883243, "o", " "] [161.075469, "o", "s"] [161.229463, "o", "l"] [161.416524, "o", "o"] [161.524486, "o", "w"] [167.293214, "o", "^[\b \b\b \b"] [167.543741, "o", "^[\b \b\b \b"] [167.578005, "o", "^[\b \b\b \b"] [167.614352, "o", "^[\b \b\b \b"] [167.64986, "o", "^[\b \b\b \b"] [167.678083, "o", "^[\b \b\b \b"] [167.711754, "o", "^[\b \b\b \b"] [167.745027, "o", "^[\b \b\b \b"] [167.778339, "o", "^[\b \b\b \b"] [167.810864, "o", "^[\b \b\b \b"] [167.844517, "o", "^[\b \b\b \b"] [168.012097, "o", "\b \b"] [168.262716, "o", "\b \b"] [168.296208, "o", "\b \b"] [168.330071, "o", "\b \b"] [168.364279, "o", "\b \b"] [168.398918, "o", "\b \b"] [168.432997, "o", "\b \b"] [168.46694, "o", "\b \b"] [168.500469, "o", "\b \b"] [168.535262, "o", "\b \b"] [168.569243, "o", "\b \b"] [168.602376, "o", "\b \b"] [168.63558, "o", "\b \b"] [168.668045, "o", "\b \b"] [168.701816, "o", "\b \b"] [168.735791, "o", "\b \b"] [168.768926, "o", "\b \b"] [168.802002, "o", "\b \b"] [168.835698, "o", "\b \b"] [168.869717, "o", "\b \b"] [168.903577, "o", "\b \b"] [168.936855, "o", "\b \b"] [168.970255, "o", "\b \b"] [169.003473, "o", "\b \b"] [169.037001, "o", "\b \b"] [169.070459, "o", "\b \b"] [169.106225, "o", "\b \b"] [169.137083, "o", "\b \b"] [169.170444, "o", "\b \b"] [169.203853, "o", "\b \b"] [169.237119, "o", "\b \b"] [169.270454, "o", "\b \b"] [169.303775, "o", "\b \b"] [169.337283, "o", "\b \b"] [169.370569, "o", "\b \b"] [169.403888, "o", "\b \b"] [169.437329, "o", "\b \b"] [169.470419, "o", "\b \b"] [169.503484, "o", "\b \b"] [169.537466, "o", "\b \b"] [169.570939, "o", "\b \b"] [169.603778, "o", "\b \b"] [169.637584, "o", "\b \b"] [169.671365, "o", "\b \b"] [169.704103, "o", "\b \b"] [169.737744, "o", "\b \b"] [169.770865, "o", "\b \b"] [169.804304, "o", "\b \b"] [169.837629, "o", "\b \b"] [169.871041, "o", "\b \b"] [169.904426, "o", "\b \b"] [169.937688, "o", "\b \b"] [169.970437, "o", "\b \b"] [170.004348, "o", "\b \b"] [170.037725, "o", "\b \b"] [170.071155, "o", "\b \b"] [170.103802, "o", "\b \b"] [170.13777, "o", "\b \b"] [170.170803, "o", "\b \b"] [170.203971, "o", "\b \b"] [170.238057, "o", "\b \b"] [170.270643, "o", "\b \b"] [170.303989, "o", "\b \b"] [170.337429, "o", "\b \b"] [170.37077, "o", "\b \b"] [170.404069, "o", "\b \b"] [170.437928, "o", "\b \b"] [170.470974, "o", "\b \b"] [170.504817, "o", "\b \b"] [170.537558, "o", "\b \b"] [170.5716, "o", "\b \b"] [170.604249, "o", "\b \b"] [187.022409, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 134/135: hledger"] [208.519027, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [208.610929, "o", "\r\n"] [208.650759, "o", "Installing hledger-ui\r\n"] [208.650852, "o", "Trying stack install --install-ghc --resolver=lts-20.14 hledger-ui-1.29.1 hledger-1.29.1 hledger-lib-1.29.1 brick-1.6 fsnotify-0.4.1.0 --verbosity=error\r\n"] [210.456915, "o", "Progress 0/138"] [210.56121, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 1/138: Diff, OneTuple, Only, StateVar, base-compat, base-orphans, bimap, blaze-builder"] [210.631118, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [210.631278, "o", "Progress 2/138: OneTuple, Only, StateVar, base-compat, base-orphans, bimap, blaze-builder, cabal-doctest"] [210.699119, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [210.699142, "o", "Progress 3/138: Only, StateVar, base-compat, base-orphans, bimap, blaze-builder, cabal-doctest, call-stack"] [210.768085, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [210.768204, "o", "Progress 4/138: StateVar, base-compat, base-orphans, bimap, blaze-builder, cabal-doctest, call-stack, cereal"] [210.836597, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [210.836621, "o", "Progress 5/138: base-compat, base-orphans, bimap, blaze-builder, cabal-doctest, call-stack, cereal, clock"] [210.904689, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [210.904712, "o", "Progress 6/138: base-compat-batteries, base-orphans, bimap, blaze-builder, cabal-doctest, call-stack, cereal, clock"] [210.97276, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [210.97295, "o", "Progress 7/138: base-compat-batteries, bimap, blaze-builder, cabal-doctest, call-stack, cereal, clock, cmdargs"] [211.041426, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.04157, "o", "Progress 8/138: base-compat-batteries, blaze-builder, cabal-doctest, call-stack, cereal, clock, cmdargs, colour"] [211.10961, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.109752, "o", "Progress 9/138: base-compat-batteries, blaze-markup, cabal-doctest, call-stack, cereal, clock, cmdargs, colour"] [211.176626, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.176715, "o", "Progress 10/138: base-compat-batteries, blaze-markup, call-stack, cereal, clock, cmdargs, colour, contravariant"] [211.246487, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.246639, "o", "Progress 11/138: base-compat-batteries, blaze-markup, cereal, clock, cmdargs, colour, contravariant, control-monad-free"] [211.312718, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.31277, "o", "Progress 12/138: base-compat-batteries, blaze-markup, clock, cmdargs, colour, contravariant, control-monad-free, csv"] [211.378998, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.37914, "o", "Progress 13/138: base-compat-batteries, blaze-markup, cmdargs, colour, contravariant, control-monad-free, csv, data-array-byte"] [211.447096, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.447219, "o", "Progress 14/138: blaze-markup, cmdargs, colour, contravariant, control-monad-free, csv, data-array-byte, data-clist"] [211.513292, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.513417, "o", "Progress 15/138: blaze-markup, colour, contravariant, control-monad-free, csv, data-array-byte, data-clist, data-default-class"] [211.579345, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.579372, "o", "Progress 16/138: ansi-terminal, blaze-markup, contravariant, control-monad-free, csv, data-array-byte, data-clist, data-default-class"] [211.646576, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.646702, "o", "Progress 17/138: ansi-terminal, blaze-html, contravariant, control-monad-free, csv, data-array-byte, data-clist, data-default-class"] [211.712898, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.712975, "o", "Progress 18/138: ansi-terminal, blaze-html, control-monad-free, csv, data-array-byte, data-clist, data-default-class, dlist"] [211.780733, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.780869, "o", "Progress 19/138: ansi-terminal, blaze-html, csv, data-array-byte, data-clist, data-default-class, dlist, emojis"] [211.84951, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.84961, "o", "Progress 20/138: ansi-terminal, blaze-html, data-array-byte, data-clist, data-default-class, dlist, emojis, extra"] [211.917178, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.917253, "o", "Progress 21/138: ansi-terminal, blaze-html, data-clist, data-default-class, dlist, emojis, extra, file-embed"] [211.98254, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [211.982703, "o", "Progress 22/138: ansi-terminal, blaze-html, data-default-class, dlist, emojis, extra, file-embed, hashable"] [212.051007, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.05111, "o", "Progress 23/138: ansi-terminal, blaze-html, data-default-instances-containers, dlist, emojis, extra, file-embed, hashable"] [212.120578, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.120658, "o", "Progress 24/138: ansi-wl-pprint, blaze-html, data-default-instances-containers, dlist, emojis, extra, file-embed, hashable"] [212.19121, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.191316, "o", "Progress 25/138: ansi-wl-pprint, data-default-instances-containers, dlist, emojis, extra, file-embed, hashable, haskeline"] [212.25921, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.259234, "o", "Progress 26/138: ansi-wl-pprint, data-default-instances-containers, data-default-instances-dlist, emojis, extra, file-embed, hashable, haskeline"] [212.326794, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.326904, "o", "Progress 27/138: ansi-wl-pprint, data-default-instances-containers, data-default-instances-dlist, extra, file-embed, hashable, haskeline, hfsevents"] [212.394437, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.394569, "o", "Progress 28/138: ansi-wl-pprint, data-default-instances-containers, data-default-instances-dlist, file-embed, hashable, haskeline, hfsevents, html"] [212.461719, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.461844, "o", "Progress 29/138: ansi-wl-pprint, data-default-instances-containers, data-default-instances-dlist, hashable, haskeline, hfsevents, html, indexed-traversable"] [212.529895, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.529984, "o", "Progress 30/138: ansi-wl-pprint, async, data-default-instances-containers, data-default-instances-dlist, haskeline, hfsevents, html, indexed-traversable"] [212.596302, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.596332, "o", "Progress 31/138: ansi-wl-pprint, async, case-insensitive, data-default-instances-dlist, haskeline, hfsevents, html, indexed-traversable"] [212.663522, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.663711, "o", "Progress 32/138: async, case-insensitive, data-default-instances-dlist, data-fix, haskeline, hfsevents, html, indexed-traversable"] [212.732066, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.732176, "o", "Progress 33/138: async, case-insensitive, data-default-instances-dlist, data-fix, hfsevents, html, indexed-traversable, integer-logarithms"] [212.803699, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.803856, "o", "Progress 34/138: async, case-insensitive, data-fix, hfsevents, html, indexed-traversable, integer-logarithms"] [212.872589, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.872695, "o", "Progress 35/138: async, case-insensitive, data-fix, html, indexed-traversable, integer-logarithms, microlens, network"] [212.939065, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [212.939209, "o", "Progress 36/138: async, case-insensitive, data-fix, indexed-traversable, integer-logarithms, microlens, network, old-locale"] [213.007071, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.007208, "o", "Progress 37/138: async, case-insensitive, data-fix, integer-logarithms, microlens, network, old-locale, parallel"] [213.073058, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.073179, "o", "Progress 38/138: case-insensitive, data-fix, integer-logarithms, microlens, network, old-locale, parallel, parser-combinators"] [213.142147, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.142288, "o", "Progress 39/138: data-fix, integer-logarithms, microlens, network, old-locale, parallel, parser-combinators, prettyprinter"] [213.208196, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.208305, "o", "Progress 40/138: integer-logarithms, microlens, network, old-locale, parallel, parser-combinators, prettyprinter, primitive"] [213.276614, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.276737, "o", "Progress 41/138: microlens, network, old-locale, parallel, parser-combinators, prettyprinter, primitive, regex-base"] [213.344722, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.344855, "o", "Progress 42/138: microlens-ghc, network, old-locale, parallel, parser-combinators, prettyprinter, primitive, regex-base"] [213.412659, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.412773, "o", "Progress 43/138: microlens-ghc, old-locale, parallel, parser-combinators, prettyprinter, primitive, regex-base, safe"] [213.480496, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.48052, "o", "Progress 44/138: data-default-instances-old-locale, microlens-ghc, parallel, parser-combinators, prettyprinter, primitive, regex-base, safe"] [213.545224, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.545249, "o", "Progress 45/138: data-default-instances-old-locale, microlens-ghc, parser-combinators, prettyprinter, primitive, regex-base, safe, safe-exceptions"] [213.614912, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.615069, "o", "Progress 46/138: data-default-instances-old-locale, microlens-ghc, prettyprinter, primitive, regex-base, safe, safe-exceptions, split"] [213.683548, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.683573, "o", "Progress 47/138: data-default-instances-old-locale, microlens-ghc, prettyprinter-ansi-terminal, primitive, regex-base, safe, safe-exceptions, split"] [213.751275, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.751376, "o", "Progress 48/138: data-default-instances-old-locale, microlens-ghc, prettyprinter-ansi-terminal, regex-base, safe, safe-exceptions, scientific, split"] [213.818592, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.818617, "o", "Progress 49/138: data-default-instances-old-locale, microlens-ghc, prettyprinter-ansi-terminal, regex-tdfa, safe, safe-exceptions, scientific, split"] [213.882797, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.882936, "o", "Progress 50/138: data-default-instances-old-locale, prettyprinter-ansi-terminal, regex-tdfa, safe, safe-exceptions, scientific, split, splitmix"] [213.952527, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [213.952602, "o", "Progress 51/138: data-default-instances-old-locale, doclayout, prettyprinter-ansi-terminal, regex-tdfa, safe-exceptions, scientific, split, splitmix"] [214.018675, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.018755, "o", "Progress 52/138: data-default, doclayout, prettyprinter-ansi-terminal, regex-tdfa, safe-exceptions, scientific, split, splitmix"] [214.086057, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.086167, "o", "Progress 53/138: data-default, doclayout, prettyprinter-ansi-terminal, regex-tdfa, scientific, split, splitmix, tabular"] [214.153305, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.153449, "o", "Progress 54/138: data-default, doclayout, prettyprinter-ansi-terminal, regex-tdfa, scientific, splitmix, tabular, tagged"] [214.22075, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.22084, "o", "Progress 55/138: data-default, doclayout, regex-tdfa, scientific, splitmix, tabular, tagged, text-short"] [214.288325, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.288404, "o", "Progress 56/138: attoparsec, data-default, doclayout, regex-tdfa, splitmix, tabular, tagged, text-short"] [214.355698, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.355797, "o", "Progress 57/138: attoparsec, data-default, doclayout, megaparsec, splitmix, tabular, tagged, text-short"] [214.422581, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.422622, "o", "Progress 58/138: attoparsec, data-default, doclayout, megaparsec, random, tabular, tagged, text-short"] [214.489728, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.489909, "o", "Progress 59/138: attoparsec, data-default, megaparsec, random, tabular, tagged, text-short, th-abstraction"] [214.554716, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.554741, "o", "Progress 60/138: attoparsec, megaparsec, random, tabular, tagged, text-short, th-abstraction, th-compat"] [214.622802, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.62291, "o", "Progress 61/138: attoparsec, megaparsec, random, tagged, text-short, th-abstraction, th-compat, time-compat"] [214.688549, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.688705, "o", "Progress 62/138: attoparsec, distributive, megaparsec, random, text-short, th-abstraction, th-compat, time-compat"] [214.756987, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.757195, "o", "Progress 63/138: attoparsec, distributive, megaparsec, random, th-abstraction, th-compat, time-compat, timeit"] [214.893361, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.893384, "o", "Progress 64/138: distributive, megaparsec, random, th-abstraction, th-compat, time-compat, timeit, transformers-compat"] [214.96038, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [214.960487, "o", "Progress 65/138: distributive, random, th-abstraction, th-compat, time-compat, timeit, transformers-compat, uglymemo"] [215.02733, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.027448, "o", "Progress 66/138: QuickCheck, distributive, th-abstraction, th-compat, time-compat, timeit, transformers-compat, uglymemo"] [215.094405, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.094507, "o", "Progress 67/138: QuickCheck, distributive, microlens-th, th-compat, time-compat, timeit, transformers-compat, uglymemo"] [215.162117, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.162271, "o", "Progress 68/138: QuickCheck, distributive, githash, microlens-th, time-compat, timeit, transformers-compat, uglymemo"] [215.229493, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.22957, "o", "Progress 69/138: QuickCheck, distributive, githash, microlens-th, temporary, timeit, transformers-compat, uglymemo"] [215.296058, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.29621, "o", "Progress 70/138: QuickCheck, githash, microlens-th, temporary, th-lift, timeit, transformers-compat, uglymemo"] [215.362368, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.362527, "o", "Progress 71/138: QuickCheck, githash, microlens-th, temporary, th-lift, transformers-compat, uglymemo, unix-compat"] [215.429254, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.429299, "o", "Progress 72/138: Glob, QuickCheck, githash, microlens-th, temporary, th-lift, uglymemo, unix-compat"] [215.496377, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.496458, "o", "Progress 73/138: Glob, QuickCheck, comonad, githash, microlens-th, temporary, th-lift, unix-compat"] [215.563186, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.563233, "o", "Progress 74/138: Glob, comonad, githash, microlens-mtl, microlens-th, temporary, th-lift, unix-compat"] [215.641494, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.64159, "o", "Progress 75/138: Glob, comonad, githash, microlens-mtl, mmorph, temporary, th-lift, unix-compat"] [215.708527, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.708648, "o", "Progress 76/138: Glob, comonad, microlens-mtl, mmorph, optparse-applicative, temporary, th-lift, unix-compat"] [215.787125, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.787199, "o", "Progress 77/138: Glob, comonad, microlens-mtl, mmorph, optparse-applicative, th-lift, transformers-base, unix-compat"] [215.854041, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.854134, "o", "Progress 78/138: Glob, comonad, microlens-mtl, mmorph, optparse-applicative, transformers-base, unix-compat, unliftio-core"] [215.921431, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.921616, "o", "Progress 79/138: Glob, comonad, microlens-mtl, mmorph, optparse-applicative, transformers-base, unliftio-core, unordered-containers"] [215.985977, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [215.986076, "o", "Progress 80/138: comonad, microlens-mtl, mmorph, optparse-applicative, transformers-base, unliftio-core, unordered-containers, utf8-string"] [216.055557, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.055629, "o", "Progress 81/138: bifunctors, microlens-mtl, mmorph, optparse-applicative, transformers-base, unliftio-core, unordered-containers, utf8-string"] [216.133974, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.134141, "o", "Progress 82/138: bifunctors, mmorph, optparse-applicative, transformers-base, unliftio-core, unordered-containers, utf8-string, utility-ht"] [216.201068, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.2012, "o", "Progress 83/138: bifunctors, lucid, optparse-applicative, transformers-base, unliftio-core, unordered-containers, utf8-string, utility-ht"] [216.28135, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.281444, "o", "Progress 84/138: bifunctors, lucid, pretty-simple, transformers-base, unliftio-core, unordered-containers, utf8-string, utility-ht"] [216.362203, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.36229, "o", "Progress 85/138: bifunctors, lucid, monad-control, pretty-simple, unliftio-core, unordered-containers, utf8-string, utility-ht"] [216.441873, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.441907, "o", "Progress 86/138: bifunctors, lucid, monad-control, pretty-simple, resourcet, unordered-containers, utf8-string, utility-ht"] [216.520616, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.520642, "o", "Progress 87/138: bifunctors, config-ini, lucid, monad-control, pretty-simple, resourcet, utf8-string, utility-ht"] [216.60074, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.600778, "o", "Progress 88/138: bifunctors, config-ini, lucid, monad-control, pretty-simple, resourcet, tasty, utility-ht"] [216.680877, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.681021, "o", "Progress 89/138: assoc, config-ini, lucid, monad-control, pretty-simple, resourcet, tasty, utility-ht"] [216.758515, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.758539, "o", "Progress 90/138: assoc, config-ini, lucid, monad-control, pretty-simple, profunctors, resourcet, tasty"] [216.837693, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.837797, "o", "Progress 91/138: assoc, config-ini, monad-control, pretty-simple, profunctors, resourcet, semigroupoids, tasty"] [216.916621, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.916699, "o", "Progress 92/138: assoc, config-ini, monad-control, profunctors, resourcet, semigroupoids, tasty, typed-process"] [216.996599, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [216.996719, "o", "Progress 93/138: assoc, config-ini, fsnotify, profunctors, resourcet, semigroupoids, tasty, typed-process"] [217.075629, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [217.075651, "o", "Progress 94/138: assoc, config-ini, fsnotify, profunctors, semigroupoids, tasty, typed-process, uuid-types"] [217.156508, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [217.156588, "o", "Progress 95/138: assoc, fsnotify, profunctors, semigroupoids, tasty, typed-process, uuid-types, vector"] [217.235367, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [217.235479, "o", "Progress 96/138: assoc, fsnotify, profunctors, semigroupoids, tasty-hunit, typed-process, uuid-types, vector"] [217.315474, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [217.31554, "o", "Progress 97/138: fsnotify, profunctors, semigroupoids, tasty-hunit, these, typed-process, uuid-types, vector"] [217.395626, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [217.395707, "o", "Progress 98/138: fsnotify, semigroupoids, tasty-hunit, these, typed-process, uuid-types, vector, wizards"] [217.475638, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [217.475722, "o", "Progress 99/138: fsnotify, tasty-hunit, these, typed-process, uuid-types, vector, wizards, word-wrap"] [217.555656, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [217.555779, "o", "Progress 100/138: fsnotify, tasty-hunit, these, uuid-types, vector, wizards, word-wrap, zlib"] [217.635321, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [217.635451, "o", "Progress 101/138: tasty-hunit, these, uuid-types, vector, wizards, word-wrap, zlib"] [217.716021, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 102/138: tasty-hunit, these, vector, wizards, word-wrap, zlib"] [217.7976, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 103/138: cassava, foldl, hashtables, tasty-hunit, these, wizards, word-wrap, zlib"] [217.876281, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [217.876418, "o", "Progress 104/138: cassava, foldl, hashtables, indexed-traversable-instances, these, wizards, word-wrap, zlib"] [217.956031, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [217.956055, "o", "Progress 105/138: cassava, foldl, hashtables, indexed-traversable-instances, isomorphism-class, wizards, word-wrap, zlib"] [218.034092, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.034175, "o", "Progress 106/138: cassava, foldl, hashtables, indexed-traversable-instances, isomorphism-class, math-functions, word-wrap, zlib"] [218.112437, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.112463, "o", "Progress 107/138: cassava, foldl, hashtables, indexed-traversable-instances, isomorphism-class, math-functions, microlens-platform, zlib"] [218.191435, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.191458, "o", "Progress 108/138: cassava, foldl, hashtables, indexed-traversable-instances, isomorphism-class, math-functions, microlens-platform, streaming-commons"] [218.266259, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.26633, "o", "Progress 109/138: cassava-megaparsec, foldl, hashtables, indexed-traversable-instances, isomorphism-class, math-functions, microlens-platform, streaming-commons"] [218.34796, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.348118, "o", "Progress 110/138: cassava-megaparsec, deferred-folds, hashtables, indexed-traversable-instances, isomorphism-class, math-functions, microlens-platform, streaming-commons"] [218.427342, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.427456, "o", "Progress 111/138: cassava-megaparsec, deferred-folds, indexed-traversable-instances, isomorphism-class, math-functions, microlens-platform, streaming-commons, strict"] [218.506997, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.507155, "o", "Progress 112/138: cassava-megaparsec, deferred-folds, isomorphism-class, math-functions, microlens-platform, semialign, streaming-commons, strict"] [218.586308, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.586619, "o", "Progress 113/138: cassava-megaparsec, deferred-folds, math-functions, microlens-platform, semialign, streaming-commons, strict, text-zipper"] [218.662588, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.662741, "o", "Progress 114/138: cassava-megaparsec, deferred-folds, microlens-platform, semialign, streaming-commons, strict, text-zipper, vector-algorithms"] [218.743669, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.743693, "o", "Progress 115/138: cassava-megaparsec, deferred-folds, semialign, streaming-commons, strict, text-zipper, vector-algorithms, vty"] [218.822309, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.82248, "o", "Progress 116/138: cassava-megaparsec, deferred-folds, semialign, strict, text-zipper, vector-algorithms, vty, witherable"] [218.902336, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.902361, "o", "Progress 117/138: deferred-folds, semialign, strict, text-zipper, vector-algorithms, vty, witherable"] [218.981971, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [218.981993, "o", "Progress 118/138: semialign, strict, text-builder-dev, text-zipper, vector-algorithms, vty, witherable"] [219.060363, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [219.06051, "o", "Progress 119/138: semialign, text-builder-dev, text-zipper, vector-algorithms, vty, witherable"] [219.140577, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [219.140636, "o", "Progress 120/138: text-builder-dev, text-zipper, vector-algorithms, vty, witherable"] [219.220406, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 121/138: text-builder-dev, vector-algorithms, vty, witherable"] [219.299006, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 122/138: mono-traversable, text-builder-dev, vty, witherable"] [219.379084, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 123/138: brick, mono-traversable, text-builder-dev, witherable"] [219.457279, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [219.457305, "o", "Progress 124/138: aeson, brick, mono-traversable, text-builder-dev"] [219.536674, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 125/138: aeson, brick, mono-traversable, text-builder"] [219.616935, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 126/138: aeson, brick, conduit, text-builder"] [219.697345, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 127/138: aeson, conduit, text-builder"] [219.777222, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [219.777248, "o", "Progress 128/138: aeson-pretty, conduit, shakespeare, text-builder"] [219.856635, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 129/138: aeson-pretty, conduit, shakespeare, text-ansi"] [219.9347, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 130/138: aeson-pretty, conduit-extra, shakespeare, text-ansi"] [220.014352, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 131/138: conduit-extra, shakespeare, text-ansi"] [220.092454, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 132/138: conduit-extra, text-ansi"] [220.170423, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 133/138: conduit-extra"] [220.246387, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 134/138: pager"] [220.358327, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 135/138: hledger-lib"] [220.469458, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [220.469535, "o", "Progress 136/138: hledger"] [220.592862, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 137/138: hledger-ui"] [235.666409, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [235.851339, "o", "\r\n"] [235.908524, "o", "Installing hledger-web\r\n"] [235.908629, "o", "Trying stack install --install-ghc --resolver=lts-20.14 hledger-web-1.29.1 hledger-1.29.1 hledger-lib-1.29.1 brick-1.6 fsnotify-0.4.1.0 --verbosity=error\r\n"] [238.095245, "o", "Progress 0/240"] [238.100345, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.100369, "o", "Progress 1/240: Decimal, Diff, OneTuple, Only, StateVar, appar, auto-update, base-compat"] [238.198618, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.198732, "o", "Progress 2/240: Diff, OneTuple, Only, StateVar, appar, auto-update, base-compat, base-orphans"] [238.266537, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.266646, "o", "Progress 3/240: OneTuple, Only, StateVar, appar, auto-update, base-compat, base-orphans, base-unicode-symbols"] [238.334861, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.334886, "o", "Progress 4/240: Only, StateVar, appar, auto-update, base-compat, base-orphans, base-unicode-symbols, base64-bytestring"] [238.401702, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.401726, "o", "Progress 5/240: StateVar, appar, auto-update, base-compat, base-orphans, base-unicode-symbols, base64-bytestring, basement"] [238.468475, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.468578, "o", "Progress 6/240: appar, auto-update, base-compat, base-orphans, base-unicode-symbols, base64-bytestring, basement, bimap"] [238.536249, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.536415, "o", "Progress 7/240: auto-update, base-compat, base-orphans, base-unicode-symbols, base64-bytestring, basement, bimap, blaze-builder"] [238.605109, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.605134, "o", "Progress 8/240: base-compat, base-orphans, base-unicode-symbols, base64-bytestring, basement, bimap, blaze-builder, bsb-http-chunked"] [238.67192, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.672046, "o", "Progress 9/240: base-compat-batteries, base-orphans, base-unicode-symbols, base64-bytestring, basement, bimap, blaze-builder, bsb-http-chunked"] [238.740034, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.740202, "o", "Progress 10/240: base-compat-batteries, base-unicode-symbols, base64-bytestring, basement, bimap, blaze-builder, bsb-http-chunked"] [238.807621, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.807646, "o", "Progress 11/240: base-compat-batteries, base64-bytestring, basement, bimap, blaze-builder, bsb-http-chunked, byteable, byteorder"] [238.876259, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.876408, "o", "Progress 12/240: base-compat-batteries, basement, bimap, blaze-builder, bsb-http-chunked, byteable, byteorder, cabal-doctest"] [238.944602, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [238.944736, "o", "Progress 13/240: base-compat-batteries, bimap, blaze-builder, bsb-http-chunked, byteable, byteorder, cabal-doctest, call-stack"] [239.012796, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.012821, "o", "Progress 14/240: base-compat-batteries, blaze-builder, bsb-http-chunked, byteable, byteorder, cabal-doctest, call-stack, cereal"] [239.080197, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.080277, "o", "Progress 15/240: base-compat-batteries, blaze-markup, bsb-http-chunked, byteable, byteorder, cabal-doctest, call-stack, cereal"] [239.144855, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.145011, "o", "Progress 16/240: base-compat-batteries, blaze-markup, byteable, byteorder, cabal-doctest, call-stack, cereal, clock"] [239.213337, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.213484, "o", "Progress 17/240: blaze-markup, byteable, byteorder, cabal-doctest, call-stack, cereal, clock, cmdargs"] [239.278939, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.279044, "o", "Progress 18/240: blaze-markup, byteorder, cabal-doctest, call-stack, cereal, clock, cmdargs, colour"] [239.346776, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.346903, "o", "Progress 19/240: blaze-markup, cabal-doctest, call-stack, cereal, clock, cmdargs, colour, contravariant"] [239.416367, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.416435, "o", "Progress 20/240: blaze-markup, call-stack, cereal, clock, cmdargs, colour, contravariant, control-monad-free"] [239.484391, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.484492, "o", "Progress 21/240: HUnit, blaze-markup, cereal, clock, cmdargs, colour, contravariant, control-monad-free"] [239.552599, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.552726, "o", "Progress 22/240: HUnit, blaze-markup, clock, cmdargs, colour, contravariant, control-monad-free, csv"] [239.62177, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.62184, "o", "Progress 23/240: HUnit, blaze-html, clock, cmdargs, colour, contravariant, control-monad-free, csv"] [239.689679, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.689704, "o", "Progress 24/240: HUnit, blaze-html, cmdargs, colour, contravariant, control-monad-free, csv, data-array-byte"] [239.758598, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.758743, "o", "Progress 25/240: HUnit, blaze-html, colour, contravariant, control-monad-free, csv, data-array-byte, data-clist"] [239.827022, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.827157, "o", "Progress 26/240: HUnit, ansi-terminal, blaze-html, contravariant, control-monad-free, csv, data-array-byte, data-clist"] [239.895255, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.895404, "o", "Progress 27/240: HUnit, ansi-terminal, blaze-html, control-monad-free, csv, data-array-byte, data-clist, data-default-class"] [239.962592, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [239.962774, "o", "Progress 28/240: HUnit, ansi-terminal, blaze-html, csv, data-array-byte, data-clist, data-default-class, dlist"] [240.031428, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.031548, "o", "Progress 29/240: ansi-terminal, blaze-html, csv, data-array-byte, data-clist, data-default-class, dlist, easy-file"] [240.098215, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.098239, "o", "Progress 30/240: ansi-terminal, blaze-html, data-array-byte, data-clist, data-default-class, dlist, easy-file, emojis"] [240.16545, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.165545, "o", "Progress 31/240: ansi-terminal, data-array-byte, data-clist, data-default-class, dlist, easy-file, emojis, entropy"] [240.233014, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.233145, "o", "Progress 32/240: ansi-terminal, data-clist, data-default-class, dlist, easy-file, emojis, entropy, extra"] [240.30154, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.301638, "o", "Progress 33/240: ansi-terminal, data-default-class, dlist, easy-file, emojis, entropy, extra, file-embed"] [240.369081, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.369109, "o", "Progress 34/240: ansi-wl-pprint, data-default-class, dlist, easy-file, emojis, entropy, extra, file-embed"] [240.436726, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.436875, "o", "Progress 35/240: ansi-wl-pprint, cookie, dlist, easy-file, emojis, entropy, extra, file-embed"] [240.504352, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.50451, "o", "Progress 36/240: ansi-wl-pprint, cookie, data-default-instances-containers, easy-file, emojis, entropy, extra, file-embed"] [240.570262, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.570349, "o", "Progress 37/240: ansi-wl-pprint, cookie, data-default-instances-containers, data-default-instances-dlist, emojis, entropy, extra, file-embed"] [240.637479, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.637582, "o", "Progress 38/240: ansi-wl-pprint, cookie, data-default-instances-containers, data-default-instances-dlist, entropy, extra, file-embed, happy"] [240.639353, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.639367, "o", "Progress 39/240: ansi-wl-pprint, cookie, data-default-instances-containers, data-default-instances-dlist, entropy, extra, file-embed, hashable"] [240.705681, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.705758, "o", "Progress 40/240: ansi-wl-pprint, cookie, data-default-instances-containers, data-default-instances-dlist, extra, file-embed, hashable, haskeline"] [240.773428, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.773526, "o", "Progress 41/240: ansi-wl-pprint, cookie, data-default-instances-containers, data-default-instances-dlist, file-embed, hashable, haskeline, haskell-lexer"] [240.84194, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.842058, "o", "Progress 42/240: ansi-wl-pprint, cookie, data-default-instances-containers, data-default-instances-dlist, hashable, haskeline, haskell-lexer, hfsevents"] [240.909961, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.910124, "o", "Progress 43/240: cookie, data-default-instances-containers, data-default-instances-dlist, hashable, haskeline, haskell-lexer, hfsevents, hourglass"] [240.976583, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [240.976607, "o", "Progress 44/240: data-default-instances-containers, data-default-instances-dlist, hashable, haskeline, haskell-lexer, hfsevents, hourglass, hspec-discover"] [241.044678, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.044838, "o", "Progress 45/240: data-default-instances-dlist, hashable, haskeline, haskell-lexer, hfsevents, hourglass, hspec-discover, hspec-expectations"] [241.111665, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.111749, "o", "Progress 46/240: hashable, haskeline, haskell-lexer, hfsevents, hourglass, hspec-discover, hspec-expectations, html"] [241.178696, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.178773, "o", "Progress 47/240: async, haskeline, haskell-lexer, hfsevents, hourglass, hspec-discover, hspec-expectations, html"] [241.245744, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.245774, "o", "Progress 48/240: async, case-insensitive, haskell-lexer, hfsevents, hourglass, hspec-discover, hspec-expectations, html"] [241.31167, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.311774, "o", "Progress 49/240: async, case-insensitive, data-fix, hfsevents, hourglass, hspec-discover, hspec-expectations, html"] [241.379326, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.379432, "o", "Progress 50/240: async, case-insensitive, data-fix, hourglass, hspec-discover, hspec-expectations, html, indexed-traversable"] [241.447871, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.447898, "o", "Progress 51/240: async, case-insensitive, data-fix, hspec-discover, hspec-expectations, html, indexed-traversable, integer-logarithms"] [241.515852, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.516057, "o", "Progress 52/240: async, case-insensitive, data-fix, hspec-expectations, html, indexed-traversable, integer-logarithms, lift-type"] [241.585652, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.585675, "o", "Progress 53/240: async, case-insensitive, data-fix, html, indexed-traversable, integer-logarithms, lift-type, memory"] [241.650729, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.650856, "o", "Progress 54/240: async, case-insensitive, data-fix, indexed-traversable, integer-logarithms, lift-type, memory, microlens"] [241.71898, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.719148, "o", "Progress 55/240: case-insensitive, data-fix, indexed-traversable, integer-logarithms, lift-type, memory, microlens, mime-types"] [241.786658, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.786736, "o", "Progress 56/240: data-fix, http-types, indexed-traversable, integer-logarithms, lift-type, memory, microlens, mime-types"] [241.855007, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.855141, "o", "Progress 57/240: http-types, indexed-traversable, integer-logarithms, lift-type, memory, microlens, mime-types, monad-loops"] [241.92257, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.922683, "o", "Progress 58/240: http-types, integer-logarithms, lift-type, memory, microlens, mime-types, monad-loops, network"] [241.98999, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [241.990128, "o", "Progress 59/240: http-types, lift-type, memory, microlens, mime-types, monad-loops, network, network-byte-order"] [242.057033, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.057125, "o", "Progress 60/240: http-types, memory, microlens, mime-types, monad-loops, network, network-byte-order, old-locale"] [242.12536, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.125496, "o", "Progress 61/240: asn1-types, http-types, microlens, mime-types, monad-loops, network, network-byte-order, old-locale"] [242.192838, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.192912, "o", "Progress 62/240: asn1-types, cryptonite, http-types, mime-types, monad-loops, network, network-byte-order, old-locale"] [242.26057, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.260593, "o", "Progress 63/240: asn1-types, cryptonite, http-types, monad-loops, network, network-byte-order, old-locale, parallel"] [242.327874, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.327995, "o", "Progress 64/240: asn1-types, cryptonite, monad-loops, network, network-byte-order, old-locale, parallel, parser-combinators"] [242.395234, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.395379, "o", "Progress 65/240: asn1-types, cryptonite, network, network-byte-order, old-locale, parallel, parser-combinators, path-pieces"] [242.462965, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.463035, "o", "Progress 66/240: asn1-types, cryptonite, iproute, network-byte-order, old-locale, parallel, parser-combinators, path-pieces"] [242.532258, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.532282, "o", "Progress 67/240: asn1-types, cryptonite, iproute, old-locale, parallel, parser-combinators, path-pieces, pem"] [242.599596, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.599678, "o", "Progress 68/240: asn1-types, cryptonite, data-default-instances-old-locale, iproute, parallel, parser-combinators, path-pieces, pem"] [242.667841, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.667975, "o", "Progress 69/240: asn1-encoding, cryptonite, data-default-instances-old-locale, iproute, parallel, parser-combinators, path-pieces, pem"] [242.746703, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.746854, "o", "Progress 70/240: asn1-encoding, data-default-instances-old-locale, iproute, old-time, parallel, parser-combinators, path-pieces, pem"] [242.814269, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.814293, "o", "Progress 71/240: asn1-encoding, data-default-instances-old-locale, iproute, old-time, parser-combinators, path-pieces, pem, persistent-template"] [242.882447, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.882788, "o", "Progress 72/240: asn1-encoding, data-default-instances-old-locale, iproute, old-time, path-pieces, pem, persistent-template, pretty-show"] [242.951192, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [242.951446, "o", "Progress 73/240: asn1-encoding, data-default-instances-old-locale, iproute, old-time, pem, persistent-template, pretty-show, prettyprinter"] [243.020075, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.020366, "o", "Progress 74/240: asn1-encoding, data-default-instances-old-locale, iproute, old-time, persistent-template, pretty-show, prettyprinter, primitive"] [243.088836, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.089097, "o", "Progress 75/240: asn1-encoding, data-default, iproute, old-time, persistent-template, pretty-show, prettyprinter, primitive"] [243.166933, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.167115, "o", "Progress 76/240: asn1-parse, data-default, iproute, old-time, persistent-template, pretty-show, prettyprinter, primitive"] [243.235546, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.23557, "o", "Progress 77/240: asn1-parse, data-default, iproute, persistent-template, pretty-show, prettyprinter, primitive, psqueues"] [243.303784, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.303851, "o", "Progress 78/240: asn1-parse, data-default, iproute, pretty-show, prettyprinter, primitive, psqueues, recv"] [243.383822, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.383848, "o", "Progress 79/240: asn1-parse, data-default, iproute, prettyprinter, primitive, psqueues, recv, regex-base"] [243.454878, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.454906, "o", "Progress 80/240: asn1-parse, data-default, iproute, primitive, psqueues, recv, regex-base"] [243.537616, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.537642, "o", "Progress 81/240: asn1-parse, data-default, iproute, prettyprinter-ansi-terminal, psqueues, recv, regex-base, safe"] [243.606503, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.606638, "o", "Progress 82/240: asn1-parse, iproute, prettyprinter-ansi-terminal, psqueues, recv, regex-base, safe, safe-exceptions"] [243.686671, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.687397, "o", "Progress 83/240: iproute, prettyprinter-ansi-terminal, psqueues, recv, regex-base, safe, safe-exceptions, scientific"] [243.767077, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.767289, "o", "Progress 84/240: iproute, prettyprinter-ansi-terminal, recv, regex-base, safe, safe-exceptions, scientific, securemem"] [243.847742, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.847951, "o", "Progress 85/240: iproute, prettyprinter-ansi-terminal, recv, regex-tdfa, safe, safe-exceptions, scientific, securemem"] [243.927944, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [243.927991, "o", "Progress 86/240: iproute, recv, regex-tdfa, safe, safe-exceptions, scientific, securemem, setenv"] [244.008974, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [244.009153, "o", "Progress 87/240: doclayout, iproute, recv, regex-tdfa, safe-exceptions, scientific, securemem, setenv"] [244.091861, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [244.09209, "o", "Progress 88/240: doclayout, iproute, recv, regex-tdfa, scientific, securemem, setenv, silently"] [244.173747, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [244.173937, "o", "Progress 89/240: attoparsec, doclayout, iproute, recv, regex-tdfa, securemem, setenv, silently"] [244.256473, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [244.25674, "o", "Progress 90/240: attoparsec, crypto-cipher-types, doclayout, iproute, recv, regex-tdfa, setenv, silently"] [244.337873, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [244.338151, "o", "Progress 91/240: attoparsec, crypto-cipher-types, doclayout, iproute, megaparsec, recv, setenv, silently"] [244.418513, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [244.418647, "o", "Progress 92/240: attoparsec, crypto-cipher-types, doclayout, iproute, megaparsec, recv, silently"] [244.503369, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [244.503569, "o", "Progress 93/240: attoparsec, crypto-cipher-types, iproute, megaparsec, recv, silently, simple-sendfile, socks"] [244.585946, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [244.586075, "o", "Progress 94/240: attoparsec, crypto-cipher-types, iproute, megaparsec, recv, simple-sendfile, socks, split"] [244.749778, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [244.749957, "o", "Progress 95/240: crypto-cipher-types, css-text, iproute, megaparsec, recv, simple-sendfile, socks, split"] [244.833452, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [244.83358, "o", "Progress 96/240: cipher-aes, css-text, iproute, megaparsec, recv, simple-sendfile, socks, split"] [244.920648, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [244.920859, "o", "Progress 97/240: cipher-aes, css-text, email-validate, iproute, recv, simple-sendfile, socks, split"] [245.004308, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.004504, "o", "Progress 98/240: cipher-aes, css-text, email-validate, http-date, iproute, recv, simple-sendfile, socks"] [245.093061, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.093304, "o", "Progress 99/240: cipher-aes, email-validate, http-date, iproute, recv, simple-sendfile, socks, splitmix"] [245.177353, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.177536, "o", "Progress 100/240: email-validate, http-date, iproute, recv, simple-sendfile, socks, splitmix, stm-chans"] [245.25868, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.258885, "o", "Progress 101/240: http-date, iproute, recv, simple-sendfile, socks, splitmix, stm-chans, tabular"] [245.353467, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.353765, "o", "Progress 102/240: iproute, recv, simple-sendfile, socks, splitmix, stm-chans, tabular, tagged"] [245.441895, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.44205, "o", "Progress 103/240: iproute, random, recv, simple-sendfile, socks, stm-chans, tabular, tagged"] [245.53227, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.532579, "o", "Progress 104/240: iproute, random, recv, simple-sendfile, socks, tabular, tagged, tagsoup"] [245.611307, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.611444, "o", "Progress 105/240: iproute, random, recv, simple-sendfile, socks, tagged, tagsoup, text-short"] [245.702141, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.702337, "o", "Progress 106/240: crypto-api, iproute, random, recv, simple-sendfile, socks, tagsoup, text-short"] [245.783398, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.783504, "o", "Progress 107/240: QuickCheck, crypto-api, iproute, recv, simple-sendfile, socks, tagsoup, text-short"] [245.87547, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.875678, "o", "Progress 108/240: QuickCheck, crypto-api, distributive, iproute, recv, simple-sendfile, socks, text-short"] [245.956065, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [245.956259, "o", "Progress 109/240: QuickCheck, base64, crypto-api, distributive, iproute, recv, simple-sendfile, socks"] [246.037896, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [246.038091, "o", "Progress 110/240: QuickCheck, base64, distributive, iproute, recv, simple-sendfile, skein, socks"] [246.204538, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [246.204902, "o", "Progress 111/240: QuickCheck, base64, distributive, iproute, simple-sendfile, skein, socks, temporary"] [246.296273, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [246.29647, "o", "Progress 112/240: base64, distributive, iproute, quickcheck-io, simple-sendfile, skein, socks, temporary"] [246.366385, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [246.366599, "o", "Progress 113/240: base64, iproute, quickcheck-io, simple-sendfile, skein, socks, temporary, tf-random"] [246.476738, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [246.478505, "o", "Progress 114/240: iproute, quickcheck-io, simple-sendfile, skein, socks, temporary, tf-random, th-abstraction"] [246.587328, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [246.587504, "o", "Progress 115/240: iproute, quickcheck-io, simple-sendfile, socks, temporary, tf-random, th-abstraction, th-compat"] [246.669863, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [246.670044, "o", "Progress 116/240: iproute, quickcheck-io, simple-sendfile, socks, tf-random, th-abstraction, th-compat, time-compat"] [246.752851, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [246.753063, "o", "Progress 117/240: iproute, simple-sendfile, socks, tf-random, th-abstraction, th-compat, time-compat"] [246.838369, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [246.83856, "o", "Progress 118/240: hspec-core, iproute, simple-sendfile, socks, th-abstraction, th-compat, time-compat, time-manager"] [246.934921, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [246.935075, "o", "Progress 119/240: hspec-core, iproute, microlens-th, simple-sendfile, socks, th-compat, time-compat, time-manager"] [247.027299, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [247.027785, "o", "Progress 120/240: githash, hspec-core, iproute, microlens-th, simple-sendfile, socks, time-compat, time-manager"] [247.108651, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [247.108834, "o", "Progress 121/240: attoparsec-iso8601, githash, hspec-core, iproute, microlens-th, simple-sendfile, socks, time-manager"] [247.237758, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [247.238008, "o", "Progress 122/240: attoparsec-iso8601, githash, hspec-core, iproute, microlens-th, network-uri, simple-sendfile, socks"] [247.357862, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [247.358059, "o", "Progress 123/240: attoparsec-iso8601, githash, hspec, iproute, microlens-th, network-uri, simple-sendfile, socks"] [247.484202, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [247.484801, "o", "Progress 124/240: attoparsec-iso8601, githash, hspec, iproute, network-uri, simple-sendfile, socks, th-lift"] [247.580471, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [247.580607, "o", "Progress 125/240: attoparsec-iso8601, hspec, iproute, network-uri, simple-sendfile, socks, th-lift, timeit"] [247.691474, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [247.69175, "o", "Progress 126/240: attoparsec-iso8601, hspec, iproute, simple-sendfile, socks, th-lift, timeit, transformers-compat"] [247.776362, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [247.776586, "o", "Progress 127/240: attoparsec-iso8601, iproute, simple-sendfile, socks, th-lift, timeit, transformers-compat, uglymemo"] [247.873733, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [247.873881, "o", "Progress 128/240: attoparsec-iso8601, iproute, simple-sendfile, socks, timeit, transformers-compat, uglymemo, unix-compat"] [247.958887, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [247.959107, "o", "Progress 129/240: attoparsec-iso8601, iproute, simple-sendfile, socks, transformers-compat, uglymemo, unix-compat, unix-time"] [248.156759, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [248.157042, "o", "Progress 130/240: attoparsec-iso8601, iproute, socks, transformers-compat, uglymemo, unix-compat, unix-time, unliftio-core"] [248.244179, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [248.244417, "o", "Progress 131/240: Glob, attoparsec-iso8601, iproute, socks, uglymemo, unix-compat, unix-time, unliftio-core"] [248.322616, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [248.322645, "o", "Progress 132/240: Glob, attoparsec-iso8601, comonad, iproute, socks, unix-compat, unix-time, unliftio-core"] [248.400002, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [248.40003, "o", "Progress 133/240: Glob, attoparsec-iso8601, comonad, iproute, microlens-mtl, socks, unix-time, unliftio-core"] [248.501553, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [248.501819, "o", "Progress 134/240: Glob, attoparsec-iso8601, comonad, fast-logger, iproute, microlens-mtl, socks, unliftio-core"] [248.574641, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [248.574901, "o", "Progress 135/240: Glob, attoparsec-iso8601, comonad, fast-logger, http2, iproute, microlens-mtl, socks"] [248.685984, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [248.686427, "o", "Progress 136/240: attoparsec-iso8601, comonad, fast-logger, http2, iproute, microlens-mtl, mmorph, socks"] [248.796137, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [248.796355, "o", "Progress 137/240: attoparsec-iso8601, bifunctors, fast-logger, http2, iproute, microlens-mtl, mmorph, socks"] [248.986488, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [248.986635, "o", "Progress 138/240: attoparsec-iso8601, bifunctors, fast-logger, http2, microlens-mtl, mmorph, optparse-applicative, socks"] [249.077079, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [249.077229, "o", "Progress 139/240: attoparsec-iso8601, bifunctors, fast-logger, http2, mmorph, optparse-applicative, resourcet, socks"] [249.150474, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [249.150703, "o", "Progress 140/240: attoparsec-iso8601, bifunctors, http2, mmorph, optparse-applicative, resourcet, socks, transformers-base"] [249.256882, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [249.256996, "o", "Progress 141/240: attoparsec-iso8601, bifunctors, http2, lucid, optparse-applicative, resourcet, socks, transformers-base"] [249.379145, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [249.379457, "o", "Progress 142/240: assoc, attoparsec-iso8601, http2, lucid, optparse-applicative, resourcet, socks, transformers-base"] [249.477034, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [249.477127, "o", "Progress 143/240: assoc, attoparsec-iso8601, http2, lucid, pretty-simple, resourcet, socks, transformers-base"] [249.584993, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [249.585152, "o", "Progress 144/240: assoc, attoparsec-iso8601, http2, lucid, pretty-simple, profunctors, socks, transformers-base"] [249.675321, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [249.675557, "o", "Progress 145/240: assoc, attoparsec-iso8601, http2, lucid, monad-control, pretty-simple, profunctors, socks"] [249.772514, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [249.772875, "o", "Progress 146/240: assoc, attoparsec-iso8601, http2, monad-control, pretty-simple, profunctors, socks"] [249.867925, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [249.868052, "o", "Progress 147/240: attoparsec-iso8601, http2, monad-control, pretty-simple, profunctors, socks, tasty, these"] [249.957089, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [249.957225, "o", "Progress 148/240: attoparsec-iso8601, http2, monad-control, profunctors, socks, tasty, these, typed-process"] [250.060103, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [250.060263, "o", "Progress 149/240: attoparsec-iso8601, http2, monad-control, socks, tasty, these, typed-process, unliftio"] [250.152312, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [250.152514, "o", "Progress 150/240: attoparsec-iso8601, http2, socks, tasty, these, typed-process, unliftio"] [250.246532, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [250.246706, "o", "Progress 151/240: attoparsec-iso8601, fsnotify, http2, lifted-base, socks, these, typed-process, unliftio"] [250.352705, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [250.352989, "o", "Progress 152/240: attoparsec-iso8601, fsnotify, http2, lifted-base, socks, strict, typed-process, unliftio"] [250.43503, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [250.435311, "o", "Progress 153/240: attoparsec-iso8601, fsnotify, http2, lifted-base, socks, strict, tasty-hunit, unliftio"] [250.551862, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [250.551988, "o", "Progress 154/240: attoparsec-iso8601, fsnotify, http2, lifted-base, socks, strict, tasty-hunit, unordered-containers"] [250.645382, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [250.645618, "o", "Progress 155/240: attoparsec-iso8601, http2, lifted-base, socks, strict, tasty-hunit, unordered-containers, utf8-string"] [250.831046, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [250.831324, "o", "Progress 156/240: http2, lifted-base, socks, strict, tasty-hunit, unordered-containers, utf8-string, utility-ht"] [250.93094, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [250.931092, "o", "Progress 157/240: http2, lifted-base, socks, tasty-hunit, unordered-containers, utf8-string, utility-ht, uuid-types"] [251.023427, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [251.023594, "o", "Progress 158/240: http2, lifted-base, socks, unordered-containers, utf8-string, utility-ht, uuid-types, vector"] [251.130261, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [251.130426, "o", "Progress 159/240: config-ini, http2, lifted-base, socks, utf8-string, utility-ht, uuid-types, vector"] [251.225951, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [251.226094, "o", "Progress 160/240: config-ini, http2, language-javascript, lifted-base, socks, utility-ht, uuid-types, vector"] [251.417803, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [251.417946, "o", "Progress 161/240: config-ini, http2, language-javascript, lifted-base, semigroupoids, utility-ht, uuid-types, vector"] [251.519219, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [251.519464, "o", "Progress 162/240: config-ini, http2, language-javascript, lifted-base, semigroupoids, uuid-types, vault, vector"] [251.614907, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [251.615039, "o", "Progress 163/240: config-ini, http-api-data, http2, language-javascript, lifted-base, semigroupoids, vault, vector"] [251.72488, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [251.725085, "o", "Progress 164/240: cassava, config-ini, http-api-data, http2, language-javascript, lifted-base, semigroupoids, vault"] [251.831596, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [251.831804, "o", "Progress 165/240: cassava, crypto-random, http-api-data, http2, language-javascript, lifted-base, semigroupoids, vault"] [251.936229, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [251.936429, "o", "Progress 166/240: cassava, crypto-random, hashtables, http-api-data, http2, lifted-base, semigroupoids, vault"] [252.030468, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [252.030664, "o", "Progress 167/240: cassava, crypto-random, foldl, hashtables, http-api-data, http2, lifted-base, vault"] [252.158254, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [252.158429, "o", "Progress 168/240: cassava, crypto-random, foldl, hashtables, hjsmin, http-api-data, http2, lifted-base"] [252.272517, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [252.272567, "o", "Progress 169/240: cassava-megaparsec, crypto-random, foldl, hashtables, hjsmin, http-api-data, http2, lifted-base"] [252.365372, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [252.365772, "o", "Progress 170/240: cassava-megaparsec, foldl, hashtables, hjsmin, http-api-data, http2, lifted-base"] [252.472896, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [252.473089, "o", "Progress 171/240: cassava-megaparsec, cprng-aes, foldl, hjsmin, http-api-data, http2, indexed-traversable-instances, lifted-base"] [252.579823, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [252.579989, "o", "Progress 172/240: cassava-megaparsec, cprng-aes, deferred-folds, hjsmin, http-api-data, http2, indexed-traversable-instances, lifted-base"] [252.687062, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [252.687136, "o", "Progress 173/240: cassava-megaparsec, cprng-aes, deferred-folds, http-api-data, http2, indexed-traversable-instances, isomorphism-class, lifted-base"] [252.789364, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [252.789569, "o", "Progress 174/240: cprng-aes, deferred-folds, http-api-data, http2, indexed-traversable-instances, isomorphism-class, lifted-base, math-functions"] [252.908822, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [252.909011, "o", "Progress 175/240: clientsession, deferred-folds, http-api-data, http2, indexed-traversable-instances, isomorphism-class, lifted-base, math-functions"] [253.0197, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [253.019918, "o", "Progress 176/240: clientsession, deferred-folds, http-api-data, http2, isomorphism-class, lifted-base, math-functions, resource-pool"] [253.124912, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [253.125296, "o", "Progress 177/240: clientsession, http-api-data, http2, isomorphism-class, lifted-base, math-functions, resource-pool, semialign"] [253.240306, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [253.240424, "o", "Progress 178/240: clientsession, http-api-data, http2, lifted-base, math-functions, resource-pool, semialign, text-builder-dev"] [253.361235, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [253.361386, "o", "Progress 179/240: clientsession, http-api-data, http2, lifted-base, resource-pool, semialign, text-builder-dev, text-zipper"] [253.461299, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [253.46143, "o", "Progress 180/240: http-api-data, http2, lifted-base, resource-pool, semialign, text-builder-dev, text-zipper, th-lift-instances"] [253.675232, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [253.675462, "o", "Progress 181/240: http-api-data, http2, resource-pool, semialign, text-builder-dev, text-zipper, th-lift-instances, vector-algorithms"] [253.775199, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [253.775485, "o", "Progress 182/240: http-api-data, http2, resource-pool, text-builder-dev, text-zipper, th-lift-instances, vector-algorithms, vty"] [253.887785, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [253.887912, "o", "Progress 183/240: http-api-data, http2, resource-pool, text-builder, text-zipper, th-lift-instances, vector-algorithms, vty"] [254.005293, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [254.005539, "o", "Progress 184/240: http-api-data, http2, resource-pool, text-builder, th-lift-instances, vector-algorithms, vty, wai"] [254.110908, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [254.110945, "o", "Progress 185/240: http-api-data, http2, resource-pool, text-builder, vector-algorithms, vty, wai, witherable"] [254.264047, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [254.264096, "o", "Progress 186/240: http-api-data, http2, mono-traversable, resource-pool, text-builder, vty, wai, witherable"] [254.391877, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [254.392095, "o", "Progress 187/240: http-api-data, http2, mono-traversable, resource-pool, text-builder, wai, witherable, wizards"] [254.516051, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [254.516235, "o", "Progress 188/240: http-api-data, http2, mono-traversable, resource-pool, text-ansi, wai, witherable, wizards"] [254.625001, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [254.625071, "o", "Progress 189/240: aeson, http-api-data, http2, mono-traversable, resource-pool, text-ansi, wai, wizards"] [254.740618, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [254.740783, "o", "Progress 190/240: aeson, conduit, http-api-data, http2, resource-pool, text-ansi, wai, wizards"] [254.867277, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [254.867462, "o", "Progress 191/240: aeson, conduit, http-api-data, http2, resource-pool, text-ansi, wai, word-wrap"] [254.979744, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [254.979889, "o", "Progress 192/240: aeson, conduit, http-api-data, http2, resource-pool, wai, word-wrap, word8"] [255.096189, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [255.096481, "o", "Progress 193/240: aeson-pretty, conduit, http-api-data, http2, resource-pool, wai, word-wrap, word8"] [255.229598, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [255.229941, "o", "Progress 194/240: aeson-pretty, http-api-data, http2, libyaml, resource-pool, wai, word-wrap, word8"] [255.365664, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [255.365848, "o", "Progress 195/240: aeson-pretty, brick, http-api-data, http2, libyaml, resource-pool, wai, word8"] [255.486174, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [255.486274, "o", "Progress 196/240: aeson-pretty, brick, http-api-data, http2, libyaml, resource-pool, shakespeare, wai"] [255.602276, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [255.602404, "o", "Progress 197/240: brick, http-api-data, http2, libyaml, resource-pool, shakespeare, wai"] [255.727853, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [255.728002, "o", "Progress 198/240: brick, http-api-data, http2, resource-pool, shakespeare, wai, x509, xml-types"] [255.845601, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [255.845746, "o", "Progress 199/240: http-api-data, http2, resource-pool, shakespeare, wai, x509, xml-types, xss-sanitize"] [256.038051, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [256.038204, "o", "Progress 200/240: http-api-data, http2, shakespeare, wai, x509, xml-types, xss-sanitize, yaml"] [256.17251, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [256.17324, "o", "Progress 201/240: http-api-data, http2, wai, x509, xml-types, xss-sanitize, yaml, zlib"] [256.279842, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [256.280022, "o", "Progress 202/240: http-api-data, http2, wai, x509-store, xml-types, xss-sanitize, yaml, zlib"] [256.403791, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [256.4039, "o", "Progress 203/240: http-api-data, http2, wai, x509-store, xss-sanitize, yaml, zlib"] [256.500573, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 204/240: http-api-data, http2, wai, x509-store, yaml, zlib"] [256.614574, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [256.614694, "o", "Progress 205/240: http-api-data, http2, streaming-commons, wai, x509-store, yaml"] [256.807331, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 206/240: http-api-data, http2, streaming-commons, wai-cors, wai-logger, x509-store, yaml"] [256.947798, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [256.947953, "o", "Progress 207/240: http-api-data, http2, streaming-commons, wai-cors, wai-logger, x509-system, x509-validation, yaml"] [257.129081, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [257.129581, "o", "Progress 208/240: conduit-extra, http-api-data, http2, wai-cors, wai-logger, x509-system, x509-validation, yaml"] [257.267193, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [257.267332, "o", "Progress 209/240: conduit-extra, http-api-data, http-client, http2, wai-cors, wai-logger, x509-validation, yaml"] [257.407419, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [257.407603, "o", "Progress 210/240: conduit-extra, http-api-data, http-client, http2, tls, wai-cors, wai-logger, yaml"] [257.551015, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [257.55119, "o", "Progress 211/240: cryptonite-conduit, http-api-data, http-client, http2, tls, wai-cors, wai-logger, yaml"] [260.521759, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [260.521827, "o", "Progress 212/240: cryptonite-conduit, http-api-data, http-client, http2, monad-logger, tls, wai-logger, yaml"] [262.390527, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [262.390612, "o", "Progress 213/240: cryptonite-conduit, http-client, http2, monad-logger, pager, tls, wai-logger, yaml"] [262.58713, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [262.58741, "o", "Progress 214/240: cryptonite-conduit, hledger-lib, http-client, http2, monad-logger, tls, wai-logger, yaml"] [262.772832, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [262.772883, "o", "Progress 215/240: cryptonite-conduit, hledger, http-client, http2, monad-logger, tls, wai-logger, yaml"] [262.95233, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [262.953018, "o", "Progress 216/240: cryptonite-conduit, http-client, http2, monad-logger, tls, wai-logger, xml-conduit, yaml"] [263.490861, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [263.490991, "o", "Progress 217/240: cryptonite-conduit, http-client, http2, monad-logger, tls, xml-conduit, yaml"] [263.731057, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [263.731216, "o", "Progress 218/240: cryptonite-conduit, http-client, http2, monad-logger, tls, xml-conduit"] [265.252348, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [265.252497, "o", "Progress 219/240: cryptonite-conduit, http-client, monad-logger, tls, warp, xml-conduit"] [266.270033, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [266.270186, "o", "Progress 220/240: http-client, monad-logger, tls, warp, xml-conduit"] [269.223805, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 221/240: http-client, persistent, tls, warp, xml-conduit"] [271.75887, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 222/240: persistent, tls, warp, xml-conduit"] [277.797344, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 223/240: persistent, tls, wai-extra, wai-handler-launch, xml-conduit"] [279.813295, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [279.813445, "o", "Progress 224/240: html-conduit, persistent, tls, wai-extra, wai-handler-launch"] [281.589886, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 225/240: html-conduit, persistent, tls, wai-extra"] [286.120649, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 226/240: persistent, tls, wai-extra"] [289.139744, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 227/240: persistent, tls, wai-app-static, yesod-core"] [290.334113, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [290.334344, "o", "Progress 228/240: connection, persistent, wai-app-static, yesod-core"] [294.24231, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 229/240: http-client-tls, persistent, wai-app-static, yesod-core"] [297.378746, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [297.378938, "o", "Progress 230/240: http-conduit, persistent, wai-app-static, yesod-core"] [298.032819, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 231/240: http-conduit, persistent, yesod-core"] [300.492745, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 232/240: persistent, yesod-core"] [308.438763, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 233/240: persistent, yesod-static, yesod-test"] [313.355814, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [313.355942, "o", "Progress 234/240: yesod-persistent, yesod-static, yesod-test"] [314.365925, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 235/240: yesod-persistent, yesod-test"] [315.656714, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 236/240: yesod-form, yesod-test"] [316.173906, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 237/240: yesod-form"] [332.717061, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\bProgress 238/240: yesod"] [336.713324, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [336.7134, "o", "Progress 239/240: hledger-web"] [354.974123, "o", "\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b \b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b\b"] [355.23619, "o", "\r\n"] [356.997391, "o", "\r\nNew install status:\r\n"] [357.509073, "o", "hledger 1.29.1 is installed at /Users/simon/.local/bin/hledger\r\n"] [358.045447, "o", "hledger-ui 1.29.1 is installed at /Users/simon/.local/bin/hledger-ui\r\n"] [358.903871, "o", "hledger-web 1.29.1 is installed at /Users/simon/.local/bin/hledger-web\r\n"] [358.932765, "o", "hledger-stockquotes 0.1.2.1 is installed at /Users/simon/.local/bin/hledger-stockquotes\r\n"] [359.662483, "o", "hledger-edit 1.13.2 is installed at /opt/homebrew/bin/hledger-edit\r\n"] [360.354996, "o", "hledger-plot 1.13.2 is installed at /opt/homebrew/bin/hledger-plot\r\n"] [360.375546, "o", "hledger-interest 1.6.5 is installed at /Users/simon/.local/bin/hledger-interest\r\n"] [360.413586, "o", "hledger-iadd 1.3.17 is installed at /Users/simon/.cabal/bin/hledger-iadd\r\n"] [360.416339, "o", "\u001b[?2004h"] [360.416385, "o", "$ "] [365.313147, "o", "#"] [366.306759, "o", " "] [366.624867, "o", "d"] [366.768587, "o", "o"] [366.822121, "o", "e"] [366.825189, "o", "n"] [367.50777, "o", "\b\u001b[K"] [367.680683, "o", "\b\u001b[K"] [367.916256, "o", "n"] [368.044179, "o", "e"] [368.287415, "o", "."] [368.363115, "o", " "] [368.961613, "o", "S"] [369.187915, "o", "o"] [369.246177, "o", "m"] [369.34153, "o", "e"] [369.445492, "o", " "] [369.5779, "o", "a"] [369.818719, "o", "d"] [369.98427, "o", "d"] [370.187788, "o", "o"] [370.259924, "o", "n"] [370.397534, "o", "s"] [370.525574, "o", " "] [370.864266, "o", "w"] [370.958329, "o", "e"] [371.111432, "o", "r"] [371.182965, "o", "e"] [371.560046, "o", " "] [371.756584, "o", "n"] [371.80506, "o", "o"] [371.89748, "o", "t"] [372.040847, "o", " "] [372.650083, "o", "u"] [372.72412, "o", "p"] [372.826074, "o", "g"] [372.851334, "o", "r"] [373.011351, "o", "a"] [373.130255, "o", "d"] [373.328552, "o", "e"] [373.488942, "o", "d"] [373.646344, "o", " "] [373.854596, "o", "a"] [373.96003, "o", "s"] [374.103067, "o", " "] [374.30972, "o", "t"] [374.423943, "o", "h"] [374.546169, "o", "e"] [374.65783, "o", "y"] [374.751791, "o", " "] [374.920814, "o", "d"] [375.025355, "o", "o"] [375.070231, "o", "n"] [375.194212, "o", "'"] [376.96099, "o", "t"] [377.219954, "o", " "] [377.543877, "o", "y"] [377.669859, "o", "e"] [377.793524, "o", "t"] [377.91397, "o", " "] [378.295377, "o", "h"] [378.371338, "o", "a"] [378.45759, "o", "v"] [378.54082, "o", "e"] [378.601699, "o", " "] [378.788839, "o", "n"] [378.862145, "o", "e"] [378.990827, "o", "w"] [379.399231, "o", " "] [379.601514, "o", "v"] [379.787963, "o", "e"] [379.830847, "o", "r"] [379.959845, "o", "s"] [380.114249, "o", "i"] [380.154449, "o", "o"] [380.227695, "o", "n"] [380.301919, "o", "s"] [382.740552, "o", "\r\u001b[C\u001b[C\u001b[K"] [383.332762, "o", "\u001b[?2004l\r\r\n"] hledger-1.32.3/embeddedfiles/print.cast0000644000000000000000000000242314555053231016170 0ustar0000000000000000{"version": 2, "width": 80, "height": 25, "timestamp": 1678904454, "idle_time_limit": 0.5, "env": {"SHELL": "/opt/homebrew/bin/bash", "TERM": "xterm-256color"}, "title": "Show full transactions (print)"} [97.851861, "o", "\u001b[?2004h~$ "] [99.846929, "o", "h"] [99.937799, "o", "l"] [100.053606, "o", "e"] [100.200706, "o", "d"] [100.294199, "o", "g"] [100.442973, "o", "e"] [100.539811, "o", "r"] [100.67039, "o", " "] [100.863265, "o", "p"] [101.011799, "o", "r"] [101.106802, "o", "i"] [101.159327, "o", "n"] [101.248174, "o", "t"] [101.70797, "o", " "] [101.896357, "o", " "] [102.07318, "o", " "] [102.261496, "o", "#"] [102.529299, "o", " "] [102.975838, "o", "s"] [103.097044, "o", "h"] [103.157234, "o", "o"] [103.241647, "o", "w"] [103.371897, "o", " "] [104.520774, "o", "t"] [104.586339, "o", "r"] [104.675919, "o", "a"] [104.793261, "o", "n"] [104.894559, "o", "s"] [104.97797, "o", "a"] [105.074301, "o", "c"] [105.278951, "o", "t"] [105.371914, "o", "i"] [105.402599, "o", "o"] [105.467888, "o", "n"] [105.52808, "o", "s"] [106.697984, "o", "\r\n"] [106.698066, "o", "\u001b[?2004l\r"] [106.877241, "o", "2023-03-15 opening balances\r\n cash $50.25\r\n equity $-50.25\r\n\r\n"] [107, "o", "\u001b[?2004h"] [107, "o", "~$ "] [108, "o", "\u001b[?2004l\r\r\n"] hledger-1.32.3/embeddedfiles/hledger.10000644000000000000000000132632014555433336015672 0ustar0000000000000000.\"t .TH "HLEDGER" "1" "January 2024" "hledger-1.32.3 " "hledger User Manuals" .SH NAME hledger \- robust, friendly plain text accounting (CLI version) .SH SYNOPSIS \f[CR]hledger\f[R] .PD 0 .P .PD \f[CR]hledger COMMAND [OPTS] [ARGS]\f[R] .PD 0 .P .PD \f[CR]hledger ADDONCMD \-\- [OPTS] [ARGS]\f[R] .SH DESCRIPTION hledger is a robust, user\-friendly, cross\-platform set of programs for tracking money, time, or any other commodity, using double\-entry accounting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). .PP This manual is for hledger\[aq]s command line interface, version 1.32.3. It also describes the common options, file formats and concepts used by all hledger programs. It might accidentally teach you some bookkeeping/accounting as well! You don\[aq]t need to know everything in here to use hledger productively, but when you have a question about functionality, this doc should answer it. It is detailed, so do skip ahead or skim when needed. You can read it on hledger.org, or as an info manual or man page on your system. You can also get it from hledger itself with .PD 0 .P .PD \f[CR]hledger \-\-man\f[R], \f[CR]hledger \-\-info\f[R] or \f[CR]hledger help [TOPIC]\f[R]. .PP The main function of the hledger CLI is to read plain text files describing financial transactions, crunch the numbers, and print a useful report on the terminal (or save it as HTML, CSV, JSON or SQL). Many reports are available, as subcommands. hledger will also detect other \f[CR]hledger\-*\f[R] executables as extra subcommands. .PP hledger usually reads from (and appends to) a journal file specified by the \f[CR]LEDGER_FILE\f[R] environment variable (defaulting to \f[CR]$HOME/.hledger.journal\f[R]); or you can specify files with \f[CR]\-f\f[R] options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. .PP Here is a small journal file describing one transaction: .IP .EX 2015\-10\-16 bought food expenses:food $10 assets:cash .EE .PP Transactions are dated movements of money (etc.) between two or more \f[I]accounts\f[R]: bank accounts, your wallet, revenue/expense categories, people, etc. You can choose any account names you wish, using \f[CR]:\f[R] to indicate subaccounts. There must be at least two spaces between account name and amount. Positive amounts are inflow to that account (\f[I]debit\f[R]), negatives are outflow from it (\f[I]credit\f[R]). (Some reports show revenue, liability and equity account balances as negative numbers as a result; this is normal.) .PP hledger\[cq]s add command can help you add transactions, or you can install other data entry UIs like hledger\-web or hledger\-iadd. For more extensive/efficient changes, use a text editor: Emacs + ledger\-mode, VIM + vim\-ledger, or VS Code + hledger\-vscode are some good choices (see https://hledger.org/editors.html). .PP To get started, run \f[CR]hledger add\f[R] and follow the prompts, or save some entries like the above in \f[CR]$HOME/.hledger.journal\f[R], then try commands like: .PD 0 .P .PD \f[CR]hledger print \-x\f[R] .PD 0 .P .PD \f[CR]hledger aregister assets\f[R] .PD 0 .P .PD \f[CR]hledger balance\f[R] .PD 0 .P .PD \f[CR]hledger balancesheet\f[R] .PD 0 .P .PD \f[CR]hledger incomestatement\f[R]. .PD 0 .P .PD Run \f[CR]hledger\f[R] to list the commands. See also the \[dq]Starting a journal file\[dq] and \[dq]Setting opening balances\[dq] sections in PART 5: COMMON TASKS. .SH PART 1: USER INTERFACE .SH Input hledger reads one or more data files, each time you run it. You can specify a file with \f[CR]\-f\f[R], like so .IP .EX $ hledger \-f FILE print .EE .PP Files are most often in hledger\[aq]s journal format, with the \f[CR].journal\f[R] file extension (\f[CR].hledger\f[R] or \f[CR].j\f[R] also work); these files describe transactions, like an accounting general journal. .PP When no file is specified, hledger looks for \f[CR].hledger.journal\f[R] in your home directory. .PP But most people prefer to keep financial files in a dedicated folder, perhaps with version control. Also, starting a new journal file each year is common (it\[aq]s not required, but helps keep things fast and organised). So we usually configure a different journal file, by setting the \f[CR]LEDGER_FILE\f[R] environment variable, to something like \f[CR]\[ti]/finance/2023.journal\f[R]. For more about how to do that on your system, see Common tasks > Setting LEDGER_FILE. .SS Data formats Usually the data file is in hledger\[aq]s journal format, but it can be in any of the supported file formats, which currently are: .PP .TS tab(@); lw(12.3n) lw(30.0n) lw(27.7n). T{ Reader: T}@T{ Reads: T}@T{ Used for file extensions: T} _ T{ \f[CR]journal\f[R] T}@T{ hledger journal files and some Ledger journals, for transactions T}@T{ \f[CR].journal\f[R] \f[CR].j\f[R] \f[CR].hledger\f[R] \f[CR].ledger\f[R] T} T{ \f[CR]timeclock\f[R] T}@T{ timeclock files, for precise time logging T}@T{ \f[CR].timeclock\f[R] T} T{ \f[CR]timedot\f[R] T}@T{ timedot files, for approximate time logging T}@T{ \f[CR].timedot\f[R] T} T{ \f[CR]csv\f[R] T}@T{ CSV/SSV/TSV/character\-separated values, for data import T}@T{ \f[CR].csv\f[R] \f[CR].ssv\f[R] \f[CR].tsv\f[R] \f[CR].csv.rules\f[R] \f[CR].ssv.rules\f[R] \f[CR].tsv.rules\f[R] T} .TE .PP These formats are described in more detail below. .PP hledger detects the format automatically based on the file extensions shown above. If it can\[aq]t recognise the file extension, it assumes \f[CR]journal\f[R] format. So for non\-journal files, it\[aq]s important to use a recognised file extension, so as to either read successfully or to show relevant error messages. .PP You can also force a specific reader/format by prefixing the file path with the format and a colon. Eg, to read a .dat file as csv format: .IP .EX $ hledger \-f csv:/some/csv\-file.dat stats .EE .SS Standard input The file name \f[CR]\-\f[R] means standard input: .IP .EX $ cat FILE | hledger \-f\- print .EE .PP If reading non\-journal data in this way, you\[aq]ll need to add a file format prefix, like: .IP .EX $ echo \[aq]i 2009/13/1 08:00:00\[aq] | hledger print \-f timeclock:\- .EE .SS Multiple files You can specify multiple \f[CR]\-f\f[R] options, to read multiple files as one big journal. When doing this, note that certain features (described below) will be affected: .IP \[bu] 2 Balance assertions will not see the effect of transactions in previous files. (Usually this doesn\[aq]t matter as each file will set the corresponding opening balances.) .IP \[bu] 2 Some directives will not affect previous or subsequent files. .PP If needed, you can work around these by using a single parent file which includes the others, or concatenating the files into one, eg: \f[CR]cat a.journal b.journal | hledger \-f\- CMD\f[R]. .SS Strict mode hledger checks input files for valid data. By default, the most important errors are detected, while still accepting easy journal files without a lot of declarations: .IP \[bu] 2 Are the input files parseable, with valid syntax ? .IP \[bu] 2 Are all transactions balanced ? .IP \[bu] 2 Do all balance assertions pass ? .PP With the \f[CR]\-s\f[R]/\f[CR]\-\-strict\f[R] flag, additional checks are performed: .IP \[bu] 2 Are all accounts posted to, declared with an \f[CR]account\f[R] directive ? (Account error checking) .IP \[bu] 2 Are all commodities declared with a \f[CR]commodity\f[R] directive ? (Commodity error checking) .IP \[bu] 2 Are all commodity conversions declared explicitly ? .PP You can use the check command to run individual checks \-\- the ones listed above and some more. .SH Commands hledger provides various subcommands for getting things done. Most of these commands do not change the journal file; they just read it and output a report. A few commands assist with adding data and file management. .PP To show the commands list, run \f[CR]hledger\f[R] with no arguments. The commands are described in detail in PART 4: COMMANDS, below. .PP To use a particular command, run \f[CR]hledger CMD [CMDOPTS] [CMDARGS]\f[R], .IP \[bu] 2 CMD is the full command name, or its standard abbreviation shown in the commands list, or any unambiguous prefix of the name. .IP \[bu] 2 CMDOPTS are command\-specific options, if any. Command\-specific options must be written after the command name. Eg: \f[CR]hledger print \-x\f[R]. .IP \[bu] 2 CMDARGS are additional arguments to the command, if any. Most hledger commands accept arguments representing a query, to limit the data in some way. Eg: \f[CR]hledger reg assets:checking\f[R]. .PP To list a command\[aq]s options, arguments, and documentation in the terminal, run \f[CR]hledger CMD \-h\f[R]. Eg: \f[CR]hledger bal \-h\f[R]. .SS Add\-on commands In addition to the built\-in commands, you can install \f[I]add\-on commands\f[R]: programs or scripts named \[dq]hledger\-SOMETHING\[dq], which will also appear in hledger\[aq]s commands list. If you used the hledger\-install script, you will have several add\-ons installed already. Some more can be found in hledger\[aq]s bin/ directory, documented at https://hledger.org/scripts.html. .PP More precisely, add\-on commands are programs or scripts in your shell\[aq]s PATH, whose name starts with \[dq]hledger\-\[dq] and ends with no extension or a recognised extension (\[dq].bat\[dq], \[dq].com\[dq], \[dq].exe\[dq], \[dq].hs\[dq], \[dq].js\[dq], \[dq].lhs\[dq], \[dq].lua\[dq], \[dq].php\[dq], \[dq].pl\[dq], \[dq].py\[dq], \[dq].rb\[dq], \[dq].rkt\[dq], or \[dq].sh\[dq]), and (on unix and mac) which has executable permission for the current user. .PP You can run add\-on commands using hledger, much like built\-in commands: \f[CR]hledger ADDONCMD [\-\- ADDONCMDOPTS] [ADDONCMDARGS]\f[R]. But note the double hyphen argument, required before add\-on\-specific options. Eg: \f[CR]hledger ui \-\- \-\-watch\f[R] or \f[CR]hledger web \-\- \-\-serve\f[R]. If this causes difficulty, you can always run the add\-on directly, without using \f[CR]hledger\f[R]: \f[CR]hledger\-ui \-\-watch\f[R] or \f[CR]hledger\-web \-\-serve\f[R]. .SH Options Run \f[CR]hledger \-h\f[R] to see general command line help, and general options which are common to most hledger commands. These options can be written anywhere on the command line. They can be grouped into help, input, and reporting options: .SS General help options .TP \f[CR]\-h \-\-help\f[R] show general or COMMAND help .TP \f[CR]\-\-man\f[R] show general or COMMAND user manual with man .TP \f[CR]\-\-info\f[R] show general or COMMAND user manual with info .TP \f[CR]\-\-version\f[R] show general or ADDONCMD version .TP \f[CR]\-\-debug[=N]\f[R] show debug output (levels 1\-9, default: 1) .SS General input options .TP \f[CR]\-f FILE \-\-file=FILE\f[R] use a different input file. For stdin, use \- (default: \f[CR]$LEDGER_FILE\f[R] or \f[CR]$HOME/.hledger.journal\f[R]) .TP \f[CR]\-\-rules\-file=RULESFILE\f[R] Conversion rules file to use when reading CSV (default: FILE.rules) .TP \f[CR]\-\-separator=CHAR\f[R] Field separator to expect when reading CSV (default: \[aq],\[aq]) .TP \f[CR]\-\-alias=OLD=NEW\f[R] rename accounts named OLD to NEW .TP \f[CR]\-\-pivot FIELDNAME\f[R] use some other field or tag for the account name .TP \f[CR]\-I \-\-ignore\-assertions\f[R] disable balance assertion checks (note: does not disable balance assignments) .TP \f[CR]\-s \-\-strict\f[R] do extra error checking (check that all posted accounts are declared) .SS General reporting options .TP \f[CR]\-b \-\-begin=DATE\f[R] include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) .TP \f[CR]\-e \-\-end=DATE\f[R] include postings/txns before this date (will be adjusted to following subperiod end when using a report interval) .TP \f[CR]\-D \-\-daily\f[R] multiperiod/multicolumn report by day .TP \f[CR]\-W \-\-weekly\f[R] multiperiod/multicolumn report by week .TP \f[CR]\-M \-\-monthly\f[R] multiperiod/multicolumn report by month .TP \f[CR]\-Q \-\-quarterly\f[R] multiperiod/multicolumn report by quarter .TP \f[CR]\-Y \-\-yearly\f[R] multiperiod/multicolumn report by year .TP \f[CR]\-p \-\-period=PERIODEXP\f[R] set start date, end date, and/or reporting interval all at once using period expressions syntax .TP \f[CR]\-\-date2\f[R] match the secondary date instead (see command help for other effects) .TP \f[CR]\-\-today=DATE\f[R] override today\[aq]s date (affects relative smart dates, for tests/examples) .TP \f[CR]\-U \-\-unmarked\f[R] include only unmarked postings/txns (can combine with \-P or \-C) .TP \f[CR]\-P \-\-pending\f[R] include only pending postings/txns .TP \f[CR]\-C \-\-cleared\f[R] include only cleared postings/txns .TP \f[CR]\-R \-\-real\f[R] include only non\-virtual postings .TP \f[CR]\-NUM \-\-depth=NUM\f[R] hide/aggregate accounts or postings more than NUM levels deep .TP \f[CR]\-E \-\-empty\f[R] show items with zero amount, normally hidden (and vice\-versa in hledger\-ui/hledger\-web) .TP \f[CR]\-B \-\-cost\f[R] convert amounts to their cost/selling amount at transaction time .TP \f[CR]\-V \-\-market\f[R] convert amounts to their market value in default valuation commodities .TP \f[CR]\-X \-\-exchange=COMM\f[R] convert amounts to their market value in commodity COMM .TP \f[CR]\-\-value\f[R] convert amounts to cost or market value, more flexibly than \-B/\-V/\-X .TP \f[CR]\-\-infer\-equity\f[R] infer conversion equity postings from costs .TP \f[CR]\-\-infer\-costs\f[R] infer costs from conversion equity postings .TP \f[CR]\-\-infer\-market\-prices\f[R] use costs as additional market prices, as if they were P directives .TP \f[CR]\-\-forecast\f[R] generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger\-ui make future\-dated transactions visible. .TP \f[CR]\-\-auto\f[R] generate extra postings by applying auto posting rules to all txns (not just forecast txns) .TP \f[CR]\-\-verbose\-tags\f[R] add visible tags indicating transactions or postings which have been generated/modified .TP \f[CR]\-\-commodity\-style\f[R] Override the commodity style in the output for the specified commodity. For example \[aq]EUR1.000,00\[aq]. .TP \f[CR]\-\-color=WHEN (or \-\-colour=WHEN)\f[R] Should color\-supporting commands use ANSI color codes in text output. \[aq]auto\[aq] (default): whenever stdout seems to be a color\-supporting terminal. \[aq]always\[aq] or \[aq]yes\[aq]: always, useful eg when piping output into \[aq]less \-R\[aq]. \[aq]never\[aq] or \[aq]no\[aq]: never. A NO_COLOR environment variable overrides this. .TP \f[CR]\-\-pretty[=WHEN]\f[R] Show prettier output, e.g. using unicode box\-drawing characters. Accepts \[aq]yes\[aq] (the default) or \[aq]no\[aq] (\[aq]y\[aq], \[aq]n\[aq], \[aq]always\[aq], \[aq]never\[aq] also work). If you provide an argument you must use \[aq]=\[aq], e.g. \[aq]\-\-pretty=yes\[aq]. .PP When a reporting option appears more than once in the command line, the last one takes precedence. .PP Some reporting options can also be written as query arguments. .SH Command line tips Here are some details useful to know about for hledger command lines (and elsewhere). Feel free to skip this section until you need it. .SS Option repetition If options are repeated in a command line, hledger will generally use the last (right\-most) occurence. .SS Special characters .SS Single escaping (shell metacharacters) In shell command lines, characters significant to your shell \- such as spaces, \f[CR]<\f[R], \f[CR]>\f[R], \f[CR](\f[R], \f[CR])\f[R], \f[CR]|\f[R], \f[CR]$\f[R] and \f[CR]\[rs]\f[R] \- should be \[dq]shell\-escaped\[dq] if you want hledger to see them. This is done by enclosing them in single or double quotes, or by writing a backslash before them. Eg to match an account name containing a space: .IP .EX $ hledger register \[aq]credit card\[aq] .EE .PP or: .IP .EX $ hledger register credit\[rs] card .EE .PP Windows users should keep in mind that \f[CR]cmd\f[R] treats single quote as a regular character, so you should be using double quotes exclusively. PowerShell treats both single and double quotes as quotes. .SS Double escaping (regular expression metacharacters) Characters significant in regular expressions (described below) \- such as \f[CR].\f[R], \f[CR]\[ha]\f[R], \f[CR]$\f[R], \f[CR][\f[R], \f[CR]]\f[R], \f[CR](\f[R], \f[CR])\f[R], \f[CR]|\f[R], and \f[CR]\[rs]\f[R] \- may need to be \[dq]regex\-escaped\[dq] if you don\[aq]t want them to be interpreted by hledger\[aq]s regular expression engine. This is done by writing backslashes before them, but since backslash is typically also a shell metacharacter, both shell\-escaping and regex\-escaping will be needed. Eg to match a literal \f[CR]$\f[R] sign while using the bash shell: .IP .EX $ hledger balance cur:\[aq]\[rs]$\[aq] .EE .PP or: .IP .EX $ hledger balance cur:\[rs]\[rs]$ .EE .SS Triple escaping (for add\-on commands) When you use hledger to run an external add\-on command (described below), one level of shell\-escaping is lost from any options or arguments intended for by the add\-on command, so those need an extra level of shell\-escaping. Eg to match a literal \f[CR]$\f[R] sign while using the bash shell and running an add\-on command (\f[CR]ui\f[R]): .IP .EX $ hledger ui cur:\[aq]\[rs]\[rs]$\[aq] .EE .PP or: .IP .EX $ hledger ui cur:\[rs]\[rs]\[rs]\[rs]$ .EE .PP If you wondered why \f[I]four\f[R] backslashes, perhaps this helps: .PP .TS tab(@); l l. T{ unescaped: T}@T{ \f[CR]$\f[R] T} T{ escaped: T}@T{ \f[CR]\[rs]$\f[R] T} T{ double\-escaped: T}@T{ \f[CR]\[rs]\[rs]$\f[R] T} T{ triple\-escaped: T}@T{ \f[CR]\[rs]\[rs]\[rs]\[rs]$\f[R] T} .TE .PP Or, you can avoid the extra escaping by running the add\-on executable directly: .IP .EX $ hledger\-ui cur:\[rs]\[rs]$ .EE .SS Less escaping Options and arguments are sometimes used in places other than the shell command line, where shell\-escaping is not needed, so there you should use one less level of escaping. Those places include: .IP \[bu] 2 an \[at]argumentfile .IP \[bu] 2 hledger\-ui\[aq]s filter field .IP \[bu] 2 hledger\-web\[aq]s search form .IP \[bu] 2 GHCI\[aq]s prompt (used by developers). .SS Unicode characters hledger is expected to handle non\-ascii characters correctly: .IP \[bu] 2 they should be parsed correctly in input files and on the command line, by all hledger tools (add, iadd, hledger\-web\[aq]s search/add/edit forms, etc.) .IP \[bu] 2 they should be displayed correctly by all hledger tools, and on\-screen alignment should be preserved. .PP This requires a well\-configured environment. Here are some tips: .IP \[bu] 2 A system locale must be configured, and it must be one that can decode the characters being used. In bash, you can set a locale like this: \f[CR]export LANG=en_US.UTF\-8\f[R]. There are some more details in Troubleshooting. This step is essential \- without it, hledger will quit on encountering a non\-ascii character (as with all GHC\-compiled programs). .IP \[bu] 2 your terminal software (eg Terminal.app, iTerm, CMD.exe, xterm..) must support unicode .IP \[bu] 2 the terminal must be using a font which includes the required unicode glyphs .IP \[bu] 2 the terminal should be configured to display wide characters as double width (for report alignment) .IP \[bu] 2 on Windows, for best results you should run hledger in the same kind of environment in which it was built. Eg hledger built in the standard CMD.EXE environment (like the binaries on our download page) might show display problems when run in a cygwin or msys terminal, and vice versa. (See eg #961). .SS Regular expressions A regular expression (regexp) is a small piece of text where certain characters (like \f[CR].\f[R], \f[CR]\[ha]\f[R], \f[CR]$\f[R], \f[CR]+\f[R], \f[CR]*\f[R], \f[CR]()\f[R], \f[CR]|\f[R], \f[CR][]\f[R], \f[CR]\[rs]\f[R]) have special meanings, forming a tiny language for matching text precisely \- very useful in hledger and elsewhere. To learn all about them, visit regular\-expressions.info. .PP hledger supports regexps whenever you are entering a pattern to match something, eg in query arguments, account aliases, CSV if rules, hledger\-web\[aq]s search form, hledger\-ui\[aq]s \f[CR]/\f[R] search, etc. You may need to wrap them in quotes, especially at the command line (see Special characters above). Here are some examples: .PP Account name queries (quoted for command line use): .IP .EX Regular expression: Matches: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- bank assets:bank, assets:bank:savings, expenses:art:banksy, ... :bank assets:bank:savings, expenses:art:banksy :bank: assets:bank:savings \[aq]\[ha]bank\[aq] none of those ( \[ha] matches beginning of text ) \[aq]bank$\[aq] assets:bank ( $ matches end of text ) \[aq]big \[rs]$ bank\[aq] big $ bank ( \[rs] disables following character\[aq]s special meaning ) \[aq]\[rs]bbank\[rs]b\[aq] assets:bank, assets:bank:savings ( \[rs]b matches word boundaries ) \[aq](sav|check)ing\[aq] saving or checking ( (|) matches either alternative ) \[aq]saving|checking\[aq] saving or checking ( outer parentheses are not needed ) \[aq]savings?\[aq] saving or savings ( ? matches 0 or 1 of the preceding thing ) \[aq]my +bank\[aq] my bank, my bank, ... ( + matches 1 or more of the preceding thing ) \[aq]my *bank\[aq] mybank, my bank, my bank, ... ( * matches 0 or more of the preceding thing ) \[aq]b.nk\[aq] bank, bonk, b nk, ... ( . matches any character ) .EE .PP Some other queries: .IP .EX desc:\[aq]amazon|amzn|audible\[aq] Amazon transactions cur:EUR amounts with commodity symbol containing EUR cur:\[aq]\[rs]$\[aq] amounts with commodity symbol containing $ cur:\[aq]\[ha]\[rs]$$\[aq] only $ amounts, not eg AU$ or CA$ cur:....? amounts with 4\-or\-more\-character symbols tag:.=202[1\-3] things with any tag whose value contains 2021, 2022 or 2023 .EE .PP Account name aliases: accept \f[CR].\f[R] instead of \f[CR]:\f[R] as account separator: .IP .EX alias /\[rs]./=: replaces all periods in account names with colons .EE .PP Show multiple top\-level accounts combined as one: .IP .EX \-\-alias=\[aq]/\[ha][\[ha]:]+/=combined\[aq] ( [\[ha]:] matches any character other than : ) .EE .PP Show accounts with the second\-level part removed: .IP .EX \-\-alias \[aq]/\[ha]([\[ha]:]+):[\[ha]:]+/ = \[rs]1\[aq] match a top\-level account and a second\-level account and replace those with just the top\-level account ( \[rs]1 in the replacement text means \[dq]whatever was matched by the first parenthesised part of the regexp\[dq] .EE .PP CSV rules: match CSV records containing dining\-related MCC codes: .IP .EX if \[rs]?MCC581[124] .EE .PP Match CSV records with a specific amount around the end/start of month: .IP .EX if %amount \[rs]b3\[rs].99 & %date (29|30|31|01|02|03)$ .EE .SS hledger\[aq]s regular expressions hledger\[aq]s regular expressions come from the regex\-tdfa library. If they\[aq]re not doing what you expect, it\[aq]s important to know exactly what they support: .IP "1." 3 they are case insensitive .IP "2." 3 they are infix matching (they do not need to match the entire thing being matched) .IP "3." 3 they are POSIX ERE (extended regular expressions) .IP "4." 3 they also support GNU word boundaries (\f[CR]\[rs]b\f[R], \f[CR]\[rs]B\f[R], \f[CR]\[rs]<\f[R], \f[CR]\[rs]>\f[R]) .IP "5." 3 backreferences are supported when doing text replacement in account aliases or CSV rules, where backreferences can be used in the replacement string to reference capturing groups in the search regexp. Otherwise, if you write \f[CR]\[rs]1\f[R], it will match the digit \f[CR]1\f[R]. .IP "6." 3 they do not support mode modifiers (\f[CR](?s)\f[R]), character classes (\f[CR]\[rs]w\f[R], \f[CR]\[rs]d\f[R]), or anything else not mentioned above. .PP Some things to note: .IP \[bu] 2 In the \f[CR]alias\f[R] directive and \f[CR]\-\-alias\f[R] option, regular expressions must be enclosed in forward slashes (\f[CR]/REGEX/\f[R]). Elsewhere in hledger, these are not required. .IP \[bu] 2 In queries, to match a regular expression metacharacter like \f[CR]$\f[R] as a literal character, prepend a backslash. Eg to search for amounts with the dollar sign in hledger\-web, write \f[CR]cur:\[rs]$\f[R]. .IP \[bu] 2 On the command line, some metacharacters like \f[CR]$\f[R] have a special meaning to the shell and so must be escaped at least once more. See Special characters. .SS Argument files You can save a set of command line options and arguments in a file, and then reuse them by writing \f[CR]\[at]FILENAME\f[R] as a command line argument. Eg: \f[CR]hledger bal \[at]foo.args\f[R]. .PP Inside the argument file, each line should contain just one option or argument. Don\[aq]t use spaces except inside quotes (or you\[aq]ll see a confusing error); write \f[CR]=\f[R] (or nothing) between a flag and its argument. For the special characters mentioned above, use one less level of quoting than you would at the command prompt. .SH Output .SS Output destination hledger commands send their output to the terminal by default. You can of course redirect this, eg into a file, using standard shell syntax: .IP .EX $ hledger print > foo.txt .EE .PP Some commands (print, register, stats, the balance commands) also provide the \f[CR]\-o/\-\-output\-file\f[R] option, which does the same thing without needing the shell. Eg: .IP .EX $ hledger print \-o foo.txt $ hledger print \-o \- # write to stdout (the default) .EE .SS Output format Some commands offer other kinds of output, not just text on the terminal. Here are those commands and the formats currently supported: .PP .TS tab(@); lw(16.1n) lw(14.5n) lw(14.5n) lw(16.1n) lw(4.8n) lw(4.0n). T{ \- T}@T{ txt T}@T{ csv/tsv T}@T{ html T}@T{ json T}@T{ sql T} _ T{ aregister T}@T{ Y T}@T{ Y T}@T{ Y T}@T{ Y T}@T{ T} T{ balance T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1,2\f[R] T}@T{ Y T}@T{ T} T{ balancesheet T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y T}@T{ T} T{ balancesheetequity T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y T}@T{ T} T{ cashflow T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y T}@T{ T} T{ incomestatement T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y \f[I]1\f[R] T}@T{ Y T}@T{ T} T{ print T}@T{ Y T}@T{ Y T}@T{ T}@T{ Y T}@T{ Y T} T{ register T}@T{ Y T}@T{ Y T}@T{ T}@T{ Y T}@T{ T} .TE .IP \[bu] 2 \f[I]1 Also affected by the balance commands\[aq] \f[CI]\-\-layout\f[I] option.\f[R] .IP \[bu] 2 \f[I]2 \f[CI]balance\f[I] does not support html output without a report interval or with \f[CI]\-\-budget\f[I].\f[R] .PP The output format is selected by the \f[CR]\-O/\-\-output\-format=FMT\f[R] option: .IP .EX $ hledger print \-O csv # print CSV on stdout .EE .PP or by the filename extension of an output file specified with the \f[CR]\-o/\-\-output\-file=FILE.FMT\f[R] option: .IP .EX $ hledger balancesheet \-o foo.csv # write CSV to foo.csv .EE .PP The \f[CR]\-O\f[R] option can be combined with \f[CR]\-o\f[R] to override the file extension, if needed: .IP .EX $ hledger balancesheet \-o foo.txt \-O csv # write CSV to foo.txt .EE .PP Some notes about the various output formats: .SS CSV output .IP \[bu] 2 In CSV output, digit group marks (such as thousands separators) are disabled automatically. .SS HTML output .IP \[bu] 2 HTML output can be styled by an optional \f[CR]hledger.css\f[R] file in the same directory. .SS JSON output .IP \[bu] 2 This is not yet much used; real\-world feedback is welcome. .IP \[bu] 2 Our JSON is rather large and verbose, since it is a faithful representation of hledger\[aq]s internal data types. To understand the JSON, read the Haskell type definitions, which are mostly in https://github.com/simonmichael/hledger/blob/master/hledger\-lib/Hledger/Data/Types.hs. .IP \[bu] 2 hledger represents quantities as Decimal values storing up to 255 significant digits, eg for repeating decimals. Such numbers can arise in practice (from automatically\-calculated transaction prices), and would break most JSON consumers. So in JSON, we show quantities as simple Numbers with at most 10 decimal places. We don\[aq]t limit the number of integer digits, but that part is under your control. We hope this approach will not cause problems in practice; if you find otherwise, please let us know. (Cf #1195) .SS SQL output .IP \[bu] 2 This is not yet much used; real\-world feedback is welcome. .IP \[bu] 2 SQL output is expected to work at least with SQLite, MySQL and Postgres. .IP \[bu] 2 For SQLite, it will be more useful if you modify the generated \f[CR]id\f[R] field to be a PRIMARY KEY. Eg: .RS 2 .IP .EX $ hledger print \-O sql | sed \[aq]s/id serial/id INTEGER PRIMARY KEY AUTOINCREMENT NOT NULL/g\[aq] | ... .EE .RE .IP \[bu] 2 SQL output is structured with the expectations that statements will be executed in the empty database. If you already have tables created via SQL output of hledger, you would probably want to either clear tables of existing data (via \f[CR]delete\f[R] or \f[CR]truncate\f[R] SQL statements) or drop tables completely as otherwise your postings will be duped. .SS Commodity styles When displaying amounts, hledger infers a standard display style for each commodity/currency, as described below in Commodity display style. .PP If needed, this can be overridden by a \f[CR]\-c/\-\-commodity\-style\f[R] option (except for cost amounts and amounts displayed by the \f[CR]print\f[R] command, which are always displayed with all decimal digits). For example, the following will force dollar amounts to be displayed as shown: .IP .EX $ hledger print \-c \[aq]$1.000,0\[aq] .EE .PP This option can repeated to set the display style for multiple commodities/currencies. Its argument is as described in the commodity directive. .SS Colour In terminal output, some commands can produce colour when the terminal supports it: .IP \[bu] 2 if the \f[CR]\-\-color/\-\-colour\f[R] option is given a value of \f[CR]yes\f[R] or \f[CR]always\f[R] (or \f[CR]no\f[R] or \f[CR]never\f[R]), colour will (or will not) be used; .IP \[bu] 2 otherwise, if the \f[CR]NO_COLOR\f[R] environment variable is set, colour will not be used; .IP \[bu] 2 otherwise, colour will be used if the output (terminal or file) supports it. .SS Box\-drawing In terminal output, you can enable unicode box\-drawing characters to render prettier tables: .IP \[bu] 2 if the \f[CR]\-\-pretty\f[R] option is given a value of \f[CR]yes\f[R] or \f[CR]always\f[R] (or \f[CR]no\f[R] or \f[CR]never\f[R]), unicode characters will (or will not) be used; .IP \[bu] 2 otherwise, unicode characters will not be used. .SS Paging When showing long output in the terminal, hledger will try to use the pager specified by the \f[CR]PAGER\f[R] environment variable, or \f[CR]less\f[R], or \f[CR]more\f[R]. (A pager is a helper program that shows one page at a time rather than scrolling everything off screen). Currently it does this only for help output, not for reports; specifically, .IP \[bu] 2 when listing commands, with \f[CR]hledger\f[R] .IP \[bu] 2 when showing help with \f[CR]hledger [CMD] \-\-help\f[R], .IP \[bu] 2 when viewing manuals with \f[CR]hledger help\f[R] or \f[CR]hledger \-\-man\f[R]. .PP Note the pager is expected to handle ANSI codes, which hledger uses eg for bold emphasis. For the common pager \f[CR]less\f[R] (and its \f[CR]more\f[R] compatibility mode), we add \f[CR]R\f[R] to the \f[CR]LESS\f[R] and \f[CR]MORE\f[R] environment variables to make this work. If you use a different pager, you might need to configure it similarly, to avoid seeing junk on screen (let us know). Otherwise, you can set the \f[CR]NO_COLOR\f[R] environment variable to 1 to disable all ANSI output (see Colour). .SS Debug output We intend hledger to be relatively easy to troubleshoot, introspect and develop. You can add \f[CR]\-\-debug[=N]\f[R] to any hledger command line to see additional debug output. N ranges from 1 (least output, the default) to 9 (maximum output). Typically you would start with 1 and increase until you are seeing enough. Debug output goes to stderr, and is not affected by \f[CR]\-o/\-\-output\-file\f[R] (unless you redirect stderr to stdout, eg: \f[CR]2>&1\f[R]). It will be interleaved with normal output, which can help reveal when parts of the code are evaluated. To capture debug output in a log file instead, you can usually redirect stderr, eg: .IP .EX hledger bal \-\-debug=3 2>hledger.log .EE .SH Environment These environment variables affect hledger: .PP \f[B]COLUMNS\f[R] This is normally set by your terminal; some hledger commands (\f[CR]register\f[R]) will format their output to this width. If not set, they will try to use the available terminal width. .PP \f[B]LEDGER_FILE\f[R] The main journal file to use when not specified with \f[CR]\-f/\-\-file\f[R]. Default: \f[CR]$HOME/.hledger.journal\f[R]. .PP \f[B]NO_COLOR\f[R] If this environment variable is set (with any value), hledger will not use ANSI color codes in terminal output, unless overridden by an explicit \f[CR]\-\-color/\-\-colour\f[R] option. .SH PART 2: DATA FORMATS .SH Journal hledger\[aq]s default file format, representing a General Journal. Here\[aq]s a cheatsheet/mini\-tutorial, or you can skip ahead to About journal format. .SS Journal cheatsheet .IP .EX # Here is the main syntax of hledger\[aq]s journal format # (omitting extra Ledger compatibility syntax). # hledger journals contain comments, directives, and transactions, in any order: ############################################################################### # 1. Comment lines are for notes or temporarily disabling things. # They begin with #, ;, or a line containing the word \[dq]comment\[dq]. # hash comment line ; semicolon comment line comment These lines are commented. end comment # Some but not all hledger entries can have same\-line comments attached to them, # from ; (semicolon) to end of line. ############################################################################### # 2. Directives modify parsing or reports in some way. # They begin with a word or letter (or symbol). account actifs ; type:A, declare an account that is an Asset. 2+ spaces before ;. account passifs ; type:L, declare an account that is a Liability, and so on.. (ALERX) alias chkg = assets:checking commodity $0.00 decimal\-mark . include /dev/null payee Whole Foods P 2022\-01\-01 AAAA $1.40 \[ti] monthly budget goals ; <\- 2+ spaces between period expression and description expenses:food $400 expenses:home $1000 budgeted ############################################################################### # 3. Transactions are what it\[aq]s all about; they are dated events, # usually describing movements of money. # They begin with a date. # DATE DESCRIPTION ; This is a transaction comment. # ACCOUNT NAME 1 AMOUNT1 ; <\- posting 1. This is a posting comment. # ACCOUNT NAME 2 AMOUNT2 ; <\- posting 2. Postings must be indented. # ; \[ha]\[ha] At least 2 spaces between account and amount. # ... ; Any number of postings is allowed. The amounts must balance (sum to 0). 2022\-01\-01 opening balances are declared this way assets:checking $1000 ; Account names can be anything. lower case is easy to type. assets:savings $1000 ; assets, liabilities, equity, revenues, expenses are common. assets:cash:wallet $100 ; : indicates subaccounts. liabilities:credit card $\-200 ; liabilities, equity, revenues balances are usually negative. equity ; One amount can be left blank; $\-1900 is inferred here. 2022\-04\-15 * (#12345) pay taxes ; There can be a ! or * after the date meaning \[dq]pending\[dq] or \[dq]cleared\[dq]. ; There can be a transaction code (text in parentheses) after the date/status. ; Amounts\[aq] sign represents direction of flow, or credit/debit: assets:checking $\-500 ; minus means removed from this account (credit) expenses:tax:us:2021 $500 ; plus means added to this account (debit) ; revenue/expense categories are also \[dq]accounts\[dq] 2022\-01\-01 ; The description is optional. ; Any currency/commodity symbols are allowed, on either side. assets:cash:wallet GBP \-10 expenses:clothing GBP 10 assets:gringotts \-10 gold assets:pouch 10 gold revenues:gifts \-2 \[dq]Liquorice Wands\[dq] ; Complex symbols assets:bag 2 \[dq]Liquorice Wands\[dq] ; must be double\-quoted. 2022\-01\-01 Cost in another commodity can be noted with \[at] or \[at]\[at] assets:investments 2.0 AAAA \[at] $1.50 ; \[at] means per\-unit cost assets:investments 3.0 AAAA \[at]\[at] $4 ; \[at]\[at] means total cost assets:checking $\-7.00 2022\-01\-02 assert balances ; Balances can be asserted for extra error checking, in any transaction. assets:investments 0 AAAA = 5.0 AAAA assets:pouch 0 gold = 10 gold assets:savings $0 = $1000 1999\-12\-31 Ordering transactions by date is recommended but not required. ; Postings are not required. 2022.01.01 These date 2022/1/1 formats are 12/31 also allowed (but consistent YYYY\-MM\-DD is recommended). .EE .SS About journal format hledger\[aq]s usual data source is a plain text file containing journal entries in hledger journal format. This file represents a standard accounting general journal. I use file names ending in \f[CR].journal\f[R], but that\[aq]s not required. The journal file contains a number of transaction entries, each describing a transfer of money (or any commodity) between two or more named accounts, in a simple format readable by both hledger and humans. .PP hledger\[aq]s journal format is compatible with most of Ledger\[aq]s journal format, but not all of it. The differences and interoperation tips are described at hledger and Ledger. With some care, and by avoiding incompatible features, you can keep your hledger journal readable by Ledger and vice versa. This can useful eg for comparing the behaviour of one app against the other. .PP You can use hledger without learning any more about this file; just use the add or web or import commands to create and update it. .PP Many users, though, edit the journal file with a text editor, and track changes with a version control system such as git. Editor addons such as ledger\-mode or hledger\-mode for Emacs, vim\-ledger for Vim, and hledger\-vscode for Visual Studio Code, make this easier, adding colour, formatting, tab completion, and useful commands. See Editor configuration at hledger.org for the full list. .PP Here\[aq]s a description of each part of the file format (and hledger\[aq]s data model). .PP A hledger journal file can contain three kinds of thing: file comments, transactions, and/or directives (counting periodic transaction rules and auto posting rules as directives). .SS Comments Lines in the journal will be ignored if they begin with a hash (\f[CR]#\f[R]) or a semicolon (\f[CR];\f[R]). (See also Other syntax.) hledger will also ignore regions beginning with a \f[CR]comment\f[R] line and ending with an \f[CR]end comment\f[R] line (or file end). Here\[aq]s a suggestion for choosing between them: .IP \[bu] 2 \f[CR]#\f[R] for top\-level notes .IP \[bu] 2 \f[CR];\f[R] for commenting out things temporarily .IP \[bu] 2 \f[CR]comment\f[R] for quickly commenting large regions (remember it\[aq]s there, or you might get confused) .PP Eg: .IP .EX # a comment line ; another commentline comment A multi\-line comment block, continuing until \[dq]end comment\[dq] directive or the end of the current file. end comment .EE .PP Some hledger entries can have same\-line comments attached to them, from ; (semicolon) to end of line. See Transaction comments, Posting comments, and Account comments below. .SS Transactions Transactions are the main unit of information in a journal file. They represent events, typically a movement of some quantity of commodities between two or more named accounts. .PP Each transaction is recorded as a journal entry, beginning with a simple date in column 0. This can be followed by any of the following optional fields, separated by spaces: .IP \[bu] 2 a status character (empty, \f[CR]!\f[R], or \f[CR]*\f[R]) .IP \[bu] 2 a code (any short number or text, enclosed in parentheses) .IP \[bu] 2 a description (any remaining text until end of line or a semicolon) .IP \[bu] 2 a comment (any remaining text following a semicolon until end of line, and any following indented lines beginning with a semicolon) .IP \[bu] 2 0 or more indented \f[I]posting\f[R] lines, describing what was transferred and the accounts involved (indented comment lines are also allowed, but not blank lines or non\-indented lines). .PP Here\[aq]s a simple journal file containing one transaction: .IP .EX 2008/01/01 income assets:bank:checking $1 income:salary $\-1 .EE .SS Dates .SS Simple dates Dates in the journal file use \f[I]simple dates\f[R] format: \f[CR]YYYY\-MM\-DD\f[R] or \f[CR]YYYY/MM/DD\f[R] or \f[CR]YYYY.MM.DD\f[R], with leading zeros optional. The year may be omitted, in which case it will be inferred from the context: the current transaction, the default year set with a \f[CR]Y\f[R] directive, or the current date when the command is run. Some examples: \f[CR]2010\-01\-31\f[R], \f[CR]2010/01/31\f[R], \f[CR]2010.1.31\f[R], \f[CR]1/31\f[R]. .PP (The UI also accepts simple dates, as well as the more flexible smart dates documented in the hledger manual.) .SS Posting dates You can give individual postings a different date from their parent transaction, by adding a posting comment containing a tag (see below) like \f[CR]date:DATE\f[R]. This is probably the best way to control posting dates precisely. Eg in this example the expense should appear in May reports, and the deduction from checking should be reported on 6/1 for easy bank reconciliation: .IP .EX 2015/5/30 expenses:food $10 ; food purchased on saturday 5/30 assets:checking ; bank cleared it on monday, date:6/1 .EE .IP .EX $ hledger \-f t.j register food 2015\-05\-30 expenses:food $10 $10 .EE .IP .EX $ hledger \-f t.j register checking 2015\-06\-01 assets:checking $\-10 $\-10 .EE .PP DATE should be a simple date; if the year is not specified it will use the year of the transaction\[aq]s date. .PD 0 .P .PD The \f[CR]date:\f[R] tag must have a valid simple date value if it is present, eg a \f[CR]date:\f[R] tag with no value is not allowed. .SS Status Transactions, or individual postings within a transaction, can have a status mark, which is a single character before the transaction description or posting account name, separated from it by a space, indicating one of three statuses: .PP .TS tab(@); l l. T{ mark \ T}@T{ status T} _ T{ \ T}@T{ unmarked T} T{ \f[CR]!\f[R] T}@T{ pending T} T{ \f[CR]*\f[R] T}@T{ cleared T} .TE .PP When reporting, you can filter by status with the \f[CR]\-U/\-\-unmarked\f[R], \f[CR]\-P/\-\-pending\f[R], and \f[CR]\-C/\-\-cleared\f[R] flags; or the \f[CR]status:\f[R], \f[CR]status:!\f[R], and \f[CR]status:*\f[R] queries; or the U, P, C keys in hledger\-ui. .PP Note, in Ledger and in older versions of hledger, the \[dq]unmarked\[dq] state is called \[dq]uncleared\[dq]. As of hledger 1.3 we have renamed it to unmarked for clarity. .PP To replicate Ledger and old hledger\[aq]s behaviour of also matching pending, combine \-U and \-P. .PP Status marks are optional, but can be helpful eg for reconciling with real\-world accounts. Some editor modes provide highlighting and shortcuts for working with status. Eg in Emacs ledger\-mode, you can toggle transaction status with C\-c C\-e, or posting status with C\-c C\-c. .PP What \[dq]uncleared\[dq], \[dq]pending\[dq], and \[dq]cleared\[dq] actually mean is up to you. Here\[aq]s one suggestion: .PP .TS tab(@); lw(9.7n) lw(60.3n). T{ status T}@T{ meaning T} _ T{ uncleared T}@T{ recorded but not yet reconciled; needs review T} T{ pending T}@T{ tentatively reconciled (if needed, eg during a big reconciliation) T} T{ cleared T}@T{ complete, reconciled as far as possible, and considered correct T} .TE .PP With this scheme, you would use \f[CR]\-PC\f[R] to see the current balance at your bank, \f[CR]\-U\f[R] to see things which will probably hit your bank soon (like uncashed checks), and no flags to see the most up\-to\-date state of your finances. .SS Code After the status mark, but before the description, you can optionally write a transaction \[dq]code\[dq], enclosed in parentheses. This is a good place to record a check number, or some other important transaction id or reference number. .SS Description A transaction\[aq]s description is the rest of the line following the date and status mark (or until a comment begins). Sometimes called the \[dq]narration\[dq] in traditional bookkeeping, it can be used for whatever you wish, or left blank. Transaction descriptions can be queried, unlike comments. .SS Payee and note You can optionally include a \f[CR]|\f[R] (pipe) character in descriptions to subdivide the description into separate fields for payee/payer name on the left (up to the first \f[CR]|\f[R]) and an additional note field on the right (after the first \f[CR]|\f[R]). This may be worthwhile if you need to do more precise querying and pivoting by payee or by note. .SS Transaction comments Text following \f[CR];\f[R], after a transaction description, and/or on indented lines immediately below it, form comments for that transaction. They are reproduced by \f[CR]print\f[R] but otherwise ignored, except they may contain tags, which are not ignored. .IP .EX 2012\-01\-01 something ; a transaction comment ; a second line of transaction comment expenses 1 assets .EE .SS Postings A posting is an addition of some amount to, or removal of some amount from, an account. Each posting line begins with at least one space or tab (2 or 4 spaces is common), followed by: .IP \[bu] 2 (optional) a status character (empty, \f[CR]!\f[R], or \f[CR]*\f[R]), followed by a space .IP \[bu] 2 (required) an account name (any text, optionally containing \f[B]single spaces\f[R], until end of line or a double space) .IP \[bu] 2 (optional) \f[B]two or more spaces\f[R] or tabs followed by an amount. .PP Positive amounts are being added to the account, negative amounts are being removed. .PP The amounts within a transaction must always sum up to zero. As a convenience, one amount may be left blank; it will be inferred so as to balance the transaction. .PP Be sure to note the unusual two\-space delimiter between account name and amount. This makes it easy to write account names containing spaces. But if you accidentally leave only one space (or tab) before the amount, the amount will be considered part of the account name. .SS Account names Accounts are the main way of categorising things in hledger. As in Double Entry Bookkeeping, they can represent real world accounts (such as a bank account), or more abstract categories such as \[dq]money borrowed from Frank\[dq] or \[dq]money spent on electricity\[dq]. .PP You can use any account names you like, but we usually start with the traditional accounting categories, which in english are \f[CR]assets\f[R], \f[CR]liabilities\f[R], \f[CR]equity\f[R], \f[CR]revenues\f[R], \f[CR]expenses\f[R]. (You might see these referred to as A, L, E, R, X for short.) .PP For more precise reporting, we usually divide the top level accounts into more detailed subaccounts, by writing a full colon between account name parts. For example, from the account names \f[CR]assets:bank:checking\f[R] and \f[CR]expenses:food\f[R], hledger will infer this hierarchy of five accounts: .IP .EX assets assets:bank assets:bank:checking expenses expenses:food .EE .PP Shown as an outline, the hierarchical tree structure is more clear: .IP .EX assets bank checking expenses food .EE .PP hledger reports can summarise the account tree to any depth, so you can go as deep as you like with subcategories, but keeping your account names relatively simple may be best when starting out. .PP Account names may be capitalised or not; they may contain letters, numbers, symbols, or single spaces. Note, when an account name and an amount are written on the same line, they must be separated by \f[B]two or more spaces\f[R] (or tabs). .PP Parentheses or brackets enclosing the full account name indicate virtual postings, described below. Parentheses or brackets internal to the account name have no special meaning. .PP Account names can be altered temporarily or permanently by account aliases. .SS Amounts After the account name, there is usually an amount. (Important: between account name and amount, there must be \f[B]two or more spaces\f[R].) .PP hledger\[aq]s amount format is flexible, supporting several international formats. Here are some examples. Amounts have a number (the \[dq]quantity\[dq]): .IP .EX 1 .EE .PP \&..and usually a currency symbol or commodity name (more on this below), to the left or right of the quantity, with or without a separating space: .IP .EX $1 4000 AAPL 3 \[dq]green apples\[dq] .EE .PP Amounts can be preceded by a minus sign (or a plus sign, though plus is the default), The sign can be written before or after a left\-side commodity symbol: .IP .EX \-$1 $\-1 .EE .PP One or more spaces between the sign and the number are acceptable when parsing (but they won\[aq]t be displayed in output): .IP .EX + $1 $\- 1 .EE .PP Scientific E notation is allowed: .IP .EX 1E\-6 EUR 1E3 .EE .SS Decimal marks, digit group marks A \f[I]decimal mark\f[R] can be written as a period or a comma: .IP .EX 1.23 1,23 .EE .PP In the integer part of the quantity (left of the decimal mark), groups of digits can optionally be separated by a \f[I]digit group mark\f[R] \- a space, comma, or period (different from the decimal mark): .IP .EX $1,000,000.00 EUR 2.000.000,00 INR 9,99,99,999.00 1 000 000.9455 .EE .PP hledger is not biased towards period or comma decimal marks, so a number containing just one period or comma, like \f[CR]1,000\f[R] or \f[CR]1.000\f[R], is ambiguous. In such cases hledger assumes it is a decimal mark, parsing both of these as 1. .PP To disambiguate these and ensure accurate number parsing, especially if you use digit group marks, we recommend declaring the decimal mark. You can declare it for each file with \f[CR]decimal\-mark\f[R] directives, or for each commodity with \f[CR]commodity\f[R] directives (described below). .SS Commodity Amounts in hledger have both a \[dq]quantity\[dq], which is a signed decimal number, and a \[dq]commodity\[dq], which is a currency symbol, stock ticker, or any word or phrase describing something you are tracking. .PP If the commodity name contains non\-letters (spaces, numbers, or punctuation), you must always write it inside double quotes (\f[CR]\[dq]green apples\[dq]\f[R], \f[CR]\[dq]ABC123\[dq]\f[R]). .PP If you write just a bare number, that too will have a commodity, with name \f[CR]\[dq]\[dq]\f[R]; we call that the \[dq]no\-symbol commodity\[dq]. .PP Actually, hledger combines these single\-commodity amounts into more powerful multi\-commodity amounts, which are what it works with most of the time. A multi\-commodity amount could be, eg: \f[CR]1 USD, 2 EUR, 3.456 TSLA\f[R]. In practice, you will only see multi\-commodity amounts in hledger\[aq]s output; you can\[aq]t write them directly in the journal file. .PP (If you are writing scripts or working with hledger\[aq]s internals, these are the \f[CR]Amount\f[R] and \f[CR]MixedAmount\f[R] types.) .SS Directives influencing number parsing and display You can add \f[CR]decimal\-mark\f[R] and \f[CR]commodity\f[R] directives to the journal, to declare and control these things more explicitly and precisely. These are described below, but here\[aq]s a quick example: .IP .EX # the decimal mark character used by all amounts in this file (all commodities) decimal\-mark . # display styles for the $, EUR, INR and no\-symbol commodities: commodity $1,000.00 commodity EUR 1.000,00 commodity INR 9,99,99,999.00 commodity 1 000 000.9455 .EE .PP .SS Commodity display style For the amounts in each commodity, hledger chooses a consistent display style (symbol placement, decimal mark and digit group marks, number of decimal digits) to use in most reports. This is inferred as follows: .PP First, if there\[aq]s a \f[CR]D\f[R] directive declaring a default commodity, that commodity symbol and amount format is applied to all no\-symbol amounts in the journal. .PP Then each commodity\[aq]s display style is determined from its \f[CR]commodity\f[R] directive. We recommend always declaring commodities with \f[CR]commodity\f[R] directives, since they help ensure consistent display styles and precisions, and bring other benefits such as error checking for commodity symbols. .PP But if a \f[CR]commodity\f[R] directive is not present, hledger infers a commodity\[aq]s display styles from its amounts as they are written in the journal (excluding cost amounts and amounts in periodic transaction rules or auto posting rules). It uses .IP \[bu] 2 the symbol placement and decimal mark of the first amount seen .IP \[bu] 2 the digit group marks of the first amount with digit group marks .IP \[bu] 2 and the maximum number of decimal digits seen across all amounts. .PP And as fallback if no applicable amounts are found, it would use a default style, like \f[CR]$1000.00\f[R] (symbol on the left with no space, period as decimal mark, and two decimal digits). .PP Finally, commodity styles can be overridden by the \f[CR]\-c/\-\-commodity\-style\f[R] command line option. .SS Rounding Amounts are stored internally as decimal numbers with up to 255 decimal places. They are displayed with their original journal precisions by print and print\-like reports, and rounded to their display precision (the number of decimal digits specified by the commodity display style) by other reports. When rounding, hledger uses banker\[aq]s rounding (it rounds to the nearest even digit). So eg 0.5 displayed with zero decimal digits appears as \[dq]0\[dq]. .PP .SS Costs After a posting amount, you can note its cost (when buying) or selling price (when selling) in another commodity, by writing either \f[CR]\[at] UNITPRICE\f[R] or \f[CR]\[at]\[at] TOTALPRICE\f[R] after it. This indicates a conversion transaction, where one commodity is exchanged for another. .PP (You might also see this called \[dq]transaction price\[dq] in hledger docs, discussions, or code; that term was directionally neutral and reminded that it is a price specific to a transaction, but we now just call it \[dq]cost\[dq], with the understanding that the transaction could be a purchase or a sale.) .PP Costs are usually written explicitly with \f[CR]\[at]\f[R] or \f[CR]\[at]\[at]\f[R], but can also be inferred automatically for simple multi\-commodity transactions. Note, if costs are inferred, the order of postings is significant; the first posting will have a cost attached, in the commodity of the second. .PP As an example, here are several ways to record purchases of a foreign currency in hledger, using the cost notation either explicitly or implicitly: .IP "1." 3 Write the price per unit, as \f[CR]\[at] UNITPRICE\f[R] after the amount: .RS 4 .IP .EX 2009/1/1 assets:euros €100 \[at] $1.35 ; one hundred euros purchased at $1.35 each assets:dollars ; balancing amount is \-$135.00 .EE .RE .IP "2." 3 Write the total price, as \f[CR]\[at]\[at] TOTALPRICE\f[R] after the amount: .RS 4 .IP .EX 2009/1/1 assets:euros €100 \[at]\[at] $135 ; one hundred euros purchased at $135 for the lot assets:dollars .EE .RE .IP "3." 3 Specify amounts for all postings, using exactly two commodities, and let hledger infer the price that balances the transaction. Note the effect of posting order: the price is added to first posting, making it \f[CR]€100 \[at]\[at] $135\f[R], as in example 2: .RS 4 .IP .EX 2009/1/1 assets:euros €100 ; one hundred euros purchased assets:dollars $\-135 ; for $135 .EE .RE .PP Amounts can be converted to cost at report time using the \f[CR]\-B/\-\-cost\f[R] flag; this is discussed more in the Cost reporting section. .PP Note that the cost normally should be a positive amount, though it\[aq]s not required to be. This can be a little confusing, see discussion at \-\-infer\-market\-prices: market prices from transactions. .SS Other cost/lot notations A slight digression for Ledger and Beancount users. Ledger has a number of cost/lot\-related notations: .IP \[bu] 2 \f[CR]\[at] UNITCOST\f[R] and \f[CR]\[at]\[at] TOTALCOST\f[R] .RS 2 .IP \[bu] 2 expresses a conversion rate, as in hledger .IP \[bu] 2 when buying, also creates a lot than can be selected at selling time .RE .IP \[bu] 2 \f[CR](\[at]) UNITCOST\f[R] and \f[CR](\[at]\[at]) TOTALCOST\f[R] (virtual cost) .RS 2 .IP \[bu] 2 like the above, but also means \[dq]this cost was exceptional, don\[aq]t use it when inferring market prices\[dq]. .RE .PP Currently, hledger treats the above like \f[CR]\[at]\f[R] and \f[CR]\[at]\[at]\f[R]; the parentheses are ignored. .IP \[bu] 2 \f[CR]{=FIXEDUNITCOST}\f[R] and \f[CR]{{=FIXEDTOTALCOST}}\f[R] (fixed price) .RS 2 .IP \[bu] 2 when buying, means \[dq]this cost is also the fixed price, don\[aq]t let it fluctuate in value reports\[dq] .RE .IP \[bu] 2 \f[CR]{UNITCOST}\f[R] and \f[CR]{{TOTALCOST}}\f[R] (lot price) .RS 2 .IP \[bu] 2 can be used identically to \f[CR]\[at] UNITCOST\f[R] and \f[CR]\[at]\[at] TOTALCOST\f[R], also creates a lot .IP \[bu] 2 when selling, combined with \f[CR]\[at] ...\f[R], specifies an investment lot by its cost basis; does not check if that lot is present .RE .IP \[bu] 2 and related: \f[CR][YYYY/MM/DD]\f[R] (lot date) .RS 2 .IP \[bu] 2 when buying, attaches this acquisition date to the lot .IP \[bu] 2 when selling, selects a lot by its acquisition date .RE .IP \[bu] 2 \f[CR](SOME TEXT)\f[R] (lot note) .RS 2 .IP \[bu] 2 when buying, attaches this note to the lot .IP \[bu] 2 when selling, selects a lot by its note .RE .PP Currently, hledger accepts any or all of the above in any order after the posting amount, but ignores them. (This can break transaction balancing.) .PP For Beancount users, the notation and behaviour is different: .IP \[bu] 2 \f[CR]\[at] UNITCOST\f[R] and \f[CR]\[at]\[at] TOTALCOST\f[R] .RS 2 .IP \[bu] 2 expresses a cost without creating a lot, as in hledger .IP \[bu] 2 when buying (augmenting) or selling (reducing) a lot, combined with \f[CR]{...}\f[R]: documents the cost/selling price (not used for transaction balancing) .RE .IP \[bu] 2 \f[CR]{UNITCOST}\f[R] and \f[CR]{{TOTALCOST}}\f[R] .RS 2 .IP \[bu] 2 when buying (augmenting), expresses the cost for transaction balancing, and also creates a lot with this cost basis attached .IP \[bu] 2 when selling (reducing), .RS 2 .IP \[bu] 2 selects a lot by its cost basis .IP \[bu] 2 raises an error if that lot is not present or can not be selected unambiguously (depending on booking method configured) .IP \[bu] 2 expresses the selling price for transaction balancing .RE .RE .PP Currently, hledger accepts the \f[CR]{UNITCOST}\f[R]/\f[CR]{{TOTALCOST}}\f[R] notation but ignores it. .IP \[bu] 2 variations: \f[CR]{}\f[R], \f[CR]{YYYY\-MM\-DD}\f[R], \f[CR]{\[dq]LABEL\[dq]}\f[R], \f[CR]{UNITCOST, \[dq]LABEL\[dq]}\f[R], \f[CR]{UNITCOST, YYYY\-MM\-DD, \[dq]LABEL\[dq]}\f[R] etc. .PP Currently, hledger rejects these. .SS Balance assertions hledger supports Ledger\-style balance assertions in journal files. These look like, for example, \f[CR]= EXPECTEDBALANCE\f[R] following a posting\[aq]s amount. Eg here we assert the expected dollar balance in accounts a and b after each posting: .IP .EX 2013/1/1 a $1 =$1 b =$\-1 2013/1/2 a $1 =$2 b $\-1 =$\-2 .EE .PP After reading a journal file, hledger will check all balance assertions and report an error if any of them fail. Balance assertions can protect you from, eg, inadvertently disrupting reconciled balances while cleaning up old entries. You can disable them temporarily with the \f[CR]\-I/\-\-ignore\-assertions\f[R] flag, which can be useful for troubleshooting or for reading Ledger files. (Note: this flag currently does not disable balance assignments, described below). .SS Assertions and ordering hledger sorts an account\[aq]s postings and assertions first by date and then (for postings on the same day) by parse order. Note this is different from Ledger, which sorts assertions only by parse order. (Also, Ledger assertions do not see the accumulated effect of repeated postings to the same account within a transaction.) .PP So, hledger balance assertions keep working if you reorder differently\-dated transactions within the journal. But if you reorder same\-dated transactions or postings, assertions might break and require updating. This order dependence does bring an advantage: precise control over the order of postings and assertions within a day, so you can assert intra\-day balances. .SS Assertions and multiple included files Multiple files included with the \f[CR]include\f[R] directive are processed as if concatenated into one file, preserving their order and the posting order within each file. It means that balance assertions in later files will see balance from earlier files. .PP And if you have multiple postings to an account on the same day, split across multiple files, and you want to assert the account\[aq]s balance on that day, you\[aq]ll need to put the assertion in the right file \- the last one in the sequence, probably. .SS Assertions and multiple \-f files Unlike \f[CR]include\f[R], when multiple files are specified on the command line with multiple \f[CR]\-f/\-\-file\f[R] options, balance assertions will not see balance from earlier files. This can be useful when you do not want problems in earlier files to disrupt valid assertions in later files. .PP If you do want assertions to see balance from earlier files, use \f[CR]include\f[R], or concatenate the files temporarily. .SS Assertions and commodities The asserted balance must be a simple single\-commodity amount, and in fact the assertion checks only this commodity\[aq]s balance within the (possibly multi\-commodity) account balance. This is how assertions work in Ledger also. We could call this a \[dq]partial\[dq] balance assertion. .PP To assert the balance of more than one commodity in an account, you can write multiple postings, each asserting one commodity\[aq]s balance. .PP You can make a stronger \[dq]total\[dq] balance assertion by writing a double equals sign (\f[CR]== EXPECTEDBALANCE\f[R]). This asserts that there are no other commodities in the account besides the asserted one (or at least, that their balance is 0). .IP .EX 2013/1/1 a $1 a 1€ b $\-1 c \-1€ 2013/1/2 ; These assertions succeed a 0 = $1 a 0 = 1€ b 0 == $\-1 c 0 == \-1€ 2013/1/3 ; This assertion fails as \[aq]a\[aq] also contains 1€ a 0 == $1 .EE .PP It\[aq]s not yet possible to make a complete assertion about a balance that has multiple commodities. One workaround is to isolate each commodity into its own subaccount: .IP .EX 2013/1/1 a:usd $1 a:euro 1€ b 2013/1/2 a 0 == 0 a:usd 0 == $1 a:euro 0 == 1€ .EE .SS Assertions and costs Balance assertions ignore costs, and should normally be written without one: .IP .EX 2019/1/1 (a) $1 \[at] €1 = $1 .EE .PP We do allow costs to be written in balance assertion amounts, however, and print shows them, but they don\[aq]t affect whether the assertion passes or fails. This is for backward compatibility (hledger\[aq]s close command used to generate balance assertions with costs), and because balance \f[I]assignments\f[R] do use costs (see below). .SS Assertions and subaccounts The balance assertions above (\f[CR]=\f[R] and \f[CR]==\f[R]) do not count the balance from subaccounts; they check the account\[aq]s exclusive balance only. You can assert the balance including subaccounts by writing \f[CR]=*\f[R] or \f[CR]==*\f[R], eg: .IP .EX 2019/1/1 equity:opening balances checking:a 5 checking:b 5 checking 1 ==* 11 .EE .SS Assertions and virtual postings Balance assertions always consider both real and virtual postings; they are not affected by the \f[CR]\-\-real/\-R\f[R] flag or \f[CR]real:\f[R] query. .SS Assertions and auto postings Balance assertions \f[I]are\f[R] affected by the \f[CR]\-\-auto\f[R] flag, which generates auto postings, which can alter account balances. Because auto postings are optional in hledger, accounts affected by them effectively have two balances. But balance assertions can only test one or the other of these. So to avoid making fragile assertions, either: .IP \[bu] 2 assert the balance calculated with \f[CR]\-\-auto\f[R], and always use \f[CR]\-\-auto\f[R] with that file .IP \[bu] 2 or assert the balance calculated without \f[CR]\-\-auto\f[R], and never use \f[CR]\-\-auto\f[R] with that file .IP \[bu] 2 or avoid balance assertions on accounts affected by auto postings (or avoid auto postings entirely). .SS Assertions and precision Balance assertions compare the exactly calculated amounts, which are not always what is shown by reports. Eg a commodity directive may limit the display precision, but this will not affect balance assertions. Balance assertion failure messages show exact amounts. .SS Posting comments Text following \f[CR];\f[R], at the end of a posting line, and/or on indented lines immediately below it, form comments for that posting. They are reproduced by \f[CR]print\f[R] but otherwise ignored, except they may contain tags, which are not ignored. .IP .EX 2012\-01\-01 expenses 1 ; a comment for posting 1 assets ; a comment for posting 2 ; a second comment line for posting 2 .EE .SS Tags Tags are a way to add extra labels or labelled data to transactions, postings, or accounts, which you can then search or pivot on. .PP They are written as a word (optionally hyphenated) immediately followed by a full colon, in a transaction or posting or account directive\[aq]s comment. (This is an exception to the usual rule that things in comments are ignored.) Eg, here four different tags are recorded: one on the checking account, two on the transaction, and one on the expenses posting: .IP .EX account assets:checking ; accounttag: 2017/1/16 bought groceries ; transactiontag\-1: ; transactiontag\-2: assets:checking $\-1 expenses:food $1 ; postingtag: .EE .PP Postings also inherit tags from their transaction and their account. And transactions also acquire tags from their postings (and postings\[aq] accounts). So in the example above, the expenses posting effectively has all four tags (by inheriting from account and transaction), and the transaction also has all four tags (by acquiring from the expenses posting). .PP You can list tag names with \f[CR]hledger tags [NAMEREGEX]\f[R], or match by tag name with a \f[CR]tag:NAMEREGEX\f[R] query. .SS Tag values Tags can have a value, which is any text after the colon up until a comma or end of line (with surrounding whitespace removed). Note this means that hledger tag values can not contain commas. Eg in the following posting, the three tags\[aq] values are \[dq]value 1\[dq], \[dq]value 2\[dq], and \[dq]\[dq] (empty) respectively: .IP .EX expenses:food $10 ; foo, tag1: value 1 , tag2:value 2, bar tag3: , baz .EE .PP Note that tags can be repeated, and are additive rather than overriding: when the same tag name is seen again with a new value, the new name:value pair is added to the tags. (It is not possible to override a tag\[aq]s value or remove a tag.) .PP You can list a tag\[aq]s values with \f[CR]hledger tags TAGNAME \-\-values\f[R], or match by tag value with a \f[CR]tag:NAMEREGEX=VALUEREGEX\f[R] query. .SS Directives Besides transactions, there is something else you can put in a \f[CR]journal\f[R] file: directives. These are declarations, beginning with a keyword, that modify hledger\[aq]s behaviour. Some directives can have more specific subdirectives, indented below them. hledger\[aq]s directives are similar to Ledger\[aq]s in many cases, but there are also many differences. Directives are not required, but can be useful. Here are the main directives: .PP .TS tab(@); lw(39.7n) lw(30.3n). T{ purpose T}@T{ directive T} _ T{ \f[B]READING DATA:\f[R] T}@T{ T} T{ Rewrite account names T}@T{ \f[CR]alias\f[R] T} T{ Comment out sections of the file T}@T{ \f[CR]comment\f[R] T} T{ Declare file\[aq]s decimal mark, to help parse amounts accurately T}@T{ \f[CR]decimal\-mark\f[R] T} T{ Include other data files T}@T{ \f[CR]include\f[R] T} T{ \f[B]GENERATING DATA:\f[R] T}@T{ T} T{ Generate recurring transactions or budget goals T}@T{ \f[CR]\[ti]\f[R] T} T{ Generate extra postings on existing transactions T}@T{ \f[CR]=\f[R] T} T{ \f[B]CHECKING FOR ERRORS:\f[R] T}@T{ T} T{ Define valid entities to provide more error checking T}@T{ \f[CR]account\f[R], \f[CR]commodity\f[R], \f[CR]payee\f[R], \f[CR]tag\f[R] T} T{ \f[B]REPORTING:\f[R] T}@T{ T} T{ Declare accounts\[aq] type and display order T}@T{ \f[CR]account\f[R] T} T{ Declare commodity display styles T}@T{ \f[CR]commodity\f[R] T} T{ Declare market prices T}@T{ \f[CR]P\f[R] T} .TE .SS Directives and multiple files Directives vary in their scope, ie which journal entries and which input files they affect. Most often, a directive will affect the following entries and included files if any, until the end of the current file \- and no further. You might find this inconvenient! For example, \f[CR]alias\f[R] directives do not affect parent or sibling files. But there are usually workarounds; for example, put \f[CR]alias\f[R] directives in your top\-most file, before including other files. .PP The restriction, though it may be annoying at first, is in a good cause; it allows reports to be stable and deterministic, independent of the order of input. Without it, reports could show different numbers depending on the order of \-f options, or the positions of include directives in your files. .SS Directive effects Here are all hledger\[aq]s directives, with their effects and scope summarised \- nine main directives, plus four others which we consider non\-essential: .PP .TS tab(@); lw(3.5n) lw(64.1n) lw(2.4n). T{ directive T}@T{ what it does T}@T{ ends at file end? T} _ T{ \f[B]\f[CB]account\f[B]\f[R] T}@T{ Declares an account, for checking all entries in all files; and its display order and type. Subdirectives: any text, ignored. T}@T{ N T} T{ \f[B]\f[CB]alias\f[B]\f[R] T}@T{ Rewrites account names, in following entries until end of current file or \f[CR]end aliases\f[R]. Command line equivalent: \f[CR]\-\-alias\f[R] T}@T{ Y T} T{ \f[B]\f[CB]comment\f[B]\f[R] T}@T{ Ignores part of the journal file, until end of current file or \f[CR]end comment\f[R]. T}@T{ Y T} T{ \f[B]\f[CB]commodity\f[B]\f[R] T}@T{ Declares up to four things: 1. a commodity symbol, for checking all amounts in all files 2. the decimal mark for parsing amounts of this commodity, in the following entries until end of current file (if there is no \f[CR]decimal\-mark\f[R] directive) 3. and the display style for amounts of this commodity 4. which is also the precision to use for balanced\-transaction checking in this commodity. Takes precedence over \f[CR]D\f[R]. Subdirectives: \f[CR]format\f[R] (Ledger\-compatible syntax). Command line equivalent: \f[CR]\-c/\-\-commodity\-style\f[R] T}@T{ N,Y,N,N T} T{ \f[B]\f[CB]decimal\-mark\f[B]\f[R] T}@T{ Declares the decimal mark, for parsing amounts of all commodities in following entries until next \f[CR]decimal\-mark\f[R] or end of current file. Included files can override. Takes precedence over \f[CR]commodity\f[R] and \f[CR]D\f[R]. T}@T{ Y T} T{ \f[B]\f[CB]include\f[B]\f[R] T}@T{ Includes entries and directives from another file, as if they were written inline. Command line alternative: multiple \f[CR]\-f/\-\-file\f[R] T}@T{ N T} T{ \f[B]\f[CB]payee\f[B]\f[R] T}@T{ Declares a payee name, for checking all entries in all files. T}@T{ N T} T{ \f[B]\f[CB]P\f[B]\f[R] T}@T{ Declares the market price of a commodity on some date, for value reports. T}@T{ N T} T{ \f[B]\f[CB]\[ti]\f[B]\f[R] (tilde) T}@T{ Declares a periodic transaction rule that generates future transactions with \f[CR]\-\-forecast\f[R] and budget goals with \f[CR]balance \-\-budget\f[R]. T}@T{ N T} T{ Other syntax: T}@T{ T}@T{ T} T{ \f[B]\f[CB]apply account\f[B]\f[R] T}@T{ Prepends a common parent account to all account names, in following entries until end of current file or \f[CR]end apply account\f[R]. T}@T{ Y T} T{ \f[B]\f[CB]D\f[B]\f[R] T}@T{ Sets a default commodity to use for no\-symbol amounts;and, if there is no \f[CR]commodity\f[R] directive for this commodity: its decimal mark, balancing precision, and display style, as above. T}@T{ Y,Y,N,N T} T{ \f[B]\f[CB]Y\f[B]\f[R] T}@T{ Sets a default year to use for any yearless dates, in following entries until end of current file. T}@T{ Y T} T{ \f[B]\f[CB]=\f[B]\f[R] (equals) T}@T{ Declares an auto posting rule that generates extra postings on matched transactions with \f[CR]\-\-auto\f[R], in current, parent, and child files (but not sibling files, see #1212). T}@T{ partly T} T{ \f[B]Other Ledger directives\f[R] T}@T{ Other directives from Ledger\[aq]s file format are accepted but ignored. T}@T{ T} .TE .SS \f[CR]account\f[R] directive \f[CR]account\f[R] directives can be used to declare accounts (ie, the places that amounts are transferred from and to). Though not required, these declarations can provide several benefits: .IP \[bu] 2 They can document your intended chart of accounts, providing a reference. .IP \[bu] 2 In strict mode, they restrict which accounts may be posted to by transactions, which helps detect typos. .IP \[bu] 2 They control account display order in reports, allowing non\-alphabetic sorting (eg Revenues to appear above Expenses). .IP \[bu] 2 They help with account name completion (in hledger add, hledger\-web, hledger\-iadd, ledger\-mode, etc.) .IP \[bu] 2 They can store additional account information as comments, or as tags which can be used to filter or pivot reports. .IP \[bu] 2 They can help hledger know your accounts\[aq] types (asset, liability, equity, revenue, expense), affecting reports like balancesheet and incomestatement. .PP They are written as the word \f[CR]account\f[R] followed by a hledger\-style account name, eg: .IP .EX account assets:bank:checking .EE .PP Note, however, that accounts declared in account directives are not allowed to have surrounding brackets and parentheses, unlike accounts used in postings. So the following journal will not parse: .IP .EX account (assets:bank:checking) .EE .SS Account comments Text following \f[B]two or more spaces\f[R] and \f[CR];\f[R] at the end of an account directive line, and/or following \f[CR];\f[R] on indented lines immediately below it, form comments for that account. They are ignored except they may contain tags, which are not ignored. .PP The two\-space requirement for same\-line account comments is because \f[CR];\f[R] is allowed in account names. .IP .EX account assets:bank:checking ; same\-line comment, at least 2 spaces before the semicolon ; next\-line comment ; some tags \- type:A, acctnum:12345 .EE .SS Account subdirectives Ledger\-style indented subdirectives are also accepted, but currently ignored: .IP .EX account assets:bank:checking format subdirective is ignored .EE .SS Account error checking By default, accounts need not be declared; they come into existence when a posting references them. This is convenient, but it means hledger can\[aq]t warn you when you mis\-spell an account name in the journal. Usually you\[aq]ll find that error later, as an extra account in balance reports, or an incorrect balance when reconciling. .PP In strict mode, enabled with the \f[CR]\-s\f[R]/\f[CR]\-\-strict\f[R] flag, hledger will report an error if any transaction uses an account name that has not been declared by an account directive. Some notes: .IP \[bu] 2 The declaration is case\-sensitive; transactions must use the correct account name capitalisation. .IP \[bu] 2 The account directive\[aq]s scope is \[dq]whole file and below\[dq] (see directives). This means it affects all of the current file, and any files it includes, but not parent or sibling files. The position of account directives within the file does not matter, though it\[aq]s usual to put them at the top. .IP \[bu] 2 Accounts can only be declared in \f[CR]journal\f[R] files, but will affect included files of all types. .IP \[bu] 2 It\[aq]s currently not possible to declare \[dq]all possible subaccounts\[dq] with a wildcard; every account posted to must be declared. .SS Account display order The order in which account directives are written influences the order in which accounts appear in reports, hledger\-ui, hledger\-web etc. By default accounts appear in alphabetical order, but if you add these account directives to the journal file: .IP .EX account assets account liabilities account equity account revenues account expenses .EE .PP those accounts will be displayed in declaration order: .IP .EX $ hledger accounts \-1 assets liabilities equity revenues expenses .EE .PP Any undeclared accounts are displayed last, in alphabetical order. .PP Sorting is done at each level of the account tree, within each group of sibling accounts under the same parent. And currently, this directive: .IP .EX account other:zoo .EE .PP would influence the position of \f[CR]zoo\f[R] among \f[CR]other\f[R]\[aq]s subaccounts, but not the position of \f[CR]other\f[R] among the top\-level accounts. This means: .IP \[bu] 2 you will sometimes declare parent accounts (eg \f[CR]account other\f[R] above) that you don\[aq]t intend to post to, just to customize their display order .IP \[bu] 2 sibling accounts stay together (you couldn\[aq]t display \f[CR]x:y\f[R] in between \f[CR]a:b\f[R] and \f[CR]a:c\f[R]). .SS Account types hledger knows that accounts come in several types: assets, liabilities, expenses and so on. This enables easy reports like balancesheet and incomestatement, and filtering by account type with the \f[CR]type:\f[R] query. .PP As a convenience, hledger will detect these account types automatically if you are using common english\-language top\-level account names (described below). But generally we recommend you declare types explicitly, by adding a \f[CR]type:\f[R] tag to your top\-level account directives. Subaccounts will inherit the type of their parent. The tag\[aq]s value should be one of the five main account types: .IP \[bu] 2 \f[CR]A\f[R] or \f[CR]Asset\f[R] (things you own) .IP \[bu] 2 \f[CR]L\f[R] or \f[CR]Liability\f[R] (things you owe) .IP \[bu] 2 \f[CR]E\f[R] or \f[CR]Equity\f[R] (investment/ownership; balanced counterpart of assets & liabilities) .IP \[bu] 2 \f[CR]R\f[R] or \f[CR]Revenue\f[R] (what you received money from, AKA income; technically part of Equity) .IP \[bu] 2 \f[CR]X\f[R] or \f[CR]Expense\f[R] (what you spend money on; technically part of Equity) .PP or, it can be (these are used less often): .IP \[bu] 2 \f[CR]C\f[R] or \f[CR]Cash\f[R] (a subtype of Asset, indicating liquid assets for the cashflow report) .IP \[bu] 2 \f[CR]V\f[R] or \f[CR]Conversion\f[R] (a subtype of Equity, for conversions (see Cost reporting).) .PP Here is a typical set of account type declarations: .IP .EX account assets ; type: A account liabilities ; type: L account equity ; type: E account revenues ; type: R account expenses ; type: X account assets:bank ; type: C account assets:cash ; type: C account equity:conversion ; type: V .EE .PP Here are some tips for working with account types. .IP \[bu] 2 The rules for inferring types from account names are as follows. These are just a convenience that sometimes help new users get going; if they don\[aq]t work for you, just ignore them and declare your account types. See also Regular expressions. .RS 2 .IP .EX If account\[aq]s name contains this (CI) regular expression: | its type is: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-|\-\-\-\-\-\-\-\-\-\-\-\-\- \[ha]assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|current)(:|$) | Cash \[ha]assets?(:|$) | Asset \[ha](debts?|liabilit(y|ies))(:|$) | Liability \[ha]equity:(trad(e|ing)|conversion)s?(:|$) | Conversion \[ha]equity(:|$) | Equity \[ha](income|revenue)s?(:|$) | Revenue \[ha]expenses?(:|$) | Expense .EE .RE .IP \[bu] 2 If you declare any account types, it\[aq]s a good idea to declare an account for all of the account types, because a mixture of declared and name\-inferred types can disrupt certain reports. .IP \[bu] 2 Certain uses of account aliases can disrupt account types. See Rewriting accounts > Aliases and account types. .IP \[bu] 2 As mentioned above, subaccounts will inherit a type from their parent account. More precisely, an account\[aq]s type is decided by the first of these that exists: .RS 2 .IP "1." 3 A \f[CR]type:\f[R] declaration for this account. .IP "2." 3 A \f[CR]type:\f[R] declaration in the parent accounts above it, preferring the nearest. .IP "3." 3 An account type inferred from this account\[aq]s name. .IP "4." 3 An account type inferred from a parent account\[aq]s name, preferring the nearest parent. .IP "5." 3 Otherwise, it will have no type. .RE .IP \[bu] 2 For troubleshooting, you can list accounts and their types with: .RS 2 .IP .EX $ hledger accounts \-\-types [ACCTPAT] [\-DEPTH] [type:TYPECODES] .EE .RE .SS \f[CR]alias\f[R] directive You can define account alias rules which rewrite your account names, or parts of them, before generating reports. This can be useful for: .IP \[bu] 2 expanding shorthand account names to their full form, allowing easier data entry and a less verbose journal .IP \[bu] 2 adapting old journals to your current chart of accounts .IP \[bu] 2 experimenting with new account organisations, like a new hierarchy .IP \[bu] 2 combining two accounts into one, eg to see their sum or difference on one line .IP \[bu] 2 customising reports .PP Account aliases also rewrite account names in account directives. They do not affect account names being entered via hledger add or hledger\-web. .PP Account aliases are very powerful. They are generally easy to use correctly, but you can also generate invalid account names with them; more on this below. .PP See also Rewrite account names. .SS Basic aliases To set an account alias, use the \f[CR]alias\f[R] directive in your journal file. This affects all subsequent journal entries in the current file or its included files (but note: not sibling or parent files). The spaces around the = are optional: .IP .EX alias OLD = NEW .EE .PP Or, you can use the \f[CR]\-\-alias \[aq]OLD=NEW\[aq]\f[R] option on the command line. This affects all entries. It\[aq]s useful for trying out aliases interactively. .PP OLD and NEW are case sensitive full account names. hledger will replace any occurrence of the old account name with the new one. Subaccounts are also affected. Eg: .IP .EX alias checking = assets:bank:wells fargo:checking ; rewrites \[dq]checking\[dq] to \[dq]assets:bank:wells fargo:checking\[dq], or \[dq]checking:a\[dq] to \[dq]assets:bank:wells fargo:checking:a\[dq] .EE .SS Regex aliases There is also a more powerful variant that uses a regular expression, indicated by wrapping the pattern in forward slashes. (This is the only place where hledger requires forward slashes around a regular expression.) .PP Eg: .IP .EX alias /REGEX/ = REPLACEMENT .EE .PP or: .IP .EX $ hledger \-\-alias \[aq]/REGEX/=REPLACEMENT\[aq] ... .EE .PP Any part of an account name matched by REGEX will be replaced by REPLACEMENT. REGEX is case\-insensitive as usual. .PP If you need to match a forward slash, escape it with a backslash, eg \f[CR]/\[rs]/=:\f[R]. .PP If REGEX contains parenthesised match groups, these can be referenced by the usual backslash and number in REPLACEMENT: .IP .EX alias /\[ha](.+):bank:([\[ha]:]+):(.*)/ = \[rs]1:\[rs]2 \[rs]3 ; rewrites \[dq]assets:bank:wells fargo:checking\[dq] to \[dq]assets:wells fargo checking\[dq] .EE .PP REPLACEMENT continues to the end of line (or on command line, to end of option argument), so it can contain trailing whitespace. .SS Combining aliases You can define as many aliases as you like, using journal directives and/or command line options. .PP Recursive aliases \- where an account name is rewritten by one alias, then by another alias, and so on \- are allowed. Each alias sees the effect of previously applied aliases. .PP In such cases it can be important to understand which aliases will be applied and in which order. For (each account name in) each journal entry, we apply: .IP "1." 3 \f[CR]alias\f[R] directives preceding the journal entry, most recently parsed first (ie, reading upward from the journal entry, bottom to top) .IP "2." 3 \f[CR]\-\-alias\f[R] options, in the order they appeared on the command line (left to right). .PP In other words, for (an account name in) a given journal entry: .IP \[bu] 2 the nearest alias declaration before/above the entry is applied first .IP \[bu] 2 the next alias before/above that will be be applied next, and so on .IP \[bu] 2 aliases defined after/below the entry do not affect it. .PP This gives nearby aliases precedence over distant ones, and helps provide semantic stability \- aliases will keep working the same way independent of which files are being read and in which order. .PP In case of trouble, adding \f[CR]\-\-debug=6\f[R] to the command line will show which aliases are being applied when. .SS Aliases and multiple files As explained at Directives and multiple files, \f[CR]alias\f[R] directives do not affect parent or sibling files. Eg in this command, .IP .EX hledger \-f a.aliases \-f b.journal .EE .PP account aliases defined in a.aliases will not affect b.journal. Including the aliases doesn\[aq]t work either: .IP .EX include a.aliases 2023\-01\-01 ; not affected by a.aliases foo 1 bar .EE .PP This means that account aliases should usually be declared at the start of your top\-most file, like this: .IP .EX alias foo=Foo alias bar=Bar 2023\-01\-01 ; affected by aliases above foo 1 bar include c.journal ; also affected .EE .SS \f[CR]end aliases\f[R] directive You can clear (forget) all currently defined aliases (seen in the journal so far, or defined on the command line) with this directive: .IP .EX end aliases .EE .SS Aliases can generate bad account names Be aware that account aliases can produce malformed account names, which could cause confusing reports or invalid \f[CR]print\f[R] output. For example, you could erase all account names: .IP .EX 2021\-01\-01 a:aa 1 b .EE .IP .EX $ hledger print \-\-alias \[aq]/.*/=\[aq] 2021\-01\-01 1 .EE .PP The above \f[CR]print\f[R] output is not a valid journal. Or you could insert an illegal double space, causing \f[CR]print\f[R] output that would give a different journal when reparsed: .IP .EX 2021\-01\-01 old 1 other .EE .IP .EX $ hledger print \-\-alias old=\[dq]new USD\[dq] | hledger \-f\- print 2021\-01\-01 new USD 1 other .EE .SS Aliases and account types If an account with a type declaration (see Declaring accounts > Account types) is renamed by an alias, normally the account type remains in effect. .PP However, renaming in a way that reshapes the account tree (eg renaming parent accounts but not their children, or vice versa) could prevent child accounts from inheriting the account type of their parents. .PP Secondly, if an account\[aq]s type is being inferred from its name, renaming it by an alias could prevent or alter that. .PP If you are using account aliases and the \f[CR]type:\f[R] query is not matching accounts as you expect, try troubleshooting with the accounts command, eg something like: .IP .EX $ hledger accounts \-\-alias assets=bassetts type:a .EE .SS \f[CR]commodity\f[R] directive The \f[CR]commodity\f[R] directive performs several functions: .IP "1." 3 It declares which commodity symbols may be used in the journal, enabling useful error checking with strict mode or the check command. (See Commodity error checking below.) .IP "2." 3 It declares the precision with which this commodity\[aq]s amounts should be compared when checking for balanced transactions. .IP "3." 3 It declares how this commodity\[aq]s amounts should be displayed, eg their symbol placement, digit group mark if any, digit group sizes, decimal mark (period or comma), and the number of decimal places. (See Commodity display style above.) .IP "4." 3 It sets which decimal mark (period or comma) to expect when parsing subsequent amounts in this commodity (if there is no \f[CR]decimal\-mark\f[R] directive in effect. See Decimal marks, digit group marks above. For related dev discussion, see #793.) .PP Declaring commodities solves several common parsing/display problems, so we recommend it. Generally you should put \f[CR]commodity\f[R] directives at the top of your journal file (because function 4 is position\-sensitive). .SS Commodity directive syntax A commodity directive is normally the word \f[CR]commodity\f[R] followed by a sample amount (and optionally a comment). Only the amount\[aq]s symbol and format is significant. Eg: .IP .EX commodity $1000.00 commodity 1.000,00 EUR commodity 1 000 000.0000 ; the no\-symbol commodity .EE .PP Commodities do not have tags (tags in the comment will be ignored). .PP A commodity directive\[aq]s sample amount must always include a period or comma decimal mark (this rule helps disambiguate decimal marks and digit group marks). If you don\[aq]t want to show any decimal digits, write the decimal mark at the end: .IP .EX commodity 1000. AAAA ; show AAAA with no decimals .EE .PP Commodity symbols containing spaces, numbers, or punctuation must be enclosed in double quotes, as usual: .IP .EX commodity 1.0000 \[dq]AAAA 2023\[dq] .EE .PP Commodity directives normally include a sample amount, but can declare only a symbol (ie, just function 1 above): .IP .EX commodity $ commodity INR commodity \[dq]AAAA 2023\[dq] commodity \[dq]\[dq] ; the no\-symbol commodity .EE .PP Commodity directives may also be written with an indented \f[CR]format\f[R] subdirective, as in Ledger. The symbol is repeated and must be the same in both places. Other subdirectives are currently ignored: .IP .EX ; display indian rupees with currency name on the left, ; thousands, lakhs and crores comma\-separated, ; period as decimal point, and two decimal places. commodity INR format INR 1,00,00,000.00 an unsupported subdirective ; ignored by hledger .EE .SS Commodity error checking In strict mode (\f[CR]\-s\f[R]/\f[CR]\-\-strict\f[R]) (or when you run \f[CR]hledger check commodities\f[R]), hledger will report an error if an undeclared commodity symbol is used. (With one exception: zero amounts are always allowed to have no commodity symbol.) It works like account error checking (described above). .SS \f[CR]decimal\-mark\f[R] directive You can use a \f[CR]decimal\-mark\f[R] directive \- usually one per file, at the top of the file \- to declare which character represents a decimal mark when parsing amounts in this file. It can look like .IP .EX decimal\-mark . .EE .PP or .IP .EX decimal\-mark , .EE .PP This prevents any ambiguity when parsing numbers in the file, so we recommend it, especially if the file contains digit group marks (eg thousands separators). .SS \f[CR]include\f[R] directive You can pull in the content of additional files by writing an include directive, like this: .IP .EX include FILEPATH .EE .PP Only journal files can include, and only journal, timeclock or timedot files can be included (not CSV files, currently). .PP If the file path does not begin with a slash, it is relative to the current file\[aq]s folder. .PP A tilde means home directory, eg: \f[CR]include \[ti]/main.journal\f[R]. .PP The path may contain glob patterns to match multiple files, eg: \f[CR]include *.journal\f[R]. .PP There is limited support for recursive wildcards: \f[CR]**/\f[R] (the slash is required) matches 0 or more subdirectories. It\[aq]s not super convenient since you have to avoid include cycles and including directories, but this can be done, eg: \f[CR]include */**/*.journal\f[R]. .PP The path may also be prefixed to force a specific file format, overriding the file extension (as described in Data formats): \f[CR]include timedot:\[ti]/notes/2023*.md\f[R]. .SS \f[CR]P\f[R] directive The \f[CR]P\f[R] directive declares a market price, which is a conversion rate between two commodities on a certain date. This allows value reports to convert amounts of one commodity to their value in another, on or after that date. These prices are often obtained from a stock exchange, cryptocurrency exchange, the or foreign exchange market. .PP The format is: .IP .EX P DATE COMMODITY1SYMBOL COMMODITY2AMOUNT .EE .PP DATE is a simple date, COMMODITY1SYMBOL is the symbol of the commodity being priced, and COMMODITY2AMOUNT is the amount (symbol and quantity) of commodity 2 that one unit of commodity 1 is worth on this date. Examples: .IP .EX # one euro was worth $1.35 from 2009\-01\-01 onward: P 2009\-01\-01 € $1.35 # and $1.40 from 2010\-01\-01 onward: P 2010\-01\-01 € $1.40 .EE .PP The \f[CR]\-V\f[R], \f[CR]\-X\f[R] and \f[CR]\-\-value\f[R] flags use these market prices to show amount values in another commodity. See Value reporting. .PP .SS \f[CR]payee\f[R] directive \f[CR]payee PAYEE NAME\f[R] .PP This directive can be used to declare a limited set of payees which may appear in transaction descriptions. The \[dq]payees\[dq] check will report an error if any transaction refers to a payee that has not been declared. Eg: .IP .EX payee Whole Foods ; a comment .EE .PP Payees do not have tags (tags in the comment will be ignored). .PP To declare the empty payee name, use \f[CR]\[dq]\[dq]\f[R]. .IP .EX payee \[dq]\[dq] .EE .PP Ledger\-style indented subdirectives, if any, are currently ignored. .SS \f[CR]tag\f[R] directive \f[CR]tag TAGNAME\f[R] .PP This directive can be used to declare a limited set of tag names allowed in tags. TAGNAME should be a valid tag name (no spaces). Eg: .IP .EX tag item\-id .EE .PP Any indented subdirectives are currently ignored. .PP The \[dq]tags\[dq] check will report an error if any undeclared tag name is used. It is quite easy to accidentally create a tag through normal use of colons in comments(#comments]; if you want to prevent this, you can declare and check your tags . .SS Periodic transactions The \f[CR]\[ti]\f[R] directive declares a \[dq]periodic rule\[dq] which generates temporary extra transactions, usually recurring at some interval, when hledger is run with the \f[CR]\-\-forecast\f[R] flag. These \[dq]forecast transactions\[dq] are useful for forecasting future activity. They exist only for the duration of the report, and only when \f[CR]\-\-forecast\f[R] is used; they are not saved in the journal file by hledger. .PP Periodic rules also have a second use: with the \f[CR]\-\-budget\f[R] flag they set budget goals for budgeting. .PP Periodic rules can be a little tricky, so before you use them, read this whole section, or at least the following tips: .IP "1." 3 Two spaces accidentally added or omitted will cause you trouble \- read about this below. .IP "2." 3 For troubleshooting, show the generated transactions with \f[CR]hledger print \-\-forecast tag:generated\f[R] or \f[CR]hledger register \-\-forecast tag:generated\f[R]. .IP "3." 3 Forecasted transactions will begin only after the last non\-forecasted transaction\[aq]s date. .IP "4." 3 Forecasted transactions will end 6 months from today, by default. See below for the exact start/end rules. .IP "5." 3 period expressions can be tricky. Their documentation needs improvement, but is worth studying. .IP "6." 3 Some period expressions with a repeating interval must begin on a natural boundary of that interval. Eg in \f[CR]weekly from DATE\f[R], DATE must be a monday. \f[CR]\[ti] weekly from 2019/10/1\f[R] (a tuesday) will give an error. .IP "7." 3 Other period expressions with an interval are automatically expanded to cover a whole number of that interval. (This is done to improve reports, but it also affects periodic transactions. Yes, it\[aq]s a bit inconsistent with the above.) Eg: \f[CR]\[ti] every 10th day of month from 2023/01\f[R], which is equivalent to \f[CR]\[ti] every 10th day of month from 2023/01/01\f[R], will be adjusted to start on 2019/12/10. .SS Periodic rule syntax A periodic transaction rule looks like a normal journal entry, with the date replaced by a tilde (\f[CR]\[ti]\f[R]) followed by a period expression (mnemonic: \f[CR]\[ti]\f[R] looks like a recurring sine wave.): .IP .EX # every first of month \[ti] monthly expenses:rent $2000 assets:bank:checking # every 15th of month in 2023\[aq]s first quarter: \[ti] monthly from 2023\-04\-15 to 2023\-06\-16 expenses:utilities $400 assets:bank:checking .EE .PP The period expression is the same syntax used for specifying multi\-period reports, just interpreted differently; there, it specifies report periods; here it specifies recurrence dates (the periods\[aq] start dates). .SS Periodic rules and relative dates Partial or relative dates (like \f[CR]12/31\f[R], \f[CR]25\f[R], \f[CR]tomorrow\f[R], \f[CR]last week\f[R], \f[CR]next quarter\f[R]) are usually not recommended in periodic rules, since the results will change as time passes. If used, they will be interpreted relative to, in order of preference: .IP "1." 3 the first day of the default year specified by a recent \f[CR]Y\f[R] directive .IP "2." 3 or the date specified with \f[CR]\-\-today\f[R] .IP "3." 3 or the date on which you are running the report. .PP They will not be affected at all by report period or forecast period dates. .SS Two spaces between period expression and description! If the period expression is followed by a transaction description, these must be separated by \f[B]two or more spaces\f[R]. This helps hledger know where the period expression ends, so that descriptions can not accidentally alter their meaning, as in this example: .IP .EX ; 2 or more spaces needed here, so the period is not understood as \[dq]every 2 months in 2023\[dq] ; || ; vv \[ti] every 2 months in 2023, we will review assets:bank:checking $1500 income:acme inc .EE .PP So, .IP \[bu] 2 Do write two spaces between your period expression and your transaction description, if any. .IP \[bu] 2 Don\[aq]t accidentally write two spaces in the middle of your period expression. .SS Auto postings The \f[CR]=\f[R] directive declares an \[dq]auto posting rule\[dq] which generates temporary extra postings on existing transactions, when hledger is run with the \f[CR]\-\-auto\f[R] flag. (Remember, postings are the account name & amount lines.) The rule contains a query and one or more posting templates. Wherever the query matches an existing posting, the new posting(s) will be generated and added below that one. Optionally the generated amount(s) can depend on the matched posting\[aq]s amount. .PP These auto postings can be useful for, eg, adding tax postings with a standard percentage. They exist only for the duration of the report, and only when \f[CR]\-\-auto\f[R] is used; they are not saved in the journal file by hledger. .PP Note that depending fully on generated data such as this has some drawbacks \- it\[aq]s less portable, less future\-proof, less auditable by others, and less robust (eg your balance assertions will depend on whether you use or don\[aq]t use \f[CR]\-\-auto\f[R]). An alternative is to use auto postings in \[dq]one time\[dq] fashion \- use them to help build a complex journal entry, view it with \f[CR]hledger print \-\-auto\f[R], and then copy that output into the journal file to make it permanent. .PP Here\[aq]s the journal file syntax. An auto posting rule looks a bit like a transaction: .IP .EX = QUERY ACCOUNT AMOUNT ... ACCOUNT [AMOUNT] .EE .PP except the first line is an equals sign (mnemonic: \f[CR]=\f[R] suggests matching), followed by a query (which matches existing postings), and each \[dq]posting\[dq] line describes a posting to be generated, and the posting amounts can be: .IP \[bu] 2 a normal amount with a commodity symbol, eg \f[CR]$2\f[R]. This will be used as\-is. .IP \[bu] 2 a number, eg \f[CR]2\f[R]. The commodity symbol (if any) from the matched posting will be added to this. .IP \[bu] 2 a numeric multiplier, eg \f[CR]*2\f[R] (a star followed by a number N). The matched posting\[aq]s amount (and total price, if any) will be multiplied by N. .IP \[bu] 2 a multiplier with a commodity symbol, eg \f[CR]*$2\f[R] (a star, number N, and symbol S). The matched posting\[aq]s amount will be multiplied by N, and its commodity symbol will be replaced with S. .PP Any query term containing spaces must be enclosed in single or double quotes, as on the command line. Eg, note the quotes around the second query term below: .IP .EX = expenses:groceries \[aq]expenses:dining out\[aq] (budget:funds:dining out) *\-1 .EE .PP Some examples: .IP .EX ; every time I buy food, schedule a dollar donation = expenses:food (liabilities:charity) $\-1 ; when I buy a gift, also deduct that amount from a budget envelope subaccount = expenses:gifts assets:checking:gifts *\-1 assets:checking *1 2017/12/1 expenses:food $10 assets:checking 2017/12/14 expenses:gifts $20 assets:checking .EE .IP .EX $ hledger print \-\-auto 2017\-12\-01 expenses:food $10 assets:checking (liabilities:charity) $\-1 2017\-12\-14 expenses:gifts $20 assets:checking assets:checking:gifts \-$20 assets:checking $20 .EE .SS Auto postings and multiple files An auto posting rule can affect any transaction in the current file, or in any parent file or child file. Note, currently it will not affect sibling files (when multiple \f[CR]\-f\f[R]/\f[CR]\-\-file\f[R] are used \- see #1212). .SS Auto postings and dates A posting date (or secondary date) in the matched posting, or (taking precedence) a posting date in the auto posting rule itself, will also be used in the generated posting. .SS Auto postings and transaction balancing / inferred amounts / balance assertions Currently, auto postings are added: .IP \[bu] 2 after missing amounts are inferred, and transactions are checked for balancedness, .IP \[bu] 2 but before balance assertions are checked. .PP Note this means that journal entries must be balanced both before and after auto postings are added. This changed in hledger 1.12+; see #893 for background. .PP This also means that you cannot have more than one auto\-posting with a missing amount applied to a given transaction, as it will be unable to infer amounts. .SS Auto posting tags Automated postings will have some extra tags: .IP \[bu] 2 \f[CR]generated\-posting:= QUERY\f[R] \- shows this was generated by an auto posting rule, and the query .IP \[bu] 2 \f[CR]_generated\-posting:= QUERY\f[R] \- a hidden tag, which does not appear in hledger\[aq]s output. This can be used to match postings generated \[dq]just now\[dq], rather than generated in the past and saved to the journal. .PP Also, any transaction that has been changed by auto posting rules will have these tags added: .IP \[bu] 2 \f[CR]modified:\f[R] \- this transaction was modified .IP \[bu] 2 \f[CR]_modified:\f[R] \- a hidden tag not appearing in the comment; this transaction was modified \[dq]just now\[dq]. .SS Auto postings on forecast transactions only Tip: you can can make auto postings that will apply to forecast transactions but not recorded transactions, by adding \f[CR]tag:_generated\-transaction\f[R] to their QUERY. This can be useful when generating new journal entries to be saved in the journal. .SS Other syntax hledger journal format supports quite a few other features, mainly to make interoperating with or converting from Ledger easier. Note some of the features below are powerful and can be useful in special cases, but in general, features in this section are considered less important or even not recommended for most users. Downsides are mentioned to help you decide if you want to use them. .SS Balance assignments Ledger\-style balance assignments are also supported. These are like balance assertions, but with no posting amount on the left side of the equals sign; instead it is calculated automatically so as to satisfy the assertion. This can be a convenience during data entry, eg when setting opening balances: .IP .EX ; starting a new journal, set asset account balances 2016/1/1 opening balances assets:checking = $409.32 assets:savings = $735.24 assets:cash = $42 equity:opening balances .EE .PP or when adjusting a balance to reality: .IP .EX ; no cash left; update balance, record any untracked spending as a generic expense 2016/1/15 assets:cash = $0 expenses:misc .EE .PP The calculated amount depends on the account\[aq]s balance in the commodity at that point (which depends on the previously\-dated postings of the commodity to that account since the last balance assertion or assignment). .PP Downsides: using balance assignments makes your journal less explicit; to know the exact amount posted, you have to run hledger or do the calculations yourself, instead of just reading it. Also balance assignments\[aq] forcing of balances can hide errors. These things make your financial data less portable, less future\-proof, and less trustworthy in an audit. .SS Balance assignments and prices A cost in a balance assignment will cause the calculated amount to have that price attached: .IP .EX 2019/1/1 (a) = $1 \[at] €2 .EE .IP .EX $ hledger print \-\-explicit 2019\-01\-01 (a) $1 \[at] €2 = $1 \[at] €2 .EE .SS Balance assignments and multiple files Balance assignments handle multiple files like balance assertions. They see balance from other files previously included from the current file, but not from previous sibling or parent files. .SS Bracketed posting dates For setting posting dates and secondary posting dates, Ledger\[aq]s bracketed date syntax is also supported: \f[CR][DATE]\f[R], \f[CR][DATE=DATE2]\f[R] or \f[CR][=DATE2]\f[R] in posting comments. hledger will attempt to parse any square\-bracketed sequence of the \f[CR]0123456789/\-.=\f[R] characters in this way. With this syntax, DATE infers its year from the transaction and DATE2 infers its year from DATE. .PP Downsides: another syntax to learn, redundant with hledger\[aq]s \f[CR]date:\f[R]/\f[CR]date2:\f[R] tags, and confusingly similar to Ledger\[aq]s lot date syntax. .SS \f[CR]D\f[R] directive \f[CR]D AMOUNT\f[R] .PP This directive sets a default commodity, to be used for any subsequent commodityless amounts (ie, plain numbers) seen while parsing the journal. This effect lasts until the next \f[CR]D\f[R] directive, or the end of the journal. .PP For compatibility/historical reasons, \f[CR]D\f[R] also acts like a \f[CR]commodity\f[R] directive (setting the commodity\[aq]s decimal mark for parsing and display style for output). So its argument is not just a commodity symbol, but a full amount demonstrating the style. The amount must include a decimal mark (either period or comma). Eg: .IP .EX ; commodity\-less amounts should be treated as dollars ; (and displayed with the dollar sign on the left, thousands separators and two decimal places) D $1,000.00 1/1 a 5 ; <\- commodity\-less amount, parsed as $5 and displayed as $5.00 b .EE .PP Interactions with other directives: .PP For setting a commodity\[aq]s display style, a \f[CR]commodity\f[R] directive has highest priority, then a \f[CR]D\f[R] directive. .PP For detecting a commodity\[aq]s decimal mark during parsing, \f[CR]decimal\-mark\f[R] has highest priority, then \f[CR]commodity\f[R], then \f[CR]D\f[R]. .PP For checking commodity symbols with the check command, a \f[CR]commodity\f[R] directive is required (\f[CR]hledger check commodities\f[R] ignores \f[CR]D\f[R] directives). .PP Downsides: omitting commodity symbols makes your financial data less explicit, less portable, and less trustworthy in an audit. It is usually an unsustainable shortcut; sooner or later you will want to track multiple commodities. D is overloaded with functions redundant with \f[CR]commodity\f[R] and \f[CR]decimal\-mark\f[R]. And it works differently from Ledger\[aq]s \f[CR]D\f[R]. .SS \f[CR]apply account\f[R] directive This directive sets a default parent account, which will be prepended to all accounts in following entries, until an \f[CR]end apply account\f[R] directive or end of current file. Eg: .IP .EX apply account home 2010/1/1 food $10 cash end apply account .EE .PP is equivalent to: .IP .EX 2010/01/01 home:food $10 home:cash $\-10 .EE .PP \f[CR]account\f[R] directives are also affected, and so is any \f[CR]include\f[R]d content. .PP Account names entered via hledger add or hledger\-web are not affected. .PP Account aliases, if any, are applied after the parent account is prepended. .PP Downsides: this can make your financial data less explicit, less portable, and less trustworthy in an audit. .SS \f[CR]Y\f[R] directive \f[CR]Y YEAR\f[R] .PP or (deprecated backward\-compatible forms): .PP \f[CR]year YEAR\f[R] \f[CR]apply year YEAR\f[R] .PP The space is optional. This sets a default year to be used for subsequent dates which don\[aq]t specify a year. Eg: .IP .EX Y2009 ; set default year to 2009 12/15 ; equivalent to 2009/12/15 expenses 1 assets year 2010 ; change default year to 2010 2009/1/30 ; specifies the year, not affected expenses 1 assets 1/31 ; equivalent to 2010/1/31 expenses 1 assets .EE .PP Downsides: omitting the year (from primary transaction dates, at least) makes your financial data less explicit, less portable, and less trustworthy in an audit. Such dates can get separated from their corresponding Y directive, eg when evaluating a region of the journal in your editor. A missing Y directive makes reports dependent on today\[aq]s date. .SS Secondary dates A secondary date is written after the primary date, following an equals sign. If the year is omitted, the primary date\[aq]s year is assumed. When running reports, the primary (left) date is used by default, but with the \f[CR]\-\-date2\f[R] flag (or \f[CR]\-\-aux\-date\f[R] or \f[CR]\-\-effective\f[R]), the secondary (right) date will be used instead. .PP The meaning of secondary dates is up to you, but it\[aq]s best to follow a consistent rule. Eg \[dq]primary = the bank\[aq]s clearing date, secondary = date the transaction was initiated, if different\[dq]. .PP Downsides: makes your financial data more complicated, less portable, and less trustworthy in an audit. Keeping the meaning of the two dates consistent requires discipline, and you have to remember which reporting mode is appropriate for a given report. Posting dates are simpler and better. .SS Star comments Lines beginning with \f[CR]*\f[R] (star/asterisk) are also comment lines. This feature allows Emacs users to insert org headings in their journal, allowing them to fold/unfold/navigate it like an outline when viewed with org mode. .PP Downsides: another, unconventional comment syntax to learn. Decreases your journal\[aq]s portability. And switching to Emacs org mode just for folding/unfolding meant losing the benefits of ledger mode; nowadays you can add outshine mode to ledger mode to get folding without losing ledger mode\[aq]s features. .SS Valuation expressions Ledger allows a valuation function or value to be written in double parentheses after an amount. hledger ignores these. .SS Virtual postings A posting with parentheses around the account name (\f[CR](some:account)\f[R]) is called a \f[I]unbalanced virtual posting\f[R]. Such postings do not participate in transaction balancing. (And if you write them without an amount, a zero amount is always inferred.) These can occasionally be convenient for special circumstances, but they violate double entry bookkeeping and make your data less portable across applications, so many people avoid using them at all. .PP A posting with brackets around the account name (\f[CR][some:account]\f[R]) is called a \f[I]balanced virtual posting\f[R]. The balanced virtual postings in a transaction must add up to zero, just like ordinary postings, but separately from them. These are not part of double entry bookkeeping either, but they are at least balanced. An example: .IP .EX 2022\-01\-01 buy food with cash, update budget envelope subaccounts, & something else assets:cash $\-10 ; <\- these balance each other expenses:food $7 ; <\- expenses:food $3 ; <\- [assets:checking:budget:food] $\-10 ; <\- and these balance each other [assets:checking:available] $10 ; <\- (something:else) $5 ; <\- this is not required to balance .EE .PP Ordinary postings, whose account names are neither parenthesised nor bracketed, are called \f[I]real postings\f[R]. You can exclude virtual postings from reports with the \f[CR]\-R/\-\-real\f[R] flag or a \f[CR]real:1\f[R] query. .SS Other Ledger directives These other Ledger directives are currently accepted but ignored. This allows hledger to read more Ledger files, but be aware that hledger\[aq]s reports may differ from Ledger\[aq]s if you use these. .IP .EX apply fixed COMM AMT apply tag TAG assert EXPR bucket / A ACCT capture ACCT REGEX check EXPR define VAR=EXPR end apply fixed end apply tag end apply year end tag eval / expr EXPR python PYTHONCODE tag NAME value EXPR \-\-command\-line\-flags .EE .PP See also https://hledger.org/ledger.html for a detailed hledger/Ledger syntax comparison. .PP .SH CSV hledger can read CSV files (Character Separated Value \- usually comma, semicolon, or tab) containing dated records, automatically converting each record into a transaction. .PP (To learn about \f[I]writing\f[R] CSV, see CSV output.) .PP For best error messages when reading CSV/TSV/SSV files, make sure they have a corresponding \f[CR].csv\f[R], \f[CR].tsv\f[R] or \f[CR].ssv\f[R] file extension or use a hledger file prefix (see File Extension below). .PP Each CSV file must be described by a corresponding \f[I]rules file\f[R]. .PD 0 .P .PD This contains rules describing the CSV data (header line, fields layout, date format etc.), how to construct hledger transactions from it, and how to categorise transactions based on description or other attributes. .PP By default hledger looks for a rules file named like the CSV file with an extra \f[CR].rules\f[R] extension, in the same directory. Eg when asked to read \f[CR]foo/FILE.csv\f[R], hledger looks for \f[CR]foo/FILE.csv.rules\f[R]. You can specify a different rules file with the \f[CR]\-\-rules\-file\f[R] option. If no rules file is found, hledger will create a sample rules file, which you\[aq]ll need to adjust. .PP At minimum, the rules file must identify the date and amount fields, and often it also specifies the date format and how many header lines there are. Here\[aq]s a simple CSV file and a rules file for it: .IP .EX Date, Description, Id, Amount 12/11/2019, Foo, 123, 10.23 .EE .IP .EX # basic.csv.rules skip 1 fields date, description, , amount date\-format %d/%m/%Y .EE .IP .EX $ hledger print \-f basic.csv 2019\-11\-12 Foo expenses:unknown 10.23 income:unknown \-10.23 .EE .PP There\[aq]s an introductory Importing CSV data tutorial on hledger.org, and more CSV rules examples below, and a larger collection at https://github.com/simonmichael/hledger/tree/master/examples/csv. .SS CSV rules cheatsheet The following kinds of rule can appear in the rules file, in any order. (Blank lines and lines beginning with \f[CR]#\f[R] or \f[CR];\f[R] or \f[CR]*\f[R] are ignored.) .PP .TS tab(@); lw(23.7n) lw(46.3n). T{ \f[B]\f[CB]source\f[B]\f[R] T}@T{ optionally declare which file to read data from T} T{ \f[B]\f[CB]separator\f[B]\f[R] T}@T{ declare the field separator, instead of relying on file extension T} T{ \f[B]\f[CB]skip\f[B]\f[R] T}@T{ skip one or more header lines at start of file T} T{ \f[B]\f[CB]date\-format\f[B]\f[R] T}@T{ declare how to parse CSV dates/date\-times T} T{ \f[B]\f[CB]timezone\f[B]\f[R] T}@T{ declare the time zone of ambiguous CSV date\-times T} T{ \f[B]\f[CB]newest\-first\f[B]\f[R] T}@T{ improve txn order when: there are multiple records, newest first, all with the same date T} T{ \f[B]\f[CB]intra\-day\-reversed\f[B]\f[R] T}@T{ improve txn order when: same\-day txns are in opposite order to the overall file T} T{ \f[B]\f[CB]decimal\-mark\f[B]\f[R] T}@T{ declare the decimal mark used in CSV amounts, when ambiguous T} T{ \f[B]\f[CB]fields\f[B] list\f[R] T}@T{ name CSV fields for easy reference, and optionally assign their values to hledger fields T} T{ \f[B]Field assignment\f[R] T}@T{ assign a CSV value or interpolated text value to a hledger field T} T{ \f[B]\f[CB]if\f[B] block\f[R] T}@T{ conditionally assign values to hledger fields, or \f[CR]skip\f[R] a record or \f[CR]end\f[R] (skip rest of file) T} T{ \f[B]\f[CB]if\f[B] table\f[R] T}@T{ conditionally assign values to hledger fields, using compact syntax T} T{ \f[B]\f[CB]balance\-type\f[B]\f[R] T}@T{ select which type of balance assertions/assignments to generate T} T{ \f[B]\f[CB]include\f[B]\f[R] T}@T{ inline another CSV rules file T} .TE .PP Working with CSV tips can be found below, including How CSV rules are evaluated. .SS \f[CR]source\f[R] If you tell hledger to read a csv file with \f[CR]\-f foo.csv\f[R], it will look for rules in \f[CR]foo.csv.rules\f[R]. Or, you can tell it to read the rules file, with \f[CR]\-f foo.csv.rules\f[R], and it will look for data in \f[CR]foo.csv\f[R] (since 1.30). .PP These are mostly equivalent, but the second method provides some extra features. For one, the data file can be missing, without causing an error; it is just considered empty. And, you can specify a different data file by adding a \[dq]source\[dq] rule: .IP .EX source ./Checking1.csv .EE .PP If you specify just a file name with no path, hledger will look for it in your system\[aq]s downloads directory (\f[CR]\[ti]/Downloads\f[R], currently): .IP .EX source Checking1.csv .EE .PP And if you specify a glob pattern, hledger will read the most recent of the matched files (useful with repeated downloads): .IP .EX source Checking1*.csv .EE .PP See also \[dq]Working with CSV > Reading files specified by rule\[dq]. .SS \f[CR]separator\f[R] You can use the \f[CR]separator\f[R] rule to read other kinds of character\-separated data. The argument is any single separator character, or the words \f[CR]tab\f[R] or \f[CR]space\f[R] (case insensitive). Eg, for comma\-separated values (CSV): .IP .EX separator , .EE .PP or for semicolon\-separated values (SSV): .IP .EX separator ; .EE .PP or for tab\-separated values (TSV): .IP .EX separator TAB .EE .PP If the input file has a \f[CR].csv\f[R], \f[CR].ssv\f[R] or \f[CR].tsv\f[R] file extension (or a \f[CR]csv:\f[R], \f[CR]ssv:\f[R], \f[CR]tsv:\f[R] prefix), the appropriate separator will be inferred automatically, and you won\[aq]t need this rule. .SS \f[CR]skip\f[R] .IP .EX skip N .EE .PP The word \f[CR]skip\f[R] followed by a number (or no number, meaning 1) tells hledger to ignore this many non\-empty lines at the start of the input data. You\[aq]ll need this whenever your CSV data contains header lines. Note, empty and blank lines are skipped automatically, so you don\[aq]t need to count those. .PP \f[CR]skip\f[R] has a second meaning: it can be used inside if blocks (described below), to skip one or more records whenever the condition is true. Records skipped in this way are ignored, except they are still required to be valid CSV. .SS \f[CR]date\-format\f[R] .IP .EX date\-format DATEFMT .EE .PP This is a helper for the \f[CR]date\f[R] (and \f[CR]date2\f[R]) fields. If your CSV dates are not formatted like \f[CR]YYYY\-MM\-DD\f[R], \f[CR]YYYY/MM/DD\f[R] or \f[CR]YYYY.MM.DD\f[R], you\[aq]ll need to add a date\-format rule describing them with a strptime\-style date parsing pattern \- see https://hackage.haskell.org/package/time/docs/Data\-Time\-Format.html#v:formatTime. The pattern must parse the CSV date value completely. Some examples: .IP .EX # MM/DD/YY date\-format %m/%d/%y .EE .IP .EX # D/M/YYYY # The \- makes leading zeros optional. date\-format %\-d/%\-m/%Y .EE .IP .EX # YYYY\-Mmm\-DD date\-format %Y\-%h\-%d .EE .IP .EX # M/D/YYYY HH:MM AM some other junk # Note the time and junk must be fully parsed, though only the date is used. date\-format %\-m/%\-d/%Y %l:%M %p some other junk .EE .SS \f[CR]timezone\f[R] .IP .EX timezone TIMEZONE .EE .PP When CSV contains date\-times that are implicitly in some time zone other than yours, but containing no explicit time zone information, you can use this rule to declare the CSV\[aq]s native time zone, which helps prevent off\-by\-one dates. .PP When the CSV date\-times do contain time zone information, you don\[aq]t need this rule; instead, use \f[CR]%Z\f[R] in \f[CR]date\-format\f[R] (or \f[CR]%z\f[R], \f[CR]%EZ\f[R], \f[CR]%Ez\f[R]; see the formatTime link above). .PP In either of these cases, hledger will do a time\-zone\-aware conversion, localising the CSV date\-times to your current system time zone. If you prefer to localise to some other time zone, eg for reproducibility, you can (on unix at least) set the output timezone with the TZ environment variable, eg: .IP .EX $ TZ=\-1000 hledger print \-f foo.csv # or TZ=\-1000 hledger import foo.csv .EE .PP \f[CR]timezone\f[R] currently does not understand timezone names, except \[dq]UTC\[dq], \[dq]GMT\[dq], \[dq]EST\[dq], \[dq]EDT\[dq], \[dq]CST\[dq], \[dq]CDT\[dq], \[dq]MST\[dq], \[dq]MDT\[dq], \[dq]PST\[dq], or \[dq]PDT\[dq]. For others, use numeric format: +HHMM or \-HHMM. .SS \f[CR]newest\-first\f[R] hledger tries to ensure that the generated transactions will be ordered chronologically, including same\-day transactions. Usually it can auto\-detect how the CSV records are ordered. But if it encounters CSV where all records are on the same date, it assumes that the records are oldest first. If in fact the CSV\[aq]s records are normally newest first, like: .IP .EX 2022\-10\-01, txn 3... 2022\-10\-01, txn 2... 2022\-10\-01, txn 1... .EE .PP you can add the \f[CR]newest\-first\f[R] rule to help hledger generate the transactions in correct order. .IP .EX # same\-day CSV records are newest first newest\-first .EE .SS \f[CR]intra\-day\-reversed\f[R] If CSV records within a single day are ordered opposite to the overall record order, you can add the \f[CR]intra\-day\-reversed\f[R] rule to improve the order of journal entries. Eg, here the overall record order is newest first, but same\-day records are oldest first: .IP .EX 2022\-10\-02, txn 3... 2022\-10\-02, txn 4... 2022\-10\-01, txn 1... 2022\-10\-01, txn 2... .EE .IP .EX # transactions within each day are reversed with respect to the overall date order intra\-day\-reversed .EE .SS \f[CR]decimal\-mark\f[R] .IP .EX decimal\-mark . .EE .PP or: .IP .EX decimal\-mark , .EE .PP hledger automatically accepts either period or comma as a decimal mark when parsing numbers (cf Amounts). However if any numbers in the CSV contain digit group marks, such as thousand\-separating commas, you should declare the decimal mark explicitly with this rule, to avoid misparsed numbers. .SS \f[CR]fields\f[R] list .IP .EX fields FIELDNAME1, FIELDNAME2, ... .EE .PP A fields list (the word \f[CR]fields\f[R] followed by comma\-separated field names) is optional, but convenient. It does two things: .IP "1." 3 It names the CSV field in each column. This can be convenient if you are referencing them in other rules, so you can say \f[CR]%SomeField\f[R] instead of remembering \f[CR]%13\f[R]. .IP "2." 3 Whenever you use one of the special hledger field names (described below), it assigns the CSV value in this position to that hledger field. This is the quickest way to populate hledger\[aq]s fields and build a transaction. .PP Here\[aq]s an example that says \[dq]use the 1st, 2nd and 4th fields as the transaction\[aq]s date, description and amount; name the last two fields for later reference; and ignore the others\[dq]: .IP .EX fields date, description, , amount, , , somefield, anotherfield .EE .PP In a fields list, the separator is always comma; it is unrelated to the CSV file\[aq]s separator. Also: .IP \[bu] 2 There must be least two items in the list (at least one comma). .IP \[bu] 2 Field names may not contain spaces. Spaces before/after field names are optional. .IP \[bu] 2 Field names may contain \f[CR]_\f[R] (underscore) or \f[CR]\-\f[R] (hyphen). .IP \[bu] 2 Fields you don\[aq]t care about can be given a dummy name or an empty name. .PP If the CSV contains column headings, it\[aq]s convenient to use these for your field names, suitably modified (eg lower\-cased with spaces replaced by underscores). .PP Sometimes you may want to alter a CSV field name to avoid assigning to a hledger field with the same name. Eg you could call the CSV\[aq]s \[dq]balance\[dq] field \f[CR]balance_\f[R] to avoid directly setting hledger\[aq]s \f[CR]balance\f[R] field (and generating a balance assertion). .SS Field assignment .IP .EX HLEDGERFIELD FIELDVALUE .EE .PP Field assignments are the more flexible way to assign CSV values to hledger fields. They can be used instead of or in addition to a fields list (see above). .PP To assign a value to a hledger field, write the field name (any of the standard hledger field/pseudo\-field names, defined below), a space, followed by a text value on the same line. This text value may interpolate CSV fields, referenced either by their 1\-based position in the CSV record (\f[CR]%N\f[R]) or by the name they were given in the fields list (\f[CR]%CSVFIELD\f[R]), and regular expression match groups (\f[CR]\[rs]N\f[R]). .PP Some examples: .IP .EX # set the amount to the 4th CSV field, with \[dq] USD\[dq] appended amount %4 USD # combine three fields to make a comment, containing note: and date: tags comment note: %somefield \- %anotherfield, date: %1 .EE .PP Tips: .IP \[bu] 2 Interpolation strips outer whitespace (so a CSV value like \f[CR]\[dq] 1 \[dq]\f[R] becomes \f[CR]1\f[R] when interpolated) (#1051). .IP \[bu] 2 Interpolations always refer to a CSV field \- you can\[aq]t interpolate a hledger field. (See Referencing other fields below). .SS Field names Note the two kinds of field names mentioned here, and used only in hledger CSV rules files: .IP "1." 3 \f[B]CSV field names\f[R] (\f[CR]CSVFIELD\f[R] in these docs): you can optionally name the CSV columns for easy reference (since hledger doesn\[aq]t yet automatically recognise column headings in a CSV file), by writing arbitrary names in a \f[CR]fields\f[R] list, eg: .RS 4 .IP .EX fields When, What, Some_Id, Net, Total, Foo, Bar .EE .RE .IP "2." 3 Special \f[B]hledger field names\f[R] (\f[CR]HLEDGERFIELD\f[R] in these docs): you must set at least some of these to generate the hledger transaction from a CSV record, by writing them as the left hand side of a field assignment, eg: .RS 4 .IP .EX date %When code %Some_Id description %What comment %Foo %Bar amount1 $ %Total .EE .PP or directly in a \f[CR]fields\f[R] list: .IP .EX fields date, description, code, , amount1, Foo, Bar currency $ comment %Foo %Bar .EE .RE .PP Here are all the special hledger field names available, and what happens when you assign values to them: .SS date field Assigning to \f[CR]date\f[R] sets the transaction date. .SS date2 field \f[CR]date2\f[R] sets the transaction\[aq]s secondary date, if any. .SS status field \f[CR]status\f[R] sets the transaction\[aq]s status, if any. .SS code field \f[CR]code\f[R] sets the transaction\[aq]s code, if any. .SS description field \f[CR]description\f[R] sets the transaction\[aq]s description, if any. .SS comment field \f[CR]comment\f[R] sets the transaction\[aq]s comment, if any. .PP \f[CR]commentN\f[R], where N is a number, sets the Nth posting\[aq]s comment. .PP You can assign multi\-line comments by writing literal \f[CR]\[rs]n\f[R] in the code. A comment starting with \f[CR]\[rs]n\f[R] will begin on a new line. .PP Comments can contain tags, as usual. .SS account field Assigning to \f[CR]accountN\f[R], where N is 1 to 99, sets the account name of the Nth posting, and causes that posting to be generated. .PP Most often there are two postings, so you\[aq]ll want to set \f[CR]account1\f[R] and \f[CR]account2\f[R]. Typically \f[CR]account1\f[R] is associated with the CSV file, and is set once with a top\-level assignment, while \f[CR]account2\f[R] is set based on each transaction\[aq]s description, in conditional rules. .PP If a posting\[aq]s account name is left unset but its amount is set (see below), a default account name will be chosen (like \[dq]expenses:unknown\[dq] or \[dq]income:unknown\[dq]). .SS amount field There are several ways to set posting amounts from CSV, useful in different situations. .IP "1." 3 \f[B]\f[CB]amount\f[B]\f[R] is the oldest and simplest. Assigning to this sets the amount of the first and second postings. In the second posting, the amount will be negated; also, if it has a cost attached, it will be converted to cost. .IP "2." 3 \f[B]\f[CB]amount\-in\f[B]\f[R] and \f[B]\f[CB]amount\-out\f[B]\f[R] work exactly like the above, but should be used when the CSV has two amount fields (such as \[dq]Debit\[dq] and \[dq]Credit\[dq], or \[dq]Inflow\[dq] and \[dq]Outflow\[dq]). Whichever field has a non\-zero value will be used as the amount of the first and second postings. Here are some tips to avoid confusion: .RS 4 .IP \[bu] 2 It\[aq]s not \[dq]amount\-in for posting 1 and amount\-out for posting 2\[dq], it is \[dq]extract a single amount from the amount\-in or amount\-out field, and use that for posting 1 and (negated) for posting 2\[dq]. .IP \[bu] 2 Don\[aq]t use both \f[CR]amount\f[R] and \f[CR]amount\-in\f[R]/\f[CR]amount\-out\f[R] in the same rules file; choose based on whether the amount is in a single CSV field or spread across two fields. .IP \[bu] 2 In each record, at most one of the two CSV fields should contain a non\-zero amount; the other field must contain a zero or nothing. .IP \[bu] 2 hledger assumes both CSV fields contain unsigned numbers, and it automatically negates the amount\-out values. .IP \[bu] 2 If the data doesn\[aq]t fit these requirements, you\[aq]ll probably need an if rule (see below). .RE .IP "3." 3 \f[B]\f[CB]amountN\f[B]\f[R] (where N is a number from 1 to 99) sets the amount of only a single posting: the Nth posting in the transaction. You\[aq]ll usually need at least two such assignments to make a balanced transaction. You can also generate more than two postings, to represent more complex transactions. The posting numbers don\[aq]t have to be consecutive; with if rules, higher posting numbers can be useful to ensure a certain order of postings. .IP "4." 3 \f[B]\f[CB]amountN\-in\f[B]\f[R] and \f[B]\f[CB]amountN\-out\f[B]\f[R] work exactly like the above, but should be used when the CSV has two amount fields. This is analogous to \f[CR]amount\-in\f[R] and \f[CR]amount\-out\f[R], and those tips also apply here. .IP "5." 3 Remember that a \f[CR]fields\f[R] list can also do assignments. So in a fields list if you name a CSV field \[dq]amount\[dq], that counts as assigning to \f[CR]amount\f[R]. (If you don\[aq]t want that, call it something else in the fields list, like \[dq]amount_\[dq].) .IP "6." 3 The above don\[aq]t handle every situation; if you need more flexibility, use an \f[CR]if\f[R] rule to set amounts conditionally. See \[dq]Working with CSV > Setting amounts\[dq] below for more on this and on amount\-setting generally. .SS currency field \f[CR]currency\f[R] sets a currency symbol, to be prepended to all postings\[aq] amounts. You can use this if the CSV amounts do not have a currency symbol, eg if it is in a separate column. .PP \f[CR]currencyN\f[R] prepends a currency symbol to just the Nth posting\[aq]s amount. .SS balance field \f[CR]balanceN\f[R] sets a balance assertion amount (or if the posting amount is left empty, a balance assignment) on posting N. .PP \f[CR]balance\f[R] is a compatibility spelling for hledger <1.17; it is equivalent to \f[CR]balance1\f[R]. .PP You can adjust the type of assertion/assignment with the \f[CR]balance\-type\f[R] rule (see below). .PP See Tips below for more about setting amounts and currency. .SS \f[CR]if\f[R] block Rules can be applied conditionally, depending on patterns in the CSV data. This allows flexibility; in particular, it is how you can categorise transactions, selecting an appropriate account name based on their description (for example). There are two ways to write conditional rules: \[dq]if blocks\[dq], described here, and \[dq]if tables\[dq], described below. .PP An if block is the word \f[CR]if\f[R] and one or more \[dq]matcher\[dq] expressions (can be a word or phrase), one per line, starting either on the same or next line; followed by one or more indented rules. Eg, .IP .EX if MATCHER RULE .EE .PP or .IP .EX if MATCHER MATCHER MATCHER RULE RULE .EE .PP If any of the matchers succeeds, all of the indented rules will be applied. They are usually field assignments, but the following special rules may also be used within an if block: .IP \[bu] 2 \f[CR]skip\f[R] \- skips the matched CSV record (generating no transaction from it) .IP \[bu] 2 \f[CR]end\f[R] \- skips the rest of the current CSV file. .PP Some examples: .IP .EX # if the record contains \[dq]groceries\[dq], set account2 to \[dq]expenses:groceries\[dq] if groceries account2 expenses:groceries .EE .IP .EX # if the record contains any of these phrases, set account2 and a transaction comment as shown if monthly service fee atm transaction fee banking thru software account2 expenses:business:banking comment XXX deductible ? check it .EE .IP .EX # if an empty record is seen (assuming five fields), ignore the rest of the CSV file if ,,,, end .EE .SS Matchers There are two kinds: .IP "1." 3 A record matcher is a word or single\-line text fragment or regular expression (\f[CR]REGEX\f[R]), which hledger will try to match case\-insensitively anywhere within the CSV record. .PD 0 .P .PD Eg: \f[CR]whole foods\f[R] .IP "2." 3 A field matcher is preceded with a percent sign and CSV field name (\f[CR]%CSVFIELD REGEX\f[R]). hledger will try to match these just within the named CSV field. .PD 0 .P .PD Eg: \f[CR]%date 2023\f[R] .PP The regular expression is (as usual in hledger) a POSIX extended regular expression, that also supports GNU word boundaries (\f[CR]\[rs]b\f[R], \f[CR]\[rs]B\f[R], \f[CR]\[rs]<\f[R], \f[CR]\[rs]>\f[R]), and nothing else. If you have trouble, see \[dq]Regular expressions\[dq] in the hledger manual (https://hledger.org/hledger.html#regular\-expressions). .SS What matchers match With record matchers, it\[aq]s important to know that the record matched is not the original CSV record, but a modified one: separators will be converted to commas, and enclosing double quotes (but not enclosing whitespace) are removed. So for example, when reading an SSV file, if the original record was: .IP .EX 2023\-01\-01; \[dq]Acme, Inc.\[dq]; 1,000 .EE .PP the regex would see, and try to match, this modified record text: .IP .EX 2023\-01\-01,Acme, Inc., 1,000 .EE .SS Combining matchers When an if block has multiple matchers, they are combined as follows: .IP \[bu] 2 By default they are OR\[aq]d (any one of them can match) .IP \[bu] 2 When a matcher is preceded by ampersand (\f[CR]&\f[R]) it will be AND\[aq]ed with the previous matcher (both of them must match) .IP \[bu] 2 When a matcher is preceded by an exclamation mark (\f[CR]!\f[R]), the matcher is negated (it may not match). .PP Currently there is a limitation: you can\[aq]t use both \f[CR]&\f[R] and \f[CR]!\f[R] on the same line (you can\[aq]t AND a negated matcher). .SS Match groups Matchers can define match groups: parenthesised portions of the regular expression which are available for reference in field assignments. Groups are enclosed in regular parentheses (\f[CR](\f[R] and \f[CR])\f[R]) and can be nested. Each group is available in field assignments using the token \f[CR]\[rs]N\f[R], where N is an index into the match groups for this conditional block (e.g. \f[CR]\[rs]1\f[R], \f[CR]\[rs]2\f[R], etc.). .PP Example: Warp credit card payment postings to the beginning of the billing period (Month start), to match how they are presented in statements, using posting dates: .IP .EX if %date (....\-..)\-.. comment2 date:\[rs]1\-01 .EE .PP Another example: Read the expense account from the CSV field, but throw away a prefix: .IP .EX if %account1 liabilities:family:(expenses:.*) account1 \[rs]1 .EE .SS \f[CR]if\f[R] table \[dq]if tables\[dq] are an alternative to if blocks; they can express many matchers and field assignments in a more compact tabular format, like this: .IP .EX if,HLEDGERFIELD1,HLEDGERFIELD2,... MATCHERA,VALUE1,VALUE2,... MATCHERB,VALUE1,VALUE2,... MATCHERC,VALUE1,VALUE2,... .EE .PP The first character after \f[CR]if\f[R] is taken to be this if table\[aq]s field separator. It is unrelated to the separator used in the CSV file. It should be a non\-alphanumeric character like \f[CR],\f[R] or \f[CR]|\f[R] that does not appear anywhere else in the table (it should not be used in field names or matchers or values, and it cannot be escaped with a backslash). .PP Each line must contain the same number of separators; empty values are allowed. Whitespace can be used in the matcher lines for readability (but not in the if line, currently). The table must be terminated by an empty line (or end of file). .PP An if table like the above is interpreted as follows: try all of the matchers; whenever a matcher succeeds, assign all of the values on that line to the corresponding hledger fields; later lines can overrider earlier ones. It is equivalent to this sequence of if blocks: .IP .EX if MATCHERA HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERB HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERC HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... .EE .PP Example: .IP .EX if,account2,comment atm transaction fee,expenses:business:banking,deductible? check it %description groceries,expenses:groceries, 2023/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call\-out .EE .SS \f[CR]balance\-type\f[R] Balance assertions generated by assigning to balanceN are of the simple \f[CR]=\f[R] type by default, which is a single\-commodity, subaccount\-excluding assertion. You may find the subaccount\-including variants more useful, eg if you have created some virtual subaccounts of checking to help with budgeting. You can select a different type of assertion with the \f[CR]balance\-type\f[R] rule: .IP .EX # balance assertions will consider all commodities and all subaccounts balance\-type ==* .EE .PP Here are the balance assertion types for quick reference: .IP .EX = single commodity, exclude subaccounts =* single commodity, include subaccounts == multi commodity, exclude subaccounts ==* multi commodity, include subaccounts .EE .SS \f[CR]include\f[R] .IP .EX include RULESFILE .EE .PP This includes the contents of another CSV rules file at this point. \f[CR]RULESFILE\f[R] is an absolute file path or a path relative to the current file\[aq]s directory. This can be useful for sharing common rules between several rules files, eg: .IP .EX # someaccount.csv.rules ## someaccount\-specific rules fields date,description,amount account1 assets:someaccount account2 expenses:misc ## common rules include categorisation.rules .EE .SS Working with CSV Some tips: .SS Rapid feedback It\[aq]s a good idea to get rapid feedback while creating/troubleshooting CSV rules. Here\[aq]s a good way, using entr from eradman.com/entrproject: .IP .EX $ ls foo.csv* | entr bash \-c \[aq]echo \-\-\-\-; hledger \-f foo.csv print desc:SOMEDESC\[aq] .EE .PP A desc: query (eg) is used to select just one, or a few, transactions of interest. \[dq]bash \-c\[dq] is used to run multiple commands, so we can echo a separator each time the command re\-runs, making it easier to read the output. .SS Valid CSV Note that hledger will only accept valid CSV conforming to RFC 4180, and equivalent SSV and TSV formats (like RFC 4180 but with semicolon or tab as separators). This means, eg: .IP \[bu] 2 Values may be enclosed in double quotes, or not. Enclosing in single quotes is not allowed. (Eg \f[CR]\[aq]A\[aq],\[aq]B\[aq]\f[R] is rejected.) .IP \[bu] 2 When values are enclosed in double quotes, spaces outside the quotes are not allowed. (Eg \f[CR]\[dq]A\[dq], \[dq]B\[dq]\f[R] is rejected.) .IP \[bu] 2 When values are not enclosed in quotes, they may not contain double quotes. (Eg \f[CR]A\[dq]A, B\f[R] is rejected.) .PP If your CSV/SSV/TSV is not valid in this sense, you\[aq]ll need to transform it before reading with hledger. Try using sed, or a more permissive CSV parser like python\[aq]s csv lib. .SS File Extension To help hledger choose the CSV file reader and show the right error messages (and choose the right field separator character by default), it\[aq]s best if CSV/SSV/TSV files are named with a \f[CR].csv\f[R], \f[CR].ssv\f[R] or \f[CR].tsv\f[R] filename extension. (More about this at Data formats.) .PP When reading files with the \[dq]wrong\[dq] extension, you can ensure the CSV reader (and the default field separator) by prefixing the file path with \f[CR]csv:\f[R], \f[CR]ssv:\f[R] or \f[CR]tsv:\f[R]: Eg: .IP .EX $ hledger \-f ssv:foo.dat print .EE .PP You can also override the default field separator with a separator rule if needed. .SS Reading CSV from standard input You\[aq]ll need the file format prefix when reading CSV from stdin also, since hledger assumes journal format by default. Eg: .IP .EX $ cat foo.dat | hledger \-f ssv:\- print .EE .SS Reading multiple CSV files If you use multiple \f[CR]\-f\f[R] options to read multiple CSV files at once, hledger will look for a correspondingly\-named rules file for each CSV file. But if you use the \f[CR]\-\-rules\-file\f[R] option, that rules file will be used for all the CSV files. .SS Reading files specified by rule Instead of specifying a CSV file in the command line, you can specify a rules file, as in \f[CR]hledger \-f foo.csv.rules CMD\f[R]. By default this will read data from foo.csv in the same directory, but you can add a source rule to specify a different data file, perhaps located in your web browser\[aq]s download directory. .PP This feature was added in hledger 1.30, so you won\[aq]t see it in most CSV rules examples. But it helps remove some of the busywork of managing CSV downloads. Most of your financial institutions\[aq]s default CSV filenames are different and can be recognised by a glob pattern. So you can put a rule like \f[CR]source Checking1*.csv\f[R] in foo\-checking.csv.rules, and then periodically follow a workflow like: .IP "1." 3 Download CSV from Foo\[aq]s website, using your browser\[aq]s defaults .IP "2." 3 Run \f[CR]hledger import foo\-checking.csv.rules\f[R] to import any new transactions .PP After import, you can: discard the CSV, or leave it where it is for a while, or move it into your archives, as you prefer. If you do nothing, next time your browser will save something like Checking1\-2.csv, and hledger will use that because of the \f[CR]*\f[R] wild card and because it is the most recent. .SS Valid transactions After reading a CSV file, hledger post\-processes and validates the generated journal entries as it would for a journal file \- balancing them, applying balance assignments, and canonicalising amount styles. Any errors at this stage will be reported in the usual way, displaying the problem entry. .PP There is one exception: balance assertions, if you have generated them, will not be checked, since normally these will work only when the CSV data is part of the main journal. If you do need to check balance assertions generated from CSV right away, pipe into another hledger: .IP .EX $ hledger \-f file.csv print | hledger \-f\- print .EE .SS Deduplicating, importing When you download a CSV file periodically, eg to get your latest bank transactions, the new file may overlap with the old one, containing some of the same records. .PP The import command will (a) detect the new transactions, and (b) append just those transactions to your main journal. It is idempotent, so you don\[aq]t have to remember how many times you ran it or with which version of the CSV. (It keeps state in a hidden \f[CR].latest.FILE.csv\f[R] file.) This is the easiest way to import CSV data. Eg: .IP .EX # download the latest CSV files, then run this command. # Note, no \-f flags needed here. $ hledger import *.csv [\-\-dry] .EE .PP This method works for most CSV files. (Where records have a stable chronological order, and new records appear only at the new end.) .PP A number of other tools and workflows, hledger\-specific and otherwise, exist for converting, deduplicating, classifying and managing CSV data. See: .IP \[bu] 2 https://hledger.org/cookbook.html#setups\-and\-workflows .IP \[bu] 2 https://plaintextaccounting.org \-> data import/conversion .SS Setting amounts Continuing from amount field above, here are more tips for amount\-setting: .IP "1." 3 \f[B]If the amount is in a single CSV field:\f[R] .PD 0 .P .PD .RS 4 .IP "a." 3 \f[B]If its sign indicates direction of flow:\f[R] .PD 0 .P .PD Assign it to \f[CR]amountN\f[R], to set the Nth posting\[aq]s amount. N is usually 1 or 2 but can go up to 99. .IP "b." 3 \f[B]If another field indicates direction of flow:\f[R] .PD 0 .P .PD Use one or more conditional rules to set the appropriate amount sign. Eg: .IP .EX # assume a withdrawal unless Type contains \[dq]deposit\[dq]: amount1 \-%Amount if %Type deposit amount1 %Amount .EE .RE .IP "2." 3 \f[B]If the amount is in two CSV fields (such as Debit and Credit, or In and Out):\f[R] .PD 0 .P .PD .RS 4 .IP "a." 3 \f[B]If both fields are unsigned:\f[R] .PD 0 .P .PD Assign one field to \f[CR]amountN\-in\f[R] and the other to \f[CR]amountN\-out\f[R]. hledger will automatically negate the \[dq]out\[dq] field, and will use whichever field value is non\-zero as posting N\[aq]s amount. .IP "b." 3 \f[B]If either field is signed:\f[R] .PD 0 .P .PD You will probably need to override hledger\[aq]s sign for one or the other field, as in the following example: .IP .EX # Negate the \-out value, but only if it is not empty: fields date, description, amount1\-in, amount1\-out if %amount1\-out [1\-9] amount1\-out \-%amount1\-out .EE .IP "c." 3 \f[B]If both fields can contain a non\-zero value (or both can be empty):\f[R] .PD 0 .P .PD The \-in/\-out rules normally choose the value which is non\-zero/non\-empty. Some value pairs can be ambiguous, such as \f[CR]1\f[R] and \f[CR]none\f[R]. For such cases, use conditional rules to help select the amount. Eg, to handle the above you could select the value containing non\-zero digits: .IP .EX fields date, description, in, out if %in [1\-9] amount1 %in if %out [1\-9] amount1 %out .EE .RE .IP "3." 3 \f[B]If you want posting 2\[aq]s amount converted to cost:\f[R] .PD 0 .P .PD Use the unnumbered \f[CR]amount\f[R] (or \f[CR]amount\-in\f[R] and \f[CR]amount\-out\f[R]) syntax. .IP "4." 3 \f[B]If the CSV has only balance amounts, not transaction amounts:\f[R] .PD 0 .P .PD Assign to \f[CR]balanceN\f[R], to set a balance assignment on the Nth posting, causing the posting\[aq]s amount to be calculated automatically. \f[CR]balance\f[R] with no number is equivalent to \f[CR]balance1\f[R]. In this situation hledger is more likely to guess the wrong default account name, so you may need to set that explicitly. .SS Amount signs There is some special handling making it easier to parse and to reverse amount signs. (This only works for whole amounts, not for cost amounts such as COST in \f[CR]amount1 AMT \[at] COST\f[R]): .IP \[bu] 2 \f[B]If an amount value begins with a plus sign:\f[R] .PD 0 .P .PD that will be removed: \f[CR]+AMT\f[R] becomes \f[CR]AMT\f[R] .IP \[bu] 2 \f[B]If an amount value is parenthesised:\f[R] .PD 0 .P .PD it will be de\-parenthesised and sign\-flipped: \f[CR](AMT)\f[R] becomes \f[CR]\-AMT\f[R] .IP \[bu] 2 \f[B]If an amount value has two minus signs (or two sets of parentheses, or a minus sign and parentheses):\f[R] .PD 0 .P .PD they cancel out and will be removed: \f[CR]\-\-AMT\f[R] or \f[CR]\-(AMT)\f[R] becomes \f[CR]AMT\f[R] .IP \[bu] 2 \f[B]If an amount value contains just a sign (or just a set of parentheses):\f[R] .PD 0 .P .PD that is removed, making it an empty value. \f[CR]\[dq]+\[dq]\f[R] or \f[CR]\[dq]\-\[dq]\f[R] or \f[CR]\[dq]()\[dq]\f[R] becomes \f[CR]\[dq]\[dq]\f[R]. .PP It\[aq]s not possible (without preprocessing the CSV) to set an amount to its absolute value, ie discard its sign. .SS Setting currency/commodity If the currency/commodity symbol is included in the CSV\[aq]s amount field(s): .IP .EX 2023\-01\-01,foo,$123.00 .EE .PP you don\[aq]t have to do anything special for the commodity symbol, it will be assigned as part of the amount. Eg: .IP .EX fields date,description,amount .EE .IP .EX 2023\-01\-01 foo expenses:unknown $123.00 income:unknown $\-123.00 .EE .PP If the currency is provided as a separate CSV field: .IP .EX 2023\-01\-01,foo,USD,123.00 .EE .PP You can assign that to the \f[CR]currency\f[R] pseudo\-field, which has the special effect of prepending itself to every amount in the transaction (on the left, with no separating space): .IP .EX fields date,description,currency,amount .EE .IP .EX 2023\-01\-01 foo expenses:unknown USD123.00 income:unknown USD\-123.00 .EE .PP Or, you can use a field assignment to construct the amount yourself, with more control. Eg to put the symbol on the right, and separated by a space: .IP .EX fields date,description,cur,amt amount %amt %cur .EE .IP .EX 2023\-01\-01 foo expenses:unknown 123.00 USD income:unknown \-123.00 USD .EE .PP Note we used a temporary field name (\f[CR]cur\f[R]) that is not \f[CR]currency\f[R] \- that would trigger the prepending effect, which we don\[aq]t want here. .SS Amount decimal places Like amounts in a journal file, the amounts generated by CSV rules like \f[CR]amount1\f[R] influence commodity display styles, such as the number of decimal places displayed in reports. .PP The original amounts as written in the CSV file do not affect display style (because we don\[aq]t yet reliably know their commodity). .SS Referencing other fields In field assignments, you can interpolate only CSV fields, not hledger fields. In the example below, there\[aq]s both a CSV field and a hledger field named amount1, but %amount1 always means the CSV field, not the hledger field: .IP .EX # Name the third CSV field \[dq]amount1\[dq] fields date,description,amount1 # Set hledger\[aq]s amount1 to the CSV amount1 field followed by USD amount1 %amount1 USD # Set comment to the CSV amount1 (not the amount1 assigned above) comment %amount1 .EE .PP Here, since there\[aq]s no CSV amount1 field, %amount1 will produce a literal \[dq]amount1\[dq]: .IP .EX fields date,description,csvamount amount1 %csvamount USD # Can\[aq]t interpolate amount1 here comment %amount1 .EE .PP When there are multiple field assignments to the same hledger field, only the last one takes effect. Here, comment\[aq]s value will be be B, or C if \[dq]something\[dq] is matched, but never A: .IP .EX comment A comment B if something comment C .EE .SS How CSV rules are evaluated Here\[aq]s how to think of CSV rules being evaluated (if you really need to). First, .IP \[bu] 2 \f[CR]include\f[R] \- all includes are inlined, from top to bottom, depth first. (At each include point the file is inlined and scanned for further includes, recursively, before proceeding.) .PP Then \[dq]global\[dq] rules are evaluated, top to bottom. If a rule is repeated, the last one wins: .IP \[bu] 2 \f[CR]skip\f[R] (at top level) .IP \[bu] 2 \f[CR]date\-format\f[R] .IP \[bu] 2 \f[CR]newest\-first\f[R] .IP \[bu] 2 \f[CR]fields\f[R] \- names the CSV fields, optionally sets up initial assignments to hledger fields .PP Then for each CSV record in turn: .IP \[bu] 2 test all \f[CR]if\f[R] blocks. If any of them contain a \f[CR]end\f[R] rule, skip all remaining CSV records. Otherwise if any of them contain a \f[CR]skip\f[R] rule, skip that many CSV records. If there are multiple matched \f[CR]skip\f[R] rules, the first one wins. .IP \[bu] 2 collect all field assignments at top level and in matched \f[CR]if\f[R] blocks. When there are multiple assignments for a field, keep only the last one. .IP \[bu] 2 compute a value for each hledger field \- either the one that was assigned to it (and interpolate the %CSVFIELD references), or a default .IP \[bu] 2 generate a hledger transaction (journal entry) from these values. .PP This is all part of the CSV reader, one of several readers hledger can use to parse input files. When all files have been read successfully, the transactions are passed as input to whichever hledger command the user specified. .PP .SS Well factored rules Some things than can help reduce duplication and complexity in rules files: .IP \[bu] 2 Extracting common rules usable with multiple CSV files into a \f[CR]common.rules\f[R], and adding \f[CR]include common.rules\f[R] to each CSV\[aq]s rules file. .IP \[bu] 2 Splitting if blocks into smaller if blocks, extracting the frequently used parts. .SS CSV rules examples .SS Bank of Ireland Here\[aq]s a CSV with two amount fields (Debit and Credit), and a balance field, which we can use to add balance assertions, which is not necessary but provides extra error checking: .IP .EX Date,Details,Debit,Credit,Balance 07/12/2012,LODGMENT 529898,,10.0,131.21 07/12/2012,PAYMENT,5,,126 .EE .IP .EX # bankofireland\-checking.csv.rules # skip the header line skip # name the csv fields, and assign some of them as journal entry fields fields date, description, amount\-out, amount\-in, balance # We generate balance assertions by assigning to \[dq]balance\[dq] # above, but you may sometimes need to remove these because: # # \- the CSV balance differs from the true balance, # by up to 0.0000000000005 in my experience # # \- it is sometimes calculated based on non\-chronological ordering, # eg when multiple transactions clear on the same day # date is in UK/Ireland format date\-format %d/%m/%Y # set the currency currency EUR # set the base account for all txns account1 assets:bank:boi:checking .EE .IP .EX $ hledger \-f bankofireland\-checking.csv print 2012\-12\-07 LODGMENT 529898 assets:bank:boi:checking EUR10.0 = EUR131.2 income:unknown EUR\-10.0 2012\-12\-07 PAYMENT assets:bank:boi:checking EUR\-5.0 = EUR126.0 expenses:unknown EUR5.0 .EE .PP The balance assertions don\[aq]t raise an error above, because we\[aq]re reading directly from CSV, but they will be checked if these entries are imported into a journal file. .SS Coinbase A simple example with some CSV from Coinbase. The spot price is recorded using cost notation. The legacy \f[CR]amount\f[R] field name conveniently sets amount 2 (posting 2\[aq]s amount) to the total cost. .IP .EX # Timestamp,Transaction Type,Asset,Quantity Transacted,Spot Price Currency,Spot Price at Transaction,Subtotal,Total (inclusive of fees and/or spread),Fees and/or Spread,Notes # 2021\-12\-30T06:57:59Z,Receive,USDC,100,GBP,0.740000,\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]Received 100.00 USDC from an external account\[dq] .EE .IP .EX # coinbase.csv.rules skip 1 fields Timestamp,Transaction_Type,Asset,Quantity_Transacted,Spot_Price_Currency,Spot_Price_at_Transaction,Subtotal,Total,Fees_Spread,Notes date %Timestamp date\-format %Y\-%m\-%dT%T%Z description %Notes account1 assets:coinbase:cc amount %Quantity_Transacted %Asset \[at] %Spot_Price_at_Transaction %Spot_Price_Currency .EE .IP .EX $ hledger print \-f coinbase.csv 2021\-12\-30 Received 100.00 USDC from an external account assets:coinbase:cc 100 USDC \[at] 0.740000 GBP income:unknown \-74.000000 GBP .EE .SS Amazon Here we convert amazon.com order history, and use an if block to generate a third posting if there\[aq]s a fee. (In practice you\[aq]d probably get this data from your bank instead, but it\[aq]s an example.) .IP .EX \[dq]Date\[dq],\[dq]Type\[dq],\[dq]To/From\[dq],\[dq]Name\[dq],\[dq]Status\[dq],\[dq]Amount\[dq],\[dq]Fees\[dq],\[dq]Transaction ID\[dq] \[dq]Jul 29, 2012\[dq],\[dq]Payment\[dq],\[dq]To\[dq],\[dq]Foo.\[dq],\[dq]Completed\[dq],\[dq]$20.00\[dq],\[dq]$0.00\[dq],\[dq]16000000000000DGLNJPI1P9B8DKPVHL\[dq] \[dq]Jul 30, 2012\[dq],\[dq]Payment\[dq],\[dq]To\[dq],\[dq]Adapteva, Inc.\[dq],\[dq]Completed\[dq],\[dq]$25.00\[dq],\[dq]$1.00\[dq],\[dq]17LA58JSKRD4HDGLNJPI1P9B8DKPVHL\[dq] .EE .IP .EX # amazon\-orders.csv.rules # skip one header line skip 1 # name the csv fields, and assign the transaction\[aq]s date, amount and code. # Avoided the \[dq]status\[dq] and \[dq]amount\[dq] hledger field names to prevent confusion. fields date, _, toorfrom, name, amzstatus, amzamount, fees, code # how to parse the date date\-format %b %\-d, %Y # combine two fields to make the description description %toorfrom %name # save the status as a tag comment status:%amzstatus # set the base account for all transactions account1 assets:amazon # leave amount1 blank so it can balance the other(s). # I\[aq]m assuming amzamount excludes the fees, don\[aq]t remember # set a generic account2 account2 expenses:misc amount2 %amzamount # and maybe refine it further: #include categorisation.rules # add a third posting for fees, but only if they are non\-zero. if %fees [1\-9] account3 expenses:fees amount3 %fees .EE .IP .EX $ hledger \-f amazon\-orders.csv print 2012\-07\-29 (16000000000000DGLNJPI1P9B8DKPVHL) To Foo. ; status:Completed assets:amazon expenses:misc $20.00 2012\-07\-30 (17LA58JSKRD4HDGLNJPI1P9B8DKPVHL) To Adapteva, Inc. ; status:Completed assets:amazon expenses:misc $25.00 expenses:fees $1.00 .EE .SS Paypal Here\[aq]s a real\-world rules file for (customised) Paypal CSV, with some Paypal\-specific rules, and a second rules file included: .IP .EX \[dq]Date\[dq],\[dq]Time\[dq],\[dq]TimeZone\[dq],\[dq]Name\[dq],\[dq]Type\[dq],\[dq]Status\[dq],\[dq]Currency\[dq],\[dq]Gross\[dq],\[dq]Fee\[dq],\[dq]Net\[dq],\[dq]From Email Address\[dq],\[dq]To Email Address\[dq],\[dq]Transaction ID\[dq],\[dq]Item Title\[dq],\[dq]Item ID\[dq],\[dq]Reference Txn ID\[dq],\[dq]Receipt ID\[dq],\[dq]Balance\[dq],\[dq]Note\[dq] \[dq]10/01/2019\[dq],\[dq]03:46:20\[dq],\[dq]PDT\[dq],\[dq]Calm Radio\[dq],\[dq]Subscription Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]\-6.99\[dq],\[dq]0.00\[dq],\[dq]\-6.99\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]memberships\[at]calmradio.com\[dq],\[dq]60P57143A8206782E\[dq],\[dq]MONTHLY \- $1 for the first 2 Months: Me \- Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month\[dq],\[dq]\[dq],\[dq]I\-R8YLY094FJYR\[dq],\[dq]\[dq],\[dq]\-6.99\[dq],\[dq]\[dq] \[dq]10/01/2019\[dq],\[dq]03:46:20\[dq],\[dq]PDT\[dq],\[dq]\[dq],\[dq]Bank Deposit to PP Account \[dq],\[dq]Pending\[dq],\[dq]USD\[dq],\[dq]6.99\[dq],\[dq]0.00\[dq],\[dq]6.99\[dq],\[dq]\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]0TU1544T080463733\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]60P57143A8206782E\[dq],\[dq]\[dq],\[dq]0.00\[dq],\[dq]\[dq] \[dq]10/01/2019\[dq],\[dq]08:57:01\[dq],\[dq]PDT\[dq],\[dq]Patreon\[dq],\[dq]PreApproved Payment Bill User Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]\-7.00\[dq],\[dq]0.00\[dq],\[dq]\-7.00\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]support\[at]patreon.com\[dq],\[dq]2722394R5F586712G\[dq],\[dq]Patreon* Membership\[dq],\[dq]\[dq],\[dq]B\-0PG93074E7M86381M\[dq],\[dq]\[dq],\[dq]\-7.00\[dq],\[dq]\[dq] \[dq]10/01/2019\[dq],\[dq]08:57:01\[dq],\[dq]PDT\[dq],\[dq]\[dq],\[dq]Bank Deposit to PP Account \[dq],\[dq]Pending\[dq],\[dq]USD\[dq],\[dq]7.00\[dq],\[dq]0.00\[dq],\[dq]7.00\[dq],\[dq]\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]71854087RG994194F\[dq],\[dq]Patreon* Membership\[dq],\[dq]\[dq],\[dq]2722394R5F586712G\[dq],\[dq]\[dq],\[dq]0.00\[dq],\[dq]\[dq] \[dq]10/19/2019\[dq],\[dq]03:02:12\[dq],\[dq]PDT\[dq],\[dq]Wikimedia Foundation, Inc.\[dq],\[dq]Subscription Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]\-2.00\[dq],\[dq]0.00\[dq],\[dq]\-2.00\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]tle\[at]wikimedia.org\[dq],\[dq]K9U43044RY432050M\[dq],\[dq]Monthly donation to the Wikimedia Foundation\[dq],\[dq]\[dq],\[dq]I\-R5C3YUS3285L\[dq],\[dq]\[dq],\[dq]\-2.00\[dq],\[dq]\[dq] \[dq]10/19/2019\[dq],\[dq]03:02:12\[dq],\[dq]PDT\[dq],\[dq]\[dq],\[dq]Bank Deposit to PP Account \[dq],\[dq]Pending\[dq],\[dq]USD\[dq],\[dq]2.00\[dq],\[dq]0.00\[dq],\[dq]2.00\[dq],\[dq]\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]3XJ107139A851061F\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]K9U43044RY432050M\[dq],\[dq]\[dq],\[dq]0.00\[dq],\[dq]\[dq] \[dq]10/22/2019\[dq],\[dq]05:07:06\[dq],\[dq]PDT\[dq],\[dq]Noble Benefactor\[dq],\[dq]Subscription Payment\[dq],\[dq]Completed\[dq],\[dq]USD\[dq],\[dq]10.00\[dq],\[dq]\-0.59\[dq],\[dq]9.41\[dq],\[dq]noble\[at]bene.fac.tor\[dq],\[dq]simon\[at]joyful.com\[dq],\[dq]6L8L1662YP1334033\[dq],\[dq]Joyful Systems\[dq],\[dq]\[dq],\[dq]I\-KC9VBGY2GWDB\[dq],\[dq]\[dq],\[dq]9.41\[dq],\[dq]\[dq] .EE .IP .EX # paypal\-custom.csv.rules # Tips: # Export from Activity \-> Statements \-> Custom \-> Activity download # Suggested transaction type: \[dq]Balance affecting\[dq] # Paypal\[aq]s default fields in 2018 were: # \[dq]Date\[dq],\[dq]Time\[dq],\[dq]TimeZone\[dq],\[dq]Name\[dq],\[dq]Type\[dq],\[dq]Status\[dq],\[dq]Currency\[dq],\[dq]Gross\[dq],\[dq]Fee\[dq],\[dq]Net\[dq],\[dq]From Email Address\[dq],\[dq]To Email Address\[dq],\[dq]Transaction ID\[dq],\[dq]Shipping Address\[dq],\[dq]Address Status\[dq],\[dq]Item Title\[dq],\[dq]Item ID\[dq],\[dq]Shipping and Handling Amount\[dq],\[dq]Insurance Amount\[dq],\[dq]Sales Tax\[dq],\[dq]Option 1 Name\[dq],\[dq]Option 1 Value\[dq],\[dq]Option 2 Name\[dq],\[dq]Option 2 Value\[dq],\[dq]Reference Txn ID\[dq],\[dq]Invoice Number\[dq],\[dq]Custom Number\[dq],\[dq]Quantity\[dq],\[dq]Receipt ID\[dq],\[dq]Balance\[dq],\[dq]Address Line 1\[dq],\[dq]Address Line 2/District/Neighborhood\[dq],\[dq]Town/City\[dq],\[dq]State/Province/Region/County/Territory/Prefecture/Republic\[dq],\[dq]Zip/Postal Code\[dq],\[dq]Country\[dq],\[dq]Contact Phone Number\[dq],\[dq]Subject\[dq],\[dq]Note\[dq],\[dq]Country Code\[dq],\[dq]Balance Impact\[dq] # This rules file assumes the following more detailed fields, configured in \[dq]Customize report fields\[dq]: # \[dq]Date\[dq],\[dq]Time\[dq],\[dq]TimeZone\[dq],\[dq]Name\[dq],\[dq]Type\[dq],\[dq]Status\[dq],\[dq]Currency\[dq],\[dq]Gross\[dq],\[dq]Fee\[dq],\[dq]Net\[dq],\[dq]From Email Address\[dq],\[dq]To Email Address\[dq],\[dq]Transaction ID\[dq],\[dq]Item Title\[dq],\[dq]Item ID\[dq],\[dq]Reference Txn ID\[dq],\[dq]Receipt ID\[dq],\[dq]Balance\[dq],\[dq]Note\[dq] fields date, time, timezone, description_, type, status_, currency, grossamount, feeamount, netamount, fromemail, toemail, code, itemtitle, itemid, referencetxnid, receiptid, balance, note skip 1 date\-format %\-m/%\-d/%Y # ignore some paypal events if In Progress Temporary Hold Update to skip # add more fields to the description description %description_ %itemtitle # save some other fields as tags comment itemid:%itemid, fromemail:%fromemail, toemail:%toemail, time:%time, type:%type, status:%status_ # convert to short currency symbols if %currency USD currency $ if %currency EUR currency E if %currency GBP currency P # generate postings # the first posting will be the money leaving/entering my paypal account # (negative means leaving my account, in all amount fields) account1 assets:online:paypal amount1 %netamount # the second posting will be money sent to/received from other party # (account2 is set below) amount2 \-%grossamount # if there\[aq]s a fee, add a third posting for the money taken by paypal. if %feeamount [1\-9] account3 expenses:banking:paypal amount3 \-%feeamount comment3 business: # choose an account for the second posting # override the default account names: # if the amount is positive, it\[aq]s income (a debit) if %grossamount \[ha][\[ha]\-] account2 income:unknown # if negative, it\[aq]s an expense (a credit) if %grossamount \[ha]\- account2 expenses:unknown # apply common rules for setting account2 & other tweaks include common.rules # apply some overrides specific to this csv # Transfers from/to bank. These are usually marked Pending, # which can be disregarded in this case. if Bank Account Bank Deposit to PP Account description %type for %referencetxnid %itemtitle account2 assets:bank:wf:pchecking account1 assets:online:paypal # Currency conversions if Currency Conversion account2 equity:currency conversion .EE .IP .EX # common.rules if darcs noble benefactor account2 revenues:foss donations:darcshub comment2 business: if Calm Radio account2 expenses:online:apps if electronic frontier foundation Patreon wikimedia Advent of Code account2 expenses:dues if Google account2 expenses:online:apps description google | music .EE .IP .EX $ hledger \-f paypal\-custom.csv print 2019\-10\-01 (60P57143A8206782E) Calm Radio MONTHLY \- $1 for the first 2 Months: Me \- Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month ; itemid:, fromemail:simon\[at]joyful.com, toemail:memberships\[at]calmradio.com, time:03:46:20, type:Subscription Payment, status:Completed assets:online:paypal $\-6.99 = $\-6.99 expenses:online:apps $6.99 2019\-10\-01 (0TU1544T080463733) Bank Deposit to PP Account for 60P57143A8206782E ; itemid:, fromemail:, toemail:simon\[at]joyful.com, time:03:46:20, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $6.99 = $0.00 assets:bank:wf:pchecking $\-6.99 2019\-10\-01 (2722394R5F586712G) Patreon Patreon* Membership ; itemid:, fromemail:simon\[at]joyful.com, toemail:support\[at]patreon.com, time:08:57:01, type:PreApproved Payment Bill User Payment, status:Completed assets:online:paypal $\-7.00 = $\-7.00 expenses:dues $7.00 2019\-10\-01 (71854087RG994194F) Bank Deposit to PP Account for 2722394R5F586712G Patreon* Membership ; itemid:, fromemail:, toemail:simon\[at]joyful.com, time:08:57:01, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $7.00 = $0.00 assets:bank:wf:pchecking $\-7.00 2019\-10\-19 (K9U43044RY432050M) Wikimedia Foundation, Inc. Monthly donation to the Wikimedia Foundation ; itemid:, fromemail:simon\[at]joyful.com, toemail:tle\[at]wikimedia.org, time:03:02:12, type:Subscription Payment, status:Completed assets:online:paypal $\-2.00 = $\-2.00 expenses:dues $2.00 expenses:banking:paypal ; business: 2019\-10\-19 (3XJ107139A851061F) Bank Deposit to PP Account for K9U43044RY432050M ; itemid:, fromemail:, toemail:simon\[at]joyful.com, time:03:02:12, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $2.00 = $0.00 assets:bank:wf:pchecking $\-2.00 2019\-10\-22 (6L8L1662YP1334033) Noble Benefactor Joyful Systems ; itemid:, fromemail:noble\[at]bene.fac.tor, toemail:simon\[at]joyful.com, time:05:07:06, type:Subscription Payment, status:Completed assets:online:paypal $9.41 = $9.41 revenues:foss donations:darcshub $\-10.00 ; business: expenses:banking:paypal $0.59 ; business: .EE .SH Timeclock The time logging format of timeclock.el, as read by hledger. .PP hledger can read time logs in timeclock format. As with Ledger, these are (a subset of) timeclock.el\[aq]s format, containing clock\-in and clock\-out entries as in the example below. The date is a simple date. The time format is HH:MM[:SS][+\-ZZZZ]. Seconds and timezone are optional. The timezone, if present, must be four digits and is ignored (currently the time is always interpreted as a local time). Lines beginning with \f[CR]#\f[R] or \f[CR];\f[R] or \f[CR]*\f[R], and blank lines, are ignored. .IP .EX i 2015/03/30 09:00:00 some account optional description after 2 spaces ; optional comment, tags: o 2015/03/30 09:20:00 i 2015/03/31 22:21:45 another:account o 2015/04/01 02:00:34 .EE .PP hledger treats each clock\-in/clock\-out pair as a transaction posting some number of hours to an account. Or if the session spans more than one day, it is split into several transactions, one for each day. For the above time log, \f[CR]hledger print\f[R] generates these journal entries: .IP .EX $ hledger \-f t.timeclock print 2015\-03\-30 * optional description after 2 spaces ; optional comment, tags: (some account) 0.33h 2015\-03\-31 * 22:21\-23:59 (another:account) 1.64h 2015\-04\-01 * 00:00\-02:00 (another:account) 2.01h .EE .PP Here is a sample.timeclock to download and some queries to try: .IP .EX $ hledger \-f sample.timeclock balance # current time balances $ hledger \-f sample.timeclock register \-p 2009/3 # sessions in march 2009 $ hledger \-f sample.timeclock register \-p weekly \-\-depth 1 \-\-empty # time summary by week .EE .PP To generate time logs, ie to clock in and clock out, you could: .IP \[bu] 2 use emacs and the built\-in timeclock.el, or the extended timeclock\-x.el and perhaps the extras in ledgerutils.el .IP \[bu] 2 at the command line, use these bash aliases: \f[CR]shell alias ti=\[dq]echo i \[ga]date \[aq]+%Y\-%m\-%d %H:%M:%S\[aq]\[ga] \[rs]$* >>$TIMELOG\[dq] alias to=\[dq]echo o \[ga]date \[aq]+%Y\-%m\-%d %H:%M:%S\[aq]\[ga] >>$TIMELOG\[dq]\f[R] .IP \[bu] 2 or use the old \f[CR]ti\f[R] and \f[CR]to\f[R] scripts in the ledger 2.x repository. These rely on a \[dq]timeclock\[dq] executable which I think is just the ledger 2 executable renamed. .PP .SH Timedot \f[CR]timedot\f[R] format is hledger\[aq]s human\-friendly time logging format. Compared to \f[CR]timeclock\f[R] format, it is more convenient for quick, approximate, and retroactive time logging, and more human\-readable (you can see at a glance where time was spent). A quick example: .IP .EX 2023\-05\-01 hom:errands .... .... ; two hours; the space is ignored fos:hledger:timedot .. ; half an hour per:admin:finance ; no time spent yet .EE .PP hledger reads this as a transaction on this day with three (unbalanced) postings, where each dot represents \[dq]0.25\[dq]. No commodity symbol is assumed, but we typically interpret it as hours. .IP .EX $ hledger \-f a.timedot print # .timedot file extension (or timedot: prefix) is required 2023\-05\-01 * (hom:errands) 2.00 ; two hours (fos:hledger:timedot) 0.50 ; half an hour (per:admin:finance) 0 .EE .PP A timedot file contains a series of transactions (usually one per day). Each begins with a \f[B]simple date\f[R] (Y\-M\-D, Y/M/D, or Y.M.D), optionally be followed on the same line by a transaction description, and/or a transaction comment following a semicolon. .PP After the date line are zero or more time postings, consisting of: .IP \[bu] 2 \f[B]An account name\f[R] \- any hledger\-style account name, optionally indented. .IP \[bu] 2 \f[B]Two or more spaces\f[R] \- required if there is an amount (as in journal format). .IP \[bu] 2 \f[B]A timedot amount\f[R], which can be .RS 2 .IP \[bu] 2 empty (representing zero) .IP \[bu] 2 a number, optionally followed by a unit \f[CR]s\f[R], \f[CR]m\f[R], \f[CR]h\f[R], \f[CR]d\f[R], \f[CR]w\f[R], \f[CR]mo\f[R], or \f[CR]y\f[R], representing a precise number of seconds, minutes, hours, days weeks, months or years (hours is assumed by default), which will be converted to hours according to 60s = 1m, 60m = 1h, 24h = 1d, 7d = 1w, 30d = 1mo, 365d = 1y. .IP \[bu] 2 one or more dots (period characters), each representing 0.25. These are the dots in \[dq]timedot\[dq]. Spaces are ignored and can be used for grouping/alignment. .IP \[bu] 2 one or more letters. These are like dots but they also generate a tag \f[CR]t:\f[R] (short for \[dq]type\[dq]) with the letter as its value, and a separate posting for each of the values. This provides a second dimension of categorisation, viewable in reports with \f[CR]\-\-pivot t\f[R]. .RE .IP \[bu] 2 \f[B]An optional comment\f[R] following a semicolon (a hledger\-style posting comment). .PP There is some flexibility to help with keeping time log data and notes in the same file: .IP \[bu] 2 Blank lines and lines beginning with \f[CR]#\f[R] or \f[CR];\f[R] are ignored. .IP \[bu] 2 After the first date line, lines which do not contain a double space are parsed as postings with zero amount. (hledger\[aq]s register reports will show these if you add \-E). .IP \[bu] 2 Before the first date line, lines beginning with \f[CR]*\f[R] (eg org headings) are ignored. And from the first date line onward, Emacs org mode heading prefixes at the start of lines (one or more \f[CR]*\f[R]\[aq]s followed by a space) will be ignored. This means the time log can also be a org outline. .SS Timedot examples Numbers: .IP .EX 2016/2/3 inc:client1 4 fos:hledger 3h biz:research 60m .EE .PP Dots: .IP .EX # on this day, 6h was spent on client work, 1.5h on haskell FOSS work, etc. 2016/2/1 inc:client1 .... .... .... .... .... .... fos:haskell .... .. biz:research . 2016/2/2 inc:client1 .... .... biz:research . .EE .IP .EX $ hledger \-f a.timedot print date:2016/2/2 2016\-02\-02 * (inc:client1) 2.00 2016\-02\-02 * (biz:research) 0.25 .EE .IP .EX $ hledger \-f a.timedot bal \-\-daily \-\-tree Balance changes in 2016\-02\-01\-2016\-02\-03: || 2016\-02\-01d 2016\-02\-02d 2016\-02\-03d ============++======================================== biz || 0.25 0.25 1.00 research || 0.25 0.25 1.00 fos || 1.50 0 3.00 haskell || 1.50 0 0 hledger || 0 0 3.00 inc || 6.00 2.00 4.00 client1 || 6.00 2.00 4.00 \-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || 7.75 2.25 8.00 .EE .PP Letters: .IP .EX # Activity types: # c cleanup/catchup/repair # e enhancement # s support # l learning/research 2023\-11\-01 work:adm ccecces .EE .IP .EX $ hledger \-f a.timedot print 2023\-11\-01 (work:adm) 1 ; t:c (work:adm) 0.5 ; t:e (work:adm) 0.25 ; t:s .EE .IP .EX $ hledger \-f a.timedot bal 1.75 work:adm \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 1.75 .EE .IP .EX $ hledger \-f a.timedot bal \-\-pivot t 1.00 c 0.50 e 0.25 s \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 1.75 .EE .PP Org: .IP .EX * 2023 Work Diary ** Q1 *** 2023\-02\-29 **** DONE 0700 yoga **** UNPLANNED **** BEGUN hom:chores cleaning ... water plants outdoor \- one full watering can indoor \- light watering **** TODO adm:planning: trip *** LATER .EE .PP Using \f[CR].\f[R] as account name separator: .IP .EX 2016/2/4 fos.hledger.timedot 4h fos.ledger .. .EE .IP .EX $ hledger \-f a.timedot \-\-alias \[aq]/\[rs]./=:\[aq] bal \-t 4.50 fos 4.00 hledger:timedot 0.50 ledger \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 4.50 .EE .SH PART 3: REPORTING CONCEPTS .SH Amount formatting, parseability If you\[aq]re wondering why your \f[CR]print\f[R] report sometimes shows trailing decimal marks, with no decimal digits; it does this when showing amounts that have digit group marks but no decimal digits, to disambiguate them and allow them to be re\-parsed reliably (see also Decimal marks, digit group marks. Eg: .IP .EX commodity $1,000.00 2023\-01\-02 (a) $1000 .EE .IP .EX $ hledger print 2023\-01\-02 (a) $1,000. .EE .PP If this is a problem (eg when exporting to Ledger), you can avoid it by disabling digit group marks, eg with \-c/\-\-commodity (for each affected commodity): .IP .EX $ hledger print \-c \[aq]$1000.00\[aq] 2023\-01\-02 (a) $1000 .EE .PP or by forcing print to always show decimal digits, with \-\-round: .IP .EX $ hledger print \-c \[aq]$1,000.00\[aq] \-\-round=soft 2023\-01\-02 (a) $1,000.00 .EE .PP More generally: hledger output falls into three rough categories, which format amounts a little bit differently to suit different consumers: .PP \f[B]1. \[dq]hledger\-readable output\[dq] \- should be readable by hledger (and by humans)\f[R] .IP \[bu] 2 This is produced by reports that show full journal entries: \f[CR]print\f[R], \f[CR]import\f[R], \f[CR]close\f[R], \f[CR]rewrite\f[R] etc. .IP \[bu] 2 It shows amounts with their original journal precisions, which may not be consistent. .IP \[bu] 2 It adds a trailing decimal mark when needed to avoid showing ambiguous amounts. .IP \[bu] 2 It can be parsed reliably (by hledger and ledger2beancount at least, but perhaps not by Ledger..) .PP \f[B]2. \[dq]human\-readable output\[dq] \- usually for humans\f[R] .IP \[bu] 2 This is produced by all other reports. .IP \[bu] 2 It shows amounts with standard display precisions, which will be consistent within each commodity. .IP \[bu] 2 It shows ambiguous amounts unmodified. .IP \[bu] 2 It can be parsed reliably in the context of a known report (when you know decimals are consistently not being shown, you can assume a single mark is a digit group mark). .PP \f[B]3. \[dq]machine\-readable output\[dq] \- usually for other software\f[R] .IP \[bu] 2 This is produced by all reports when an output format like \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]json\f[R], or \f[CR]sql\f[R] is selected. .IP \[bu] 2 It shows amounts as 1 or 2 do, but without digit group marks. .IP \[bu] 2 It can be parsed reliably (if needed, the decimal mark can be changed with \-c/\-\-commodity\-style). .SH Time periods .SS Report start & end date By default, most hledger reports will show the full span of time represented by the journal. The report start date will be the earliest transaction or posting date, and the report end date will be the latest transaction, posting, or market price date. .PP Often you will want to see a shorter time span, such as the current month. You can specify a start and/or end date using \f[CR]\-b/\-\-begin\f[R], \f[CR]\-e/\-\-end\f[R], \f[CR]\-p/\-\-period\f[R] or a \f[CR]date:\f[R] query (described below). All of these accept the smart date syntax (below). .PP Some notes: .IP \[bu] 2 End dates are exclusive, as in Ledger, so you should write the date \f[I]after\f[R] the last day you want to see in the report. .IP \[bu] 2 As noted in reporting options: among start/end dates specified with \f[I]options\f[R], the last (i.e. right\-most) option takes precedence. .IP \[bu] 2 The effective report start and end dates are the intersection of the start/end dates from options and that from \f[CR]date:\f[R] queries. That is, \f[CR]date:2019\-01 date:2019 \-p\[aq]2000 to 2030\[aq]\f[R] yields January 2019, the smallest common time span. .IP \[bu] 2 In some cases a report interval will adjust start/end dates to fall on interval boundaries (see below). .PP Examples: .PP .TS tab(@); lw(12.4n) lw(57.6n). T{ \f[CR]\-b 2016/3/17\f[R] T}@T{ begin on St.\ Patrick\[cq]s day 2016 T} T{ \f[CR]\-e 12/1\f[R] T}@T{ end at the start of december 1st of the current year (11/30 will be the last date included) T} T{ \f[CR]\-b thismonth\f[R] T}@T{ all transactions on or after the 1st of the current month T} T{ \f[CR]\-p thismonth\f[R] T}@T{ all transactions in the current month T} T{ \f[CR]date:2016/3/17..\f[R] T}@T{ the above written as queries instead (\f[CR]..\f[R] can also be replaced with \f[CR]\-\f[R]) T} T{ \f[CR]date:..12/1\f[R] T}@T{ T} T{ \f[CR]date:thismonth..\f[R] T}@T{ T} T{ \f[CR]date:thismonth\f[R] T}@T{ T} .TE .SS Smart dates hledger\[aq]s user interfaces accept a \[dq]smart date\[dq] syntax for added convenience. Smart dates optionally can be relative to today\[aq]s date, be written with english words, and have less\-significant parts omitted (missing parts are inferred as 1). Some examples: .PP .TS tab(@); lw(24.2n) lw(45.8n). T{ \f[CR]2004/10/1\f[R], \f[CR]2004\-01\-01\f[R], \f[CR]2004.9.1\f[R] T}@T{ exact date, several separators allowed. Year is 4+ digits, month is 1\-12, day is 1\-31 T} T{ \f[CR]2004\f[R] T}@T{ start of year T} T{ \f[CR]2004/10\f[R] T}@T{ start of month T} T{ \f[CR]10/1\f[R] T}@T{ month and day in current year T} T{ \f[CR]21\f[R] T}@T{ day in current month T} T{ \f[CR]october, oct\f[R] T}@T{ start of month in current year T} T{ \f[CR]yesterday, today, tomorrow\f[R] T}@T{ \-1, 0, 1 days from today T} T{ \f[CR]last/this/next day/week/month/quarter/year\f[R] T}@T{ \-1, 0, 1 periods from the current period T} T{ \f[CR]in n days/weeks/months/quarters/years\f[R] T}@T{ n periods from the current period T} T{ \f[CR]n days/weeks/months/quarters/years ahead\f[R] T}@T{ n periods from the current period T} T{ \f[CR]n days/weeks/months/quarters/years ago\f[R] T}@T{ \-n periods from the current period T} T{ \f[CR]20181201\f[R] T}@T{ 8 digit YYYYMMDD with valid year month and day T} T{ \f[CR]201812\f[R] T}@T{ 6 digit YYYYMM with valid year and month T} .TE .PP Some counterexamples \- malformed digit sequences might give surprising results: .PP .TS tab(@); lw(11.4n) lw(58.6n). T{ \f[CR]201813\f[R] T}@T{ 6 digits with an invalid month is parsed as start of 6\-digit year T} T{ \f[CR]20181301\f[R] T}@T{ 8 digits with an invalid month is parsed as start of 8\-digit year T} T{ \f[CR]20181232\f[R] T}@T{ 8 digits with an invalid day gives an error T} T{ \f[CR]201801012\f[R] T}@T{ 9+ digits beginning with a valid YYYYMMDD gives an error T} .TE .PP \[dq]Today\[aq]s date\[dq] can be overridden with the \f[CR]\-\-today\f[R] option, in case it\[aq]s needed for testing or for recreating old reports. (Except for periodic transaction rules, which are not affected by \f[CR]\-\-today\f[R].) .SS Report intervals A report interval can be specified so that reports like register, balance or activity become multi\-period, showing each subperiod as a separate row or column. .PP The following standard intervals can be enabled with command\-line flags: .IP \[bu] 2 \f[CR]\-D/\-\-daily\f[R] .IP \[bu] 2 \f[CR]\-W/\-\-weekly\f[R] .IP \[bu] 2 \f[CR]\-M/\-\-monthly\f[R] .IP \[bu] 2 \f[CR]\-Q/\-\-quarterly\f[R] .IP \[bu] 2 \f[CR]\-Y/\-\-yearly\f[R] .PP More complex intervals can be specified using \f[CR]\-p/\-\-period\f[R], described below. .SS Date adjustment When there is a report interval (other than daily), report start/end dates which have been inferred, eg from the journal, are automatically adjusted to natural period boundaries. This is convenient for producing simple periodic reports. More precisely: .IP \[bu] 2 an inferred start date will be adjusted earlier if needed to fall on a natural period boundary .IP \[bu] 2 an inferred end date will be adjusted later if needed to make the last period the same length as the others. .PP By contrast, start/end dates which have been specified explicitly, with \f[CR]\-b\f[R], \f[CR]\-e\f[R], \f[CR]\-p\f[R] or \f[CR]date:\f[R], will not be adjusted (since hledger 1.29). This makes it possible to specify non\-standard report periods, but it also means that if you are specifying a start date, you should pick one that\[aq]s on a period boundary if you want to see simple report period headings. .SS Period expressions The \f[CR]\-p/\-\-period\f[R] option specifies a period expression, which is a compact way of expressing a start date, end date, and/or report interval. .PP Here\[aq]s a period expression with a start and end date (specifying the first quarter of 2009): .PP .TS tab(@); l. T{ \f[CR]\-p \[dq]from 2009/1/1 to 2009/4/1\[dq]\f[R] T} .TE .PP Several keywords like \[dq]from\[dq] and \[dq]to\[dq] are supported for readability; these are optional. \[dq]to\[dq] can also be written as \[dq]..\[dq] or \[dq]\-\[dq]. The spaces are also optional, as long as you don\[aq]t run two dates together. So the following are equivalent to the above: .PP .TS tab(@); l. T{ \f[CR]\-p \[dq]2009/1/1 2009/4/1\[dq]\f[R] T} T{ \f[CR]\-p2009/1/1to2009/4/1\f[R] T} T{ \f[CR]\-p2009/1/1..2009/4/1\f[R] T} .TE .PP Dates are smart dates, so if the current year is 2009, these are also equivalent to the above: .PP .TS tab(@); l. T{ \f[CR]\-p \[dq]1/1 4/1\[dq]\f[R] T} T{ \f[CR]\-p \[dq]jan\-apr\[dq]\f[R] T} T{ \f[CR]\-p \[dq]this year to 4/1\[dq]\f[R] T} .TE .PP If you specify only one date, the missing start or end date will be the earliest or latest transaction date in the journal: .PP .TS tab(@); l l. T{ \f[CR]\-p \[dq]from 2009/1/1\[dq]\f[R] T}@T{ everything after january 1, 2009 T} T{ \f[CR]\-p \[dq]since 2009/1\[dq]\f[R] T}@T{ the same, since is a synonym T} T{ \f[CR]\-p \[dq]from 2009\[dq]\f[R] T}@T{ the same T} T{ \f[CR]\-p \[dq]to 2009\[dq]\f[R] T}@T{ everything before january 1, 2009 T} .TE .PP You can also specify a period by writing a single partial or full date: .PP .TS tab(@); lw(14.5n) lw(55.5n). T{ \f[CR]\-p \[dq]2009\[dq]\f[R] T}@T{ the year 2009; equivalent to \[lq]2009/1/1 to 2010/1/1\[rq] T} T{ \f[CR]\-p \[dq]2009/1\[dq]\f[R] T}@T{ the month of january 2009; equivalent to \[lq]2009/1/1 to 2009/2/1\[rq] T} T{ \f[CR]\-p \[dq]2009/1/1\[dq]\f[R] T}@T{ the first day of 2009; equivalent to \[lq]2009/1/1 to 2009/1/2\[rq] T} .TE .PP or by using the \[dq]Q\[dq] quarter\-year syntax (case insensitive): .PP .TS tab(@); lw(15.3n) lw(54.7n). T{ \f[CR]\-p \[dq]2009Q1\[dq]\f[R] T}@T{ first quarter of 2009, equivalent to \[lq]2009/1/1 to 2009/4/1\[rq] T} T{ \f[CR]\-p \[dq]q4\[dq]\f[R] T}@T{ fourth quarter of the current year T} .TE .SS Period expressions with a report interval A period expression can also begin with a report interval, separated from the start/end dates (if any) by a space or the word \f[CR]in\f[R]: .PP .TS tab(@); l. T{ \f[CR]\-p \[dq]weekly from 2009/1/1 to 2009/4/1\[dq]\f[R] T} T{ \f[CR]\-p \[dq]monthly in 2008\[dq]\f[R] T} T{ \f[CR]\-p \[dq]quarterly\[dq]\f[R] T} .TE .SS More complex report intervals Some more complex intervals can be specified within period expressions, such as: .IP \[bu] 2 \f[CR]biweekly\f[R] (every two weeks) .IP \[bu] 2 \f[CR]fortnightly\f[R] .IP \[bu] 2 \f[CR]bimonthly\f[R] (every two months) .IP \[bu] 2 \f[CR]every day|week|month|quarter|year\f[R] .IP \[bu] 2 \f[CR]every N days|weeks|months|quarters|years\f[R] .PP Weekly on a custom day: .IP \[bu] 2 \f[CR]every Nth day of week\f[R] (\f[CR]th\f[R], \f[CR]nd\f[R], \f[CR]rd\f[R], or \f[CR]st\f[R] are all accepted after the number) .IP \[bu] 2 \f[CR]every WEEKDAYNAME\f[R] (full or three\-letter english weekday name, case insensitive) .PP Monthly on a custom day: .IP \[bu] 2 \f[CR]every Nth day [of month]\f[R] .IP \[bu] 2 \f[CR]every Nth WEEKDAYNAME [of month]\f[R] .PP Yearly on a custom day: .IP \[bu] 2 \f[CR]every MM/DD [of year]\f[R] (month number and day of month number) .IP \[bu] 2 \f[CR]every MONTHNAME DDth [of year]\f[R] (full or three\-letter english month name, case insensitive, and day of month number) .IP \[bu] 2 \f[CR]every DDth MONTHNAME [of year]\f[R] (equivalent to the above) .PP Examples: .PP .TS tab(@); lw(26.8n) lw(43.2n). T{ \f[CR]\-p \[dq]bimonthly from 2008\[dq]\f[R] T}@T{ T} T{ \f[CR]\-p \[dq]every 2 weeks\[dq]\f[R] T}@T{ T} T{ \f[CR]\-p \[dq]every 5 months from 2009/03\[dq]\f[R] T}@T{ T} T{ \f[CR]\-p \[dq]every 2nd day of week\[dq]\f[R] T}@T{ periods will go from Tue to Tue T} T{ \f[CR]\-p \[dq]every Tue\[dq]\f[R] T}@T{ same T} T{ \f[CR]\-p \[dq]every 15th day\[dq]\f[R] T}@T{ period boundaries will be on 15th of each month T} T{ \f[CR]\-p \[dq]every 2nd Monday\[dq]\f[R] T}@T{ period boundaries will be on second Monday of each month T} T{ \f[CR]\-p \[dq]every 11/05\[dq]\f[R] T}@T{ yearly periods with boundaries on 5th of November T} T{ \f[CR]\-p \[dq]every 5th November\[dq]\f[R] T}@T{ same T} T{ \f[CR]\-p \[dq]every Nov 5th\[dq]\f[R] T}@T{ same T} .TE .PP Show historical balances at end of the 15th day of each month (N is an end date, exclusive as always): .IP .EX $ hledger balance \-H \-p \[dq]every 16th day\[dq] .EE .PP Group postings from the start of wednesday to end of the following tuesday (N is both (inclusive) start date and (exclusive) end date): .IP .EX $ hledger register checking \-p \[dq]every 3rd day of week\[dq] .EE .SS Multiple weekday intervals This special form is also supported: .IP \[bu] 2 \f[CR]every WEEKDAYNAME,WEEKDAYNAME,...\f[R] (full or three\-letter english weekday names, case insensitive) .PP Also, \f[CR]weekday\f[R] and \f[CR]weekendday\f[R] are shorthand for \f[CR]mon,tue,wed,thu,fri\f[R] and \f[CR]sat,sun\f[R]. .PP This is mainly intended for use with \f[CR]\-\-forecast\f[R], to generate periodic transactions on arbitrary days of the week. It may be less useful with \f[CR]\-p\f[R], since it divides each week into subperiods of unequal length, which is unusual. (Related: #1632) .PP Examples: .PP .TS tab(@); lw(17.8n) lw(52.2n). T{ \f[CR]\-p \[dq]every mon,wed,fri\[dq]\f[R] T}@T{ dates will be Mon, Wed, Fri; periods will be Mon\-Tue, Wed\-Thu, Fri\-Sun T} T{ \f[CR]\-p \[dq]every weekday\[dq]\f[R] T}@T{ dates will be Mon, Tue, Wed, Thu, Fri; periods will be Mon, Tue, Wed, Thu, Fri\-Sun T} T{ \f[CR]\-p \[dq]every weekendday\[dq]\f[R] T}@T{ dates will be Sat, Sun; periods will be Sat, Sun\-Fri T} .TE .SH Depth With the \f[CR]\-\-depth NUM\f[R] option (short form: \f[CR]\-NUM\f[R]), reports will show accounts only to the specified depth, hiding deeper subaccounts. Use this when you want a summary with less detail. This flag has the same effect as a \f[CR]depth:\f[R] query argument: \f[CR]depth:2\f[R], \f[CR]\-\-depth=2\f[R] or \f[CR]\-2\f[R] are equivalent. .SH Queries One of hledger\[aq]s strengths is being able to quickly report on a precise subset of your data. Most hledger commands accept query arguments, to restrict their scope. Multiple query terms can be provided to build up a more complex query. .IP \[bu] 2 By default, a query term is interpreted as a case\-insensitive substring pattern for matching account names: .RS 2 .PP \f[CR]car:fuel\f[R] .PD 0 .P .PD \f[CR]dining groceries\f[R] .PD 0 .P .PD .RE .IP \[bu] 2 Patterns containing spaces or other special characters must be enclosed in single or double quotes: .RS 2 .PP \f[CR]\[aq]personal care\[aq]\f[R] .PD 0 .P .PD .RE .IP \[bu] 2 These patterns are actually regular expressions, so you can add regexp metacharacters for more precision (see \[dq]Regular expressions\[dq] above for details): .RS 2 .PP \f[CR]\[aq]\[ha]expenses\[rs]b\[aq]\f[R] .PD 0 .P .PD \f[CR]\[aq]food$\[aq]\f[R] .PD 0 .P .PD \f[CR]\[aq]fuel|repair\[aq]\f[R] .PD 0 .P .PD \f[CR]\[aq]accounts (payable|receivable)\[aq]\f[R] .PD 0 .P .PD .RE .IP \[bu] 2 To match something other than account name, add one of the query type prefixes described in \[dq]Query types\[dq] below: .RS 2 .PP \f[CR]date:202312\-\f[R] .PD 0 .P .PD \f[CR]status:\f[R] .PD 0 .P .PD \f[CR]desc:amazon\f[R] .PD 0 .P .PD \f[CR]cur:USD\f[R] .PD 0 .P .PD \f[CR]cur:\[rs]\[rs]$\f[R] .PD 0 .P .PD \f[CR]amt:\[aq]>0\[aq]\f[R] .PD 0 .P .PD .RE .IP \[bu] 2 Add a \f[CR]not:\f[R] prefix to negate a term: .RS 2 .PP \f[CR]not:status:\[aq]*\[aq]\f[R] .PD 0 .P .PD \f[CR]not:desc:\[aq]opening|closing\[aq]\f[R] .PD 0 .P .PD \f[CR]not:cur:USD\f[R] .PD 0 .P .PD .RE .IP \[bu] 2 Terms with different types are AND\-ed, terms with the same type are OR\-ed (mostly; see \[dq]Combining query terms\[dq] below). The following query: .RS 2 .PP \f[CR]date:2022 desc:amazon desc:amzn\f[R] .PP is interpreted as: .PP \f[I]date is in 2022 AND ( transaction description contains \[dq]amazon\[dq] OR \[dq]amzn\[dq] )\f[R] .RE .SS Query types Here are the types of query term available. Remember these can also be prefixed with \f[B]\f[CB]not:\f[B]\f[R] to convert them into a negative match. .PP \f[B]\f[CB]acct:REGEX\f[B]\f[R] or \f[B]\f[CB]REGEX\f[B]\f[R] .PD 0 .P .PD Match account names containing this case insensitive regular expression. This is the default query type, so we usually don\[aq]t bother writing the \[dq]acct:\[dq] prefix. .PP \f[B]\f[CB]amt:N, amt:N, amt:>=N\f[B]\f[R] .PD 0 .P .PD Match postings with a single\-commodity amount equal to, less than, or greater than N. (Postings with multi\-commodity amounts are not tested and will always match.) The comparison has two modes: if N is preceded by a + or \- sign (or is 0), the two signed numbers are compared. Otherwise, the absolute magnitudes are compared, ignoring sign. .PP \f[B]\f[CB]code:REGEX\f[B]\f[R] .PD 0 .P .PD Match by transaction code (eg check number). .PP \f[B]\f[CB]cur:REGEX\f[B]\f[R] .PD 0 .P .PD Match postings or transactions including any amounts whose currency/commodity symbol is fully matched by REGEX. (For a partial match, use \f[CR].*REGEX.*\f[R]). Note, to match special characters which are regex\-significant, you need to escape them with \f[CR]\[rs]\f[R]. And for characters which are significant to your shell you may need one more level of escaping. So eg to match the dollar sign: .PD 0 .P .PD \f[CR]hledger print cur:\[rs]\[rs]$\f[R]. .PP \f[B]\f[CB]desc:REGEX\f[B]\f[R] .PD 0 .P .PD Match transaction descriptions. .PP \f[B]\f[CB]date:PERIODEXPR\f[B]\f[R] .PD 0 .P .PD Match dates (or with the \f[CR]\-\-date2\f[R] flag, secondary dates) within the specified period. PERIODEXPR is a period expression with no report interval. Examples: .PD 0 .P .PD \f[CR]date:2016\f[R], \f[CR]date:thismonth\f[R], \f[CR]date:2/1\-2/15\f[R], \f[CR]date:2021\-07\-27..nextquarter\f[R]. .PP \f[B]\f[CB]date2:PERIODEXPR\f[B]\f[R] .PD 0 .P .PD Match secondary dates within the specified period (independent of the \f[CR]\-\-date2\f[R] flag). .PP \f[B]\f[CB]depth:N\f[B]\f[R] .PD 0 .P .PD Match (or display, depending on command) accounts at or above this depth. .PP \f[B]\f[CB]expr:\[dq]TERM AND NOT (TERM OR TERM)\[dq]\f[B]\f[R] (eg) .PD 0 .P .PD Match with a boolean combination of queries (which must be enclosed in quotes). See Combining query terms below. .PP \f[B]\f[CB]note:REGEX\f[B]\f[R] .PD 0 .P .PD Match transaction notes (the part of the description right of \f[CR]|\f[R], or the whole description if there\[aq]s no \f[CR]|\f[R]). .PP \f[B]\f[CB]payee:REGEX\f[B]\f[R] .PD 0 .P .PD Match transaction payee/payer names (the part of the description left of \f[CR]|\f[R], or the whole description if there\[aq]s no \f[CR]|\f[R]). .PP \f[B]\f[CB]real:, real:0\f[B]\f[R] .PD 0 .P .PD Match real or virtual postings respectively. .PP \f[B]\f[CB]status:, status:!, status:*\f[B]\f[R] .PD 0 .P .PD Match unmarked, pending, or cleared transactions respectively. .PP \f[B]\f[CB]type:TYPECODES\f[B]\f[R] .PD 0 .P .PD Match by account type (see Declaring accounts > Account types). \f[CR]TYPECODES\f[R] is one or more of the single\-letter account type codes \f[CR]ALERXCV\f[R], case insensitive. Note \f[CR]type:A\f[R] and \f[CR]type:E\f[R] will also match their respective subtypes \f[CR]C\f[R] (Cash) and \f[CR]V\f[R] (Conversion). Certain kinds of account alias can disrupt account types, see Rewriting accounts > Aliases and account types. .PP \f[B]\f[CB]tag:REGEX[=REGEX]\f[B]\f[R] .PD 0 .P .PD Match by tag name, and optionally also by tag value. (To match only by value, use \f[CR]tag:.=REGEX\f[R].) .PP When querying by tag, note that: .IP \[bu] 2 Accounts also inherit the tags of their parent accounts .IP \[bu] 2 Postings also inherit the tags of their account and their transaction .IP \[bu] 2 Transactions also acquire the tags of their postings. .PP (\f[B]\f[CB]inacct:ACCTNAME\f[B]\f[R] .PD 0 .P .PD A special query term used automatically in hledger\-web only: tells hledger\-web to show the transaction register for an account.) .SS Combining query terms When given multiple space\-separated query terms, most commands select things which match: .IP \[bu] 2 any of the description terms AND .IP \[bu] 2 any of the account terms AND .IP \[bu] 2 any of the status terms AND .IP \[bu] 2 all the other terms. .PP The print command is a little different, showing transactions which: .IP \[bu] 2 match any of the description terms AND .IP \[bu] 2 have any postings matching any of the positive account terms AND .IP \[bu] 2 have no postings matching any of the negative account terms AND .IP \[bu] 2 match all the other terms. .PP We also support more complex boolean queries with the \[aq]expr:\[aq] prefix. This allows one to combine queries using one of three operators: AND, OR, and NOT, where NOT is different syntax for \[aq]not:\[aq]. .PP Examples of such queries are: .IP \[bu] 2 Match transactions with \[aq]cool\[aq] in the description AND with the \[aq]A\[aq] tag .RS 2 .PP \f[CR]expr:\[dq]desc:cool AND tag:A\[dq]\f[R] .RE .IP \[bu] 2 Match transactions NOT to the \[aq]expenses:food\[aq] account OR with the \[aq]A\[aq] tag .RS 2 .PP \f[CR]expr:\[dq]NOT expenses:food OR tag:A\[dq]\f[R] .RE .IP \[bu] 2 Match transactions NOT involving the \[aq]expenses:food\[aq] account OR with the \[aq]A\[aq] tag AND involving the \[aq]expenses:drink\[aq] account. (the AND is implicitly added by space\-separation, following the rules above) .RS 2 .PP \f[CR]expr:\[dq]expenses:food OR (tag:A expenses:drink)\[dq]\f[R] .RE .SS Queries and command options Some queries can also be expressed as command\-line options: \f[CR]depth:2\f[R] is equivalent to \f[CR]\-\-depth 2\f[R], \f[CR]date:2023\f[R] is equivalent to \f[CR]\-p 2023\f[R], etc. When you mix command options and query arguments, generally the resulting query is their intersection. .SS Queries and valuation When amounts are converted to other commodities in cost or value reports, \f[CR]cur:\f[R] and \f[CR]amt:\f[R] match the old commodity symbol and the old amount quantity, not the new ones (except in hledger 1.22.0 where it\[aq]s reversed, see #1625). .SS Querying with account aliases When account names are rewritten with \f[CR]\-\-alias\f[R] or \f[CR]alias\f[R], note that \f[CR]acct:\f[R] will match either the old or the new account name. .SS Querying with cost or value When amounts are converted to other commodities in cost or value reports, note that \f[CR]cur:\f[R] matches the new commodity symbol, and not the old one, and \f[CR]amt:\f[R] matches the new quantity, and not the old one. Note: this changed in hledger 1.22, previously it was the reverse, see the discussion at #1625. .SH Pivoting Normally, hledger groups and sums amounts within each account. The \f[CR]\-\-pivot FIELD\f[R] option substitutes some other transaction field for account names, causing amounts to be grouped and summed by that field\[aq]s value instead. FIELD can be any of the transaction fields \f[CR]acct\f[R], \f[CR]status\f[R], \f[CR]code\f[R], \f[CR]desc\f[R], \f[CR]payee\f[R], \f[CR]note\f[R], or a tag name. When pivoting on a tag and a posting has multiple values of that tag, only the first value is displayed. Values containing \f[CR]colon:separated:parts\f[R] will be displayed hierarchically, like account names. Multiple, colon\-delimited fields can be pivoted simultaneously, generating a hierarchical account name. .PP Some examples: .IP .EX 2016/02/16 Yearly Dues Payment assets:bank account 2 EUR income:dues \-2 EUR ; member: John Doe, kind: Lifetime .EE .PP Normal balance report showing account names: .IP .EX $ hledger balance 2 EUR assets:bank account \-2 EUR income:dues \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP Pivoted balance report, using member: tag values instead: .IP .EX $ hledger balance \-\-pivot member 2 EUR \-2 EUR John Doe \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP One way to show only amounts with a member: value (using a query): .IP .EX $ hledger balance \-\-pivot member tag:member=. \-2 EUR John Doe \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \-2 EUR .EE .PP Another way (the acct: query matches against the pivoted \[dq]account name\[dq]): .IP .EX $ hledger balance \-\-pivot member acct:. \-2 EUR John Doe \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \-2 EUR .EE .PP Hierarchical reports can be generated with multiple pivots: .IP .EX $ hledger balance Income:Dues \-\-pivot kind:member \-2 EUR Lifetime:John Doe \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \-2 EUR .EE .SH Generating data hledger has several features for generating data, such as: .IP \[bu] 2 Periodic transaction rules can generate single or repeating transactions following a template. These are usually dated in the future, eg to help with forecasting. They are activated by the \f[CR]\-\-forecast\f[R] option. .IP \[bu] 2 The balance command\[aq]s \f[CR]\-\-budget\f[R] option uses these same periodic rules to generate goals for the budget report. .IP \[bu] 2 Auto posting rules can generate extra postings on certain matched transactions. They are always applied to forecast transactions; with the \f[CR]\-\-auto\f[R] flag they are applied to transactions recorded in the journal as well. .IP \[bu] 2 The \f[CR]\-\-infer\-equity\f[R] flag infers missing conversion equity postings from \[at]/\[at]\[at] costs. And the inverse \f[CR]\-\-infer\-costs\f[R] flag infers missing \[at]/\[at]\[at] costs from conversion equity postings. .PP Generated data of this kind is temporary, existing only at report time. But you can see it in the output of \f[CR]hledger print\f[R], and you can save that to your journal, in effect converting it from temporary generated data to permanent recorded data. This could be useful as a data entry aid. .PP If you are wondering what data is being generated and why, add the \f[CR]\-\-verbose\-tags\f[R] flag. In \f[CR]hledger print\f[R] output you will see extra tags like \f[CR]generated\-transaction\f[R], \f[CR]generated\-posting\f[R], and \f[CR]modified\f[R] on generated/modified data. Also, even without \f[CR]\-\-verbose\-tags\f[R], generated data always has equivalen hidden tags (with an underscore prefix), so eg you could match generated transactions with \f[CR]tag:_generated\-transaction\f[R]. .SH Forecasting Forecasting, or speculative future reporting, can be useful for estimating future balances, or for exploring different future scenarios. .PP The simplest and most flexible way to do it with hledger is to manually record a bunch of future\-dated transactions. You could keep these in a separate \f[CR]future.journal\f[R] and include that with \f[CR]\-f\f[R] only when you want to see them. .SS \-\-forecast There is another way: with the \f[CR]\-\-forecast\f[R] option, hledger can generate temporary \[dq]forecast transactions\[dq] for reporting purposes, according to periodic transaction rules defined in the journal. Each rule can generate multiple recurring transactions, so by changing one rule you can change many forecasted transactions. .PP Forecast transactions usually start after ordinary transactions end. By default, they begin after your latest\-dated ordinary transaction, or today, whichever is later, and they end six months from today. (The exact rules are a little more complicated, and are given below.) .PP This is the \[dq]forecast period\[dq], which need not be the same as the report period. You can override it \- eg to forecast farther into the future, or to force forecast transactions to overlap your ordinary transactions \- by giving the \-\-forecast option a period expression argument, like \f[CR]\-\-forecast=..2099\f[R] or \f[CR]\-\-forecast=2023\-02\-15..\f[R]. Note that the \f[CR]=\f[R] is required. .SS Inspecting forecast transactions \f[CR]print\f[R] is the best command for inspecting and troubleshooting forecast transactions. Eg: .IP .EX \[ti] monthly from 2022\-12\-20 rent assets:bank:checking expenses:rent $1000 .EE .IP .EX $ hledger print \-\-forecast \-\-today=2023/4/21 2023\-05\-20 rent ; generated\-transaction: \[ti] monthly from 2022\-12\-20 assets:bank:checking expenses:rent $1000 2023\-06\-20 rent ; generated\-transaction: \[ti] monthly from 2022\-12\-20 assets:bank:checking expenses:rent $1000 2023\-07\-20 rent ; generated\-transaction: \[ti] monthly from 2022\-12\-20 assets:bank:checking expenses:rent $1000 2023\-08\-20 rent ; generated\-transaction: \[ti] monthly from 2022\-12\-20 assets:bank:checking expenses:rent $1000 2023\-09\-20 rent ; generated\-transaction: \[ti] monthly from 2022\-12\-20 assets:bank:checking expenses:rent $1000 .EE .PP Here there are no ordinary transactions, so the forecasted transactions begin on the first occurence after today\[aq]s date. (You won\[aq]t normally use \f[CR]\-\-today\f[R]; it\[aq]s just to make these examples reproducible.) .SS Forecast reports Forecast transactions affect all reports, as you would expect. Eg: .IP .EX $ hledger areg rent \-\-forecast \-\-today=2023/4/21 Transactions in expenses:rent and subaccounts: 2023\-05\-20 rent as:ba:checking $1000 $1000 2023\-06\-20 rent as:ba:checking $1000 $2000 2023\-07\-20 rent as:ba:checking $1000 $3000 2023\-08\-20 rent as:ba:checking $1000 $4000 2023\-09\-20 rent as:ba:checking $1000 $5000 .EE .IP .EX $ hledger bal \-M expenses \-\-forecast \-\-today=2023/4/21 Balance changes in 2023\-05\-01..2023\-09\-30: || May Jun Jul Aug Sep ===============++=================================== expenses:rent || $1000 $1000 $1000 $1000 $1000 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || $1000 $1000 $1000 $1000 $1000 .EE .SS Forecast tags Forecast transactions generated by \-\-forecast have a hidden tag, \f[CR]_generated\-transaction\f[R]. So if you ever need to match forecast transactions, you could use \f[CR]tag:_generated\-transaction\f[R] (or just \f[CR]tag:generated\f[R]) in a query. .PP For troubleshooting, you can add the \f[CR]\-\-verbose\-tags\f[R] flag. Then, visible \f[CR]generated\-transaction\f[R] tags will be added also, so you can view them with the \f[CR]print\f[R] command. Their value indicates which periodic rule was responsible. .SS Forecast period, in detail Forecast start/end dates are chosen so as to do something useful by default in almost all situations, while also being flexible. Here are (with luck) the exact rules, to help with troubleshooting: .PP The forecast period starts on: .IP \[bu] 2 the later of .RS 2 .IP \[bu] 2 the start date in the periodic transaction rule .IP \[bu] 2 the start date in \f[CR]\-\-forecast\f[R]\[aq]s argument .RE .IP \[bu] 2 otherwise (if those are not available): the later of .RS 2 .IP \[bu] 2 the report start date specified with \f[CR]\-b\f[R]/\f[CR]\-p\f[R]/\f[CR]date:\f[R] .IP \[bu] 2 the day after the latest ordinary transaction in the journal .RE .IP \[bu] 2 otherwise (if none of these are available): today. .PP The forecast period ends on: .IP \[bu] 2 the earlier of .RS 2 .IP \[bu] 2 the end date in the periodic transaction rule .IP \[bu] 2 the end date in \f[CR]\-\-forecast\f[R]\[aq]s argument .RE .IP \[bu] 2 otherwise: the report end date specified with \f[CR]\-e\f[R]/\f[CR]\-p\f[R]/\f[CR]date:\f[R] .IP \[bu] 2 otherwise: 180 days (\[ti]6 months) from today. .SS Forecast troubleshooting When \-\-forecast is not doing what you expect, one of these tips should help: .IP \[bu] 2 Remember to use the \f[CR]\-\-forecast\f[R] option. .IP \[bu] 2 Remember to have at least one periodic transaction rule in your journal. .IP \[bu] 2 Test with \f[CR]print \-\-forecast\f[R]. .IP \[bu] 2 Check for typos or too\-restrictive start/end dates in your periodic transaction rule. .IP \[bu] 2 Leave at least 2 spaces between the rule\[aq]s period expression and description fields. .IP \[bu] 2 Check for future\-dated ordinary transactions suppressing forecasted transactions. .IP \[bu] 2 Try setting explicit report start and/or end dates with \f[CR]\-b\f[R], \f[CR]\-e\f[R], \f[CR]\-p\f[R] or \f[CR]date:\f[R] .IP \[bu] 2 Try adding the \f[CR]\-E\f[R] flag to encourage display of empty periods/zero transactions. .IP \[bu] 2 Try setting explicit forecast start and/or end dates with \f[CR]\-\-forecast=START..END\f[R] .IP \[bu] 2 Consult Forecast period, in detail, above. .IP \[bu] 2 Check inside the engine: add \f[CR]\-\-debug=2\f[R] (eg). .SH Budgeting With the balance command\[aq]s \f[CR]\-\-budget\f[R] report, each periodic transaction rule generates recurring budget goals in specified accounts, and goals and actual performance can be compared. See the balance command\[aq]s doc below. .PP You can generate budget goals and forecast transactions at the same time, from the same or different periodic transaction rules: \f[CR]hledger bal \-M \-\-budget \-\-forecast ...\f[R] .PP See also: Budgeting and Forecasting. .SH Cost reporting In some transactions \- for example a currency conversion, or a purchase or sale of stock \- one commodity is exchanged for another. In these transactions there is a conversion rate, also called the cost (when buying) or selling price (when selling). In hledger docs we just say \[dq]cost\[dq], for convenience; feel free to mentally translate to \[dq]conversion rate\[dq] or \[dq]selling price\[dq] if helpful. .SS Recording costs We\[aq]ll explore several ways of recording transactions involving costs. These are also summarised at hledger Cookbook > Cost notation. .PP Costs can be recorded explicitly in the journal, using the \f[CR]\[at] UNITCOST\f[R] or \f[CR]\[at]\[at] TOTALCOST\f[R] notation described in Journal > Costs: .PP \f[B]Variant 1\f[R] .IP .EX 2022\-01\-01 assets:dollars $\-135 assets:euros €100 \[at] $1.35 ; $1.35 per euro (unit cost) .EE .PP \f[B]Variant 2\f[R] .IP .EX 2022\-01\-01 assets:dollars $\-135 assets:euros €100 \[at]\[at] $135 ; $135 total cost .EE .PP Typically, writing the unit cost (variant 1) is preferable; it can be more effort, requiring more attention to decimal digits; but it reveals the per\-unit cost basis, and makes stock sales easier. .PP Costs can also be left implicit, and hledger will infer the cost that is consistent with a balanced transaction: .PP \f[B]Variant 3\f[R] .IP .EX 2022\-01\-01 assets:dollars $\-135 assets:euros €100 .EE .PP Here, hledger will attach a \f[CR]\[at]\[at] €100\f[R] cost to the first amount (you can see it with \f[CR]hledger print \-x\f[R]). This form looks convenient, but there are downsides: .IP \[bu] 2 It sacrifices some error checking. For example, if you accidentally wrote €10 instead of €100, hledger would not be able to detect the mistake. .IP \[bu] 2 It is sensitive to the order of postings \- if they were reversed, a different entry would be inferred and reports would be different. .IP \[bu] 2 The per\-unit cost basis is not easy to read. .PP So generally this kind of entry is not recommended. You can make sure you have none of these by using \f[CR]\-s\f[R] (strict mode), or by running \f[CR]hledger check balanced\f[R]. .SS Reporting at cost Now when you add the \f[CR]\-B\f[R]/\f[CR]\-\-cost\f[R] flag to reports (\[dq]B\[dq] is from Ledger\[aq]s \-B/\-\-basis/\-\-cost flag), any amounts which have been annotated with costs will be converted to their cost\[aq]s commodity (in the report output). Ie they will be displayed \[dq]at cost\[dq] or \[dq]at sale price\[dq]. .PP Some things to note: .IP \[bu] 2 Costs are attached to specific posting amounts in specific transactions, and once recorded they do not change. This contrasts with market prices, which are ambient and fluctuating. .IP \[bu] 2 Conversion to cost is performed before conversion to market value (described below). .SS Equity conversion postings There is a problem with the entries above \- they are not conventional Double Entry Bookkeeping (DEB) notation, and because of the \[dq]magical\[dq] transformation of one commodity into another, they cause an imbalance in the Accounting Equation. This shows up as a non\-zero grand total in balance reports like \f[CR]hledger bse\f[R]. .PP For most hledger users, this doesn\[aq]t matter in practice and can safely be ignored ! But if you\[aq]d like to learn more, keep reading. .PP Conventional DEB uses an extra pair of equity postings to balance the transaction. Of course you can do this in hledger as well: .PP \f[B]Variant 4\f[R] .IP .EX 2022\-01\-01 assets:dollars $\-135 assets:euros €100 equity:conversion $135 equity:conversion €\-100 .EE .PP Now the transaction is perfectly balanced according to standard DEB, and \f[CR]hledger bse\f[R]\[aq]s total will not be disrupted. .PP And, hledger can still infer the cost for cost reporting, but it\[aq]s not done by default \- you must add the \f[CR]\-\-infer\-costs\f[R] flag like so: .IP .EX $ hledger print \-\-infer\-costs 2022\-01\-01 one hundred euros purchased at $1.35 each assets:dollars $\-135 \[at]\[at] €100 assets:euros €100 equity:conversion $135 equity:conversion €\-100 .EE .IP .EX $ hledger bal \-\-infer\-costs \-B €\-100 assets:dollars €100 assets:euros \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP Here are some downsides of this kind of entry: .IP \[bu] 2 The per\-unit cost basis is not easy to read. .IP \[bu] 2 Instead of \f[CR]\-B\f[R] you must remember to type \f[CR]\-B \-\-infer\-costs\f[R]. .IP \[bu] 2 \f[CR]\-\-infer\-costs\f[R] works only where hledger can identify the two equity:conversion postings and match them up with the two non\-equity postings. So writing the journal entry in a particular format becomes more important. More on this below. .SS Inferring equity conversion postings Can we go in the other direction ? Yes, if you have transactions written with the \[at]/\[at]\[at] cost notation, hledger can infer the missing equity postings, if you add the \f[CR]\-\-infer\-equity\f[R] flag. Eg: .IP .EX 2022\-01\-01 assets:dollars \-$135 assets:euros €100 \[at] $1.35 .EE .IP .EX $ hledger print \-\-infer\-equity 2022\-01\-01 assets:dollars $\-135 assets:euros €100 \[at] $1.35 equity:conversion:$\-€:€ €\-100 equity:conversion:$\-€:$ $135.00 .EE .PP The equity account names will be \[dq]equity:conversion:A\-B:A\[dq] and \[dq]equity:conversion:A\-B:B\[dq] where A is the alphabetically first commodity symbol. You can customise the \[dq]equity:conversion\[dq] part by declaring an account with the \f[CR]V\f[R]/\f[CR]Conversion\f[R] account type. .SS Combining costs and equity conversion postings Finally, you can use both the \[at]/\[at]\[at] cost notation and equity postings at the same time. This in theory gives the best of all worlds \- preserving the accounting equation, revealing the per\-unit cost basis, and providing more flexibility in how you write the entry: .PP \f[B]Variant 5\f[R] .IP .EX 2022\-01\-01 one hundred euros purchased at $1.35 each assets:dollars $\-135 equity:conversion $135 equity:conversion €\-100 assets:euros €100 \[at] $1.35 .EE .PP All the other variants above can (usually) be rewritten to this final form with: .IP .EX $ hledger print \-x \-\-infer\-costs \-\-infer\-equity .EE .PP Downsides: .IP \[bu] 2 This was added in hledger\-1.29 and is still somewhat experimental. .IP \[bu] 2 The precise format of the journal entry becomes more important. If hledger can\[aq]t detect and match up the cost and equity postings, it will give a transaction balancing error. .IP \[bu] 2 The add command does not yet accept this kind of entry (#2056). .IP \[bu] 2 This is the most verbose form. .SS Requirements for detecting equity conversion postings \f[CR]\-\-infer\-costs\f[R] has certain requirements (unlike \f[CR]\-\-infer\-equity\f[R], which always works). It will infer costs only in transactions with: .IP \[bu] 2 Two non\-equity postings, in different commodities. Their order is significant: the cost will be added to the first of them. .IP \[bu] 2 Two postings to equity conversion accounts, next to one another, which balance the two non\-equity postings. This balancing is checked to the same precision (number of decimal places) used in the conversion posting\[aq]s amount. Equity conversion accounts are: .RS 2 .IP \[bu] 2 any accounts declared with account type \f[CR]V\f[R]/\f[CR]Conversion\f[R], or their subaccounts .IP \[bu] 2 otherwise, accounts named \f[CR]equity:conversion\f[R], \f[CR]equity:trade\f[R], or \f[CR]equity:trading\f[R], or their subaccounts. .RE .PP And multiple such four\-posting groups can coexist within a single transaction. When \f[CR]\-\-infer\-costs\f[R] fails, it does not infer a cost in that transaction, and does not raise an error (ie, it infers costs where it can). .PP Reading variant 5 journal entries, combining cost notation and equity postings, has all the same requirements. When reading such an entry fails, hledger raises an \[dq]unbalanced transaction\[dq] error. .SS Infer cost and equity by default ? Should \f[CR]\-\-infer\-costs\f[R] and \f[CR]\-\-infer\-equity\f[R] be enabled by default ? Try using them always, eg with a shell alias: .IP .EX alias h=\[dq]hledger \-\-infer\-equity \-\-infer\-costs\[dq] .EE .PP and let us know what problems you find. .PP .SH Value reporting Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), and/or to market value (using some market price on a certain date). This is controlled by the \f[CR]\-\-value=TYPE[,COMMODITY]\f[R] option, which will be described below. We also provide the simpler \f[CR]\-V\f[R] and \f[CR]\-X COMMODITY\f[R] options, and often one of these is all you need: .SS \-V: Value The \f[CR]\-V/\-\-market\f[R] flag converts amounts to market value in their default \f[I]valuation commodity\f[R], using the market prices in effect on the \f[I]valuation date(s)\f[R], if any. More on these in a minute. .SS \-X: Value in specified commodity The \f[CR]\-X/\-\-exchange=COMM\f[R] option is like \f[CR]\-V\f[R], except you tell it which currency you want to convert to, and it tries to convert everything to that. .SS Valuation date Market prices can change from day to day. hledger will use the prices on a particular valuation date (or on more than one date). By default hledger uses \[dq]end\[dq] dates for valuation. More specifically: .IP \[bu] 2 For single period reports (including normal print and register reports): .RS 2 .IP \[bu] 2 If an explicit report end date is specified, that is used .IP \[bu] 2 Otherwise the latest transaction date or P directive date is used (even if it\[aq]s in the future) .RE .IP \[bu] 2 For multiperiod reports, each period is valued on its last day. .PP This can be customised with the \-\-value option described below, which can select either \[dq]then\[dq], \[dq]end\[dq], \[dq]now\[dq], or \[dq]custom\[dq] dates. (Note, this has a bug in hledger\-ui <=1.31: turning on valuation with the \f[CR]V\f[R] key always resets it to \[dq]end\[dq].) .SS Finding market price To convert a commodity A to its market value in another commodity B, hledger looks for a suitable market price (exchange rate) as follows, in this order of preference: .IP "1." 3 A \f[I]declared market price\f[R] or \f[I]inferred market price\f[R]: A\[aq]s latest market price in B on or before the valuation date as declared by a P directive, or (with the \f[CR]\-\-infer\-market\-prices\f[R] flag) inferred from costs. \ .IP "2." 3 A \f[I]reverse market price\f[R]: the inverse of a declared or inferred market price from B to A. .IP "3." 3 A \f[I]forward chain of market prices\f[R]: a synthetic price formed by combining the shortest chain of \[dq]forward\[dq] (only 1 above) market prices, leading from A to B. .IP "4." 3 \f[I]Any chain of market prices\f[R]: a chain of any market prices, including both forward and reverse prices (1 and 2 above), leading from A to B. .PP There is a limit to the length of these price chains; if hledger reaches that length without finding a complete chain or exhausting all possibilities, it will give up (with a \[dq]gave up\[dq] message visible in \f[CR]\-\-debug=2\f[R] output). That limit is currently 1000. .PP Amounts for which no suitable market price can be found, are not converted. .SS \-\-infer\-market\-prices: market prices from transactions Normally, market value in hledger is fully controlled by, and requires, P directives in your journal. Since adding and updating those can be a chore, and since transactions usually take place at close to market value, why not use the recorded costs as additional market prices (as Ledger does) ? Adding the \f[CR]\-\-infer\-market\-prices\f[R] flag to \f[CR]\-V\f[R], \f[CR]\-X\f[R] or \f[CR]\-\-value\f[R] enables this. .PP So for example, \f[CR]hledger bs \-V \-\-infer\-market\-prices\f[R] will get market prices both from P directives and from transactions. If both occur on the same day, the P directive takes precedence. .PP There is a downside: value reports can sometimes be affected in confusing/undesired ways by your journal entries. If this happens to you, read all of this Value reporting section carefully, and try adding \f[CR]\-\-debug\f[R] or \f[CR]\-\-debug=2\f[R] to troubleshoot. .PP \f[CR]\-\-infer\-market\-prices\f[R] can infer market prices from: .IP \[bu] 2 multicommodity transactions with explicit prices (\f[CR]\[at]\f[R]/\f[CR]\[at]\[at]\f[R]) .IP \[bu] 2 multicommodity transactions with implicit prices (no \f[CR]\[at]\f[R], two commodities, unbalanced). (With these, the order of postings matters. \f[CR]hledger print \-x\f[R] can be useful for troubleshooting.) .IP \[bu] 2 multicommodity transactions with equity postings, if cost is inferred with \f[CR]\-\-infer\-costs\f[R]. .PP There is a limitation (bug) currently: when a valuation commodity is not specified, prices inferred with \f[CR]\-\-infer\-market\-prices\f[R] do not help select a default valuation commodity, as \f[CR]P\f[R] prices would. So conversion might not happen because no valuation commodity was detected (\f[CR]\-\-debug=2\f[R] will show this). To be safe, specify the valuation commmodity, eg: .IP \[bu] 2 \f[CR]\-X EUR \-\-infer\-market\-prices\f[R], not \f[CR]\-V \-\-infer\-market\-prices\f[R] .IP \[bu] 2 \f[CR]\-\-value=then,EUR \-\-infer\-market\-prices\f[R], not \f[CR]\-\-value=then \-\-infer\-market\-prices\f[R] .PP Signed costs and market prices can be confusing. For reference, here is the current behaviour, since hledger 1.25. (If you think it should work differently, see #1870.) .IP .EX 2022\-01\-01 Positive Unit prices a A 1 b B \-1 \[at] A 1 2022\-01\-01 Positive Total prices a A 1 b B \-1 \[at]\[at] A 1 2022\-01\-02 Negative unit prices a A 1 b B 1 \[at] A \-1 2022\-01\-02 Negative total prices a A 1 b B 1 \[at]\[at] A \-1 2022\-01\-03 Double Negative unit prices a A \-1 b B \-1 \[at] A \-1 2022\-01\-03 Double Negative total prices a A \-1 b B \-1 \[at]\[at] A \-1 .EE .PP All of the transactions above are considered balanced (and on each day, the two transactions are considered equivalent). Here are the market prices inferred for B: .IP .EX $ hledger \-f\- \-\-infer\-market\-prices prices P 2022\-01\-01 B A 1 P 2022\-01\-01 B A 1.0 P 2022\-01\-02 B A \-1 P 2022\-01\-02 B A \-1.0 P 2022\-01\-03 B A \-1 P 2022\-01\-03 B A \-1.0 .EE .SS Valuation commodity \f[B]When you specify a valuation commodity (\f[CB]\-X COMM\f[B] or \f[CB]\-\-value TYPE,COMM\f[B]):\f[R] .PD 0 .P .PD hledger will convert all amounts to COMM, wherever it can find a suitable market price (including by reversing or chaining prices). .PP \f[B]When you leave the valuation commodity unspecified (\f[CB]\-V\f[B] or \f[CB]\-\-value TYPE\f[B]):\f[R] .PD 0 .P .PD For each commodity A, hledger picks a default valuation commodity as follows, in this order of preference: .IP "1." 3 The price commodity from the latest P\-declared market price for A on or before valuation date. .IP "2." 3 The price commodity from the latest P\-declared market price for A on any date. (Allows conversion to proceed when there are inferred prices before the valuation date.) .IP "3." 3 If there are no P directives at all (any commodity or date) and the \f[CR]\-\-infer\-market\-prices\f[R] flag is used: the price commodity from the latest transaction\-inferred price for A on or before valuation date. .PP This means: .IP \[bu] 2 If you have P directives, they determine which commodities \f[CR]\-V\f[R] will convert, and to what. .IP \[bu] 2 If you have no P directives, and use the \f[CR]\-\-infer\-market\-prices\f[R] flag, costs determine it. .PP Amounts for which no valuation commodity can be found are not converted. .SS Simple valuation examples Here are some quick examples of \f[CR]\-V\f[R]: .IP .EX ; one euro is worth this many dollars from nov 1 P 2016/11/01 € $1.10 ; purchase some euros on nov 3 2016/11/3 assets:euros €100 assets:checking ; the euro is worth fewer dollars by dec 21 P 2016/12/21 € $1.03 .EE .PP How many euros do I have ? .IP .EX $ hledger \-f t.j bal \-N euros €100 assets:euros .EE .PP What are they worth at end of nov 3 ? .IP .EX $ hledger \-f t.j bal \-N euros \-V \-e 2016/11/4 $110.00 assets:euros .EE .PP What are they worth after 2016/12/21 ? (no report end date specified, defaults to today) .IP .EX $ hledger \-f t.j bal \-N euros \-V $103.00 assets:euros .EE .SS \-\-value: Flexible valuation \f[CR]\-V\f[R] and \f[CR]\-X\f[R] are special cases of the more general \f[CR]\-\-value\f[R] option: .IP .EX \-\-value=TYPE[,COMM] TYPE is then, end, now or YYYY\-MM\-DD. COMM is an optional commodity symbol. Shows amounts converted to: \- default valuation commodity (or COMM) using market prices at posting dates \- default valuation commodity (or COMM) using market prices at period end(s) \- default valuation commodity (or COMM) using current market prices \- default valuation commodity (or COMM) using market prices at some date .EE .PP The TYPE part selects cost or value and valuation date: .TP \f[CR]\-\-value=then\f[R] Convert amounts to their value in the default valuation commodity, using market prices on each posting\[aq]s date. .TP \f[CR]\-\-value=end\f[R] Convert amounts to their value in the default valuation commodity, using market prices on the last day of the report period (or if unspecified, the journal\[aq]s end date); or in multiperiod reports, market prices on the last day of each subperiod. .TP \f[CR]\-\-value=now\f[R] Convert amounts to their value in the default valuation commodity using current market prices (as of when report is generated). .TP \f[CR]\-\-value=YYYY\-MM\-DD\f[R] Convert amounts to their value in the default valuation commodity using market prices on this date. .PP To select a different valuation commodity, add the optional \f[CR],COMM\f[R] part: a comma, then the target commodity\[aq]s symbol. Eg: \f[B]\f[CB]\-\-value=now,EUR\f[B]\f[R]. hledger will do its best to convert amounts to this commodity, deducing market prices as described above. .SS More valuation examples Here are some examples showing the effect of \f[CR]\-\-value\f[R], as seen with \f[CR]print\f[R]: .IP .EX P 2000\-01\-01 A 1 B P 2000\-02\-01 A 2 B P 2000\-03\-01 A 3 B P 2000\-04\-01 A 4 B 2000\-01\-01 (a) 1 A \[at] 5 B 2000\-02\-01 (a) 1 A \[at] 6 B 2000\-03\-01 (a) 1 A \[at] 7 B .EE .PP Show the cost of each posting: .IP .EX $ hledger \-f\- print \-\-cost 2000\-01\-01 (a) 5 B 2000\-02\-01 (a) 6 B 2000\-03\-01 (a) 7 B .EE .PP Show the value as of the last day of the report period (2000\-02\-29): .IP .EX $ hledger \-f\- print \-\-value=end date:2000/01\-2000/03 2000\-01\-01 (a) 2 B 2000\-02\-01 (a) 2 B .EE .PP With no report period specified, that shows the value as of the last day of the journal (2000\-03\-01): .IP .EX $ hledger \-f\- print \-\-value=end 2000\-01\-01 (a) 3 B 2000\-02\-01 (a) 3 B 2000\-03\-01 (a) 3 B .EE .PP Show the current value (the 2000\-04\-01 price is still in effect today): .IP .EX $ hledger \-f\- print \-\-value=now 2000\-01\-01 (a) 4 B 2000\-02\-01 (a) 4 B 2000\-03\-01 (a) 4 B .EE .PP Show the value on 2000/01/15: .IP .EX $ hledger \-f\- print \-\-value=2000\-01\-15 2000\-01\-01 (a) 1 B 2000\-02\-01 (a) 1 B 2000\-03\-01 (a) 1 B .EE .SS Interaction of valuation and queries When matching postings based on queries in the presence of valuation, the following happens. .IP "1." 3 The query is separated into two parts: .RS 4 .IP "1." 3 the currency (\f[CR]cur:\f[R]) or amount (\f[CR]amt:\f[R]). .IP "2." 3 all other parts. .RE .IP "2." 3 The postings are matched to the currency and amount queries based on pre\-valued amounts. .IP "3." 3 Valuation is applied to the postings. .IP "4." 3 The postings are matched to the other parts of the query based on post\-valued amounts. .PP See: 1625 .SS Effect of valuation on reports Here is a reference for how valuation is supposed to affect each part of hledger\[aq]s reports (and a glossary). (It\[aq]s wide, you\[aq]ll have to scroll sideways.) It may be useful when troubleshooting. If you find problems, please report them, ideally with a reproducible example. Related: #329, #1083. .PP .TS tab(@); lw(9.5n) lw(11.8n) lw(12.0n) lw(17.2n) lw(12.0n) lw(7.4n). T{ Report type T}@T{ \f[CR]\-B\f[R], \f[CR]\-\-cost\f[R] T}@T{ \f[CR]\-V\f[R], \f[CR]\-X\f[R] T}@T{ \f[CR]\-\-value=then\f[R] T}@T{ \f[CR]\-\-value=end\f[R] T}@T{ \f[CR]\-\-value=DATE\f[R], \f[CR]\-\-value=now\f[R] T} _ T{ \f[B]print\f[R] T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ posting amounts T}@T{ cost T}@T{ value at report end or today T}@T{ value at posting date T}@T{ value at report or journal end T}@T{ value at DATE/today T} T{ balance assertions/assignments T}@T{ unchanged T}@T{ unchanged T}@T{ unchanged T}@T{ unchanged T}@T{ unchanged T} T{ T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ \f[B]register\f[R] T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ starting balance (\-H) T}@T{ cost T}@T{ value at report or journal end T}@T{ valued at day each historical posting was made T}@T{ value at report or journal end T}@T{ value at DATE/today T} T{ starting balance (\-H) with report interval T}@T{ cost T}@T{ value at day before report or journal start T}@T{ valued at day each historical posting was made T}@T{ value at day before report or journal start T}@T{ value at DATE/today T} T{ posting amounts T}@T{ cost T}@T{ value at report or journal end T}@T{ value at posting date T}@T{ value at report or journal end T}@T{ value at DATE/today T} T{ summary posting amounts with report interval T}@T{ summarised cost T}@T{ value at period ends T}@T{ sum of postings in interval, valued at interval start T}@T{ value at period ends T}@T{ value at DATE/today T} T{ running total/average T}@T{ sum/average of displayed values T}@T{ sum/average of displayed values T}@T{ sum/average of displayed values T}@T{ sum/average of displayed values T}@T{ sum/average of displayed values T} T{ T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ \f[B]balance (bs, bse, cf, is)\f[R] T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ balance changes T}@T{ sums of costs T}@T{ value at report end or today of sums of postings T}@T{ value at posting date T}@T{ value at report or journal end of sums of postings T}@T{ value at DATE/today of sums of postings T} T{ budget amounts (\-\-budget) T}@T{ like balance changes T}@T{ like balance changes T}@T{ like balance changes T}@T{ like balances T}@T{ like balance changes T} T{ grand total T}@T{ sum of displayed values T}@T{ sum of displayed values T}@T{ sum of displayed valued T}@T{ sum of displayed values T}@T{ sum of displayed values T} T{ T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ \f[B]balance (bs, bse, cf, is) with report interval\f[R] T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} T{ starting balances (\-H) T}@T{ sums of costs of postings before report start T}@T{ value at report start of sums of all postings before report start T}@T{ sums of values of postings before report start at respective posting dates T}@T{ value at report start of sums of all postings before report start T}@T{ sums of postings before report start T} T{ balance changes (bal, is, bs \-\-change, cf \-\-change) T}@T{ sums of costs of postings in period T}@T{ same as \-\-value=end T}@T{ sums of values of postings in period at respective posting dates T}@T{ balance change in each period, valued at period ends T}@T{ value at DATE/today of sums of postings T} T{ end balances (bal \-H, is \-\-H, bs, cf) T}@T{ sums of costs of postings from before report start to period end T}@T{ same as \-\-value=end T}@T{ sums of values of postings from before period start to period end at respective posting dates T}@T{ period end balances, valued at period ends T}@T{ value at DATE/today of sums of postings T} T{ budget amounts (\-\-budget) T}@T{ like balance changes/end balances T}@T{ like balance changes/end balances T}@T{ like balance changes/end balances T}@T{ like balances T}@T{ like balance changes/end balances T} T{ row totals, row averages (\-T, \-A) T}@T{ sums, averages of displayed values T}@T{ sums, averages of displayed values T}@T{ sums, averages of displayed values T}@T{ sums, averages of displayed values T}@T{ sums, averages of displayed values T} T{ column totals T}@T{ sums of displayed values T}@T{ sums of displayed values T}@T{ sums of displayed values T}@T{ sums of displayed values T}@T{ sums of displayed values T} T{ grand total, grand average T}@T{ sum, average of column totals T}@T{ sum, average of column totals T}@T{ sum, average of column totals T}@T{ sum, average of column totals T}@T{ sum, average of column totals T} T{ T}@T{ T}@T{ T}@T{ T}@T{ T}@T{ T} .TE .PP \f[CR]\-\-cumulative\f[R] is omitted to save space, it works like \f[CR]\-H\f[R] but with a zero starting balance. .PP \f[B]Glossary:\f[R] .TP \f[I]cost\f[R] calculated using price(s) recorded in the transaction(s). .TP \f[I]value\f[R] market value using available market price declarations, or the unchanged amount if no conversion rate can be found. .TP \f[I]report start\f[R] the first day of the report period specified with \-b or \-p or date:, otherwise today. .TP \f[I]report or journal start\f[R] the first day of the report period specified with \-b or \-p or date:, otherwise the earliest transaction date in the journal, otherwise today. .TP \f[I]report end\f[R] the last day of the report period specified with \-e or \-p or date:, otherwise today. .TP \f[I]report or journal end\f[R] the last day of the report period specified with \-e or \-p or date:, otherwise the latest transaction date in the journal, otherwise today. .TP \f[I]report interval\f[R] a flag (\-D/\-W/\-M/\-Q/\-Y) or period expression that activates the report\[aq]s multi\-period mode (whether showing one or many subperiods). .SH PART 4: COMMANDS .SS Commands overview Here are the built\-in commands: .SS DATA ENTRY These data entry commands are the only ones which can modify your journal file. .IP \[bu] 2 add \- add transactions using terminal prompts .IP \[bu] 2 import \- add new transactions from other files, eg CSV files .SS DATA CREATION .IP \[bu] 2 close \- generate balance\-zeroing/restoring transactions .IP \[bu] 2 rewrite \- generate auto postings, like print \-\-auto .SS DATA MANAGEMENT .IP \[bu] 2 check \- check for various kinds of error in the data .IP \[bu] 2 diff \- compare account transactions in two journal files .SS REPORTS, FINANCIAL .IP \[bu] 2 aregister (areg) \- show transactions in a particular account .IP \[bu] 2 balancesheet (bs) \- show assets, liabilities and net worth .IP \[bu] 2 balancesheetequity (bse) \- show assets, liabilities and equity .IP \[bu] 2 cashflow (cf) \- show changes in liquid assets .IP \[bu] 2 incomestatement (is) \- show revenues and expenses .SS REPORTS, VERSATILE .IP \[bu] 2 balance (bal) \- show balance changes, end balances, budgets, gains.. .IP \[bu] 2 print \- show transactions or export journal data .IP \[bu] 2 register (reg) \- show postings in one or more accounts & running total .IP \[bu] 2 roi \- show return on investments .SS REPORTS, BASIC .IP \[bu] 2 accounts \- show account names .IP \[bu] 2 activity \- show bar charts of posting counts per period .IP \[bu] 2 codes \- show transaction codes .IP \[bu] 2 commodities \- show commodity/currency symbols .IP \[bu] 2 descriptions \- show transaction descriptions .IP \[bu] 2 files \- show input file paths .IP \[bu] 2 notes \- show note parts of transaction descriptions .IP \[bu] 2 payees \- show payee parts of transaction descriptions .IP \[bu] 2 prices \- show market prices .IP \[bu] 2 stats \- show journal statistics .IP \[bu] 2 tags \- show tag names .IP \[bu] 2 test \- run self tests .SS HELP .IP \[bu] 2 help \- show the hledger manual with info/man/pager .IP \[bu] 2 demo \- show small hledger demos in the terminal .PP \ .SS ADD\-ONS And here are some typical add\-on commands. Some of these are installed by the hledger\-install script. If installed, they will appear in hledger\[aq]s commands list: .IP \[bu] 2 ui \- run hledger\[aq]s terminal UI .IP \[bu] 2 web \- run hledger\[aq]s web UI .IP \[bu] 2 iadd \- add transactions using a TUI (currently hard to build) .IP \[bu] 2 interest \- generate interest transactions .IP \[bu] 2 stockquotes \- download market prices from AlphaVantage .IP \[bu] 2 Scripts and add\-ons \- check\-fancyassertions, edit, fifo, git, move, pijul, plot, and more.. .PP Next, each command is described in detail, in alphabetical order. .SS accounts Show account names. .PP This command lists account names. By default it shows all known accounts, either used in transactions or declared with account directives. .PP With query arguments, only matched account names and account names referenced by matched postings are shown. .PP Or it can show just the used accounts (\f[CR]\-\-used\f[R]/\f[CR]\-u\f[R]), the declared accounts (\f[CR]\-\-declared\f[R]/\f[CR]\-d\f[R]), the accounts declared but not used (\f[CR]\-\-unused\f[R]), the accounts used but not declared (\f[CR]\-\-undeclared\f[R]), or the first account matched by an account name pattern, if any (\f[CR]\-\-find\f[R]). .PP It shows a flat list by default. With \f[CR]\-\-tree\f[R], it uses indentation to show the account hierarchy. In flat mode you can add \f[CR]\-\-drop N\f[R] to omit the first few account name components. Account names can be depth\-clipped with \f[CR]depth:N\f[R] or \f[CR]\-\-depth N\f[R] or \f[CR]\-N\f[R]. .PP With \f[CR]\-\-types\f[R], it also shows each account\[aq]s type, if it\[aq]s known. (See Declaring accounts > Account types.) .PP With \f[CR]\-\-positions\f[R], it also shows the file and line number of each account\[aq]s declaration, if any, and the account\[aq]s overall declaration order; these may be useful when troubleshooting account display order. .PP With \f[CR]\-\-directives\f[R], it adds the \f[CR]account\f[R] keyword, showing valid account directives which can be pasted into a journal file. This is useful together with \f[CR]\-\-undeclared\f[R] when updating your account declarations to satisfy \f[CR]hledger check accounts\f[R]. .PP The \f[CR]\-\-find\f[R] flag can be used to look up a single account name, in the same way that the \f[CR]aregister\f[R] command does. It returns the alphanumerically\-first matched account name, or if none can be found, it fails with a non\-zero exit code. .PP Examples: .IP .EX $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts .EE .IP .EX $ hledger accounts \-\-undeclared \-\-directives >> $LEDGER_FILE $ hledger check accounts .EE .SS activity Show an ascii barchart of posting counts per interval. .PP The activity command displays an ascii histogram showing transaction counts by day, week, month or other reporting interval (by day is the default). With query arguments, it counts only matched transactions. .PP Examples: .IP .EX $ hledger activity \-\-quarterly 2008\-01\-01 ** 2008\-04\-01 ******* 2008\-07\-01 2008\-10\-01 ** .EE .SS add Prompt for transactions and add them to the journal. Any arguments will be used as default inputs for the first N prompts. .PP Many hledger users edit their journals directly with a text editor, or generate them from CSV. For more interactive data entry, there is the \f[CR]add\f[R] command, which prompts interactively on the console for new transactions, and appends them to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also \f[CR]import\f[R]). .PP To use it, just run \f[CR]hledger add\f[R] and follow the prompts. You can add as many transactions as you like; when you are finished, enter \f[CR].\f[R] or press control\-d or control\-c to exit. .PP Features: .IP \[bu] 2 add tries to provide useful defaults, using the most similar (by description) recent transaction (filtered by the query, if any) as a template. .IP \[bu] 2 You can also set the initial defaults with command line arguments. .IP \[bu] 2 Readline\-style edit keys can be used during data entry. .IP \[bu] 2 The tab key will auto\-complete whenever possible \- accounts, payees/descriptions, dates (\f[CR]yesterday\f[R], \f[CR]today\f[R], \f[CR]tomorrow\f[R]). If the input area is empty, it will insert the default value. .IP \[bu] 2 If the journal defines a default commodity, it will be added to any bare numbers entered. .IP \[bu] 2 A parenthesised transaction code may be entered following a date. .IP \[bu] 2 Comments and tags may be entered following a description or amount. .IP \[bu] 2 If you make a mistake, enter \f[CR]<\f[R] at any prompt to go one step backward. .IP \[bu] 2 Input prompts are displayed in a different colour when the terminal supports it. .PP Example (see https://hledger.org/add.html for a detailed tutorial): .IP .EX $ hledger add Adding transactions to journal file /src/hledger/examples/sample.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control\-d or control\-c. Date [2015/05/22]: Description: supermarket Account 1: expenses:food Amount 1: $10 Account 2: assets:checking Amount 2 [$\-10.0]: Account 3 (or . or enter to finish this transaction): . 2015/05/22 supermarket expenses:food $10 assets:checking $\-10.0 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl\-D/ctrl\-C to quit) Date [2015/05/22]: $ .EE .PP On Microsoft Windows, the add command makes sure that no part of the file path ends with a period, as that would cause problems (#1056). .SS aregister (areg) .PP Show the transactions and running historical balance of a single account, with each transaction displayed as one line. .PP \f[CR]aregister\f[R] shows the overall transactions affecting a particular account (and any subaccounts). Each report line represents one transaction in this account. Transactions before the report start date are always included in the running balance (\f[CR]\-\-historical\f[R] mode is always on). .PP This is a more \[dq]real world\[dq], bank\-like view than the \f[CR]register\f[R] command (which shows individual postings, possibly from multiple accounts, not necessarily in historical mode). As a quick rule of thumb: \- use \f[CR]aregister\f[R] for reviewing and reconciling real\-world asset/liability accounts \- use \f[CR]register\f[R] for reviewing detailed revenues/expenses. .PP \f[CR]aregister\f[R] requires one argument: the account to report on. You can write either the full account name, or a case\-insensitive regular expression which will select the alphabetically first matched account. .PP When there are multiple matches, the alphabetically\-first choice can be surprising; eg if you have \f[CR]assets:per:checking 1\f[R] and \f[CR]assets:biz:checking 2\f[R] accounts, \f[CR]hledger areg checking\f[R] would select \f[CR]assets:biz:checking 2\f[R]. It\[aq]s just a convenience to save typing, so if in doubt, write the full account name, or a distinctive substring that matches uniquely. .PP Transactions involving subaccounts of this account will also be shown. \f[CR]aregister\f[R] ignores depth limits, so its final total will always match a balance report with similar arguments. .PP Any additional arguments form a query which will filter the transactions shown. Note some queries will disturb the running balance, causing it to be different from the account\[aq]s real\-world running balance. .PP An example: this shows the transactions and historical running balance during july, in the first account whose name contains \[dq]checking\[dq]: .IP .EX $ hledger areg checking date:jul .EE .PP Each \f[CR]aregister\f[R] line item shows: .IP \[bu] 2 the transaction\[aq]s date (or the relevant posting\[aq]s date if different, see below) .IP \[bu] 2 the names of all the other account(s) involved in this transaction (probably abbreviated) .IP \[bu] 2 the total change to this account\[aq]s balance from this transaction .IP \[bu] 2 the account\[aq]s historical running balance after this transaction. .PP Transactions making a net change of zero are not shown by default; add the \f[CR]\-E/\-\-empty\f[R] flag to show them. .PP For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the \f[CR]\-\-align\-all\f[R] flag. .PP This command also supports the output destination and output format options. The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], and \f[CR]json\f[R]. .SS aregister and posting dates aregister always shows one line (and date and amount) per transaction. But sometimes transactions have postings with different dates. Also, not all of a transaction\[aq]s postings may be within the report period. To resolve this, aregister shows the earliest of the transaction\[aq]s date and posting dates that is in\-period, and the sum of the in\-period postings. In other words it will show a combined line item with just the earliest date, and the running balance will (temporarily, until the transaction\[aq]s last posting) be inaccurate. Use \f[CR]register \-H\f[R] if you need to see the individual postings. .PP There is also a \f[CR]\-\-txn\-dates\f[R] flag, which filters strictly by transaction date, ignoring posting dates. This too can cause an inaccurate running balance. .SS balance (bal) .PP Show accounts and their balances. .PP \f[CR]balance\f[R] is one of hledger\[aq]s oldest and most versatile commands, for listing account balances, balance changes, values, value changes and more, during one time period or many. Generally it shows a table, with rows representing accounts, and columns representing periods. .PP Note there are some higher\-level variants of the \f[CR]balance\f[R] command with convenient defaults, which can be simpler to use: \f[CR]balancesheet\f[R], \f[CR]balancesheetequity\f[R], \f[CR]cashflow\f[R] and \f[CR]incomestatement\f[R]. When you need more control, then use \f[CR]balance\f[R]. .SS balance features Here\[aq]s a quick overview of the \f[CR]balance\f[R] command\[aq]s features, followed by more detailed descriptions and examples. Many of these work with the higher\-level commands as well. .PP \f[CR]balance\f[R] can show.. .IP \[bu] 2 accounts as a list (\f[CR]\-l\f[R]) or a tree (\f[CR]\-t\f[R]) .IP \[bu] 2 optionally depth\-limited (\f[CR]\-[1\-9]\f[R]) .IP \[bu] 2 sorted by declaration order and name, or by amount .PP \&..and their.. .IP \[bu] 2 balance changes (the default) .IP \[bu] 2 or actual and planned balance changes (\f[CR]\-\-budget\f[R]) .IP \[bu] 2 or value of balance changes (\f[CR]\-V\f[R]) .IP \[bu] 2 or change of balance values (\f[CR]\-\-valuechange\f[R]) .IP \[bu] 2 or unrealised capital gain/loss (\f[CR]\-\-gain\f[R]) .IP \[bu] 2 or postings count (\f[CR]\-\-count\f[R]) .PP \&..in.. .IP \[bu] 2 one time period (the whole journal period by default) .IP \[bu] 2 or multiple periods (\f[CR]\-D\f[R], \f[CR]\-W\f[R], \f[CR]\-M\f[R], \f[CR]\-Q\f[R], \f[CR]\-Y\f[R], \f[CR]\-p INTERVAL\f[R]) .PP \&..either.. .IP \[bu] 2 per period (the default) .IP \[bu] 2 or accumulated since report start date (\f[CR]\-\-cumulative\f[R]) .IP \[bu] 2 or accumulated since account creation (\f[CR]\-\-historical/\-H\f[R]) .PP \&..possibly converted to.. .IP \[bu] 2 cost (\f[CR]\-\-value=cost[,COMM]\f[R]/\f[CR]\-\-cost\f[R]/\f[CR]\-B\f[R]) .IP \[bu] 2 or market value, as of transaction dates (\f[CR]\-\-value=then[,COMM]\f[R]) .IP \[bu] 2 or at period ends (\f[CR]\-\-value=end[,COMM]\f[R]) .IP \[bu] 2 or now (\f[CR]\-\-value=now\f[R]) .IP \[bu] 2 or at some other date (\f[CR]\-\-value=YYYY\-MM\-DD\f[R]) .PP \&..with.. .IP \[bu] 2 totals (\f[CR]\-T\f[R]), averages (\f[CR]\-A\f[R]), percentages (\f[CR]\-%\f[R]), inverted sign (\f[CR]\-\-invert\f[R]) .IP \[bu] 2 rows and columns swapped (\f[CR]\-\-transpose\f[R]) .IP \[bu] 2 another field used as account name (\f[CR]\-\-pivot\f[R]) .IP \[bu] 2 custom\-formatted line items (single\-period reports only) (\f[CR]\-\-format\f[R]) .IP \[bu] 2 commodities displayed on the same line or multiple lines (\f[CR]\-\-layout\f[R]) .PP This command supports the output destination and output format options, with output formats \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]json\f[R], and (multi\-period reports only:) \f[CR]html\f[R]. In \f[CR]txt\f[R] output in a colour\-supporting terminal, negative amounts are shown in red. .PP The \f[CR]\-\-related\f[R]/\f[CR]\-r\f[R] flag shows the balance of the \f[I]other\f[R] postings in the transactions of the postings which would normally be shown. .SS Simple balance report With no arguments, \f[CR]balance\f[R] shows a list of all accounts and their change of balance \- ie, the sum of posting amounts, both inflows and outflows \- during the entire period of the journal. (\[dq]Simple\[dq] here means just one column of numbers, covering a single period. You can also have multi\-period reports, described later.) .PP For real\-world accounts, these numbers will normally be their end balance at the end of the journal period; more on this below. .PP Accounts are sorted by declaration order if any, and then alphabetically by account name. For instance (using examples/sample.journal): .IP .EX $ hledger \-f examples/sample.journal bal $1 assets:bank:saving $\-2 assets:cash $1 expenses:food $1 expenses:supplies $\-1 income:gifts $\-1 income:salary $1 liabilities:debts \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP Accounts with a zero balance (and no non\-zero subaccounts, in tree mode \- see below) are hidden by default. Use \f[CR]\-E/\-\-empty\f[R] to show them (revealing \f[CR]assets:bank:checking\f[R] here): .IP .EX $ hledger \-f examples/sample.journal bal \-E 0 assets:bank:checking $1 assets:bank:saving $\-2 assets:cash $1 expenses:food $1 expenses:supplies $\-1 income:gifts $\-1 income:salary $1 liabilities:debts \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP The total of the amounts displayed is shown as the last line, unless \f[CR]\-N\f[R]/\f[CR]\-\-no\-total\f[R] is used. .SS Balance report line format For single\-period balance reports displayed in the terminal (only), you can use \f[CR]\-\-format FMT\f[R] to customise the format and content of each line. Eg: .IP .EX $ hledger \-f examples/sample.journal balance \-\-format \[dq]%20(account) %12(total)\[dq] assets $\-1 bank:saving $1 cash $\-2 expenses $2 food $1 supplies $1 income $\-2 gifts $\-1 salary $\-1 liabilities:debts $1 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP The FMT format string specifies the formatting applied to each account/balance pair. It may contain any suitable text, with data fields interpolated like so: .PP \f[CR]%[MIN][.MAX](FIELDNAME)\f[R] .IP \[bu] 2 MIN pads with spaces to at least this width (optional) .IP \[bu] 2 MAX truncates at this width (optional) .IP \[bu] 2 FIELDNAME must be enclosed in parentheses, and can be one of: .RS 2 .IP \[bu] 2 \f[CR]depth_spacer\f[R] \- a number of spaces equal to the account\[aq]s depth, or if MIN is specified, MIN * depth spaces. .IP \[bu] 2 \f[CR]account\f[R] \- the account\[aq]s name .IP \[bu] 2 \f[CR]total\f[R] \- the account\[aq]s balance/posted total, right justified .RE .PP Also, FMT can begin with an optional prefix to control how multi\-commodity amounts are rendered: .IP \[bu] 2 \f[CR]%_\f[R] \- render on multiple lines, bottom\-aligned (the default) .IP \[bu] 2 \f[CR]%\[ha]\f[R] \- render on multiple lines, top\-aligned .IP \[bu] 2 \f[CR]%,\f[R] \- render on one line, comma\-separated .PP There are some quirks. Eg in one\-line mode, \f[CR]%(depth_spacer)\f[R] has no effect, instead \f[CR]%(account)\f[R] has indentation built in. \ Experimentation may be needed to get pleasing results. .PP Some example formats: .IP \[bu] 2 \f[CR]%(total)\f[R] \- the account\[aq]s total .IP \[bu] 2 \f[CR]%\-20.20(account)\f[R] \- the account\[aq]s name, left justified, padded to 20 characters and clipped at 20 characters .IP \[bu] 2 \f[CR]%,%\-50(account) %25(total)\f[R] \- account name padded to 50 characters, total padded to 20 characters, with multiple commodities rendered on one line .IP \[bu] 2 \f[CR]%20(total) %2(depth_spacer)%\-(account)\f[R] \- the default format for the single\-column balance report .SS Filtered balance report You can show fewer accounts, a different time period, totals from cleared transactions only, etc. by using query arguments or options to limit the postings being matched. Eg: .IP .EX $ hledger \-f examples/sample.journal bal \-\-cleared assets date:200806 $\-2 assets:cash \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-2 .EE .SS List or tree mode By default, or with \f[CR]\-l/\-\-flat\f[R], accounts are shown as a flat list with their full names visible, as in the examples above. .PP With \f[CR]\-t/\-\-tree\f[R], the account hierarchy is shown, with subaccounts\[aq] \[dq]leaf\[dq] names indented below their parent: .IP .EX $ hledger \-f examples/sample.journal balance $\-1 assets $1 bank:saving $\-2 cash $2 expenses $1 food $1 supplies $\-2 income $\-1 gifts $\-1 salary $1 liabilities:debts \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP Notes: .IP \[bu] 2 \[dq]Boring\[dq] accounts are combined with their subaccount for more compact output, unless \f[CR]\-\-no\-elide\f[R] is used. Boring accounts have no balance of their own and just one subaccount (eg \f[CR]assets:bank\f[R] and \f[CR]liabilities\f[R] above). .IP \[bu] 2 All balances shown are \[dq]inclusive\[dq], ie including the balances from all subaccounts. Note this means some repetition in the output, which requires explanation when sharing reports with non\-plaintextaccounting\-users. A tree mode report\[aq]s final total is the sum of the top\-level balances shown, not of all the balances shown. .IP \[bu] 2 Each group of sibling accounts (ie, under a common parent) is sorted separately. .SS Depth limiting With a \f[CR]depth:NUM\f[R] query, or \f[CR]\-\-depth NUM\f[R] option, or just \f[CR]\-NUM\f[R] (eg: \f[CR]\-3\f[R]) balance reports will show accounts only to the specified depth, hiding the deeper subaccounts. This can be useful for getting an overview without too much detail. .PP Account balances at the depth limit always include the balances from any deeper subaccounts (even in list mode). Eg, limiting to depth 1: .IP .EX $ hledger \-f examples/sample.journal balance \-1 $\-1 assets $2 expenses $\-2 income $1 liabilities \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .SS Dropping top\-level accounts You can also hide one or more top\-level account name parts, using \f[CR]\-\-drop NUM\f[R]. This can be useful for hiding repetitive top\-level account names: .IP .EX $ hledger \-f examples/sample.journal bal expenses \-\-drop 1 $1 food $1 supplies \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $2 .EE .PP .SS Showing declared accounts With \f[CR]\-\-declared\f[R], accounts which have been declared with an account directive will be included in the balance report, even if they have no transactions. (Since they will have a zero balance, you will also need \f[CR]\-E/\-\-empty\f[R] to see them.) .PP More precisely, \f[I]leaf\f[R] declared accounts (with no subaccounts) will be included, since those are usually the more useful in reports. .PP The idea of this is to be able to see a useful \[dq]complete\[dq] balance report, even when you don\[aq]t have transactions in all of your declared accounts yet. .SS Sorting by amount With \f[CR]\-S/\-\-sort\-amount\f[R], accounts with the largest (most positive) balances are shown first. Eg: \f[CR]hledger bal expenses \-MAS\f[R] shows your biggest averaged monthly expenses first. When more than one commodity is present, they will be sorted by the alphabetically earliest commodity first, and then by subsequent commodities (if an amount is missing a commodity, it is treated as 0). .PP Revenues and liability balances are typically negative, however, so \f[CR]\-S\f[R] shows these in reverse order. To work around this, you can add \f[CR]\-\-invert\f[R] to flip the signs. (Or, use one of the higher\-level reports, which flip the sign automatically. Eg: \f[CR]hledger incomestatement \-MAS\f[R]). .PP .SS Percentages With \f[CR]\-%/\-\-percent\f[R], balance reports show each account\[aq]s value expressed as a percentage of the (column) total. .PP Note it is not useful to calculate percentages if the amounts in a column have mixed signs. In this case, make a separate report for each sign, eg: .IP .EX $ hledger bal \-% amt:\[ga]>0\[ga] $ hledger bal \-% amt:\[ga]<0\[ga] .EE .PP Similarly, if the amounts in a column have mixed commodities, convert them to one commodity with \f[CR]\-B\f[R], \f[CR]\-V\f[R], \f[CR]\-X\f[R] or \f[CR]\-\-value\f[R], or make a separate report for each commodity: .IP .EX $ hledger bal \-% cur:\[rs]\[rs]$ $ hledger bal \-% cur:€ .EE .SS Multi\-period balance report With a report interval (set by the \f[CR]\-D/\-\-daily\f[R], \f[CR]\-W/\-\-weekly\f[R], \f[CR]\-M/\-\-monthly\f[R], \f[CR]\-Q/\-\-quarterly\f[R], \f[CR]\-Y/\-\-yearly\f[R], or \f[CR]\-p/\-\-period\f[R] flag), \f[CR]balance\f[R] shows a tabular report, with columns representing successive time periods (and a title): .IP .EX $ hledger \-f examples/sample.journal bal \-\-quarterly income expenses \-E Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 ===================++================================= expenses:food || 0 $1 0 0 expenses:supplies || 0 $1 0 0 income:gifts || 0 $\-1 0 0 income:salary || $\-1 0 0 0 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || $\-1 $1 0 0 .EE .PP Notes: .IP \[bu] 2 The report\[aq]s start/end dates will be expanded, if necessary, to fully encompass the displayed subperiods (so that the first and last subperiods have the same duration as the others). .IP \[bu] 2 Leading and trailing periods (columns) containing all zeroes are not shown, unless \f[CR]\-E/\-\-empty\f[R] is used. .IP \[bu] 2 Accounts (rows) containing all zeroes are not shown, unless \f[CR]\-E/\-\-empty\f[R] is used. .IP \[bu] 2 Amounts with many commodities are shown in abbreviated form, unless \f[CR]\-\-no\-elide\f[R] is used. \f[I](experimental)\f[R] .IP \[bu] 2 Average and/or total columns can be added with the \f[CR]\-A/\-\-average\f[R] and \f[CR]\-T/\-\-row\-total\f[R] flags. .IP \[bu] 2 The \f[CR]\-\-transpose\f[R] flag can be used to exchange rows and columns. .IP \[bu] 2 The \f[CR]\-\-pivot FIELD\f[R] option causes a different transaction field to be used as \[dq]account name\[dq]. See PIVOTING. .PP Multi\-period reports with many periods can be too wide for easy viewing in the terminal. Here are some ways to handle that: .IP \[bu] 2 Hide the totals row with \f[CR]\-N/\-\-no\-total\f[R] .IP \[bu] 2 Convert to a single currency with \f[CR]\-V\f[R] .IP \[bu] 2 Maximize the terminal window .IP \[bu] 2 Reduce the terminal\[aq]s font size .IP \[bu] 2 View with a pager like less, eg: \f[CR]hledger bal \-D \-\-color=yes | less \-RS\f[R] .IP \[bu] 2 Output as CSV and use a CSV viewer like visidata (\f[CR]hledger bal \-D \-O csv | vd \-f csv\f[R]), Emacs\[aq] csv\-mode (\f[CR]M\-x csv\-mode, C\-c C\-a\f[R]), or a spreadsheet (\f[CR]hledger bal \-D \-o a.csv && open a.csv\f[R]) .IP \[bu] 2 Output as HTML and view with a browser: \f[CR]hledger bal \-D \-o a.html && open a.html\f[R] .SS Balance change, end balance It\[aq]s important to be clear on the meaning of the numbers shown in balance reports. Here is some terminology we use: .PP A \f[B]\f[BI]balance change\f[B]\f[R] is the net amount added to, or removed from, an account during some period. .PP An \f[B]\f[BI]end balance\f[B]\f[R] is the amount accumulated in an account as of some date (and some time, but hledger doesn\[aq]t store that; assume end of day in your timezone). It is the sum of previous balance changes. .PP We call it a \f[B]\f[BI]historical end balance\f[B]\f[R] if it includes all balance changes since the account was created. For a real world account, this means it will match the \[dq]historical record\[dq], eg the balances reported in your bank statements or bank web UI. (If they are correct!) .PP In general, balance changes are what you want to see when reviewing revenues and expenses, and historical end balances are what you want to see when reviewing or reconciling asset, liability and equity accounts. .PP \f[CR]balance\f[R] shows balance changes by default. To see accurate historical end balances: .IP "1." 3 Initialise account starting balances with an \[dq]opening balances\[dq] transaction (a transfer from equity to the account), unless the journal covers the account\[aq]s full lifetime. .IP "2." 3 Include all of of the account\[aq]s prior postings in the report, by not specifying a report start date, or by using the \f[CR]\-H/\-\-historical\f[R] flag. (\f[CR]\-H\f[R] causes report start date to be ignored when summing postings.) .SS Balance report types The balance command is quite flexible; here is the full detail on how to control what it reports. If the following seems complicated, don\[aq]t worry \- this is for advanced reporting, and it does take time and experimentation to get familiar with all the report modes. .PP There are three important option groups: .PP \f[CR]hledger balance [CALCULATIONTYPE] [ACCUMULATIONTYPE] [VALUATIONTYPE] ...\f[R] .SS Calculation type The basic calculation to perform for each table cell. It is one of: .IP \[bu] 2 \f[CR]\-\-sum\f[R] : sum the posting amounts (\f[B]default\f[R]) .IP \[bu] 2 \f[CR]\-\-budget\f[R] : sum the amounts, but also show the budget goal amount (for each account/period) .IP \[bu] 2 \f[CR]\-\-valuechange\f[R] : show the change in period\-end historical balance values (caused by deposits, withdrawals, and/or market price fluctuations) .IP \[bu] 2 \f[CR]\-\-gain\f[R] : show the unrealised capital gain/loss, (the current valued balance minus each amount\[aq]s original cost) .IP \[bu] 2 \f[CR]\-\-count\f[R] : show the count of postings .SS Accumulation type How amounts should accumulate across report periods. Another way to say it: which time period\[aq]s postings should contribute to each cell\[aq]s calculation. It is one of: .IP \[bu] 2 \f[CR]\-\-change\f[R] : calculate with postings from column start to column end, ie \[dq]just this column\[dq]. Typically used to see revenues/expenses. (\f[B]default for balance, incomestatement\f[R]) .IP \[bu] 2 \f[CR]\-\-cumulative\f[R] : calculate with postings from report start to column end, ie \[dq]previous columns plus this column\[dq]. Typically used to show changes accumulated since the report\[aq]s start date. Not often used. .IP \[bu] 2 \f[CR]\-\-historical/\-H\f[R] : calculate with postings from journal start to column end, ie \[dq]all postings from before report start date until this column\[aq]s end\[dq]. Typically used to see historical end balances of assets/liabilities/equity. (\f[B]default for balancesheet, balancesheetequity, cashflow\f[R]) .SS Valuation type Which kind of value or cost conversion should be applied, if any, before displaying the report. It is one of: .IP \[bu] 2 no valuation type : don\[aq]t convert to cost or value (\f[B]default\f[R]) .IP \[bu] 2 \f[CR]\-\-value=cost[,COMM]\f[R] : convert amounts to cost (then optionally to some other commodity) .IP \[bu] 2 \f[CR]\-\-value=then[,COMM]\f[R] : convert amounts to market value on transaction dates .IP \[bu] 2 \f[CR]\-\-value=end[,COMM]\f[R] : convert amounts to market value on period end date(s) .PD 0 .P .PD (\f[B]default with \f[CB]\-\-valuechange\f[B], \f[CB]\-\-gain\f[B]\f[R]) .IP \[bu] 2 \f[CR]\-\-value=now[,COMM]\f[R] : convert amounts to market value on today\[aq]s date .IP \[bu] 2 \f[CR]\-\-value=YYYY\-MM\-DD[,COMM]\f[R] : convert amounts to market value on another date .PP or one of the equivalent simpler flags: .IP \[bu] 2 \f[CR]\-B/\-\-cost\f[R] : like \-\-value=cost (though, note \-\-cost and \-\-value are independent options which can both be used at once) .IP \[bu] 2 \f[CR]\-V/\-\-market\f[R] : like \-\-value=end .IP \[bu] 2 \f[CR]\-X COMM/\-\-exchange COMM\f[R] : like \-\-value=end,COMM .PP See Cost reporting and Value reporting for more about these. .SS Combining balance report types Most combinations of these options should produce reasonable reports, but if you find any that seem wrong or misleading, let us know. The following restrictions are applied: .IP \[bu] 2 \f[CR]\-\-valuechange\f[R] implies \f[CR]\-\-value=end\f[R] .IP \[bu] 2 \f[CR]\-\-valuechange\f[R] makes \f[CR]\-\-change\f[R] the default when used with the \f[CR]balancesheet\f[R]/\f[CR]balancesheetequity\f[R] commands .IP \[bu] 2 \f[CR]\-\-cumulative\f[R] or \f[CR]\-\-historical\f[R] disables \f[CR]\-\-row\-total/\-T\f[R] .PP For reference, here is what the combinations of accumulation and valuation show: .PP .TS tab(@); lw(7.9n) lw(16.4n) lw(16.9n) lw(15.1n) lw(13.7n). T{ Valuation:> Accumulation:v T}@T{ no valuation T}@T{ \f[CR]\-\-value= then\f[R] T}@T{ \f[CR]\-\-value= end\f[R] T}@T{ \f[CR]\-\-value= YYYY\-MM\-DD /now\f[R] T} _ T{ \f[CR]\-\-change\f[R] T}@T{ change in period T}@T{ sum of posting\-date market values in period T}@T{ period\-end value of change in period T}@T{ DATE\-value of change in period T} T{ \f[CR]\-\-cumulative\f[R] T}@T{ change from report start to period end T}@T{ sum of posting\-date market values from report start to period end T}@T{ period\-end value of change from report start to period end T}@T{ DATE\-value of change from report start to period end T} T{ \f[CR]\-\-historical /\-H\f[R] T}@T{ change from journal start to period end (historical end balance) T}@T{ sum of posting\-date market values from journal start to period end T}@T{ period\-end value of change from journal start to period end T}@T{ DATE\-value of change from journal start to period end T} .TE .SS Budget report The \f[CR]\-\-budget\f[R] report type is like a regular balance report, but with two main differences: .IP \[bu] 2 Budget goals and performance percentages are also shown, in brackets .IP \[bu] 2 Accounts which don\[aq]t have budget goals are hidden by default. .PP This is useful for comparing planned and actual income, expenses, time usage, etc. .PP Periodic transaction rules are used to define budget goals. For example, here\[aq]s a periodic rule defining monthly goals for bus travel and food expenses: .IP .EX ;; Budget \[ti] monthly (expenses:bus) $30 (expenses:food) $400 .EE .PP After recording some actual expenses, .IP .EX ;; Two months worth of expenses 2017\-11\-01 income $\-1950 expenses:bus $35 expenses:food:groceries $310 expenses:food:dining $42 expenses:movies $38 assets:bank:checking 2017\-12\-01 income $\-2100 expenses:bus $53 expenses:food:groceries $380 expenses:food:dining $32 expenses:gifts $100 assets:bank:checking .EE .PP we can see a budget report like this: .IP .EX $ hledger bal \-M \-\-budget Budget performance in 2017\-11\-01..2017\-12\-31: || Nov Dec ===============++============================================ || $\-425 $\-565 expenses || $425 [ 99% of $430] $565 [131% of $430] expenses:bus || $35 [117% of $30] $53 [177% of $30] expenses:food || $352 [ 88% of $400] $412 [103% of $400] \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || 0 [ 0% of $430] 0 [ 0% of $430] .EE .PP This is \[dq]goal\-based budgeting\[dq]; you define goals for accounts and periods, often recurring, and hledger shows performance relative to the goals. This contrasts with \[dq]envelope budgeting\[dq], which is more detailed and strict \- useful when cash is tight, but also quite a bit more work. https://plaintextaccounting.org/Budgeting has more on this topic. .SS Using the budget report Historically this report has been confusing and fragile. hledger\[aq]s version should be relatively robust and intuitive, but you may still find surprises. Here are more notes to help with learning and troubleshooting. .IP \[bu] 2 In the above example, \f[CR]expenses:bus\f[R] and \f[CR]expenses:food\f[R] are shown because they have budget goals during the report period. .IP \[bu] 2 Their parent \f[CR]expenses\f[R] is also shown, with budget goals aggregated from the children. .IP \[bu] 2 The subaccounts \f[CR]expenses:food:groceries\f[R] and \f[CR]expenses:food:dining\f[R] are not shown since they have no budget goal of their own, but they contribute to \f[CR]expenses:food\f[R]\[aq]s actual amount. .IP \[bu] 2 Unbudgeted accounts \f[CR]expenses:movies\f[R] and \f[CR]expenses:gifts\f[R] are also not shown, but they contribute to \f[CR]expenses\f[R]\[aq]s actual amount. .IP \[bu] 2 The other unbudgeted accounts \f[CR]income\f[R] and \f[CR]assets:bank:checking\f[R] are grouped as \f[CR]\f[R]. .IP \[bu] 2 \f[CR]\-\-depth\f[R] or \f[CR]depth:\f[R] can be used to limit report depth in the usual way (but will not reveal unbudgeted subaccounts). .IP \[bu] 2 Amounts are always inclusive of subaccounts (even in \f[CR]\-l/\-\-list\f[R] mode). .IP \[bu] 2 Numbers displayed in a \-\-budget report will not always agree with the totals, because of hidden unbudgeted accounts; this is normal. \f[CR]\-E/\-\-empty\f[R] can be used to reveal the hidden accounts. .IP \[bu] 2 In the periodic rules used for setting budget goals, unbalanced postings are convenient. .IP \[bu] 2 You can filter budget reports with the usual queries, eg to focus on particular accounts. It\[aq]s common to restrict them to just expenses. (The \f[CR]\f[R] account is occasionally hard to exclude; this is because of date surprises, discussed below.) .IP \[bu] 2 When you have multiple currencies, you may want to convert them to one (\f[CR]\-X COMM \-\-infer\-market\-prices\f[R]) and/or show just one at a time (\f[CR]cur:COMM\f[R]). If you do need to show multiple currencies at once, \f[CR]\-\-layout bare\f[R] can be helpful. .IP \[bu] 2 You can \[dq]roll over\[dq] amounts (actual and budgeted) to the next period with \f[CR]\-\-cumulative\f[R]. .PP See also: https://hledger.org/budgeting.html. .SS Budget date surprises With small data, or when starting out, some of the generated budget goal transaction dates might fall outside the report periods. Eg with the following journal and report, the first period appears to have no \f[CR]expenses:food\f[R] budget. (Also the \f[CR]\f[R] account should be excluded by the \f[CR]expenses\f[R] query, but isn\[aq]t.): .IP .EX \[ti] monthly in 2020 (expenses:food) $500 2020\-01\-15 expenses:food $400 assets:checking .EE .IP .EX $ hledger bal \-\-budget expenses Budget performance in 2020\-01\-15: || 2020\-01\-15 ===============++==================== || $400 expenses:food || 0 [ 0% of $500] \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || $400 [80% of $500] .EE .PP In this case, the budget goal transactions are generated on first days of of month (this can be seen with \f[CR]hledger print \-\-forecast tag:generated expenses\f[R]). Whereas the report period defaults to just the 15th day of january (this can be seen from the report table\[aq]s column headings). .PP To fix this kind of thing, be more explicit about the report period (and/or the periodic rules\[aq] dates). In this case, adding \f[CR]\-b 2020\f[R] does the trick. .SS Selecting budget goals By default, the budget report uses all available periodic transaction rules to generate goals. This includes rules with a different report interval from your report. Eg if you have daily, weekly and monthly periodic rules, all of these will contribute to the goals in a monthly budget report. .PP You can select a subset of periodic rules by providing an argument to the \f[CR]\-\-budget\f[R] flag. \f[CR]\-\-budget=DESCPAT\f[R] will match all periodic rules whose description contains DESCPAT, a case\-insensitive substring (not a regular expression or query). This means you can give your periodic rules descriptions (remember that two spaces are needed between period expression and description), and then select from multiple budgets defined in your journal. .SS Budgeting vs forecasting \f[CR]\-\-budget\f[R] and \f[CR]\-\-forecast\f[R] both use the periodic transaction rules in the journal to generate temporary transactions for reporting purposes. However they are separate features \- though you can use both at the same time if you want. Here are some differences between them: .IP "1." 3 \f[CR]\-\-budget\f[R] is a command\-specific option; it selects the \f[B]budget report\f[R]. .RS 4 .PP \f[CR]\-\-forecast\f[R] is a general option; \f[B]forecasting works with all reports\f[R]. .RE .IP "2." 3 \f[CR]\-\-budget\f[R] uses \f[B]all periodic rules\f[R]; \f[CR]\-\-budget=DESCPAT\f[R] uses \f[B]just the rules matched\f[R] by DESCPAT. .RS 4 .PP \f[CR]\-\-forecast\f[R] uses \f[B]all periodic rules\f[R]. .RE .IP "3." 3 \f[CR]\-\-budget\f[R]\[aq]s budget goal transactions are invisible, except that they produce \f[B]goal amounts\f[R]. .RS 4 .PP \f[CR]\-\-forecast\f[R]\[aq]s forecast transactions are visible, and \f[B]appear in reports\f[R]. .RE .IP "4." 3 \f[CR]\-\-budget\f[R] generates budget goal transactions \f[B]throughout the report period\f[R], optionally restricted by periods specified in the periodic transaction rules. .RS 4 .PP \f[CR]\-\-forecast\f[R] generates forecast transactions from \f[B]after the last regular transaction\f[R], to the end of the report period; while \f[CR]\-\-forecast=PERIODEXPR\f[R] generates them \f[B]throughout the specified period\f[R]; both optionally restricted by periods specified in the periodic transaction rules. .RE .SS Balance report layout The \f[CR]\-\-layout\f[R] option affects how balance reports show multi\-commodity amounts and commodity symbols, which can improve readability. It can also normalise the data for easy consumption by other programs. It has four possible values: .IP \[bu] 2 \f[CR]\-\-layout=wide[,WIDTH]\f[R]: commodities are shown on a single line, optionally elided to WIDTH .IP \[bu] 2 \f[CR]\-\-layout=tall\f[R]: each commodity is shown on a separate line .IP \[bu] 2 \f[CR]\-\-layout=bare\f[R]: commodity symbols are in their own column, amounts are bare numbers .IP \[bu] 2 \f[CR]\-\-layout=tidy\f[R]: data is normalised to easily\-consumed \[dq]tidy\[dq] form, with one row per data value .PP Here are the \f[CR]\-\-layout\f[R] modes supported by each output format; note only CSV output supports all of them: .PP .TS tab(@); l l l l l l. T{ \- T}@T{ txt T}@T{ csv T}@T{ html T}@T{ json T}@T{ sql T} _ T{ wide T}@T{ Y T}@T{ Y T}@T{ Y T}@T{ T}@T{ T} T{ tall T}@T{ Y T}@T{ Y T}@T{ Y T}@T{ T}@T{ T} T{ bare T}@T{ Y T}@T{ Y T}@T{ Y T}@T{ T}@T{ T} T{ tidy T}@T{ T}@T{ Y T}@T{ T}@T{ T}@T{ T} .TE .PP Examples: .IP \[bu] 2 Wide layout. With many commodities, reports can be very wide: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-T \-Y \-\-layout=wide Balance changes in 2012\-01\-01..2014\-12\-31: || 2012 2013 2014 Total ==================++==================================================================================================================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, \-98.12 USD, 10.00 VEA, 18.00 VHT \-11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, \-98.12 USD, 10.00 VEA, 18.00 VHT \-11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT .EE .RE .IP \[bu] 2 Limited wide layout. A width limit reduces the width, but some commodities will be hidden: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-T \-Y \-\-layout=wide,32 Balance changes in 2012\-01\-01..2014\-12\-31: || 2012 2013 2014 Total ==================++=========================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. \-11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. \-11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. .EE .RE .IP \[bu] 2 Tall layout. Each commodity gets a new line (may be different in each column), and account names are repeated: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-T \-Y \-\-layout=tall Balance changes in 2012\-01\-01..2014\-12\-31: || 2012 2013 2014 Total ==================++================================================== Assets:US:ETrade || 10.00 ITOT 70.00 GLD \-11.00 ITOT 70.00 GLD Assets:US:ETrade || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT Assets:US:ETrade || 12.00 VEA \-98.12 USD 14.00 VEA 5120.50 USD Assets:US:ETrade || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA Assets:US:ETrade || 18.00 VHT 294.00 VHT \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || 10.00 ITOT 70.00 GLD \-11.00 ITOT 70.00 GLD || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT || 12.00 VEA \-98.12 USD 14.00 VEA 5120.50 USD || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA || 18.00 VHT 294.00 VHT .EE .RE .IP \[bu] 2 Bare layout. Commodity symbols are kept in one column, each commodity gets its own report row, account names are repeated: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-T \-Y \-\-layout=bare Balance changes in 2012\-01\-01..2014\-12\-31: || Commodity 2012 2013 2014 Total ==================++============================================= Assets:US:ETrade || GLD 0 70.00 0 70.00 Assets:US:ETrade || ITOT 10.00 18.00 \-11.00 17.00 Assets:US:ETrade || USD 337.18 \-98.12 4881.44 5120.50 Assets:US:ETrade || VEA 12.00 10.00 14.00 36.00 Assets:US:ETrade || VHT 106.00 18.00 170.00 294.00 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || GLD 0 70.00 0 70.00 || ITOT 10.00 18.00 \-11.00 17.00 || USD 337.18 \-98.12 4881.44 5120.50 || VEA 12.00 10.00 14.00 36.00 || VHT 106.00 18.00 170.00 294.00 .EE .RE .IP \[bu] 2 Bare layout also affects CSV output, which is useful for producing data that is easier to consume, eg for making charts: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-O csv \-\-layout=bare \[dq]account\[dq],\[dq]commodity\[dq],\[dq]balance\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]GLD\[dq],\[dq]70.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]ITOT\[dq],\[dq]17.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]USD\[dq],\[dq]5120.50\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]VEA\[dq],\[dq]36.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]VHT\[dq],\[dq]294.00\[dq] \[dq]total\[dq],\[dq]GLD\[dq],\[dq]70.00\[dq] \[dq]total\[dq],\[dq]ITOT\[dq],\[dq]17.00\[dq] \[dq]total\[dq],\[dq]USD\[dq],\[dq]5120.50\[dq] \[dq]total\[dq],\[dq]VEA\[dq],\[dq]36.00\[dq] \[dq]total\[dq],\[dq]VHT\[dq],\[dq]294.00\[dq] .EE .RE .IP \[bu] 2 Note: bare layout will sometimes display an extra row for the no\-symbol commodity, because of zero amounts (hledger treats zeroes as commodity\-less, usually). This can break \f[CR]hledger\-bar\f[R] confusingly (workaround: add a \f[CR]cur:\f[R] query to exclude the no\-symbol row). .IP \[bu] 2 Tidy layout produces normalised \[dq]tidy data\[dq], where every variable has its own column and each row represents a single data point. See https://cran.r\-project.org/web/packages/tidyr/vignettes/tidy\-data.html for more. This is the easiest kind of data for other software to consume. Here\[aq]s how it looks: .RS 2 .IP .EX $ hledger \-f examples/bcexample.hledger bal assets:us:etrade \-3 \-Y \-O csv \-\-layout=tidy \[dq]account\[dq],\[dq]period\[dq],\[dq]start_date\[dq],\[dq]end_date\[dq],\[dq]commodity\[dq],\[dq]value\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2012\[dq],\[dq]2012\-01\-01\[dq],\[dq]2012\-12\-31\[dq],\[dq]GLD\[dq],\[dq]0\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2012\[dq],\[dq]2012\-01\-01\[dq],\[dq]2012\-12\-31\[dq],\[dq]ITOT\[dq],\[dq]10.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2012\[dq],\[dq]2012\-01\-01\[dq],\[dq]2012\-12\-31\[dq],\[dq]USD\[dq],\[dq]337.18\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2012\[dq],\[dq]2012\-01\-01\[dq],\[dq]2012\-12\-31\[dq],\[dq]VEA\[dq],\[dq]12.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2012\[dq],\[dq]2012\-01\-01\[dq],\[dq]2012\-12\-31\[dq],\[dq]VHT\[dq],\[dq]106.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2013\[dq],\[dq]2013\-01\-01\[dq],\[dq]2013\-12\-31\[dq],\[dq]GLD\[dq],\[dq]70.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2013\[dq],\[dq]2013\-01\-01\[dq],\[dq]2013\-12\-31\[dq],\[dq]ITOT\[dq],\[dq]18.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2013\[dq],\[dq]2013\-01\-01\[dq],\[dq]2013\-12\-31\[dq],\[dq]USD\[dq],\[dq]\-98.12\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2013\[dq],\[dq]2013\-01\-01\[dq],\[dq]2013\-12\-31\[dq],\[dq]VEA\[dq],\[dq]10.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2013\[dq],\[dq]2013\-01\-01\[dq],\[dq]2013\-12\-31\[dq],\[dq]VHT\[dq],\[dq]18.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2014\[dq],\[dq]2014\-01\-01\[dq],\[dq]2014\-12\-31\[dq],\[dq]GLD\[dq],\[dq]0\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2014\[dq],\[dq]2014\-01\-01\[dq],\[dq]2014\-12\-31\[dq],\[dq]ITOT\[dq],\[dq]\-11.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2014\[dq],\[dq]2014\-01\-01\[dq],\[dq]2014\-12\-31\[dq],\[dq]USD\[dq],\[dq]4881.44\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2014\[dq],\[dq]2014\-01\-01\[dq],\[dq]2014\-12\-31\[dq],\[dq]VEA\[dq],\[dq]14.00\[dq] \[dq]Assets:US:ETrade\[dq],\[dq]2014\[dq],\[dq]2014\-01\-01\[dq],\[dq]2014\-12\-31\[dq],\[dq]VHT\[dq],\[dq]170.00\[dq] .EE .RE .SS Useful balance reports Some frequently used \f[CR]balance\f[R] options/reports are: .IP \[bu] 2 \f[CR]bal \-M revenues expenses\f[R] .PD 0 .P .PD Show revenues/expenses in each month. Also available as the \f[CR]incomestatement\f[R] command. .IP \[bu] 2 \f[CR]bal \-M \-H assets liabilities\f[R] .PD 0 .P .PD Show historical asset/liability balances at each month end. Also available as the \f[CR]balancesheet\f[R] command. .IP \[bu] 2 \f[CR]bal \-M \-H assets liabilities equity\f[R] .PD 0 .P .PD Show historical asset/liability/equity balances at each month end. Also available as the \f[CR]balancesheetequity\f[R] command. .IP \[bu] 2 \f[CR]bal \-M assets not:receivable\f[R] .PD 0 .P .PD Show changes to liquid assets in each month. Also available as the \f[CR]cashflow\f[R] command. .PP Also: .IP \[bu] 2 \f[CR]bal \-M expenses \-2 \-SA\f[R] .PD 0 .P .PD Show monthly expenses summarised to depth 2 and sorted by average amount. .IP \[bu] 2 \f[CR]bal \-M \-\-budget expenses\f[R] .PD 0 .P .PD Show monthly expenses and budget goals. .IP \[bu] 2 \f[CR]bal \-M \-\-valuechange investments\f[R] .PD 0 .P .PD Show monthly change in market value of investment assets. .IP \[bu] 2 \f[CR]bal investments \-\-valuechange \-D date:lastweek amt:\[aq]>1000\[aq] \-STA [\-\-invert]\f[R] .PD 0 .P .PD Show top gainers [or losers] last week .SS balancesheet (bs) .PP This command displays a balance sheet, showing historical ending balances of asset and liability accounts. (To see equity as well, use the balancesheetequity command.) Amounts are shown with normal positive sign, as in conventional financial statements. .PP This report shows accounts declared with the \f[CR]Asset\f[R], \f[CR]Cash\f[R] or \f[CR]Liability\f[R] type (see account types). Or if no such accounts are declared, it shows top\-level accounts named \f[CR]asset\f[R] or \f[CR]liability\f[R] (case insensitive, plurals allowed) and their subaccounts. .PP Example: .IP .EX $ hledger balancesheet Balance Sheet Assets: $\-1 assets $1 bank:saving $\-2 cash \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-1 Liabilities: $1 liabilities:debts \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $1 Total: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP This command is a higher\-level variant of the \f[CR]balance\f[R] command, and supports many of that command\[aq]s features, such as multi\-period reports. It is similar to \f[CR]hledger balance \-H assets liabilities\f[R], but with smarter account detection, and liabilities displayed with their sign flipped. .PP This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]html\f[R], and (experimental) \f[CR]json\f[R]. .SS balancesheetequity (bse) .PP This command displays a balance sheet, showing historical ending balances of asset, liability and equity accounts. Amounts are shown with normal positive sign, as in conventional financial statements. .PP This report shows accounts declared with the \f[CR]Asset\f[R], \f[CR]Cash\f[R], \f[CR]Liability\f[R] or \f[CR]Equity\f[R] type (see account types). Or if no such accounts are declared, it shows top\-level accounts named \f[CR]asset\f[R], \f[CR]liability\f[R] or \f[CR]equity\f[R] (case insensitive, plurals allowed) and their subaccounts. .PP Example: .IP .EX $ hledger balancesheetequity Balance Sheet With Equity Assets: $\-2 assets $1 bank:saving $\-3 cash \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-2 Liabilities: $1 liabilities:debts \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $1 Equity: $1 equity:owner \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $1 Total: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP This command is a higher\-level variant of the \f[CR]balance\f[R] command, and supports many of that command\[aq]s features, such as multi\-period reports. It is similar to \f[CR]hledger balance \-H assets liabilities equity\f[R], but with smarter account detection, and liabilities/equity displayed with their sign flipped. .PP This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]html\f[R], and (experimental) \f[CR]json\f[R]. .SS cashflow (cf) .PP This command displays a cashflow statement, showing the inflows and outflows affecting \[dq]cash\[dq] (ie, liquid, easily convertible) assets. Amounts are shown with normal positive sign, as in conventional financial statements. .PP This report shows accounts declared with the \f[CR]Cash\f[R] type (see account types). Or if no such accounts are declared, it shows accounts .IP \[bu] 2 under a top\-level account named \f[CR]asset\f[R] (case insensitive, plural allowed) .IP \[bu] 2 whose name contains some variation of \f[CR]cash\f[R], \f[CR]bank\f[R], \f[CR]checking\f[R] or \f[CR]saving\f[R]. .PP More precisely: all accounts matching this case insensitive regular expression: .PP \f[CR]\[ha]assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|currentcash)(:|$)\f[R] .PP and their subaccounts. .PP An example cashflow report: .IP .EX $ hledger cashflow Cashflow Statement Cash flows: $\-1 assets $1 bank:saving $\-2 cash \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-1 Total: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-1 .EE .PP This command is a higher\-level variant of the \f[CR]balance\f[R] command, and supports many of that command\[aq]s features, such as multi\-period reports. It is similar to \f[CR]hledger balance assets not:fixed not:investment not:receivable\f[R], but with smarter account detection. .PP This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]html\f[R], and (experimental) \f[CR]json\f[R]. .SS check Check for various kinds of errors in your data. .PP hledger provides a number of built\-in error checks to help prevent problems in your data. Some of these are run automatically; or, you can use this \f[CR]check\f[R] command to run them on demand, with no output and a zero exit code if all is well. Specify their names (or a prefix) as argument(s). .PP Some examples: .IP .EX hledger check # basic checks hledger check \-s # basic + strict checks hledger check ordereddates payees # basic + two other checks .EE .PP If you are an Emacs user, you can also configure flycheck\-hledger to run these checks, providing instant feedback as you edit the journal. .PP Here are the checks currently available: .SS Default checks These checks are run automatically by (almost) all hledger commands: .IP \[bu] 2 \f[B]parseable\f[R] \- data files are in a supported format, with no syntax errors and no invalid include directives. .IP \[bu] 2 \f[B]autobalanced\f[R] \- all transactions are balanced, after converting to cost. Missing amounts and missing costs are inferred automatically where possible. .IP \[bu] 2 \f[B]assertions\f[R] \- all balance assertions in the journal are passing. (This check can be disabled with \f[CR]\-I\f[R]/\f[CR]\-\-ignore\-assertions\f[R].) .SS Strict checks These additional checks are run when the \f[CR]\-s\f[R]/\f[CR]\-\-strict\f[R] (strict mode) flag is used. Or, they can be run by giving their names as arguments to \f[CR]check\f[R]: .IP \[bu] 2 \f[B]balanced\f[R] \- all transactions are balanced after converting to cost, without inferring missing costs. If conversion costs are required, they must be explicit. .IP \[bu] 2 \f[B]accounts\f[R] \- all account names used by transactions have been declared .IP \[bu] 2 \f[B]commodities\f[R] \- all commodity symbols used have been declared .SS Other checks These checks can be run only by giving their names as arguments to \f[CR]check\f[R]. They are more specialised and not desirable for everyone: .IP \[bu] 2 \f[B]ordereddates\f[R] \- transactions are ordered by date within each file .IP \[bu] 2 \f[B]payees\f[R] \- all payees used by transactions have been declared .IP \[bu] 2 \f[B]recentassertions\f[R] \- all accounts with balance assertions have a balance assertion within 7 days of their latest posting .IP \[bu] 2 \f[B]tags\f[R] \- all tags used by transactions have been declared .IP \[bu] 2 \f[B]uniqueleafnames\f[R] \- all account leaf names are unique .SS Custom checks A few more checks are are available as separate add\-on commands, in https://github.com/simonmichael/hledger/tree/master/bin: .IP \[bu] 2 \f[B]hledger\-check\-tagfiles\f[R] \- all tag values containing / (a forward slash) exist as file paths .IP \[bu] 2 \f[B]hledger\-check\-fancyassertions\f[R] \- more complex balance assertions are passing .PP You could make similar scripts to perform your own custom checks. See: Cookbook \-> Scripting. .SS More about specific checks \f[CR]hledger check recentassertions\f[R] will complain if any balance\-asserted account has postings more than 7 days after its latest balance assertion. This aims to prevent the situation where you are regularly updating your journal, but forgetting to check your balances against the real world, then one day must dig back through months of data to find an error. It assumes that adding a balance assertion requires/reminds you to check the real\-world balance. (That may not be true if you auto\-generate balance assertions from bank data; in that case, I recommend to import transactions uncleared, and when you manually review and clear them, also check the latest assertion against the real\-world balance.) .SS close (equity) .PP Generate transactions which transfer account balances to and/or from another account (typically equity). This can be useful for migrating balances to a new journal file, or for merging earnings into equity at end of accounting period. .PP By default, it prints a transaction that zeroes out ALE accounts (asset, liability, equity accounts; this requires account types to be configured); or if ACCTQUERY is provided, the accounts matched by that. .PP \f[I](experimental)\f[R] .PP This command has four main modes, corresponding to the most common use cases: .IP "1." 3 With \f[CR]\-\-close\f[R] (default), it prints a \[dq]closing balances\[dq] transaction that zeroes out ALE (asset, liability, equity) accounts by default (this requires account types to be inferred or declared); or, the accounts matched by the provided ACCTQUERY arguments. .IP "2." 3 With \f[CR]\-\-open\f[R], it prints an opposite \[dq]opening balances\[dq] transaction that restores those balances from zero. This is similar to Ledger\[aq]s equity command. .IP "3." 3 With \f[CR]\-\-migrate\f[R], it prints both the closing and opening transactions. This is the preferred way to migrate balances to a new file: run \f[CR]hledger close \-\-migrate\f[R], add the closing transaction at the end of the old file, and add the opening transaction at the start of the new file. The matching closing/opening transactions cancel each other out, preserving correct balances during multi\-file reporting. .IP "4." 3 With \f[CR]\-\-retain\f[R], it prints a \[dq]retain earnings\[dq] transaction that transfers RX (revenue and expense) balances to \f[CR]equity:retained earnings\f[R]. Businesses traditionally do this at the end of each accounting period; it is less necessary with computer\-based accounting, but it could still be useful if you want to see the accounting equation (A=L+E) satisfied. .PP In all modes, the defaults can be overridden: .IP \[bu] 2 the transaction descriptions can be changed with \f[CR]\-\-close\-desc=DESC\f[R] and \f[CR]\-\-open\-desc=DESC\f[R] .IP \[bu] 2 the account to transfer to/from can be changed with \f[CR]\-\-close\-acct=ACCT\f[R] and \f[CR]\-\-open\-acct=ACCT\f[R] .IP \[bu] 2 the accounts to be closed/opened can be changed with \f[CR]ACCTQUERY\f[R] (account query arguments). .IP \[bu] 2 the closing/opening dates can be changed with \f[CR]\-e DATE\f[R] (a report end date) .PP By default just one destination/source posting will be used, with its amount left implicit. With \f[CR]\-\-x/\-\-explicit\f[R], the amount will be shown explicitly, and if it involves multiple commodities, a separate posting will be generated for each of them (similar to \f[CR]print \-x\f[R]). .PP With \f[CR]\-\-show\-costs\f[R], any amount costs are shown, with separate postings for each cost. This is currently the best way to view investment lots. If you have many currency conversion or investment transactions, it can generate very large journal entries. .PP With \f[CR]\-\-interleaved\f[R], each individual transfer is shown with source and destination postings next to each other. This could be useful for troubleshooting. .PP The default closing date is yesterday, or the journal\[aq]s end date, whichever is later. You can change this by specifying a report end date with \f[CR]\-e\f[R]. The last day of the report period will be the closing date, eg \f[CR]\-e 2024\f[R] means \[dq]close on 2023\-12\-31\[dq]. The opening date is always the day after the closing date. .SS close and balance assertions Balance assertions will be generated, verifying that the accounts have been reset to zero (and then restored to their previous balances, if there is an opening transaction). .PP These provide useful error checking, but you can ignore them temporarily with \f[CR]\-I\f[R], or remove them if you prefer. .PP You probably should avoid filtering transactions by status or realness (\f[CR]\-C\f[R], \f[CR]\-R\f[R], \f[CR]status:\f[R]), or generating postings (\f[CR]\-\-auto\f[R]), with this command, since the balance assertions would depend on these. .PP Note custom posting dates spanning the file boundary will disrupt the balance assertions: .IP .EX 2023\-12\-30 a purchase made in december, cleared in january expenses:food 5 assets:bank:checking \-5 ; date: 2023\-01\-02 .EE .PP To solve that you can transfer the money to and from a temporary account, in effect splitting the multi\-day transaction into two single\-day transactions: .IP .EX ; in 2022.journal: 2022\-12\-30 a purchase made in december, cleared in january expenses:food 5 equity:pending \-5 ; in 2023.journal: 2023\-01\-02 last year\[aq]s transaction cleared equity:pending 5 = 0 assets:bank:checking \-5 .EE .SS Example: retain earnings Record 2022\[aq]s revenues/expenses as retained earnings on 2022\-12\-31, appending the generated transaction to the journal: .IP .EX $ hledger close \-\-retain \-f 2022.journal \-p 2022 >> 2022.journal .EE .PP Note 2022\[aq]s income statement will now show only zeroes, because revenues and expenses have been moved entirely to equity. To see them again, you could exclude the retain transaction: .IP .EX $ hledger \-f 2022.journal is not:desc:\[aq]retain earnings\[aq] .EE .SS Example: migrate balances to a new file Close assets/liabilities/equity on 2022\-12\-31 and re\-open them on 2023\-01\-01: .IP .EX $ hledger close \-\-migrate \-f 2022.journal \-p 2022 # copy/paste the closing transaction to the end of 2022.journal # copy/paste the opening transaction to the start of 2023.journal .EE .PP Now 2022\[aq]s balance sheet will show only zeroes, indicating a balanced accounting equation. (Unless you are using \[at]/\[at]\[at] notation \- in that case, try adding \-\-infer\-equity.) To see the end\-of\-year balances again, you could exclude the closing transaction: .IP .EX $ hledger \-f 2022.journal bs not:desc:\[aq]closing balances\[aq] .EE .SS Example: excluding closing/opening transactions When combining many files for multi\-year reports, the closing/opening transactions cause some noise in transaction\-oriented reports like \f[CR]print\f[R] and \f[CR]register\f[R]. You can exclude them as shown above, but \f[CR]not:desc:...\f[R] is not ideal as it depends on consistent descriptions; also you will want to avoid excluding the very first opening transaction, which could be awkward. Here is one alternative, using tags: .PP Add \f[CR]clopen:\f[R] tags to all opening/closing balances transactions except the first, like this: .IP .EX ; 2021.journal 2021\-06\-01 first opening balances \&... 2021\-12\-31 closing balances ; clopen:2022 \&... .EE .IP .EX ; 2022.journal 2022\-01\-01 opening balances ; clopen:2022 \&... 2022\-12\-31 closing balances ; clopen:2023 \&... .EE .IP .EX ; 2023.journal 2023\-01\-01 opening balances ; clopen:2023 \&... .EE .PP Now, assuming a combined journal like: .IP .EX ; all.journal include 2021.journal include 2022.journal include 2023.journal .EE .PP The \f[CR]clopen:\f[R] tag can exclude all but the first opening transaction. To show a clean multi\-year checking register: .IP .EX $ hledger \-f all.journal areg checking not:tag:clopen .EE .PP And the year values allow more precision. To show 2022\[aq]s year\-end balance sheet: .IP .EX $ hledger \-f all.journal bs \-e2023 not:tag:clopen=2023 .EE .SS codes List the codes seen in transactions, in the order parsed. .PP This command prints the value of each transaction\[aq]s code field, in the order transactions were parsed. The transaction code is an optional value written in parentheses between the date and description, often used to store a cheque number, order number or similar. .PP Transactions aren\[aq]t required to have a code, and missing or empty codes will not be shown by default. With the \f[CR]\-E\f[R]/\f[CR]\-\-empty\f[R] flag, they will be printed as blank lines. .PP You can add a query to select a subset of transactions. .PP Examples: .IP .EX 2022/1/1 (123) Supermarket Food $5.00 Checking 2022/1/2 (124) Post Office Postage $8.32 Checking 2022/1/3 Supermarket Food $11.23 Checking 2022/1/4 (126) Post Office Postage $3.21 Checking .EE .IP .EX $ hledger codes 123 124 126 .EE .IP .EX $ hledger codes \-E 123 124 126 .EE .SS commodities List all commodity/currency symbols used or declared in the journal. .SS demo Play demos of hledger usage in the terminal, if asciinema is installed. .PP Run this command with no argument to list the demos. To play a demo, write its number or a prefix or substring of its title. Tips: .PP Make your terminal window large enough to see the demo clearly. .PP Use the \-s/\-\-speed SPEED option to set your preferred playback speed, eg \f[CR]\-s4\f[R] to play at 4x original speed or \f[CR]\-s.5\f[R] to play at half speed. The default speed is 2x. .PP Other asciinema options can be added following a double dash, eg \f[CR]\-\- \-i.1\f[R] to limit pauses or \f[CR]\-\- \-h\f[R] to list asciinema\[aq]s other options. .PP During playback, several keys are available: SPACE to pause/unpause, . to step forward (while paused), CTRL\-c quit. .PP Examples: .IP .EX $ hledger demo # list available demos $ hledger demo 1 # play the first demo at default speed (2x) $ hledger demo install \-s4 # play the \[dq]install\[dq] demo at 4x speed .EE .SS descriptions List the unique descriptions that appear in transactions. .PP This command lists the unique descriptions that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. .PP Example: .IP .EX $ hledger descriptions Store Name Gas Station | Petrol Person A .EE .SS diff Compares a particular account\[aq]s transactions in two input files. It shows any transactions to this account which are in one file but not in the other. .PP More precisely, for each posting affecting this account in either file, it looks for a corresponding posting in the other file which posts the same amount to the same account (ignoring date, description, etc.) Since postings not transactions are compared, this also works when multiple bank transactions have been combined into a single journal entry. .PP This is useful eg if you have downloaded an account\[aq]s transactions from your bank (eg as CSV data). When hledger and your bank disagree about the account balance, you can compare the bank data with your journal to find out the cause. .PP Examples: .IP .EX $ hledger diff \-f $LEDGER_FILE \-f bank.csv assets:bank:giro These transactions are in the first file only: 2014/01/01 Opening Balances assets:bank:giro EUR ... ... equity:opening balances EUR \-... These transactions are in the second file only: .EE .SS files List all files included in the journal. With a REGEX argument, only file names matching the regular expression (case sensitive) are shown. .SS help Show the hledger user manual in the terminal, with \f[CR]info\f[R], \f[CR]man\f[R], or a pager. With a TOPIC argument, open it at that topic if possible. TOPIC can be any heading in the manual, or a heading prefix, case insensitive. Eg: \f[CR]commands\f[R], \f[CR]print\f[R], \f[CR]forecast\f[R], \f[CR]journal\f[R], \f[CR]amount\f[R], \f[CR]\[dq]auto postings\[dq]\f[R]. .PP This command shows the hledger manual built in to your hledger version. It can be useful when offline, or when you prefer the terminal to a web browser, or when the appropriate hledger manual or viewing tools are not installed on your system. .PP By default it chooses the best viewer found in $PATH, trying (in this order): \f[CR]info\f[R], \f[CR]man\f[R], \f[CR]$PAGER\f[R], \f[CR]less\f[R], \f[CR]more\f[R]. You can force the use of info, man, or a pager with the \f[CR]\-i\f[R], \f[CR]\-m\f[R], or \f[CR]\-p\f[R] flags, If no viewer can be found, or the command is run non\-interactively, it just prints the manual to stdout. .PP If using \f[CR]info\f[R], note that version 6 or greater is needed for TOPIC lookup. If you are on mac you will likely have info 4.8, and should consider installing a newer version, eg with \f[CR]brew install texinfo\f[R] (#1770). .PP Examples .IP .EX $ hledger help \-\-help # show how the help command works $ hledger help # show the hledger manual with info, man or $PAGER $ hledger help journal # show the journal topic in the hledger manual $ hledger help \-m journal # show it with man, even if info is installed .EE .SS import Read new transactions added to each FILE provided as arguments since last run, and add them to the journal. Or with \-\-dry\-run, just print the transactions that would be added. Or with \-\-catchup, just mark all of the FILEs\[aq] current transactions as imported, without importing them. .PP This command may append new transactions to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also \f[CR]add\f[R]). .PP Unlike other hledger commands, with \f[CR]import\f[R] the journal file is an output file, and will be modified, though only by appending (existing data will not be changed). The input files are specified as arguments, so to import one or more CSV files to your main journal, you will run \f[CR]hledger import bank.csv\f[R] or perhaps \f[CR]hledger import *.csv\f[R]. .PP Note you can import from any file format, though CSV files are the most common import source, and these docs focus on that case. .SS Deduplication \f[CR]import\f[R] does \f[I]time\-based deduplication\f[R], to detect only the new transactions since the last successful import. (This does not mean \[dq]ignore transactions that look the same\[dq], but rather \[dq]ignore transactions that have been seen before\[dq].) This is intended for when you are periodically importing downloaded data, which may overlap with previous downloads. Eg if every week (or every day) you download a bank\[aq]s last three months of CSV data, you can safely run \f[CR]hledger import thebank.csv\f[R] each time and only new transactions will be imported. .PP Since the items being read (CSV records, eg) often do not come with unique identifiers, hledger detects new transactions by date, assuming that: .IP "1." 3 new items always have the newest dates .IP "2." 3 item dates do not change across reads .IP "3." 3 and items with the same date remain in the same relative order across reads. .PP These are often true of CSV files representing transactions, or true enough so that it works pretty well in practice. 1 is important, but violations of 2 and 3 amongst the old transactions won\[aq]t matter (and if you import often, the new transactions will be few, so less likely to be the ones affected). .PP hledger remembers the latest date processed in each input file by saving a hidden \[dq].latest.FILE\[dq] file in FILE\[aq]s directory (after a succesful import). .PP Eg when reading \f[CR]finance/bank.csv\f[R], it will look for and update the \f[CR]finance/.latest.bank.csv\f[R] state file. The format is simple: one or more lines containing the same ISO\-format date (YYYY\-MM\-DD), meaning \[dq]I have processed transactions up to this date, and this many of them on that date.\[dq] Normally you won\[aq]t see or manipulate these state files yourself. But if needed, you can delete them to reset the state (making all transactions \[dq]new\[dq]), or you can construct them to \[dq]catch up\[dq] to a certain date. .PP Note deduplication (and updating of state files) can also be done by \f[CR]print \-\-new\f[R], but this is less often used. .PP Related: CSV > Working with CSV > Deduplicating, importing. .SS Import testing With \f[CR]\-\-dry\-run\f[R], the transactions that will be imported are printed to the terminal, without updating your journal or state files. The output is valid journal format, like the print command, so you can re\-parse it. Eg, to see any importable transactions which CSV rules have not categorised: .IP .EX $ hledger import \-\-dry bank.csv | hledger \-f\- \-I print unknown .EE .PP or (live updating): .IP .EX $ ls bank.csv* | entr bash \-c \[aq]echo ====; hledger import \-\-dry bank.csv | hledger \-f\- \-I print unknown\[aq] .EE .PP Note: when importing from multiple files at once, it\[aq]s currently possible for some .latest files to be updated successfully, while the actual import fails because of a problem in one of the files, leaving them out of sync (and causing some transactions to be missed). To prevent this, do a \-\-dry\-run first and fix any problems before the real import. .SS Importing balance assignments Entries added by import will have their posting amounts made explicit (like \f[CR]hledger print \-x\f[R]). This means that any balance assignments in imported files must be evaluated; but, imported files don\[aq]t get to see the main file\[aq]s account balances. As a result, importing entries with balance assignments (eg from an institution that provides only balances and not posting amounts) will probably generate incorrect posting amounts. To avoid this problem, use print instead of import: .IP .EX $ hledger print IMPORTFILE [\-\-new] >> $LEDGER_FILE .EE .PP (If you think import should leave amounts implicit like print does, please test it and send a pull request.) .SS Commodity display styles Imported amounts will be formatted according to the canonical commodity styles (declared or inferred) in the main journal file. .SS incomestatement (is) .PP This command displays an income statement, showing revenues and expenses during one or more periods. Amounts are shown with normal positive sign, as in conventional financial statements. .PP This report shows accounts declared with the \f[CR]Revenue\f[R] or \f[CR]Expense\f[R] type (see account types). Or if no such accounts are declared, it shows top\-level accounts named \f[CR]revenue\f[R] or \f[CR]income\f[R] or \f[CR]expense\f[R] (case insensitive, plurals allowed) and their subaccounts. .PP Example: .IP .EX $ hledger incomestatement Income Statement Revenues: $\-2 income $\-1 gifts $\-1 salary \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $\-2 Expenses: $2 expenses $1 food $1 supplies \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $2 Total: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP This command is a higher\-level variant of the \f[CR]balance\f[R] command, and supports many of that command\[aq]s features, such as multi\-period reports. It is similar to \f[CR]hledger balance \[aq](revenues|income)\[aq] expenses\f[R], but with smarter account detection, and revenues/income displayed with their sign flipped. .PP This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]html\f[R], and (experimental) \f[CR]json\f[R]. .SS notes List the unique notes that appear in transactions. .PP This command lists the unique notes that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. The note is the part of the transaction description after a | character (or if there is no |, the whole description). .PP Example: .IP .EX $ hledger notes Petrol Snacks .EE .SS payees List the unique payee/payer names that appear in transactions. .PP This command lists unique payee/payer names which have been declared with payee directives (\-\-declared), used in transaction descriptions (\-\-used), or both (the default). .PP The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). .PP You can add query arguments to select a subset of transactions. This implies \-\-used. .PP Example: .IP .EX $ hledger payees Store Name Gas Station Person A .EE .SS prices Print the market prices declared with P directives. With \-\-infer\-market\-prices, also show any additional prices inferred from costs. With \-\-show\-reverse, also show additional prices inferred by reversing known prices. .PP Price amounts are always displayed with their full precision, except for reverse prices which are limited to 8 decimal digits. .PP Prices can be filtered by a date:, cur: or amt: query. .PP Generally if you run this command with \-\-infer\-market\-prices \-\-show\-reverse, it will show the same prices used internally to calculate value reports. But if in doubt, you can inspect those directly by running the value report with \-\-debug=2. .SS print Show transaction journal entries, sorted by date. .PP The print command displays full journal entries (transactions) from the journal file, sorted by date (or with \f[CR]\-\-date2\f[R], by secondary date). .PP Directives and inter\-transaction comments are not shown, currently. This means the print command is somewhat lossy, and if you are using it to reformat/regenerate your journal you should take care to also copy over the directives and inter\-transaction comments. .PP Eg: .IP .EX $ hledger print \-f examples/sample.journal date:200806 2008/06/01 gift assets:bank:checking $1 income:gifts $\-1 2008/06/02 save assets:bank:saving $1 assets:bank:checking $\-1 2008/06/03 * eat & shop expenses:food $1 expenses:supplies $1 assets:cash $\-2 .EE .SS print explicitness Normally, whether posting amounts are implicit or explicit is preserved. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, if a conversion cost is implied but not written, it will not appear in the output. .PP You can use the \f[CR]\-x\f[R]/\f[CR]\-\-explicit\f[R] flag to force explicit display of all amounts and costs. This can be useful for troubleshooting or for making your journal more readable and robust against data entry errors. \f[CR]\-x\f[R] is also implied by using any of \f[CR]\-B\f[R],\f[CR]\-V\f[R],\f[CR]\-X\f[R],\f[CR]\-\-value\f[R]. .PP The \f[CR]\-x\f[R]/\f[CR]\-\-explicit\f[R] flag will cause any postings with a multi\-commodity amount (which can arise when a multi\-commodity transaction has an implicit amount) to be split into multiple single\-commodity postings, keeping the output parseable. .SS print amount style Amounts are shown right\-aligned within each transaction (but not aligned across all transactions; you can do that with ledger\-mode in Emacs). .PP Amounts will be (mostly) normalised to their commodity display style: their symbol placement, decimal mark, and digit group marks will be made consistent. By default, decimal digits are shown as they are written in the journal. .PP With the \f[CR]\-\-round\f[R] option, \f[CR]print\f[R] will try increasingly hard to display decimal digits according to the commodity display styles: .IP \[bu] 2 \f[CR]\-\-round=none\f[R] show amounts with original precisions (default) .IP \[bu] 2 \f[CR]\-\-round=soft\f[R] add/remove decimal zeros in amounts (except costs) .IP \[bu] 2 \f[CR]\-\-round=hard\f[R] round amounts (except costs), possibly hiding significant digits .IP \[bu] 2 \f[CR]\-\-round=all\f[R] round all amounts and costs .PP \f[CR]soft\f[R] is good for non\-lossy cleanup, formatting amounts more consistently where it\[aq]s safe to do so. .PP \f[CR]hard\f[R] and \f[CR]all\f[R] can cause \f[CR]print\f[R] to show invalid unbalanced journal entries; they may be useful eg for stronger cleanup, with manual fixups when needed. .SS print parseability print\[aq]s output is usually a valid hledger journal, and you can process it again with a second hledger command. This can be useful for certain kinds of search (though the same can be achieved with \f[CR]expr:\f[R] queries now): .IP .EX # Show running total of food expenses paid from cash. # \-f\- reads from stdin. \-I/\-\-ignore\-assertions is sometimes needed. $ hledger print assets:cash | hledger \-f\- \-I reg expenses:food .EE .PP There are some situations where print\[aq]s output can become unparseable: .IP \[bu] 2 Value reporting affects posting amounts but not balance assertion or balance assignment amounts, potentially causing those to fail. .IP \[bu] 2 Auto postings can generate postings with too many missing amounts. .IP \[bu] 2 Account aliases can generate bad account names. .SS print, other features With \f[CR]\-B\f[R]/\f[CR]\-\-cost\f[R], amounts with costs are shown converted to cost. .PP With \f[CR]\-\-new\f[R], print shows only transactions it has not seen on a previous run. This uses the same deduplication system as the \f[CR]import\f[R] command. (See import\[aq]s docs for details.) .PP With \f[CR]\-m DESC\f[R]/\f[CR]\-\-match=DESC\f[R], print shows one recent transaction whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar\-enough match, no transaction will be shown and the program exit code will be non\-zero. .SS print output format This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]beancount\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], \f[CR]json\f[R] and \f[CR]sql\f[R]. .PP \f[I]Experimental:\f[R] The \f[CR]beancount\f[R] format tries to produce Beancount\-compatible output, as follows: .IP \[bu] 2 Transaction and postings with unmarked status are converted to cleared (\f[CR]*\f[R]) status. .IP \[bu] 2 Transactions\[aq] payee and note are backslash\-escaped and double\-quote\-escaped and wrapped in double quotes. .IP \[bu] 2 Transaction tags are copied to Beancount #tag format. .IP \[bu] 2 Commodity symbols are converted to upper case, and a small number of currency symbols like \f[CR]$\f[R] are converted to the corresponding currency names. .IP \[bu] 2 Account name parts are capitalised and unsupported characters are replaced with \f[CR]\-\f[R]. If an account name part does not begin with a letter, or if the first part is not Assets, Liabilities, Equity, Income, or Expenses, an error is raised. (Use \f[CR]\-\-alias\f[R] options to bring your accounts into compliance.) .IP \[bu] 2 An \f[CR]open\f[R] directive is generated for each account used, on the earliest transaction date. .PP Some limitations: .IP \[bu] 2 Balance assertions are removed. .IP \[bu] 2 Balance assignments become missing amounts. .IP \[bu] 2 Virtual and balanced virtual postings become regular postings. .IP \[bu] 2 Directives are not converted. .PP Here\[aq]s an example of print\[aq]s CSV output: .IP .EX $ hledger print \-Ocsv \[dq]txnidx\[dq],\[dq]date\[dq],\[dq]date2\[dq],\[dq]status\[dq],\[dq]code\[dq],\[dq]description\[dq],\[dq]comment\[dq],\[dq]account\[dq],\[dq]amount\[dq],\[dq]commodity\[dq],\[dq]credit\[dq],\[dq]debit\[dq],\[dq]posting\-status\[dq],\[dq]posting\-comment\[dq] \[dq]1\[dq],\[dq]2008/01/01\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]income\[dq],\[dq]\[dq],\[dq]assets:bank:checking\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]1\[dq],\[dq]2008/01/01\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]income\[dq],\[dq]\[dq],\[dq]income:salary\[dq],\[dq]\-1\[dq],\[dq]$\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]2\[dq],\[dq]2008/06/01\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]gift\[dq],\[dq]\[dq],\[dq]assets:bank:checking\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]2\[dq],\[dq]2008/06/01\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]gift\[dq],\[dq]\[dq],\[dq]income:gifts\[dq],\[dq]\-1\[dq],\[dq]$\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]3\[dq],\[dq]2008/06/02\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]save\[dq],\[dq]\[dq],\[dq]assets:bank:saving\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]3\[dq],\[dq]2008/06/02\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]save\[dq],\[dq]\[dq],\[dq]assets:bank:checking\[dq],\[dq]\-1\[dq],\[dq]$\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]4\[dq],\[dq]2008/06/03\[dq],\[dq]\[dq],\[dq]*\[dq],\[dq]\[dq],\[dq]eat & shop\[dq],\[dq]\[dq],\[dq]expenses:food\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]4\[dq],\[dq]2008/06/03\[dq],\[dq]\[dq],\[dq]*\[dq],\[dq]\[dq],\[dq]eat & shop\[dq],\[dq]\[dq],\[dq]expenses:supplies\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]4\[dq],\[dq]2008/06/03\[dq],\[dq]\[dq],\[dq]*\[dq],\[dq]\[dq],\[dq]eat & shop\[dq],\[dq]\[dq],\[dq]assets:cash\[dq],\[dq]\-2\[dq],\[dq]$\[dq],\[dq]2\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]5\[dq],\[dq]2008/12/31\[dq],\[dq]\[dq],\[dq]*\[dq],\[dq]\[dq],\[dq]pay off\[dq],\[dq]\[dq],\[dq]liabilities:debts\[dq],\[dq]1\[dq],\[dq]$\[dq],\[dq]\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq] \[dq]5\[dq],\[dq]2008/12/31\[dq],\[dq]\[dq],\[dq]*\[dq],\[dq]\[dq],\[dq]pay off\[dq],\[dq]\[dq],\[dq]assets:bank:checking\[dq],\[dq]\-1\[dq],\[dq]$\[dq],\[dq]1\[dq],\[dq]\[dq],\[dq]\[dq],\[dq]\[dq] .EE .IP \[bu] 2 There is one CSV record per posting, with the parent transaction\[aq]s fields repeated. .IP \[bu] 2 The \[dq]txnidx\[dq] (transaction index) field shows which postings belong to the same transaction. (This number might change if transactions are reordered within the file, files are parsed/included in a different order, etc.) .IP \[bu] 2 The amount is separated into \[dq]commodity\[dq] (the symbol) and \[dq]amount\[dq] (numeric quantity) fields. .IP \[bu] 2 The numeric amount is repeated in either the \[dq]credit\[dq] or \[dq]debit\[dq] column, for convenience. (Those names are not accurate in the accounting sense; it just puts negative amounts under credit and zero or greater amounts under debit.) .SS register (reg) .PP Show postings and their running total. .PP The register command displays matched postings, across all accounts, in date order, with their running total or running historical balance. (See also the \f[CR]aregister\f[R] command, which shows matched transactions in a specific account.) .PP register normally shows line per posting, but note that multi\-commodity amounts will occupy multiple lines (one line per commodity). .PP It is typically used with a query selecting a particular account, to see that account\[aq]s activity: .IP .EX $ hledger register checking 2008/01/01 income assets:bank:checking $1 $1 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $\-1 $1 2008/12/31 pay off assets:bank:checking $\-1 0 .EE .PP With \f[CR]\-\-date2\f[R], it shows and sorts by secondary date instead. .PP For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the \f[CR]\-\-align\-all\f[R] flag. .PP The \f[CR]\-\-historical\f[R]/\f[CR]\-H\f[R] flag adds the balance from any undisplayed prior postings to the running total. This is useful when you want to see only recent activity, with a historically accurate running balance: .IP .EX $ hledger register checking \-b 2008/6 \-\-historical 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $\-1 $1 2008/12/31 pay off assets:bank:checking $\-1 0 .EE .PP The \f[CR]\-\-depth\f[R] option limits the amount of sub\-account detail displayed. .PP The \f[CR]\-\-average\f[R]/\f[CR]\-A\f[R] flag shows the running average posting amount instead of the running total (so, the final number displayed is the average for the whole report period). This flag implies \f[CR]\-\-empty\f[R] (see below). It is affected by \f[CR]\-\-historical\f[R]. It works best when showing just one account and one commodity. .PP The \f[CR]\-\-related\f[R]/\f[CR]\-r\f[R] flag shows the \f[I]other\f[R] postings in the transactions of the postings which would normally be shown. .PP The \f[CR]\-\-invert\f[R] flag negates all amounts. For example, it can be used on an income account where amounts are normally displayed as negative numbers. It\[aq]s also useful to show postings on the checking account together with the related account: .IP .EX $ hledger register \-\-related \-\-invert assets:checking .EE .PP With a reporting interval, register shows summary postings, one per interval, aggregating the postings to each account: .IP .EX $ hledger register \-\-monthly income 2008/01 income:salary $\-1 $\-1 2008/06 income:gifts $\-1 $\-2 .EE .PP Periods with no activity, and summary postings with a zero amount, are not shown by default; use the \f[CR]\-\-empty\f[R]/\f[CR]\-E\f[R] flag to see them: .IP .EX $ hledger register \-\-monthly income \-E 2008/01 income:salary $\-1 $\-1 2008/02 0 $\-1 2008/03 0 $\-1 2008/04 0 $\-1 2008/05 0 $\-1 2008/06 income:gifts $\-1 $\-2 2008/07 0 $\-2 2008/08 0 $\-2 2008/09 0 $\-2 2008/10 0 $\-2 2008/11 0 $\-2 2008/12 0 $\-2 .EE .PP Often, you\[aq]ll want to see just one line per interval. The \f[CR]\-\-depth\f[R] option helps with this, causing subaccounts to be aggregated: .IP .EX $ hledger register \-\-monthly assets \-\-depth 1h 2008/01 assets $1 $1 2008/06 assets $\-1 0 2008/12 assets $\-1 $\-1 .EE .PP Note when using report intervals, if you specify start/end dates these will be adjusted outward if necessary to contain a whole number of intervals. This ensures that the first and last intervals are full length and comparable to the others in the report. .PP With \f[CR]\-m DESC\f[R]/\f[CR]\-\-match=DESC\f[R], register does a fuzzy search for one recent posting whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar\-enough match, no posting will be shown and the program exit code will be non\-zero. .SS Custom register output register uses the full terminal width by default, except on windows. You can override this by setting the \f[CR]COLUMNS\f[R] environment variable (not a bash shell variable) or by using the \f[CR]\-\-width\f[R]/\f[CR]\-w\f[R] option. .PP The description and account columns normally share the space equally (about half of (width \- 40) each). You can adjust this by adding a description width as part of \-\-width\[aq]s argument, comma\-separated: \f[CR]\-\-width W,D\f[R] . Here\[aq]s a diagram (won\[aq]t display correctly in \-\-help): .IP .EX <\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- width (W) \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-> date (10) description (D) account (W\-41\-D) amount (12) balance (12) DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA .EE .PP and some examples: .IP .EX $ hledger reg # use terminal width (or 80 on windows) $ hledger reg \-w 100 # use width 100 $ COLUMNS=100 hledger reg # set with one\-time environment variable $ export COLUMNS=100; hledger reg # set till session end (or window resize) $ hledger reg \-w 100,40 # set overall width 100, description width 40 $ hledger reg \-w $COLUMNS,40 # use terminal width, & description width 40 .EE .PP This command also supports the output destination and output format options The output formats supported are \f[CR]txt\f[R], \f[CR]csv\f[R], \f[CR]tsv\f[R], and (experimental) \f[CR]json\f[R]. .SS rewrite Print all transactions, rewriting the postings of matched transactions. For now the only rewrite available is adding new postings, like print \-\-auto. .PP This is a start at a generic rewriter of transaction entries. It reads the default journal and prints the transactions, like print, but adds one or more specified postings to any transactions matching QUERY. The posting amounts can be fixed, or a multiplier of the existing transaction\[aq]s first posting amount. .PP Examples: .IP .EX $ hledger\-rewrite.hs \[ha]income \-\-add\-posting \[aq](liabilities:tax) *.33 ; income tax\[aq] \-\-add\-posting \[aq](reserve:gifts) $100\[aq] $ hledger\-rewrite.hs expenses:gifts \-\-add\-posting \[aq](reserve:gifts) *\-1\[dq]\[aq] $ hledger\-rewrite.hs \-f rewrites.hledger .EE .PP rewrites.hledger may consist of entries like: .IP .EX = \[ha]income amt:<0 date:2017 (liabilities:tax) *0.33 ; tax on income (reserve:grocery) *0.25 ; reserve 25% for grocery (reserve:) *0.25 ; reserve 25% for grocery .EE .PP Note the single quotes to protect the dollar sign from bash, and the two spaces between account and amount. .PP More: .IP .EX $ hledger rewrite \-\- [QUERY] \-\-add\-posting \[dq]ACCT AMTEXPR\[dq] ... $ hledger rewrite \-\- \[ha]income \-\-add\-posting \[aq](liabilities:tax) *.33\[aq] $ hledger rewrite \-\- expenses:gifts \-\-add\-posting \[aq](budget:gifts) *\-1\[dq]\[aq] $ hledger rewrite \-\- \[ha]income \-\-add\-posting \[aq](budget:foreign currency) *0.25 JPY; diversify\[aq] .EE .PP Argument for \f[CR]\-\-add\-posting\f[R] option is a usual posting of transaction with an exception for amount specification. More precisely, you can use \f[CR]\[aq]*\[aq]\f[R] (star symbol) before the amount to indicate that that this is a factor for an amount of original matched posting. If the amount includes a commodity name, the new posting amount will be in the new commodity; otherwise, it will be in the matched posting amount\[aq]s commodity. .SS Re\-write rules in a file During the run this tool will execute so called \[dq]Automated Transactions\[dq] found in any journal it process. I.e instead of specifying this operations in command line you can put them in a journal file. .IP .EX $ rewrite\-rules.journal .EE .PP Make contents look like this: .IP .EX = \[ha]income (liabilities:tax) *.33 = expenses:gifts budget:gifts *\-1 assets:budget *1 .EE .PP Note that \f[CR]\[aq]=\[aq]\f[R] (equality symbol) that is used instead of date in transactions you usually write. It indicates the query by which you want to match the posting to add new ones. .IP .EX $ hledger rewrite \-\- \-f input.journal \-f rewrite\-rules.journal > rewritten\-tidy\-output.journal .EE .PP This is something similar to the commands pipeline: .IP .EX $ hledger rewrite \-\- \-f input.journal \[aq]\[ha]income\[aq] \-\-add\-posting \[aq](liabilities:tax) *.33\[aq] \[rs] | hledger rewrite \-\- \-f \- expenses:gifts \-\-add\-posting \[aq]budget:gifts *\-1\[aq] \[rs] \-\-add\-posting \[aq]assets:budget *1\[aq] \[rs] > rewritten\-tidy\-output.journal .EE .PP It is important to understand that relative order of such entries in journal is important. You can re\-use result of previously added postings. .SS Diff output format To use this tool for batch modification of your journal files you may find useful output in form of unified diff. .IP .EX $ hledger rewrite \-\- \-\-diff \-f examples/sample.journal \[aq]\[ha]income\[aq] \-\-add\-posting \[aq](liabilities:tax) *.33\[aq] .EE .PP Output might look like: .IP .EX \-\-\- /tmp/examples/sample.journal +++ /tmp/examples/sample.journal \[at]\[at] \-18,3 +18,4 \[at]\[at] 2008/01/01 income \- assets:bank:checking $1 + assets:bank:checking $1 income:salary + (liabilities:tax) 0 \[at]\[at] \-22,3 +23,4 \[at]\[at] 2008/06/01 gift \- assets:bank:checking $1 + assets:bank:checking $1 income:gifts + (liabilities:tax) 0 .EE .PP If you\[aq]ll pass this through \f[CR]patch\f[R] tool you\[aq]ll get transactions containing the posting that matches your query be updated. Note that multiple files might be update according to list of input files specified via \f[CR]\-\-file\f[R] options and \f[CR]include\f[R] directives inside of these files. .PP Be careful. Whole transaction being re\-formatted in a style of output from \f[CR]hledger print\f[R]. .PP See also: .PP https://github.com/simonmichael/hledger/issues/99 .SS rewrite vs. print \-\-auto This command predates print \-\-auto, and currently does much the same thing, but with these differences: .IP \[bu] 2 with multiple files, rewrite lets rules in any file affect all other files. print \-\-auto uses standard directive scoping; rules affect only child files. .IP \[bu] 2 rewrite\[aq]s query limits which transactions can be rewritten; all are printed. print \-\-auto\[aq]s query limits which transactions are printed. .IP \[bu] 2 rewrite applies rules specified on command line or in the journal. print \-\-auto applies rules specified in the journal. .SS roi Shows the time\-weighted (TWR) and money\-weighted (IRR) rate of return on your investments. .PP At a minimum, you need to supply a query (which could be just an account name) to select your investment(s) with \f[CR]\-\-inv\f[R], and another query to identify your profit and loss transactions with \f[CR]\-\-pnl\f[R]. .PP If you do not record changes in the value of your investment manually, or do not require computation of time\-weighted return (TWR), \f[CR]\-\-pnl\f[R] could be an empty query (\f[CR]\-\-pnl \[dq]\[dq]\f[R] or \f[CR]\-\-pnl STR\f[R] where \f[CR]STR\f[R] does not match any of your accounts). .PP This command will compute and display the internalized rate of return (IRR, also known as money\-weighted rate of return) and time\-weighted rate of return (TWR) for your investments for the time period requested. IRR is always annualized due to the way it is computed, but TWR is reported both as a rate over the chosen reporting period and as an annual rate. .PP Price directives will be taken into account if you supply appropriate \f[CR]\-\-cost\f[R] or \f[CR]\-\-value\f[R] flags (see VALUATION). .PP Note, in some cases this report can fail, for these reasons: .IP \[bu] 2 Error (NotBracketed): No solution for Internal Rate of Return (IRR). Possible causes: IRR is huge (>1000000%), balance of investment becomes negative at some point in time. .IP \[bu] 2 Error (SearchFailed): Failed to find solution for Internal Rate of Return (IRR). Either search does not converge to a solution, or converges too slowly. .PP Examples: .IP \[bu] 2 Using roi to compute total return of investment in stocks: https://github.com/simonmichael/hledger/blob/master/examples/investing/roi\-unrealised.ledger .IP \[bu] 2 Cookbook > Return on Investment: https://hledger.org/roi.html .SS Spaces and special characters in \f[CR]\-\-inv\f[R] and \f[CR]\-\-pnl\f[R] Note that \f[CR]\-\-inv\f[R] and \f[CR]\-\-pnl\f[R]\[aq]s argument is a query, and queries could have several space\-separated terms (see QUERIES). .PP To indicate that all search terms form single command\-line argument, you will need to put them in quotes (see Special characters): .IP .EX $ hledger roi \-\-inv \[aq]term1 term2 term3 ...\[aq] .EE .PP If any query terms contain spaces themselves, you will need an extra level of nested quoting, eg: .IP .EX $ hledger roi \-\-inv=\[dq]\[aq]Assets:Test 1\[aq]\[dq] \-\-pnl=\[dq]\[aq]Equity:Unrealized Profit and Loss\[aq]\[dq] .EE .SS Semantics of \f[CR]\-\-inv\f[R] and \f[CR]\-\-pnl\f[R] Query supplied to \f[CR]\-\-inv\f[R] has to match all transactions that are related to your investment. Transactions not matching \f[CR]\-\-inv\f[R] will be ignored. .PP In these transactions, ROI will conside postings that match \f[CR]\-\-inv\f[R] to be \[dq]investment postings\[dq] and other postings (not matching \f[CR]\-\-inv\f[R]) will be sorted into two categories: \[dq]cash flow\[dq] and \[dq]profit and loss\[dq], as ROI needs to know which part of the investment value is your contributions and which is due to the return on investment. .IP \[bu] 2 \[dq]Cash flow\[dq] is depositing or withdrawing money, buying or selling assets, or otherwise converting between your investment commodity and any other commodity. Example: .RS 2 .IP .EX 2019\-01\-01 Investing in Snake Oil assets:cash \-$100 investment:snake oil 2020\-01\-01 Selling my Snake Oil assets:cash $10 investment:snake oil = 0 .EE .RE .IP \[bu] 2 \[dq]Profit and loss\[dq] is change in the value of your investment: .RS 2 .IP .EX 2019\-06\-01 Snake Oil falls in value investment:snake oil = $57 equity:unrealized profit or loss .EE .RE .PP All non\-investment postings are assumed to be \[dq]cash flow\[dq], unless they match \f[CR]\-\-pnl\f[R] query. Changes in value of your investment due to \[dq]profit and loss\[dq] postings will be considered as part of your investment return. .PP Example: if you use \f[CR]\-\-inv snake \-\-pnl equity:unrealized\f[R], then postings in the example below would be classifed as: .IP .EX 2019\-01\-01 Snake Oil #1 assets:cash \-$100 ; cash flow posting investment:snake oil ; investment posting 2019\-03\-01 Snake Oil #2 equity:unrealized pnl \-$100 ; profit and loss posting snake oil ; investment posting 2019\-07\-01 Snake Oil #3 equity:unrealized pnl ; profit and loss posting cash \-$100 ; cash flow posting snake oil $50 ; investment posting .EE .SS IRR and TWR explained \[dq]ROI\[dq] stands for \[dq]return on investment\[dq]. Traditionally this was computed as a difference between current value of investment and its initial value, expressed in percentage of the initial value. .PP However, this approach is only practical in simple cases, where investments receives no in\-flows or out\-flows of money, and where rate of growth is fixed over time. For more complex scenarios you need different ways to compute rate of return, and this command implements two of them: IRR and TWR. .PP Internal rate of return, or \[dq]IRR\[dq] (also called \[dq]money\-weighted rate of return\[dq]) takes into account effects of in\-flows and out\-flows, and the time between them. Investment at a particular fixed interest rate is going to give you more interest than the same amount invested at the same interest rate, but made later in time. If you are withdrawing from your investment, your future gains would be smaller (in absolute numbers), and will be a smaller percentage of your initial investment, so your IRR will be smaller. And if you are adding to your investment, you will receive bigger absolute gains, which will be a bigger percentage of your initial investment, so your IRR will be larger. .PP As mentioned before, in\-flows and out\-flows would be any cash that you personally put in or withdraw, and for the \[dq]roi\[dq] command, these are the postings that match the query in the\f[CR]\-\-inv\f[R] argument and NOT match the query in the\f[CR]\-\-pnl\f[R] argument. .PP If you manually record changes in the value of your investment as transactions that balance them against \[dq]profit and loss\[dq] (or \[dq]unrealized gains\[dq]) account or use price directives, then in order for IRR to compute the precise effect of your in\-flows and out\-flows on the rate of return, you will need to record the value of your investement on or close to the days when in\- or out\-flows occur. .PP In technical terms, IRR uses the same approach as computation of net present value, and tries to find a discount rate that makes net present value of all the cash flows of your investment to add up to zero. This could be hard to wrap your head around, especially if you haven\[aq]t done discounted cash flow analysis before. Implementation of IRR in hledger should produce results that match the \f[CR]=XIRR\f[R] formula in Excel. .PP Second way to compute rate of return that \f[CR]roi\f[R] command implements is called \[dq]time\-weighted rate of return\[dq] or \[dq]TWR\[dq]. Like IRR, it will account for the effect of your in\-flows and out\-flows, but unlike IRR it will try to compute the true rate of return of the underlying asset, compensating for the effect that deposits and withdrawas have on the apparent rate of growth of your investment. .PP TWR represents your investment as an imaginary \[dq]unit fund\[dq] where in\-flows/ out\-flows lead to buying or selling \[dq]units\[dq] of your investment and changes in its value change the value of \[dq]investment unit\[dq]. Change in \[dq]unit price\[dq] over the reporting period gives you rate of return of your investment, and make TWR less sensitive than IRR to the effects of cash in\-flows and out\-flows. .PP References: .IP \[bu] 2 Explanation of rate of return .IP \[bu] 2 Explanation of IRR .IP \[bu] 2 Explanation of TWR .IP \[bu] 2 IRR vs TWR .IP \[bu] 2 Examples of computing IRR and TWR and discussion of the limitations of both metrics .SS stats Show journal and performance statistics. .PP The stats command displays summary information for the whole journal, or a matched part of it. With a reporting interval, it shows a report for each report period. .PP At the end, it shows (in the terminal) the overall run time and number of transactions processed per second. Note these are approximate and will vary based on machine, current load, data size, hledger version, haskell lib versions, GHC version.. but they may be of interest. The \f[CR]stats\f[R] command\[aq]s run time is similar to that of a single\-column balance report. .PP Example: .IP .EX $ hledger stats \-f examples/1000x1000x10.journal Main file : /Users/simon/src/hledger/examples/1000x1000x10.journal Included files : Transactions span : 2000\-01\-01 to 2002\-09\-27 (1000 days) Last transaction : 2002\-09\-26 (6995 days ago) Transactions : 1000 (1.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 1000 Accounts : 1000 (depth 10) Commodities : 26 (A, B, C, D, E, F, G, H, I, J, K, L, M, N, O, P, Q, R, S, T, U, V, W, X, Y, Z) Market prices : 1000 (A) Run time : 0.12 s Throughput : 8342 txns/s .EE .PP This command supports the \-o/\-\-output\-file option (but not \-O/\-\-output\-format selection). .SS tags List the tags used in the journal, or their values. .PP This command lists the tag names used in the journal, whether on transactions, postings, or account declarations. .PP With a TAGREGEX argument, only tag names matching this regular expression (case insensitive, infix matched) are shown. .PP With QUERY arguments, only transactions and accounts matching this query are considered. If the query involves transaction fields (date:, desc:, amt:, ...), the search is restricted to the matched transactions and their accounts. .PP With the \-\-values flag, the tags\[aq] unique non\-empty values are listed instead. With \-E/\-\-empty, blank/empty values are also shown. .PP With \-\-parsed, tags or values are shown in the order they were parsed, with duplicates included. (Except, tags from account declarations are always shown first.) .PP Tip: remember, accounts also acquire tags from their parents, postings also acquire tags from their account and transaction, transactions also acquire tags from their postings. .SS test Run built\-in unit tests. .PP This command runs the unit tests built in to hledger and hledger\-lib, printing the results on stdout. If any test fails, the exit code will be non\-zero. .PP This is mainly used by hledger developers, but you can also use it to sanity\-check the installed hledger executable on your platform. All tests are expected to pass \- if you ever see a failure, please report as a bug! .PP This command also accepts tasty test runner options, written after a \-\- (double hyphen). Eg to run only the tests in Hledger.Data.Amount, with ANSI colour codes disabled: .IP .EX $ hledger test \-\- \-pData.Amount \-\-color=never .EE .PP For help on these, see https://github.com/feuerbach/tasty#options (\f[CR]\-\- \-\-help\f[R] currently doesn\[aq]t show them). .PP .SH PART 5: COMMON TASKS Here are some quick examples of how to do some basic tasks with hledger. .SS Getting help Here\[aq]s how to list commands and view options and command docs: .IP .EX $ hledger # show available commands $ hledger \-\-help # show common options $ hledger CMD \-\-help # show CMD\[aq]s options, common options and CMD\[aq]s documentation .EE .PP You can also view your hledger version\[aq]s manual in several formats by using the help command. Eg: .IP .EX $ hledger help # show the hledger manual with info, man or $PAGER (best available) $ hledger help journal # show the journal topic in the hledger manual $ hledger help \-\-help # find out more about the help command .EE .PP To view manuals and introductory docs on the web, visit https://hledger.org. Chat and mail list support and discussion archives can be found at https://hledger.org/support. .SS Constructing command lines hledger has a flexible command line interface. We strive to keep it simple and ergonomic, but if you run into one of the sharp edges described in OPTIONS, here are some tips that might help: .IP \[bu] 2 command\-specific options must go after the command (it\[aq]s fine to put common options there too: \f[CR]hledger CMD OPTS ARGS\f[R]) .IP \[bu] 2 running add\-on executables directly simplifies command line parsing (\f[CR]hledger\-ui OPTS ARGS\f[R]) .IP \[bu] 2 enclose \[dq]problematic\[dq] args in single quotes .IP \[bu] 2 if needed, also add a backslash to hide regular expression metacharacters from the shell .IP \[bu] 2 to see how a misbehaving command line is being parsed, add \f[CR]\-\-debug=2\f[R]. .SS Starting a journal file hledger looks for your accounting data in a journal file, \f[CR]$HOME/.hledger.journal\f[R] by default: .IP .EX $ hledger stats The hledger journal file \[dq]/Users/simon/.hledger.journal\[dq] was not found. Please create it first, eg with \[dq]hledger add\[dq] or a text editor. Or, specify an existing journal file with \-f or LEDGER_FILE. .EE .PP You can override this by setting the \f[CR]LEDGER_FILE\f[R] environment variable (see below). It\[aq]s a good practice to keep this important file under version control, and to start a new file each year. So you could do something like this: .IP .EX $ mkdir \[ti]/finance $ cd \[ti]/finance $ git init Initialized empty Git repository in /Users/simon/finance/.git/ $ touch 2023.journal $ echo \[dq]export LEDGER_FILE=$HOME/finance/2023.journal\[dq] >> \[ti]/.profile $ source \[ti]/.profile $ hledger stats Main file : /Users/simon/finance/2023.journal Included files : Transactions span : to (0 days) Last transaction : none Transactions : 0 (0.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 0 Accounts : 0 (depth 0) Commodities : 0 () Market prices : 0 () .EE .SS Setting LEDGER_FILE How to set \f[CR]LEDGER_FILE\f[R] permanently depends on your setup: .PP On unix and mac, running these commands in the terminal will work for many people; adapt as needed: .IP .EX $ echo \[aq]export LEDGER_FILE=\[ti]/finance/2023.journal\[aq] >> \[ti]/.profile $ source \[ti]/.profile .EE .PP When correctly configured, in a new terminal window \f[CR]env | grep LEDGER_FILE\f[R] will show your file, and so will \f[CR]hledger files\f[R]. .PP On mac, this additional step might be helpful for GUI applications (like Emacs started from the dock): add an entry to \f[CR]\[ti]/.MacOSX/environment.plist\f[R] like .IP .EX { \[dq]LEDGER_FILE\[dq] : \[dq]\[ti]/finance/2023.journal\[dq] } .EE .PP and then run \f[CR]killall Dock\f[R] in a terminal window (or restart the machine). .PP On Windows, see https://www.java.com/en/download/help/path.html, or try running these commands in a powershell window (let us know if it persists across a reboot, and if you need to be an Administrator): .IP .EX > CD > MKDIR finance > SETX LEDGER_FILE \[dq]C:\[rs]Users\[rs]USERNAME\[rs]finance\[rs]2023.journal\[dq] .EE .SS Setting opening balances Pick a starting date for which you can look up the balances of some real\-world assets (bank accounts, wallet..) and liabilities (credit cards..). .PP To avoid a lot of data entry, you may want to start with just one or two accounts, like your checking account or cash wallet; and pick a recent starting date, like today or the start of the week. You can always come back later and add more accounts and older transactions, eg going back to january 1st. .PP Add an opening balances transaction to the journal, declaring the balances on this date. Here are two ways to do it: .IP \[bu] 2 The first way: open the journal in any text editor and save an entry like this: .RS 2 .IP .EX 2023\-01\-01 * opening balances assets:bank:checking $1000 = $1000 assets:bank:savings $2000 = $2000 assets:cash $100 = $100 liabilities:creditcard $\-50 = $\-50 equity:opening/closing balances .EE .PP These are start\-of\-day balances, ie whatever was in the account at the end of the previous day. .PP The * after the date is an optional status flag. Here it means \[dq]cleared & confirmed\[dq]. .PP The currency symbols are optional, but usually a good idea as you\[aq]ll be dealing with multiple currencies sooner or later. .PP The = amounts are optional balance assertions, providing extra error checking. .RE .IP \[bu] 2 The second way: run \f[CR]hledger add\f[R] and follow the prompts to record a similar transaction: .RS 2 .IP .EX $ hledger add Adding transactions to journal file /Users/simon/finance/2023.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control\-d or control\-c. Date [2023\-02\-07]: 2023\-01\-01 Description: * opening balances Account 1: assets:bank:checking Amount 1: $1000 Account 2: assets:bank:savings Amount 2 [$\-1000]: $2000 Account 3: assets:cash Amount 3 [$\-3000]: $100 Account 4: liabilities:creditcard Amount 4 [$\-3100]: $\-50 Account 5: equity:opening/closing balances Amount 5 [$\-3050]: Account 6 (or . or enter to finish this transaction): . 2023\-01\-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $\-50 equity:opening/closing balances $\-3050 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl\-D/ctrl\-C to quit) Date [2023\-01\-01]: . .EE .RE .PP If you\[aq]re using version control, this could be a good time to commit the journal. Eg: .IP .EX $ git commit \-m \[aq]initial balances\[aq] 2023.journal .EE .SS Recording transactions As you spend or receive money, you can record these transactions using one of the methods above (text editor, hledger add) or by using the hledger\-iadd or hledger\-web add\-ons, or by using the import command to convert CSV data downloaded from your bank. .PP Here are some simple transactions, see the hledger_journal(5) manual and hledger.org for more ideas: .IP .EX 2023/1/10 * gift received assets:cash $20 income:gifts 2023.1.12 * farmers market expenses:food $13 assets:cash 2023\-01\-15 paycheck income:salary assets:bank:checking $1000 .EE .SS Reconciling Periodically you should reconcile \- compare your hledger\-reported balances against external sources of truth, like bank statements or your bank\[aq]s website \- to be sure that your ledger accurately represents the real\-world balances (and, that the real\-world institutions have not made a mistake!). This gets easy and fast with (1) practice and (2) frequency. If you do it daily, it can take 2\-10 minutes. If you let it pile up, expect it to take longer as you hunt down errors and discrepancies. .PP A typical workflow: .IP "1." 3 Reconcile cash. Count what\[aq]s in your wallet. Compare with what hledger reports (\f[CR]hledger bal cash\f[R]). If they are different, try to remember the missing transaction, or look for the error in the already\-recorded transactions. A register report can be helpful (\f[CR]hledger reg cash\f[R]). If you can\[aq]t find the error, add an adjustment transaction. Eg if you have $105 after the above, and can\[aq]t explain the missing $2, it could be: .RS 4 .IP .EX 2023\-01\-16 * adjust cash assets:cash $\-2 = $105 expenses:misc .EE .RE .IP "2." 3 Reconcile checking. Log in to your bank\[aq]s website. Compare today\[aq]s (cleared) balance with hledger\[aq]s cleared balance (\f[CR]hledger bal checking \-C\f[R]). If they are different, track down the error or record the missing transaction(s) or add an adjustment transaction, similar to the above. Unlike the cash case, you can usually compare the transaction history and running balance from your bank with the one reported by \f[CR]hledger reg checking \-C\f[R]. This will be easier if you generally record transaction dates quite similar to your bank\[aq]s clearing dates. .IP "3." 3 Repeat for other asset/liability accounts. .PP Tip: instead of the register command, use hledger\-ui to see a live\-updating register while you edit the journal: \f[CR]hledger\-ui \-\-watch \-\-register checking \-C\f[R] .PP After reconciling, it could be a good time to mark the reconciled transactions\[aq] status as \[dq]cleared and confirmed\[dq], if you want to track that, by adding the \f[CR]*\f[R] marker. Eg in the paycheck transaction above, insert \f[CR]*\f[R] between \f[CR]2023\-01\-15\f[R] and \f[CR]paycheck\f[R] .PP If you\[aq]re using version control, this can be another good time to commit: .IP .EX $ git commit \-m \[aq]txns\[aq] 2023.journal .EE .SS Reporting Here are some basic reports. .PP Show all transactions: .IP .EX $ hledger print 2023\-01\-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $\-50 equity:opening/closing balances $\-3050 2023\-01\-10 * gift received assets:cash $20 income:gifts 2023\-01\-12 * farmers market expenses:food $13 assets:cash 2023\-01\-15 * paycheck income:salary assets:bank:checking $1000 2023\-01\-16 * adjust cash assets:cash $\-2 = $105 expenses:misc .EE .PP Show account names, and their hierarchy: .IP .EX $ hledger accounts \-\-tree assets bank checking savings cash equity opening/closing balances expenses food misc income gifts salary liabilities creditcard .EE .PP Show all account totals: .IP .EX $ hledger balance $4105 assets $4000 bank $2000 checking $2000 savings $105 cash $\-3050 equity:opening/closing balances $15 expenses $13 food $2 misc $\-1020 income $\-20 gifts $\-1000 salary $\-50 liabilities:creditcard \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- 0 .EE .PP Show only asset and liability balances, as a flat list, limited to depth 2: .IP .EX $ hledger bal assets liabilities \-2 $4000 assets:bank $105 assets:cash $\-50 liabilities:creditcard \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- $4055 .EE .PP Show the same thing without negative numbers, formatted as a simple balance sheet: .IP .EX $ hledger bs \-2 Balance Sheet 2023\-01\-16 || 2023\-01\-16 ========================++============ Assets || \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\- assets:bank || $4000 assets:cash || $105 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\- || $4105 ========================++============ Liabilities || \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\- liabilities:creditcard || $50 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\- || $50 ========================++============ Net: || $4055 .EE .PP The final total is your \[dq]net worth\[dq] on the end date. (Or use \f[CR]bse\f[R] for a full balance sheet with equity.) .PP Show income and expense totals, formatted as an income statement: .IP .EX hledger is Income Statement 2023\-01\-01\-2023\-01\-16 || 2023\-01\-01\-2023\-01\-16 ===============++======================= Revenues || \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- income:gifts || $20 income:salary || $1000 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || $1020 ===============++======================= Expenses || \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- expenses:food || $13 expenses:misc || $2 \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-++\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- || $15 ===============++======================= Net: || $1005 .EE .PP The final total is your net income during this period. .PP Show transactions affecting your wallet, with running total: .IP .EX $ hledger register cash 2023\-01\-01 opening balances assets:cash $100 $100 2023\-01\-10 gift received assets:cash $20 $120 2023\-01\-12 farmers market assets:cash $\-13 $107 2023\-01\-16 adjust cash assets:cash $\-2 $105 .EE .PP Show weekly posting counts as a bar chart: .IP .EX $ hledger activity \-W 2019\-12\-30 ***** 2023\-01\-06 **** 2023\-01\-13 **** .EE .SS Migrating to a new file At the end of the year, you may want to continue your journal in a new file, so that old transactions don\[aq]t slow down or clutter your reports, and to help ensure the integrity of your accounting history. See the close command. .PP If using version control, don\[aq]t forget to \f[CR]git add\f[R] the new file. .SH BUGS We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). .PP Some known issues and limitations: .PP The need to precede add\-on command options with \f[CR]\-\-\f[R] when invoked from hledger is awkward. (See Command options, Constructing command lines.) .PP A UTF\-8\-aware system locale must be configured to work with non\-ascii data. (See Unicode characters, Troubleshooting.) .PP On Microsoft Windows, depending whether you are running in a CMD window or a Cygwin/MSYS/Mintty window and how you installed hledger, non\-ascii characters and colours may not be supported, and the tab key may not be supported by \f[CR]hledger add\f[R]. (Running in a WSL window should resolve these.) .PP When processing large data files, hledger uses more memory than Ledger. .SS Troubleshooting Here are some common issues you might encounter when you run hledger, and how to resolve them (and remember also you can usually get quick Support): .PP \f[B]PATH issues: I get an error like \[dq]No command \[aq]hledger\[aq] found\[dq]\f[R] .PD 0 .P .PD Depending how you installed hledger, the executables may not be in your shell\[aq]s PATH. Eg on unix systems, stack installs hledger in \f[CR]\[ti]/.local/bin\f[R] and cabal installs it in \f[CR]\[ti]/.cabal/bin\f[R]. You may need to add one of these directories to your shell\[aq]s PATH, and/or open a new terminal window. .PP \f[B]LEDGER_FILE issues: I configured LEDGER_FILE but hledger is not using it\f[R] .PD 0 .P .PD .IP \[bu] 2 \f[CR]LEDGER_FILE\f[R] should be a real environment variable, not just a shell variable. Eg on unix, the command \f[CR]env | grep LEDGER_FILE\f[R] should show it. You may need to use \f[CR]export\f[R] (see https://stackoverflow.com/a/7411509). .IP \[bu] 2 You may need to force your shell to see the new configuration. A simple way is to close your terminal window and open a new one. .PP \f[B]LANG issues: I get errors like \[dq]Illegal byte sequence\[dq] or \[dq]Invalid or incomplete multibyte or wide character\[dq] or \[dq]commitAndReleaseBuffer: invalid argument (invalid character)\[dq]\f[R] .PD 0 .P .PD Programs compiled with GHC (hledger, haskell build tools, etc.) need the system locale to be UTF\-8\-aware, or they will fail when they encounter non\-ascii characters. To fix it, set the LANG environment variable to a locale which supports UTF\-8 and which is installed on your system. .PP On unix, \f[CR]locale \-a\f[R] lists the installed locales. Look for one which mentions \f[CR]utf8\f[R], \f[CR]UTF\-8\f[R] or similar. Some examples: \f[CR]C.UTF\-8\f[R], \f[CR]en_US.utf\-8\f[R], \f[CR]fr_FR.utf8\f[R]. If necessary, use your system package manager to install one. Then select it by setting the \f[CR]LANG\f[R] environment variable. Note, exact spelling and capitalisation of the locale name may be important: Here\[aq]s one common way to configure this permanently for your shell: .IP .EX $ echo \[dq]export LANG=en_US.utf8\[dq] >>\[ti]/.profile # close and re\-open terminal window .EE .PP If you are using Nix (not NixOS) for GHC and Hledger, you might need to set the \f[CR]LOCALE_ARCHIVE\f[R] variable: .IP .EX $ echo \[dq]export LOCALE_ARCHIVE=${glibcLocales}/lib/locale/locale\-archive\[dq] >>\[ti]/.profile # close and re\-open terminal window .EE .PP \f[B]COMPATIBILITY ISSUES: hledger gives an error with my Ledger file\f[R] .PD 0 .P .PD Not all of Ledger\[aq]s journal file syntax or feature set is supported. See hledger and Ledger for full details. .SH AUTHORS Simon Michael and contributors. .br See http://hledger.org/CREDITS.html .SH COPYRIGHT Copyright 2007-2023 Simon Michael and contributors. .SH LICENSE Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), ledger(1) hledger-1.32.3/embeddedfiles/hledger.txt0000644000000000000000000137546714555433336016371 0ustar0000000000000000 HLEDGER(1) hledger User Manuals HLEDGER(1) NAME hledger - robust, friendly plain text accounting (CLI version) SYNOPSIS hledger hledger COMMAND [OPTS] [ARGS] hledger ADDONCMD -- [OPTS] [ARGS] DESCRIPTION hledger is a robust, user-friendly, cross-platform set of programs for tracking money, time, or any other commodity, using double-entry ac- counting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). This manual is for hledger's command line interface, version 1.32.3. It also describes the common options, file formats and concepts used by all hledger programs. It might accidentally teach you some bookkeep- ing/accounting as well! You don't need to know everything in here to use hledger productively, but when you have a question about function- ality, this doc should answer it. It is detailed, so do skip ahead or skim when needed. You can read it on hledger.org, or as an info manual or man page on your system. You can also get it from hledger itself with hledger --man, hledger --info or hledger help [TOPIC]. The main function of the hledger CLI is to read plain text files de- scribing financial transactions, crunch the numbers, and print a useful report on the terminal (or save it as HTML, CSV, JSON or SQL). Many reports are available, as subcommands. hledger will also detect other hledger-* executables as extra subcommands. hledger usually reads from (and appends to) a journal file specified by the LEDGER_FILE environment variable (defaulting to $HOME/.hledger.journal); or you can specify files with -f options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. Here is a small journal file describing one transaction: 2015-10-16 bought food expenses:food $10 assets:cash Transactions are dated movements of money (etc.) between two or more accounts: bank accounts, your wallet, revenue/expense categories, peo- ple, etc. You can choose any account names you wish, using : to indi- cate subaccounts. There must be at least two spaces between account name and amount. Positive amounts are inflow to that account (debit), negatives are outflow from it (credit). (Some reports show revenue, liability and equity account balances as negative numbers as a result; this is normal.) hledger's add command can help you add transactions, or you can install other data entry UIs like hledger-web or hledger-iadd. For more exten- sive/efficient changes, use a text editor: Emacs + ledger-mode, VIM + vim-ledger, or VS Code + hledger-vscode are some good choices (see https://hledger.org/editors.html). To get started, run hledger add and follow the prompts, or save some entries like the above in $HOME/.hledger.journal, then try commands like: hledger print -x hledger aregister assets hledger balance hledger balancesheet hledger incomestatement. Run hledger to list the commands. See also the "Starting a journal file" and "Setting opening balances" sections in PART 5: COMMON TASKS. PART 1: USER INTERFACE Input hledger reads one or more data files, each time you run it. You can specify a file with -f, like so $ hledger -f FILE print Files are most often in hledger's journal format, with the .journal file extension (.hledger or .j also work); these files describe trans- actions, like an accounting general journal. When no file is specified, hledger looks for .hledger.journal in your home directory. But most people prefer to keep financial files in a dedicated folder, perhaps with version control. Also, starting a new journal file each year is common (it's not required, but helps keep things fast and or- ganised). So we usually configure a different journal file, by setting the LEDGER_FILE environment variable, to something like ~/fi- nance/2023.journal. For more about how to do that on your system, see Common tasks > Setting LEDGER_FILE. Data formats Usually the data file is in hledger's journal format, but it can be in any of the supported file formats, which currently are: Reader: Reads: Used for file extensions: ----------------------------------------------------------------------------- journal hledger journal files and some .journal .j .hledger .ledger Ledger journals, for transac- tions timeclock timeclock files, for precise .timeclock time logging timedot timedot files, for approximate .timedot time logging csv CSV/SSV/TSV/character-sepa- .csv .ssv .tsv .csv.rules rated values, for data import .ssv.rules .tsv.rules These formats are described in more detail below. hledger detects the format automatically based on the file extensions shown above. If it can't recognise the file extension, it assumes journal format. So for non-journal files, it's important to use a recognised file extension, so as to either read successfully or to show relevant error messages. You can also force a specific reader/format by prefixing the file path with the format and a colon. Eg, to read a .dat file as csv format: $ hledger -f csv:/some/csv-file.dat stats Standard input The file name - means standard input: $ cat FILE | hledger -f- print If reading non-journal data in this way, you'll need to add a file for- mat prefix, like: $ echo 'i 2009/13/1 08:00:00' | hledger print -f timeclock:- Multiple files You can specify multiple -f options, to read multiple files as one big journal. When doing this, note that certain features (described below) will be affected: o Balance assertions will not see the effect of transactions in previ- ous files. (Usually this doesn't matter as each file will set the corresponding opening balances.) o Some directives will not affect previous or subsequent files. If needed, you can work around these by using a single parent file which includes the others, or concatenating the files into one, eg: cat a.journal b.journal | hledger -f- CMD. Strict mode hledger checks input files for valid data. By default, the most impor- tant errors are detected, while still accepting easy journal files without a lot of declarations: o Are the input files parseable, with valid syntax ? o Are all transactions balanced ? o Do all balance assertions pass ? With the -s/--strict flag, additional checks are performed: o Are all accounts posted to, declared with an account directive ? (Account error checking) o Are all commodities declared with a commodity directive ? (Commodity error checking) o Are all commodity conversions declared explicitly ? You can use the check command to run individual checks -- the ones listed above and some more. Commands hledger provides various subcommands for getting things done. Most of these commands do not change the journal file; they just read it and output a report. A few commands assist with adding data and file man- agement. To show the commands list, run hledger with no arguments. The commands are described in detail in PART 4: COMMANDS, below. To use a particular command, run hledger CMD [CMDOPTS] [CMDARGS], o CMD is the full command name, or its standard abbreviation shown in the commands list, or any unambiguous prefix of the name. o CMDOPTS are command-specific options, if any. Command-specific op- tions must be written after the command name. Eg: hledger print -x. o CMDARGS are additional arguments to the command, if any. Most hledger commands accept arguments representing a query, to limit the data in some way. Eg: hledger reg assets:checking. To list a command's options, arguments, and documentation in the termi- nal, run hledger CMD -h. Eg: hledger bal -h. Add-on commands In addition to the built-in commands, you can install add-on commands: programs or scripts named "hledger-SOMETHING", which will also appear in hledger's commands list. If you used the hledger-install script, you will have several add-ons installed already. Some more can be found in hledger's bin/ directory, documented at https://hledger.org/scripts.html. More precisely, add-on commands are programs or scripts in your shell's PATH, whose name starts with "hledger-" and ends with no extension or a recognised extension (".bat", ".com", ".exe", ".hs", ".js", ".lhs", ".lua", ".php", ".pl", ".py", ".rb", ".rkt", or ".sh"), and (on unix and mac) which has executable permission for the current user. You can run add-on commands using hledger, much like built-in commands: hledger ADDONCMD [-- ADDONCMDOPTS] [ADDONCMDARGS]. But note the double hyphen argument, required before add-on-specific options. Eg: hledger ui -- --watch or hledger web -- --serve. If this causes difficulty, you can always run the add-on directly, without using hledger: hledger-ui --watch or hledger-web --serve. Options Run hledger -h to see general command line help, and general options which are common to most hledger commands. These options can be writ- ten anywhere on the command line. They can be grouped into help, in- put, and reporting options: General help options -h --help show general or COMMAND help --man show general or COMMAND user manual with man --info show general or COMMAND user manual with info --version show general or ADDONCMD version --debug[=N] show debug output (levels 1-9, default: 1) General input options -f FILE --file=FILE use a different input file. For stdin, use - (default: $LEDGER_FILE or $HOME/.hledger.journal) --rules-file=RULESFILE Conversion rules file to use when reading CSV (default: FILE.rules) --separator=CHAR Field separator to expect when reading CSV (default: ',') --alias=OLD=NEW rename accounts named OLD to NEW --pivot FIELDNAME use some other field or tag for the account name -I --ignore-assertions disable balance assertion checks (note: does not disable balance assignments) -s --strict do extra error checking (check that all posted accounts are de- clared) General reporting options -b --begin=DATE include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) -e --end=DATE include postings/txns before this date (will be adjusted to fol- lowing subperiod end when using a report interval) -D --daily multiperiod/multicolumn report by day -W --weekly multiperiod/multicolumn report by week -M --monthly multiperiod/multicolumn report by month -Q --quarterly multiperiod/multicolumn report by quarter -Y --yearly multiperiod/multicolumn report by year -p --period=PERIODEXP set start date, end date, and/or reporting interval all at once using period expressions syntax --date2 match the secondary date instead (see command help for other ef- fects) --today=DATE override today's date (affects relative smart dates, for tests/examples) -U --unmarked include only unmarked postings/txns (can combine with -P or -C) -P --pending include only pending postings/txns -C --cleared include only cleared postings/txns -R --real include only non-virtual postings -NUM --depth=NUM hide/aggregate accounts or postings more than NUM levels deep -E --empty show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) -B --cost convert amounts to their cost/selling amount at transaction time -V --market convert amounts to their market value in default valuation com- modities -X --exchange=COMM convert amounts to their market value in commodity COMM --value convert amounts to cost or market value, more flexibly than -B/-V/-X --infer-equity infer conversion equity postings from costs --infer-costs infer costs from conversion equity postings --infer-market-prices use costs as additional market prices, as if they were P direc- tives --forecast generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger-ui make fu- ture-dated transactions visible. --auto generate extra postings by applying auto posting rules to all txns (not just forecast txns) --verbose-tags add visible tags indicating transactions or postings which have been generated/modified --commodity-style Override the commodity style in the output for the specified commodity. For example 'EUR1.000,00'. --color=WHEN (or --colour=WHEN) Should color-supporting commands use ANSI color codes in text output. 'auto' (default): whenever stdout seems to be a color-supporting terminal. 'always' or 'yes': always, useful eg when piping output into 'less -R'. 'never' or 'no': never. A NO_COLOR environment variable overrides this. --pretty[=WHEN] Show prettier output, e.g. using unicode box-drawing charac- ters. Accepts 'yes' (the default) or 'no' ('y', 'n', 'always', 'never' also work). If you provide an argument you must use '=', e.g. '--pretty=yes'. When a reporting option appears more than once in the command line, the last one takes precedence. Some reporting options can also be written as query arguments. Command line tips Here are some details useful to know about for hledger command lines (and elsewhere). Feel free to skip this section until you need it. Option repetition If options are repeated in a command line, hledger will generally use the last (right-most) occurence. Special characters Single escaping (shell metacharacters) In shell command lines, characters significant to your shell - such as spaces, <, >, (, ), |, $ and \ - should be "shell-escaped" if you want hledger to see them. This is done by enclosing them in single or dou- ble quotes, or by writing a backslash before them. Eg to match an ac- count name containing a space: $ hledger register 'credit card' or: $ hledger register credit\ card Windows users should keep in mind that cmd treats single quote as a regular character, so you should be using double quotes exclusively. PowerShell treats both single and double quotes as quotes. Double escaping (regular expression metacharacters) Characters significant in regular expressions (described below) - such as ., ^, $, [, ], (, ), |, and \ - may need to be "regex-escaped" if you don't want them to be interpreted by hledger's regular expression engine. This is done by writing backslashes before them, but since backslash is typically also a shell metacharacter, both shell-escaping and regex-escaping will be needed. Eg to match a literal $ sign while using the bash shell: $ hledger balance cur:'\$' or: $ hledger balance cur:\\$ Triple escaping (for add-on commands) When you use hledger to run an external add-on command (described be- low), one level of shell-escaping is lost from any options or arguments intended for by the add-on command, so those need an extra level of shell-escaping. Eg to match a literal $ sign while using the bash shell and running an add-on command (ui): $ hledger ui cur:'\\$' or: $ hledger ui cur:\\\\$ If you wondered why four backslashes, perhaps this helps: unescaped: $ escaped: \$ double-escaped: \\$ triple-escaped: \\\\$ Or, you can avoid the extra escaping by running the add-on executable directly: $ hledger-ui cur:\\$ Less escaping Options and arguments are sometimes used in places other than the shell command line, where shell-escaping is not needed, so there you should use one less level of escaping. Those places include: o an @argumentfile o hledger-ui's filter field o hledger-web's search form o GHCI's prompt (used by developers). Unicode characters hledger is expected to handle non-ascii characters correctly: o they should be parsed correctly in input files and on the command line, by all hledger tools (add, iadd, hledger-web's search/add/edit forms, etc.) o they should be displayed correctly by all hledger tools, and on-screen alignment should be preserved. This requires a well-configured environment. Here are some tips: o A system locale must be configured, and it must be one that can de- code the characters being used. In bash, you can set a locale like this: export LANG=en_US.UTF-8. There are some more details in Trou- bleshooting. This step is essential - without it, hledger will quit on encountering a non-ascii character (as with all GHC-compiled pro- grams). o your terminal software (eg Terminal.app, iTerm, CMD.exe, xterm..) must support unicode o the terminal must be using a font which includes the required unicode glyphs o the terminal should be configured to display wide characters as dou- ble width (for report alignment) o on Windows, for best results you should run hledger in the same kind of environment in which it was built. Eg hledger built in the stan- dard CMD.EXE environment (like the binaries on our download page) might show display problems when run in a cygwin or msys terminal, and vice versa. (See eg #961). Regular expressions A regular expression (regexp) is a small piece of text where certain characters (like ., ^, $, +, *, (), |, [], \) have special meanings, forming a tiny language for matching text precisely - very useful in hledger and elsewhere. To learn all about them, visit regular-expres- sions.info. hledger supports regexps whenever you are entering a pattern to match something, eg in query arguments, account aliases, CSV if rules, hledger-web's search form, hledger-ui's / search, etc. You may need to wrap them in quotes, especially at the command line (see Special char- acters above). Here are some examples: Account name queries (quoted for command line use): Regular expression: Matches: ------------------- ------------------------------------------------------------ bank assets:bank, assets:bank:savings, expenses:art:banksy, ... :bank assets:bank:savings, expenses:art:banksy :bank: assets:bank:savings '^bank' none of those ( ^ matches beginning of text ) 'bank$' assets:bank ( $ matches end of text ) 'big \$ bank' big $ bank ( \ disables following character's special meaning ) '\bbank\b' assets:bank, assets:bank:savings ( \b matches word boundaries ) '(sav|check)ing' saving or checking ( (|) matches either alternative ) 'saving|checking' saving or checking ( outer parentheses are not needed ) 'savings?' saving or savings ( ? matches 0 or 1 of the preceding thing ) 'my +bank' my bank, my bank, ... ( + matches 1 or more of the preceding thing ) 'my *bank' mybank, my bank, my bank, ... ( * matches 0 or more of the preceding thing ) 'b.nk' bank, bonk, b nk, ... ( . matches any character ) Some other queries: desc:'amazon|amzn|audible' Amazon transactions cur:EUR amounts with commodity symbol containing EUR cur:'\$' amounts with commodity symbol containing $ cur:'^\$$' only $ amounts, not eg AU$ or CA$ cur:....? amounts with 4-or-more-character symbols tag:.=202[1-3] things with any tag whose value contains 2021, 2022 or 2023 Account name aliases: accept . instead of : as account separator: alias /\./=: replaces all periods in account names with colons Show multiple top-level accounts combined as one: --alias='/^[^:]+/=combined' ( [^:] matches any character other than : ) Show accounts with the second-level part removed: --alias '/^([^:]+):[^:]+/ = \1' match a top-level account and a second-level account and replace those with just the top-level account ( \1 in the replacement text means "whatever was matched by the first parenthesised part of the regexp" CSV rules: match CSV records containing dining-related MCC codes: if \?MCC581[124] Match CSV records with a specific amount around the end/start of month: if %amount \b3\.99 & %date (29|30|31|01|02|03)$ hledger's regular expressions hledger's regular expressions come from the regex-tdfa library. If they're not doing what you expect, it's important to know exactly what they support: 1. they are case insensitive 2. they are infix matching (they do not need to match the entire thing being matched) 3. they are POSIX ERE (extended regular expressions) 4. they also support GNU word boundaries (\b, \B, \<, \>) 5. backreferences are supported when doing text replacement in account aliases or CSV rules, where backreferences can be used in the re- placement string to reference capturing groups in the search regexp. Otherwise, if you write \1, it will match the digit 1. 6. they do not support mode modifiers ((?s)), character classes (\w, \d), or anything else not mentioned above. Some things to note: o In the alias directive and --alias option, regular expressions must be enclosed in forward slashes (/REGEX/). Elsewhere in hledger, these are not required. o In queries, to match a regular expression metacharacter like $ as a literal character, prepend a backslash. Eg to search for amounts with the dollar sign in hledger-web, write cur:\$. o On the command line, some metacharacters like $ have a special mean- ing to the shell and so must be escaped at least once more. See Spe- cial characters. Argument files You can save a set of command line options and arguments in a file, and then reuse them by writing @FILENAME as a command line argument. Eg: hledger bal @foo.args. Inside the argument file, each line should contain just one option or argument. Don't use spaces except inside quotes (or you'll see a con- fusing error); write = (or nothing) between a flag and its argument. For the special characters mentioned above, use one less level of quot- ing than you would at the command prompt. Output Output destination hledger commands send their output to the terminal by default. You can of course redirect this, eg into a file, using standard shell syntax: $ hledger print > foo.txt Some commands (print, register, stats, the balance commands) also pro- vide the -o/--output-file option, which does the same thing without needing the shell. Eg: $ hledger print -o foo.txt $ hledger print -o - # write to stdout (the default) Output format Some commands offer other kinds of output, not just text on the termi- nal. Here are those commands and the formats currently supported: - txt csv/tsv html json sql -------------------------------------------------------------------------------------- aregister Y Y Y Y balance Y 1 Y 1 Y 1,2 Y balancesheet Y 1 Y 1 Y 1 Y balancesheete- Y 1 Y 1 Y 1 Y quity cashflow Y 1 Y 1 Y 1 Y incomestatement Y 1 Y 1 Y 1 Y print Y Y Y Y register Y Y Y o 1 Also affected by the balance commands' --layout option. o 2 balance does not support html output without a report interval or with --budget. The output format is selected by the -O/--output-format=FMT option: $ hledger print -O csv # print CSV on stdout or by the filename extension of an output file specified with the -o/--output-file=FILE.FMT option: $ hledger balancesheet -o foo.csv # write CSV to foo.csv The -O option can be combined with -o to override the file extension, if needed: $ hledger balancesheet -o foo.txt -O csv # write CSV to foo.txt Some notes about the various output formats: CSV output o In CSV output, digit group marks (such as thousands separators) are disabled automatically. HTML output o HTML output can be styled by an optional hledger.css file in the same directory. JSON output o This is not yet much used; real-world feedback is welcome. o Our JSON is rather large and verbose, since it is a faithful repre- sentation of hledger's internal data types. To understand the JSON, read the Haskell type definitions, which are mostly in https://github.com/simonmichael/hledger/blob/mas- ter/hledger-lib/Hledger/Data/Types.hs. o hledger represents quantities as Decimal values storing up to 255 significant digits, eg for repeating decimals. Such numbers can arise in practice (from automatically-calculated transaction prices), and would break most JSON consumers. So in JSON, we show quantities as simple Numbers with at most 10 decimal places. We don't limit the number of integer digits, but that part is under your control. We hope this approach will not cause problems in practice; if you find otherwise, please let us know. (Cf #1195) SQL output o This is not yet much used; real-world feedback is welcome. o SQL output is expected to work at least with SQLite, MySQL and Post- gres. o For SQLite, it will be more useful if you modify the generated id field to be a PRIMARY KEY. Eg: $ hledger print -O sql | sed 's/id serial/id INTEGER PRIMARY KEY AUTOINCREMENT NOT NULL/g' | ... o SQL output is structured with the expectations that statements will be executed in the empty database. If you already have tables cre- ated via SQL output of hledger, you would probably want to either clear tables of existing data (via delete or truncate SQL statements) or drop tables completely as otherwise your postings will be duped. Commodity styles When displaying amounts, hledger infers a standard display style for each commodity/currency, as described below in Commodity display style. If needed, this can be overridden by a -c/--commodity-style option (ex- cept for cost amounts and amounts displayed by the print command, which are always displayed with all decimal digits). For example, the fol- lowing will force dollar amounts to be displayed as shown: $ hledger print -c '$1.000,0' This option can repeated to set the display style for multiple commodi- ties/currencies. Its argument is as described in the commodity direc- tive. Colour In terminal output, some commands can produce colour when the terminal supports it: o if the --color/--colour option is given a value of yes or always (or no or never), colour will (or will not) be used; o otherwise, if the NO_COLOR environment variable is set, colour will not be used; o otherwise, colour will be used if the output (terminal or file) sup- ports it. Box-drawing In terminal output, you can enable unicode box-drawing characters to render prettier tables: o if the --pretty option is given a value of yes or always (or no or never), unicode characters will (or will not) be used; o otherwise, unicode characters will not be used. Paging When showing long output in the terminal, hledger will try to use the pager specified by the PAGER environment variable, or less, or more. (A pager is a helper program that shows one page at a time rather than scrolling everything off screen). Currently it does this only for help output, not for reports; specifically, o when listing commands, with hledger o when showing help with hledger [CMD] --help, o when viewing manuals with hledger help or hledger --man. Note the pager is expected to handle ANSI codes, which hledger uses eg for bold emphasis. For the common pager less (and its more compatibil- ity mode), we add R to the LESS and MORE environment variables to make this work. If you use a different pager, you might need to configure it similarly, to avoid seeing junk on screen (let us know). Otherwise, you can set the NO_COLOR environment variable to 1 to disable all ANSI output (see Colour). Debug output We intend hledger to be relatively easy to troubleshoot, introspect and develop. You can add --debug[=N] to any hledger command line to see additional debug output. N ranges from 1 (least output, the default) to 9 (maximum output). Typically you would start with 1 and increase until you are seeing enough. Debug output goes to stderr, and is not affected by -o/--output-file (unless you redirect stderr to stdout, eg: 2>&1). It will be interleaved with normal output, which can help re- veal when parts of the code are evaluated. To capture debug output in a log file instead, you can usually redirect stderr, eg: hledger bal --debug=3 2>hledger.log Environment These environment variables affect hledger: COLUMNS This is normally set by your terminal; some hledger commands (register) will format their output to this width. If not set, they will try to use the available terminal width. LEDGER_FILE The main journal file to use when not specified with -f/--file. Default: $HOME/.hledger.journal. NO_COLOR If this environment variable is set (with any value), hledger will not use ANSI color codes in terminal output, unless overridden by an explicit --color/--colour option. PART 2: DATA FORMATS Journal hledger's default file format, representing a General Journal. Here's a cheatsheet/mini-tutorial, or you can skip ahead to About journal for- mat. Journal cheatsheet # Here is the main syntax of hledger's journal format # (omitting extra Ledger compatibility syntax). # hledger journals contain comments, directives, and transactions, in any order: ############################################################################### # 1. Comment lines are for notes or temporarily disabling things. # They begin with #, ;, or a line containing the word "comment". # hash comment line ; semicolon comment line comment These lines are commented. end comment # Some but not all hledger entries can have same-line comments attached to them, # from ; (semicolon) to end of line. ############################################################################### # 2. Directives modify parsing or reports in some way. # They begin with a word or letter (or symbol). account actifs ; type:A, declare an account that is an Asset. 2+ spaces before ;. account passifs ; type:L, declare an account that is a Liability, and so on.. (ALERX) alias chkg = assets:checking commodity $0.00 decimal-mark . include /dev/null payee Whole Foods P 2022-01-01 AAAA $1.40 ~ monthly budget goals ; <- 2+ spaces between period expression and description expenses:food $400 expenses:home $1000 budgeted ############################################################################### # 3. Transactions are what it's all about; they are dated events, # usually describing movements of money. # They begin with a date. # DATE DESCRIPTION ; This is a transaction comment. # ACCOUNT NAME 1 AMOUNT1 ; <- posting 1. This is a posting comment. # ACCOUNT NAME 2 AMOUNT2 ; <- posting 2. Postings must be indented. # ; ^^ At least 2 spaces between account and amount. # ... ; Any number of postings is allowed. The amounts must balance (sum to 0). 2022-01-01 opening balances are declared this way assets:checking $1000 ; Account names can be anything. lower case is easy to type. assets:savings $1000 ; assets, liabilities, equity, revenues, expenses are common. assets:cash:wallet $100 ; : indicates subaccounts. liabilities:credit card $-200 ; liabilities, equity, revenues balances are usually negative. equity ; One amount can be left blank; $-1900 is inferred here. 2022-04-15 * (#12345) pay taxes ; There can be a ! or * after the date meaning "pending" or "cleared". ; There can be a transaction code (text in parentheses) after the date/status. ; Amounts' sign represents direction of flow, or credit/debit: assets:checking $-500 ; minus means removed from this account (credit) expenses:tax:us:2021 $500 ; plus means added to this account (debit) ; revenue/expense categories are also "accounts" 2022-01-01 ; The description is optional. ; Any currency/commodity symbols are allowed, on either side. assets:cash:wallet GBP -10 expenses:clothing GBP 10 assets:gringotts -10 gold assets:pouch 10 gold revenues:gifts -2 "Liquorice Wands" ; Complex symbols assets:bag 2 "Liquorice Wands" ; must be double-quoted. 2022-01-01 Cost in another commodity can be noted with @ or @@ assets:investments 2.0 AAAA @ $1.50 ; @ means per-unit cost assets:investments 3.0 AAAA @@ $4 ; @@ means total cost assets:checking $-7.00 2022-01-02 assert balances ; Balances can be asserted for extra error checking, in any transaction. assets:investments 0 AAAA = 5.0 AAAA assets:pouch 0 gold = 10 gold assets:savings $0 = $1000 1999-12-31 Ordering transactions by date is recommended but not required. ; Postings are not required. 2022.01.01 These date 2022/1/1 formats are 12/31 also allowed (but consistent YYYY-MM-DD is recommended). About journal format hledger's usual data source is a plain text file containing journal en- tries in hledger journal format. This file represents a standard ac- counting general journal. I use file names ending in .journal, but that's not required. The journal file contains a number of transaction entries, each describing a transfer of money (or any commodity) between two or more named accounts, in a simple format readable by both hledger and humans. hledger's journal format is compatible with most of Ledger's journal format, but not all of it. The differences and interoperation tips are described at hledger and Ledger. With some care, and by avoiding in- compatible features, you can keep your hledger journal readable by Ledger and vice versa. This can useful eg for comparing the behaviour of one app against the other. You can use hledger without learning any more about this file; just use the add or web or import commands to create and update it. Many users, though, edit the journal file with a text editor, and track changes with a version control system such as git. Editor addons such as ledger-mode or hledger-mode for Emacs, vim-ledger for Vim, and hledger-vscode for Visual Studio Code, make this easier, adding colour, formatting, tab completion, and useful commands. See Editor configura- tion at hledger.org for the full list. Here's a description of each part of the file format (and hledger's data model). A hledger journal file can contain three kinds of thing: file comments, transactions, and/or directives (counting periodic transaction rules and auto posting rules as directives). Comments Lines in the journal will be ignored if they begin with a hash (#) or a semicolon (;). (See also Other syntax.) hledger will also ignore re- gions beginning with a comment line and ending with an end comment line (or file end). Here's a suggestion for choosing between them: o # for top-level notes o ; for commenting out things temporarily o comment for quickly commenting large regions (remember it's there, or you might get confused) Eg: # a comment line ; another commentline comment A multi-line comment block, continuing until "end comment" directive or the end of the current file. end comment Some hledger entries can have same-line comments attached to them, from ; (semicolon) to end of line. See Transaction comments, Posting com- ments, and Account comments below. Transactions Transactions are the main unit of information in a journal file. They represent events, typically a movement of some quantity of commodities between two or more named accounts. Each transaction is recorded as a journal entry, beginning with a sim- ple date in column 0. This can be followed by any of the following op- tional fields, separated by spaces: o a status character (empty, !, or *) o a code (any short number or text, enclosed in parentheses) o a description (any remaining text until end of line or a semicolon) o a comment (any remaining text following a semicolon until end of line, and any following indented lines beginning with a semicolon) o 0 or more indented posting lines, describing what was transferred and the accounts involved (indented comment lines are also allowed, but not blank lines or non-indented lines). Here's a simple journal file containing one transaction: 2008/01/01 income assets:bank:checking $1 income:salary $-1 Dates Simple dates Dates in the journal file use simple dates format: YYYY-MM-DD or YYYY/MM/DD or YYYY.MM.DD, with leading zeros optional. The year may be omitted, in which case it will be inferred from the context: the cur- rent transaction, the default year set with a Y directive, or the cur- rent date when the command is run. Some examples: 2010-01-31, 2010/01/31, 2010.1.31, 1/31. (The UI also accepts simple dates, as well as the more flexible smart dates documented in the hledger manual.) Posting dates You can give individual postings a different date from their parent transaction, by adding a posting comment containing a tag (see below) like date:DATE. This is probably the best way to control posting dates precisely. Eg in this example the expense should appear in May re- ports, and the deduction from checking should be reported on 6/1 for easy bank reconciliation: 2015/5/30 expenses:food $10 ; food purchased on saturday 5/30 assets:checking ; bank cleared it on monday, date:6/1 $ hledger -f t.j register food 2015-05-30 expenses:food $10 $10 $ hledger -f t.j register checking 2015-06-01 assets:checking $-10 $-10 DATE should be a simple date; if the year is not specified it will use the year of the transaction's date. The date: tag must have a valid simple date value if it is present, eg a date: tag with no value is not allowed. Status Transactions, or individual postings within a transaction, can have a status mark, which is a single character before the transaction de- scription or posting account name, separated from it by a space, indi- cating one of three statuses: mark status ------------------ unmarked ! pending * cleared When reporting, you can filter by status with the -U/--unmarked, -P/--pending, and -C/--cleared flags; or the status:, status:!, and status:* queries; or the U, P, C keys in hledger-ui. Note, in Ledger and in older versions of hledger, the "unmarked" state is called "uncleared". As of hledger 1.3 we have renamed it to un- marked for clarity. To replicate Ledger and old hledger's behaviour of also matching pend- ing, combine -U and -P. Status marks are optional, but can be helpful eg for reconciling with real-world accounts. Some editor modes provide highlighting and short- cuts for working with status. Eg in Emacs ledger-mode, you can toggle transaction status with C-c C-e, or posting status with C-c C-c. What "uncleared", "pending", and "cleared" actually mean is up to you. Here's one suggestion: status meaning -------------------------------------------------------------------------- uncleared recorded but not yet reconciled; needs review pending tentatively reconciled (if needed, eg during a big reconcil- iation) cleared complete, reconciled as far as possible, and considered cor- rect With this scheme, you would use -PC to see the current balance at your bank, -U to see things which will probably hit your bank soon (like un- cashed checks), and no flags to see the most up-to-date state of your finances. Code After the status mark, but before the description, you can optionally write a transaction "code", enclosed in parentheses. This is a good place to record a check number, or some other important transaction id or reference number. Description A transaction's description is the rest of the line following the date and status mark (or until a comment begins). Sometimes called the "narration" in traditional bookkeeping, it can be used for whatever you wish, or left blank. Transaction descriptions can be queried, unlike comments. Payee and note You can optionally include a | (pipe) character in descriptions to sub- divide the description into separate fields for payee/payer name on the left (up to the first |) and an additional note field on the right (af- ter the first |). This may be worthwhile if you need to do more pre- cise querying and pivoting by payee or by note. Transaction comments Text following ;, after a transaction description, and/or on indented lines immediately below it, form comments for that transaction. They are reproduced by print but otherwise ignored, except they may contain tags, which are not ignored. 2012-01-01 something ; a transaction comment ; a second line of transaction comment expenses 1 assets Postings A posting is an addition of some amount to, or removal of some amount from, an account. Each posting line begins with at least one space or tab (2 or 4 spaces is common), followed by: o (optional) a status character (empty, !, or *), followed by a space o (required) an account name (any text, optionally containing single spaces, until end of line or a double space) o (optional) two or more spaces or tabs followed by an amount. Positive amounts are being added to the account, negative amounts are being removed. The amounts within a transaction must always sum up to zero. As a con- venience, one amount may be left blank; it will be inferred so as to balance the transaction. Be sure to note the unusual two-space delimiter between account name and amount. This makes it easy to write account names containing spaces. But if you accidentally leave only one space (or tab) before the amount, the amount will be considered part of the account name. Account names Accounts are the main way of categorising things in hledger. As in Double Entry Bookkeeping, they can represent real world accounts (such as a bank account), or more abstract categories such as "money borrowed from Frank" or "money spent on electricity". You can use any account names you like, but we usually start with the traditional accounting categories, which in english are assets, liabil- ities, equity, revenues, expenses. (You might see these referred to as A, L, E, R, X for short.) For more precise reporting, we usually divide the top level accounts into more detailed subaccounts, by writing a full colon between account name parts. For example, from the account names assets:bank:checking and expenses:food, hledger will infer this hierarchy of five accounts: assets assets:bank assets:bank:checking expenses expenses:food Shown as an outline, the hierarchical tree structure is more clear: assets bank checking expenses food hledger reports can summarise the account tree to any depth, so you can go as deep as you like with subcategories, but keeping your account names relatively simple may be best when starting out. Account names may be capitalised or not; they may contain letters, num- bers, symbols, or single spaces. Note, when an account name and an amount are written on the same line, they must be separated by two or more spaces (or tabs). Parentheses or brackets enclosing the full account name indicate vir- tual postings, described below. Parentheses or brackets internal to the account name have no special meaning. Account names can be altered temporarily or permanently by account aliases. Amounts After the account name, there is usually an amount. (Important: be- tween account name and amount, there must be two or more spaces.) hledger's amount format is flexible, supporting several international formats. Here are some examples. Amounts have a number (the "quan- tity"): 1 ..and usually a currency symbol or commodity name (more on this below), to the left or right of the quantity, with or without a separating space: $1 4000 AAPL 3 "green apples" Amounts can be preceded by a minus sign (or a plus sign, though plus is the default), The sign can be written before or after a left-side com- modity symbol: -$1 $-1 One or more spaces between the sign and the number are acceptable when parsing (but they won't be displayed in output): + $1 $- 1 Scientific E notation is allowed: 1E-6 EUR 1E3 Decimal marks, digit group marks A decimal mark can be written as a period or a comma: 1.23 1,23 In the integer part of the quantity (left of the decimal mark), groups of digits can optionally be separated by a digit group mark - a space, comma, or period (different from the decimal mark): $1,000,000.00 EUR 2.000.000,00 INR 9,99,99,999.00 1 000 000.9455 hledger is not biased towards period or comma decimal marks, so a num- ber containing just one period or comma, like 1,000 or 1.000, is am- biguous. In such cases hledger assumes it is a decimal mark, parsing both of these as 1. To disambiguate these and ensure accurate number parsing, especially if you use digit group marks, we recommend declaring the decimal mark. You can declare it for each file with decimal-mark directives, or for each commodity with commodity directives (described below). Commodity Amounts in hledger have both a "quantity", which is a signed decimal number, and a "commodity", which is a currency symbol, stock ticker, or any word or phrase describing something you are tracking. If the commodity name contains non-letters (spaces, numbers, or punctu- ation), you must always write it inside double quotes ("green apples", "ABC123"). If you write just a bare number, that too will have a commodity, with name ""; we call that the "no-symbol commodity". Actually, hledger combines these single-commodity amounts into more powerful multi-commodity amounts, which are what it works with most of the time. A multi-commodity amount could be, eg: 1 USD, 2 EUR, 3.456 TSLA. In practice, you will only see multi-commodity amounts in hledger's output; you can't write them directly in the journal file. (If you are writing scripts or working with hledger's internals, these are the Amount and MixedAmount types.) Directives influencing number parsing and display You can add decimal-mark and commodity directives to the journal, to declare and control these things more explicitly and precisely. These are described below, but here's a quick example: # the decimal mark character used by all amounts in this file (all commodities) decimal-mark . # display styles for the $, EUR, INR and no-symbol commodities: commodity $1,000.00 commodity EUR 1.000,00 commodity INR 9,99,99,999.00 commodity 1 000 000.9455 Commodity display style For the amounts in each commodity, hledger chooses a consistent display style (symbol placement, decimal mark and digit group marks, number of decimal digits) to use in most reports. This is inferred as follows: First, if there's a D directive declaring a default commodity, that commodity symbol and amount format is applied to all no-symbol amounts in the journal. Then each commodity's display style is determined from its commodity directive. We recommend always declaring commodities with commodity directives, since they help ensure consistent display styles and preci- sions, and bring other benefits such as error checking for commodity symbols. But if a commodity directive is not present, hledger infers a commod- ity's display styles from its amounts as they are written in the jour- nal (excluding cost amounts and amounts in periodic transaction rules or auto posting rules). It uses o the symbol placement and decimal mark of the first amount seen o the digit group marks of the first amount with digit group marks o and the maximum number of decimal digits seen across all amounts. And as fallback if no applicable amounts are found, it would use a de- fault style, like $1000.00 (symbol on the left with no space, period as decimal mark, and two decimal digits). Finally, commodity styles can be overridden by the -c/--commodity-style command line option. Rounding Amounts are stored internally as decimal numbers with up to 255 decimal places. They are displayed with their original journal precisions by print and print-like reports, and rounded to their display precision (the number of decimal digits specified by the commodity display style) by other reports. When rounding, hledger uses banker's rounding (it rounds to the nearest even digit). So eg 0.5 displayed with zero deci- mal digits appears as "0". Costs After a posting amount, you can note its cost (when buying) or selling price (when selling) in another commodity, by writing either @ UNIT- PRICE or @@ TOTALPRICE after it. This indicates a conversion transac- tion, where one commodity is exchanged for another. (You might also see this called "transaction price" in hledger docs, discussions, or code; that term was directionally neutral and reminded that it is a price specific to a transaction, but we now just call it "cost", with the understanding that the transaction could be a purchase or a sale.) Costs are usually written explicitly with @ or @@, but can also be in- ferred automatically for simple multi-commodity transactions. Note, if costs are inferred, the order of postings is significant; the first posting will have a cost attached, in the commodity of the second. As an example, here are several ways to record purchases of a foreign currency in hledger, using the cost notation either explicitly or im- plicitly: 1. Write the price per unit, as @ UNITPRICE after the amount: 2009/1/1 assets:euros 100 @ $1.35 ; one hundred euros purchased at $1.35 each assets:dollars ; balancing amount is -$135.00 2. Write the total price, as @@ TOTALPRICE after the amount: 2009/1/1 assets:euros 100 @@ $135 ; one hundred euros purchased at $135 for the lot assets:dollars 3. Specify amounts for all postings, using exactly two commodities, and let hledger infer the price that balances the transaction. Note the effect of posting order: the price is added to first posting, making it 100 @@ $135, as in example 2: 2009/1/1 assets:euros 100 ; one hundred euros purchased assets:dollars $-135 ; for $135 Amounts can be converted to cost at report time using the -B/--cost flag; this is discussed more in the Cost reporting section. Note that the cost normally should be a positive amount, though it's not required to be. This can be a little confusing, see discussion at --infer-market-prices: market prices from transactions. Other cost/lot notations A slight digression for Ledger and Beancount users. Ledger has a num- ber of cost/lot-related notations: o @ UNITCOST and @@ TOTALCOST o expresses a conversion rate, as in hledger o when buying, also creates a lot than can be selected at selling time o (@) UNITCOST and (@@) TOTALCOST (virtual cost) o like the above, but also means "this cost was exceptional, don't use it when inferring market prices". Currently, hledger treats the above like @ and @@; the parentheses are ignored. o {=FIXEDUNITCOST} and {{=FIXEDTOTALCOST}} (fixed price) o when buying, means "this cost is also the fixed price, don't let it fluctuate in value reports" o {UNITCOST} and {{TOTALCOST}} (lot price) o can be used identically to @ UNITCOST and @@ TOTALCOST, also cre- ates a lot o when selling, combined with @ ..., specifies an investment lot by its cost basis; does not check if that lot is present o and related: [YYYY/MM/DD] (lot date) o when buying, attaches this acquisition date to the lot o when selling, selects a lot by its acquisition date o (SOME TEXT) (lot note) o when buying, attaches this note to the lot o when selling, selects a lot by its note Currently, hledger accepts any or all of the above in any order after the posting amount, but ignores them. (This can break transaction bal- ancing.) For Beancount users, the notation and behaviour is different: o @ UNITCOST and @@ TOTALCOST o expresses a cost without creating a lot, as in hledger o when buying (augmenting) or selling (reducing) a lot, combined with {...}: documents the cost/selling price (not used for transaction balancing) o {UNITCOST} and {{TOTALCOST}} o when buying (augmenting), expresses the cost for transaction bal- ancing, and also creates a lot with this cost basis attached o when selling (reducing), o selects a lot by its cost basis o raises an error if that lot is not present or can not be selected unambiguously (depending on booking method configured) o expresses the selling price for transaction balancing Currently, hledger accepts the {UNITCOST}/{{TOTALCOST}} notation but ignores it. o variations: {}, {YYYY-MM-DD}, {"LABEL"}, {UNITCOST, "LABEL"}, {UNIT- COST, YYYY-MM-DD, "LABEL"} etc. Currently, hledger rejects these. Balance assertions hledger supports Ledger-style balance assertions in journal files. These look like, for example, = EXPECTEDBALANCE following a posting's amount. Eg here we assert the expected dollar balance in accounts a and b after each posting: 2013/1/1 a $1 =$1 b =$-1 2013/1/2 a $1 =$2 b $-1 =$-2 After reading a journal file, hledger will check all balance assertions and report an error if any of them fail. Balance assertions can pro- tect you from, eg, inadvertently disrupting reconciled balances while cleaning up old entries. You can disable them temporarily with the -I/--ignore-assertions flag, which can be useful for troubleshooting or for reading Ledger files. (Note: this flag currently does not disable balance assignments, described below). Assertions and ordering hledger sorts an account's postings and assertions first by date and then (for postings on the same day) by parse order. Note this is dif- ferent from Ledger, which sorts assertions only by parse order. (Also, Ledger assertions do not see the accumulated effect of repeated post- ings to the same account within a transaction.) So, hledger balance assertions keep working if you reorder differ- ently-dated transactions within the journal. But if you reorder same-dated transactions or postings, assertions might break and require updating. This order dependence does bring an advantage: precise con- trol over the order of postings and assertions within a day, so you can assert intra-day balances. Assertions and multiple included files Multiple files included with the include directive are processed as if concatenated into one file, preserving their order and the posting or- der within each file. It means that balance assertions in later files will see balance from earlier files. And if you have multiple postings to an account on the same day, split across multiple files, and you want to assert the account's balance on that day, you'll need to put the assertion in the right file - the last one in the sequence, probably. Assertions and multiple -f files Unlike include, when multiple files are specified on the command line with multiple -f/--file options, balance assertions will not see bal- ance from earlier files. This can be useful when you do not want prob- lems in earlier files to disrupt valid assertions in later files. If you do want assertions to see balance from earlier files, use in- clude, or concatenate the files temporarily. Assertions and commodities The asserted balance must be a simple single-commodity amount, and in fact the assertion checks only this commodity's balance within the (possibly multi-commodity) account balance. This is how assertions work in Ledger also. We could call this a "partial" balance assertion. To assert the balance of more than one commodity in an account, you can write multiple postings, each asserting one commodity's balance. You can make a stronger "total" balance assertion by writing a double equals sign (== EXPECTEDBALANCE). This asserts that there are no other commodities in the account besides the asserted one (or at least, that their balance is 0). 2013/1/1 a $1 a 1 b $-1 c -1 2013/1/2 ; These assertions succeed a 0 = $1 a 0 = 1 b 0 == $-1 c 0 == -1 2013/1/3 ; This assertion fails as 'a' also contains 1 a 0 == $1 It's not yet possible to make a complete assertion about a balance that has multiple commodities. One workaround is to isolate each commodity into its own subaccount: 2013/1/1 a:usd $1 a:euro 1 b 2013/1/2 a 0 == 0 a:usd 0 == $1 a:euro 0 == 1 Assertions and costs Balance assertions ignore costs, and should normally be written without one: 2019/1/1 (a) $1 @ 1 = $1 We do allow costs to be written in balance assertion amounts, however, and print shows them, but they don't affect whether the assertion passes or fails. This is for backward compatibility (hledger's close command used to generate balance assertions with costs), and because balance assignments do use costs (see below). Assertions and subaccounts The balance assertions above (= and ==) do not count the balance from subaccounts; they check the account's exclusive balance only. You can assert the balance including subaccounts by writing =* or ==*, eg: 2019/1/1 equity:opening balances checking:a 5 checking:b 5 checking 1 ==* 11 Assertions and virtual postings Balance assertions always consider both real and virtual postings; they are not affected by the --real/-R flag or real: query. Assertions and auto postings Balance assertions are affected by the --auto flag, which generates auto postings, which can alter account balances. Because auto postings are optional in hledger, accounts affected by them effectively have two balances. But balance assertions can only test one or the other of these. So to avoid making fragile assertions, either: o assert the balance calculated with --auto, and always use --auto with that file o or assert the balance calculated without --auto, and never use --auto with that file o or avoid balance assertions on accounts affected by auto postings (or avoid auto postings entirely). Assertions and precision Balance assertions compare the exactly calculated amounts, which are not always what is shown by reports. Eg a commodity directive may limit the display precision, but this will not affect balance asser- tions. Balance assertion failure messages show exact amounts. Posting comments Text following ;, at the end of a posting line, and/or on indented lines immediately below it, form comments for that posting. They are reproduced by print but otherwise ignored, except they may contain tags, which are not ignored. 2012-01-01 expenses 1 ; a comment for posting 1 assets ; a comment for posting 2 ; a second comment line for posting 2 Tags Tags are a way to add extra labels or labelled data to transactions, postings, or accounts, which you can then search or pivot on. They are written as a word (optionally hyphenated) immediately followed by a full colon, in a transaction or posting or account directive's comment. (This is an exception to the usual rule that things in com- ments are ignored.) Eg, here four different tags are recorded: one on the checking account, two on the transaction, and one on the expenses posting: account assets:checking ; accounttag: 2017/1/16 bought groceries ; transactiontag-1: ; transactiontag-2: assets:checking $-1 expenses:food $1 ; postingtag: Postings also inherit tags from their transaction and their account. And transactions also acquire tags from their postings (and postings' accounts). So in the example above, the expenses posting effectively has all four tags (by inheriting from account and transaction), and the transaction also has all four tags (by acquiring from the expenses posting). You can list tag names with hledger tags [NAMEREGEX], or match by tag name with a tag:NAMEREGEX query. Tag values Tags can have a value, which is any text after the colon up until a comma or end of line (with surrounding whitespace removed). Note this means that hledger tag values can not contain commas. Eg in the fol- lowing posting, the three tags' values are "value 1", "value 2", and "" (empty) respectively: expenses:food $10 ; foo, tag1: value 1 , tag2:value 2, bar tag3: , baz Note that tags can be repeated, and are additive rather than overrid- ing: when the same tag name is seen again with a new value, the new name:value pair is added to the tags. (It is not possible to override a tag's value or remove a tag.) You can list a tag's values with hledger tags TAGNAME --values, or match by tag value with a tag:NAMEREGEX=VALUEREGEX query. Directives Besides transactions, there is something else you can put in a journal file: directives. These are declarations, beginning with a keyword, that modify hledger's behaviour. Some directives can have more spe- cific subdirectives, indented below them. hledger's directives are similar to Ledger's in many cases, but there are also many differences. Directives are not required, but can be useful. Here are the main di- rectives: purpose directive -------------------------------------------------------------------------- READING DATA: Rewrite account names alias Comment out sections of the file comment Declare file's decimal mark, to help decimal-mark parse amounts accurately Include other data files include GENERATING DATA: Generate recurring transactions or bud- ~ get goals Generate extra postings on existing = transactions CHECKING FOR ERRORS: Define valid entities to provide more account, commodity, payee, tag error checking REPORTING: Declare accounts' type and display order account Declare commodity display styles commodity Declare market prices P Directives and multiple files Directives vary in their scope, ie which journal entries and which in- put files they affect. Most often, a directive will affect the follow- ing entries and included files if any, until the end of the current file - and no further. You might find this inconvenient! For example, alias directives do not affect parent or sibling files. But there are usually workarounds; for example, put alias directives in your top-most file, before including other files. The restriction, though it may be annoying at first, is in a good cause; it allows reports to be stable and deterministic, independent of the order of input. Without it, reports could show different numbers depending on the order of -f options, or the positions of include di- rectives in your files. Directive effects Here are all hledger's directives, with their effects and scope sum- marised - nine main directives, plus four others which we consider non-essential: di- what it does ends rec- at tive file end? -------------------------------------------------------------------------------------- ac- Declares an account, for checking all entries in all files; and N count its display order and type. Subdirectives: any text, ignored. alias Rewrites account names, in following entries until end of cur- Y rent file or end aliases. Command line equivalent: --alias com- Ignores part of the journal file, until end of current file or Y ment end comment. com- Declares up to four things: 1. a commodity symbol, for checking N,Y,N,N mod- all amounts in all files 2. the decimal mark for parsing ity amounts of this commodity, in the following entries until end of current file (if there is no decimal-mark directive) 3. and the display style for amounts of this commodity 4. which is also the precision to use for balanced-transaction checking in this commodity. Takes precedence over D. Subdirectives: format (Ledger-compatible syntax). Command line equivalent: -c/--com- modity-style deci- Declares the decimal mark, for parsing amounts of all commodi- Y mal-mark ties in following entries until next decimal-mark or end of cur- rent file. Included files can override. Takes precedence over commodity and D. include Includes entries and directives from another file, as if they N were written inline. Command line alternative: multiple -f/--file payee Declares a payee name, for checking all entries in all files. N P Declares the market price of a commodity on some date, for value N reports. ~ Declares a periodic transaction rule that generates future N (tilde) transactions with --forecast and budget goals with balance --budget. Other syntax: apply Prepends a common parent account to all account names, in fol- Y account lowing entries until end of current file or end apply account. D Sets a default commodity to use for no-symbol amounts;and, if Y,Y,N,N there is no commodity directive for this commodity: its decimal mark, balancing precision, and display style, as above. Y Sets a default year to use for any yearless dates, in following Y entries until end of current file. = Declares an auto posting rule that generates extra postings on partly (equals) matched transactions with --auto, in current, parent, and child files (but not sibling files, see #1212). Other Other directives from Ledger's file format are accepted but ig- Ledger nored. direc- tives account directive account directives can be used to declare accounts (ie, the places that amounts are transferred from and to). Though not required, these dec- larations can provide several benefits: o They can document your intended chart of accounts, providing a refer- ence. o In strict mode, they restrict which accounts may be posted to by transactions, which helps detect typos. o They control account display order in reports, allowing non-alpha- betic sorting (eg Revenues to appear above Expenses). o They help with account name completion (in hledger add, hledger-web, hledger-iadd, ledger-mode, etc.) o They can store additional account information as comments, or as tags which can be used to filter or pivot reports. o They can help hledger know your accounts' types (asset, liability, equity, revenue, expense), affecting reports like balancesheet and incomestatement. They are written as the word account followed by a hledger-style ac- count name, eg: account assets:bank:checking Note, however, that accounts declared in account directives are not al- lowed to have surrounding brackets and parentheses, unlike accounts used in postings. So the following journal will not parse: account (assets:bank:checking) Account comments Text following two or more spaces and ; at the end of an account direc- tive line, and/or following ; on indented lines immediately below it, form comments for that account. They are ignored except they may con- tain tags, which are not ignored. The two-space requirement for same-line account comments is because ; is allowed in account names. account assets:bank:checking ; same-line comment, at least 2 spaces before the semicolon ; next-line comment ; some tags - type:A, acctnum:12345 Account subdirectives Ledger-style indented subdirectives are also accepted, but currently ignored: account assets:bank:checking format subdirective is ignored Account error checking By default, accounts need not be declared; they come into existence when a posting references them. This is convenient, but it means hledger can't warn you when you mis-spell an account name in the jour- nal. Usually you'll find that error later, as an extra account in bal- ance reports, or an incorrect balance when reconciling. In strict mode, enabled with the -s/--strict flag, hledger will report an error if any transaction uses an account name that has not been de- clared by an account directive. Some notes: o The declaration is case-sensitive; transactions must use the correct account name capitalisation. o The account directive's scope is "whole file and below" (see direc- tives). This means it affects all of the current file, and any files it includes, but not parent or sibling files. The position of ac- count directives within the file does not matter, though it's usual to put them at the top. o Accounts can only be declared in journal files, but will affect in- cluded files of all types. o It's currently not possible to declare "all possible subaccounts" with a wildcard; every account posted to must be declared. Account display order The order in which account directives are written influences the order in which accounts appear in reports, hledger-ui, hledger-web etc. By default accounts appear in alphabetical order, but if you add these ac- count directives to the journal file: account assets account liabilities account equity account revenues account expenses those accounts will be displayed in declaration order: $ hledger accounts -1 assets liabilities equity revenues expenses Any undeclared accounts are displayed last, in alphabetical order. Sorting is done at each level of the account tree, within each group of sibling accounts under the same parent. And currently, this directive: account other:zoo would influence the position of zoo among other's subaccounts, but not the position of other among the top-level accounts. This means: o you will sometimes declare parent accounts (eg account other above) that you don't intend to post to, just to customize their display or- der o sibling accounts stay together (you couldn't display x:y in between a:b and a:c). Account types hledger knows that accounts come in several types: assets, liabilities, expenses and so on. This enables easy reports like balancesheet and incomestatement, and filtering by account type with the type: query. As a convenience, hledger will detect these account types automatically if you are using common english-language top-level account names (de- scribed below). But generally we recommend you declare types explic- itly, by adding a type: tag to your top-level account directives. Sub- accounts will inherit the type of their parent. The tag's value should be one of the five main account types: o A or Asset (things you own) o L or Liability (things you owe) o E or Equity (investment/ownership; balanced counterpart of assets & liabilities) o R or Revenue (what you received money from, AKA income; technically part of Equity) o X or Expense (what you spend money on; technically part of Equity) or, it can be (these are used less often): o C or Cash (a subtype of Asset, indicating liquid assets for the cash- flow report) o V or Conversion (a subtype of Equity, for conversions (see Cost re- porting).) Here is a typical set of account type declarations: account assets ; type: A account liabilities ; type: L account equity ; type: E account revenues ; type: R account expenses ; type: X account assets:bank ; type: C account assets:cash ; type: C account equity:conversion ; type: V Here are some tips for working with account types. o The rules for inferring types from account names are as follows. These are just a convenience that sometimes help new users get going; if they don't work for you, just ignore them and declare your account types. See also Regular expressions. If account's name contains this (CI) regular expression: | its type is: --------------------------------------------------------------------|------------- ^assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|current)(:|$) | Cash ^assets?(:|$) | Asset ^(debts?|liabilit(y|ies))(:|$) | Liability ^equity:(trad(e|ing)|conversion)s?(:|$) | Conversion ^equity(:|$) | Equity ^(income|revenue)s?(:|$) | Revenue ^expenses?(:|$) | Expense o If you declare any account types, it's a good idea to declare an ac- count for all of the account types, because a mixture of declared and name-inferred types can disrupt certain reports. o Certain uses of account aliases can disrupt account types. See Rewriting accounts > Aliases and account types. o As mentioned above, subaccounts will inherit a type from their parent account. More precisely, an account's type is decided by the first of these that exists: 1. A type: declaration for this account. 2. A type: declaration in the parent accounts above it, preferring the nearest. 3. An account type inferred from this account's name. 4. An account type inferred from a parent account's name, preferring the nearest parent. 5. Otherwise, it will have no type. o For troubleshooting, you can list accounts and their types with: $ hledger accounts --types [ACCTPAT] [-DEPTH] [type:TYPECODES] alias directive You can define account alias rules which rewrite your account names, or parts of them, before generating reports. This can be useful for: o expanding shorthand account names to their full form, allowing easier data entry and a less verbose journal o adapting old journals to your current chart of accounts o experimenting with new account organisations, like a new hierarchy o combining two accounts into one, eg to see their sum or difference on one line o customising reports Account aliases also rewrite account names in account directives. They do not affect account names being entered via hledger add or hledger-web. Account aliases are very powerful. They are generally easy to use cor- rectly, but you can also generate invalid account names with them; more on this below. See also Rewrite account names. Basic aliases To set an account alias, use the alias directive in your journal file. This affects all subsequent journal entries in the current file or its included files (but note: not sibling or parent files). The spaces around the = are optional: alias OLD = NEW Or, you can use the --alias 'OLD=NEW' option on the command line. This affects all entries. It's useful for trying out aliases interactively. OLD and NEW are case sensitive full account names. hledger will re- place any occurrence of the old account name with the new one. Subac- counts are also affected. Eg: alias checking = assets:bank:wells fargo:checking ; rewrites "checking" to "assets:bank:wells fargo:checking", or "checking:a" to "assets:bank:wells fargo:checking:a" Regex aliases There is also a more powerful variant that uses a regular expression, indicated by wrapping the pattern in forward slashes. (This is the only place where hledger requires forward slashes around a regular ex- pression.) Eg: alias /REGEX/ = REPLACEMENT or: $ hledger --alias '/REGEX/=REPLACEMENT' ... Any part of an account name matched by REGEX will be replaced by RE- PLACEMENT. REGEX is case-insensitive as usual. If you need to match a forward slash, escape it with a backslash, eg /\/=:. If REGEX contains parenthesised match groups, these can be referenced by the usual backslash and number in REPLACEMENT: alias /^(.+):bank:([^:]+):(.*)/ = \1:\2 \3 ; rewrites "assets:bank:wells fargo:checking" to "assets:wells fargo checking" REPLACEMENT continues to the end of line (or on command line, to end of option argument), so it can contain trailing whitespace. Combining aliases You can define as many aliases as you like, using journal directives and/or command line options. Recursive aliases - where an account name is rewritten by one alias, then by another alias, and so on - are allowed. Each alias sees the effect of previously applied aliases. In such cases it can be important to understand which aliases will be applied and in which order. For (each account name in) each journal entry, we apply: 1. alias directives preceding the journal entry, most recently parsed first (ie, reading upward from the journal entry, bottom to top) 2. --alias options, in the order they appeared on the command line (left to right). In other words, for (an account name in) a given journal entry: o the nearest alias declaration before/above the entry is applied first o the next alias before/above that will be be applied next, and so on o aliases defined after/below the entry do not affect it. This gives nearby aliases precedence over distant ones, and helps pro- vide semantic stability - aliases will keep working the same way inde- pendent of which files are being read and in which order. In case of trouble, adding --debug=6 to the command line will show which aliases are being applied when. Aliases and multiple files As explained at Directives and multiple files, alias directives do not affect parent or sibling files. Eg in this command, hledger -f a.aliases -f b.journal account aliases defined in a.aliases will not affect b.journal. In- cluding the aliases doesn't work either: include a.aliases 2023-01-01 ; not affected by a.aliases foo 1 bar This means that account aliases should usually be declared at the start of your top-most file, like this: alias foo=Foo alias bar=Bar 2023-01-01 ; affected by aliases above foo 1 bar include c.journal ; also affected end aliases directive You can clear (forget) all currently defined aliases (seen in the jour- nal so far, or defined on the command line) with this directive: end aliases Aliases can generate bad account names Be aware that account aliases can produce malformed account names, which could cause confusing reports or invalid print output. For exam- ple, you could erase all account names: 2021-01-01 a:aa 1 b $ hledger print --alias '/.*/=' 2021-01-01 1 The above print output is not a valid journal. Or you could insert an illegal double space, causing print output that would give a different journal when reparsed: 2021-01-01 old 1 other $ hledger print --alias old="new USD" | hledger -f- print 2021-01-01 new USD 1 other Aliases and account types If an account with a type declaration (see Declaring accounts > Account types) is renamed by an alias, normally the account type remains in ef- fect. However, renaming in a way that reshapes the account tree (eg renaming parent accounts but not their children, or vice versa) could prevent child accounts from inheriting the account type of their parents. Secondly, if an account's type is being inferred from its name, renam- ing it by an alias could prevent or alter that. If you are using account aliases and the type: query is not matching accounts as you expect, try troubleshooting with the accounts command, eg something like: $ hledger accounts --alias assets=bassetts type:a commodity directive The commodity directive performs several functions: 1. It declares which commodity symbols may be used in the journal, en- abling useful error checking with strict mode or the check command. (See Commodity error checking below.) 2. It declares the precision with which this commodity's amounts should be compared when checking for balanced transactions. 3. It declares how this commodity's amounts should be displayed, eg their symbol placement, digit group mark if any, digit group sizes, decimal mark (period or comma), and the number of decimal places. (See Commodity display style above.) 4. It sets which decimal mark (period or comma) to expect when parsing subsequent amounts in this commodity (if there is no decimal-mark directive in effect. See Decimal marks, digit group marks above. For related dev discussion, see #793.) Declaring commodities solves several common parsing/display problems, so we recommend it. Generally you should put commodity directives at the top of your journal file (because function 4 is position-sensi- tive). Commodity directive syntax A commodity directive is normally the word commodity followed by a sam- ple amount (and optionally a comment). Only the amount's symbol and format is significant. Eg: commodity $1000.00 commodity 1.000,00 EUR commodity 1 000 000.0000 ; the no-symbol commodity Commodities do not have tags (tags in the comment will be ignored). A commodity directive's sample amount must always include a period or comma decimal mark (this rule helps disambiguate decimal marks and digit group marks). If you don't want to show any decimal digits, write the decimal mark at the end: commodity 1000. AAAA ; show AAAA with no decimals Commodity symbols containing spaces, numbers, or punctuation must be enclosed in double quotes, as usual: commodity 1.0000 "AAAA 2023" Commodity directives normally include a sample amount, but can declare only a symbol (ie, just function 1 above): commodity $ commodity INR commodity "AAAA 2023" commodity "" ; the no-symbol commodity Commodity directives may also be written with an indented format subdi- rective, as in Ledger. The symbol is repeated and must be the same in both places. Other subdirectives are currently ignored: ; display indian rupees with currency name on the left, ; thousands, lakhs and crores comma-separated, ; period as decimal point, and two decimal places. commodity INR format INR 1,00,00,000.00 an unsupported subdirective ; ignored by hledger Commodity error checking In strict mode (-s/--strict) (or when you run hledger check commodi- ties), hledger will report an error if an undeclared commodity symbol is used. (With one exception: zero amounts are always allowed to have no commodity symbol.) It works like account error checking (described above). decimal-mark directive You can use a decimal-mark directive - usually one per file, at the top of the file - to declare which character represents a decimal mark when parsing amounts in this file. It can look like decimal-mark . or decimal-mark , This prevents any ambiguity when parsing numbers in the file, so we recommend it, especially if the file contains digit group marks (eg thousands separators). include directive You can pull in the content of additional files by writing an include directive, like this: include FILEPATH Only journal files can include, and only journal, timeclock or timedot files can be included (not CSV files, currently). If the file path does not begin with a slash, it is relative to the current file's folder. A tilde means home directory, eg: include ~/main.journal. The path may contain glob patterns to match multiple files, eg: include *.journal. There is limited support for recursive wildcards: **/ (the slash is re- quired) matches 0 or more subdirectories. It's not super convenient since you have to avoid include cycles and including directories, but this can be done, eg: include */**/*.journal. The path may also be prefixed to force a specific file format, overrid- ing the file extension (as described in Data formats): include time- dot:~/notes/2023*.md. P directive The P directive declares a market price, which is a conversion rate be- tween two commodities on a certain date. This allows value reports to convert amounts of one commodity to their value in another, on or after that date. These prices are often obtained from a stock exchange, cryptocurrency exchange, the or foreign exchange market. The format is: P DATE COMMODITY1SYMBOL COMMODITY2AMOUNT DATE is a simple date, COMMODITY1SYMBOL is the symbol of the commodity being priced, and COMMODITY2AMOUNT is the amount (symbol and quantity) of commodity 2 that one unit of commodity 1 is worth on this date. Ex- amples: # one euro was worth $1.35 from 2009-01-01 onward: P 2009-01-01 $1.35 # and $1.40 from 2010-01-01 onward: P 2010-01-01 $1.40 The -V, -X and --value flags use these market prices to show amount values in another commodity. See Value reporting. payee directive payee PAYEE NAME This directive can be used to declare a limited set of payees which may appear in transaction descriptions. The "payees" check will report an error if any transaction refers to a payee that has not been declared. Eg: payee Whole Foods ; a comment Payees do not have tags (tags in the comment will be ignored). To declare the empty payee name, use "". payee "" Ledger-style indented subdirectives, if any, are currently ignored. tag directive tag TAGNAME This directive can be used to declare a limited set of tag names al- lowed in tags. TAGNAME should be a valid tag name (no spaces). Eg: tag item-id Any indented subdirectives are currently ignored. The "tags" check will report an error if any undeclared tag name is used. It is quite easy to accidentally create a tag through normal use of colons in comments(#comments]; if you want to prevent this, you can declare and check your tags . Periodic transactions The ~ directive declares a "periodic rule" which generates temporary extra transactions, usually recurring at some interval, when hledger is run with the --forecast flag. These "forecast transactions" are useful for forecasting future activity. They exist only for the duration of the report, and only when --forecast is used; they are not saved in the journal file by hledger. Periodic rules also have a second use: with the --budget flag they set budget goals for budgeting. Periodic rules can be a little tricky, so before you use them, read this whole section, or at least the following tips: 1. Two spaces accidentally added or omitted will cause you trouble - read about this below. 2. For troubleshooting, show the generated transactions with hledger print --forecast tag:generated or hledger register --forecast tag:generated. 3. Forecasted transactions will begin only after the last non-fore- casted transaction's date. 4. Forecasted transactions will end 6 months from today, by default. See below for the exact start/end rules. 5. period expressions can be tricky. Their documentation needs im- provement, but is worth studying. 6. Some period expressions with a repeating interval must begin on a natural boundary of that interval. Eg in weekly from DATE, DATE must be a monday. ~ weekly from 2019/10/1 (a tuesday) will give an error. 7. Other period expressions with an interval are automatically expanded to cover a whole number of that interval. (This is done to improve reports, but it also affects periodic transactions. Yes, it's a bit inconsistent with the above.) Eg: ~ every 10th day of month from 2023/01, which is equivalent to ~ every 10th day of month from 2023/01/01, will be adjusted to start on 2019/12/10. Periodic rule syntax A periodic transaction rule looks like a normal journal entry, with the date replaced by a tilde (~) followed by a period expression (mnemonic: ~ looks like a recurring sine wave.): # every first of month ~ monthly expenses:rent $2000 assets:bank:checking # every 15th of month in 2023's first quarter: ~ monthly from 2023-04-15 to 2023-06-16 expenses:utilities $400 assets:bank:checking The period expression is the same syntax used for specifying multi-pe- riod reports, just interpreted differently; there, it specifies report periods; here it specifies recurrence dates (the periods' start dates). Periodic rules and relative dates Partial or relative dates (like 12/31, 25, tomorrow, last week, next quarter) are usually not recommended in periodic rules, since the re- sults will change as time passes. If used, they will be interpreted relative to, in order of preference: 1. the first day of the default year specified by a recent Y directive 2. or the date specified with --today 3. or the date on which you are running the report. They will not be affected at all by report period or forecast period dates. Two spaces between period expression and description! If the period expression is followed by a transaction description, these must be separated by two or more spaces. This helps hledger know where the period expression ends, so that descriptions can not acciden- tally alter their meaning, as in this example: ; 2 or more spaces needed here, so the period is not understood as "every 2 months in 2023" ; || ; vv ~ every 2 months in 2023, we will review assets:bank:checking $1500 income:acme inc So, o Do write two spaces between your period expression and your transac- tion description, if any. o Don't accidentally write two spaces in the middle of your period ex- pression. Auto postings The = directive declares an "auto posting rule" which generates tempo- rary extra postings on existing transactions, when hledger is run with the --auto flag. (Remember, postings are the account name & amount lines.) The rule contains a query and one or more posting templates. Wherever the query matches an existing posting, the new posting(s) will be generated and added below that one. Optionally the generated amount(s) can depend on the matched posting's amount. These auto postings can be useful for, eg, adding tax postings with a standard percentage. They exist only for the duration of the report, and only when --auto is used; they are not saved in the journal file by hledger. Note that depending fully on generated data such as this has some draw- backs - it's less portable, less future-proof, less auditable by oth- ers, and less robust (eg your balance assertions will depend on whether you use or don't use --auto). An alternative is to use auto postings in "one time" fashion - use them to help build a complex journal entry, view it with hledger print --auto, and then copy that output into the journal file to make it permanent. Here's the journal file syntax. An auto posting rule looks a bit like a transaction: = QUERY ACCOUNT AMOUNT ... ACCOUNT [AMOUNT] except the first line is an equals sign (mnemonic: = suggests match- ing), followed by a query (which matches existing postings), and each "posting" line describes a posting to be generated, and the posting amounts can be: o a normal amount with a commodity symbol, eg $2. This will be used as-is. o a number, eg 2. The commodity symbol (if any) from the matched post- ing will be added to this. o a numeric multiplier, eg *2 (a star followed by a number N). The matched posting's amount (and total price, if any) will be multiplied by N. o a multiplier with a commodity symbol, eg *$2 (a star, number N, and symbol S). The matched posting's amount will be multiplied by N, and its commodity symbol will be replaced with S. Any query term containing spaces must be enclosed in single or double quotes, as on the command line. Eg, note the quotes around the second query term below: = expenses:groceries 'expenses:dining out' (budget:funds:dining out) *-1 Some examples: ; every time I buy food, schedule a dollar donation = expenses:food (liabilities:charity) $-1 ; when I buy a gift, also deduct that amount from a budget envelope subaccount = expenses:gifts assets:checking:gifts *-1 assets:checking *1 2017/12/1 expenses:food $10 assets:checking 2017/12/14 expenses:gifts $20 assets:checking $ hledger print --auto 2017-12-01 expenses:food $10 assets:checking (liabilities:charity) $-1 2017-12-14 expenses:gifts $20 assets:checking assets:checking:gifts -$20 assets:checking $20 Auto postings and multiple files An auto posting rule can affect any transaction in the current file, or in any parent file or child file. Note, currently it will not affect sibling files (when multiple -f/--file are used - see #1212). Auto postings and dates A posting date (or secondary date) in the matched posting, or (taking precedence) a posting date in the auto posting rule itself, will also be used in the generated posting. Auto postings and transaction balancing / inferred amounts / balance asser- tions Currently, auto postings are added: o after missing amounts are inferred, and transactions are checked for balancedness, o but before balance assertions are checked. Note this means that journal entries must be balanced both before and after auto postings are added. This changed in hledger 1.12+; see #893 for background. This also means that you cannot have more than one auto-posting with a missing amount applied to a given transaction, as it will be unable to infer amounts. Auto posting tags Automated postings will have some extra tags: o generated-posting:= QUERY - shows this was generated by an auto post- ing rule, and the query o _generated-posting:= QUERY - a hidden tag, which does not appear in hledger's output. This can be used to match postings generated "just now", rather than generated in the past and saved to the journal. Also, any transaction that has been changed by auto posting rules will have these tags added: o modified: - this transaction was modified o _modified: - a hidden tag not appearing in the comment; this transac- tion was modified "just now". Auto postings on forecast transactions only Tip: you can can make auto postings that will apply to forecast trans- actions but not recorded transactions, by adding tag:_generated-trans- action to their QUERY. This can be useful when generating new journal entries to be saved in the journal. Other syntax hledger journal format supports quite a few other features, mainly to make interoperating with or converting from Ledger easier. Note some of the features below are powerful and can be useful in special cases, but in general, features in this section are considered less important or even not recommended for most users. Downsides are mentioned to help you decide if you want to use them. Balance assignments Ledger-style balance assignments are also supported. These are like balance assertions, but with no posting amount on the left side of the equals sign; instead it is calculated automatically so as to satisfy the assertion. This can be a convenience during data entry, eg when setting opening balances: ; starting a new journal, set asset account balances 2016/1/1 opening balances assets:checking = $409.32 assets:savings = $735.24 assets:cash = $42 equity:opening balances or when adjusting a balance to reality: ; no cash left; update balance, record any untracked spending as a generic expense 2016/1/15 assets:cash = $0 expenses:misc The calculated amount depends on the account's balance in the commodity at that point (which depends on the previously-dated postings of the commodity to that account since the last balance assertion or assign- ment). Downsides: using balance assignments makes your journal less explicit; to know the exact amount posted, you have to run hledger or do the cal- culations yourself, instead of just reading it. Also balance assign- ments' forcing of balances can hide errors. These things make your fi- nancial data less portable, less future-proof, and less trustworthy in an audit. Balance assignments and prices A cost in a balance assignment will cause the calculated amount to have that price attached: 2019/1/1 (a) = $1 @ 2 $ hledger print --explicit 2019-01-01 (a) $1 @ 2 = $1 @ 2 Balance assignments and multiple files Balance assignments handle multiple files like balance assertions. They see balance from other files previously included from the current file, but not from previous sibling or parent files. Bracketed posting dates For setting posting dates and secondary posting dates, Ledger's brack- eted date syntax is also supported: [DATE], [DATE=DATE2] or [=DATE2] in posting comments. hledger will attempt to parse any square-bracketed sequence of the 0123456789/-.= characters in this way. With this syn- tax, DATE infers its year from the transaction and DATE2 infers its year from DATE. Downsides: another syntax to learn, redundant with hledger's date:/date2: tags, and confusingly similar to Ledger's lot date syntax. D directive D AMOUNT This directive sets a default commodity, to be used for any subsequent commodityless amounts (ie, plain numbers) seen while parsing the jour- nal. This effect lasts until the next D directive, or the end of the journal. For compatibility/historical reasons, D also acts like a commodity di- rective (setting the commodity's decimal mark for parsing and display style for output). So its argument is not just a commodity symbol, but a full amount demonstrating the style. The amount must include a deci- mal mark (either period or comma). Eg: ; commodity-less amounts should be treated as dollars ; (and displayed with the dollar sign on the left, thousands separators and two decimal places) D $1,000.00 1/1 a 5 ; <- commodity-less amount, parsed as $5 and displayed as $5.00 b Interactions with other directives: For setting a commodity's display style, a commodity directive has highest priority, then a D directive. For detecting a commodity's decimal mark during parsing, decimal-mark has highest priority, then commodity, then D. For checking commodity symbols with the check command, a commodity di- rective is required (hledger check commodities ignores D directives). Downsides: omitting commodity symbols makes your financial data less explicit, less portable, and less trustworthy in an audit. It is usu- ally an unsustainable shortcut; sooner or later you will want to track multiple commodities. D is overloaded with functions redundant with commodity and decimal-mark. And it works differently from Ledger's D. apply account directive This directive sets a default parent account, which will be prepended to all accounts in following entries, until an end apply account direc- tive or end of current file. Eg: apply account home 2010/1/1 food $10 cash end apply account is equivalent to: 2010/01/01 home:food $10 home:cash $-10 account directives are also affected, and so is any included content. Account names entered via hledger add or hledger-web are not affected. Account aliases, if any, are applied after the parent account is prepended. Downsides: this can make your financial data less explicit, less portable, and less trustworthy in an audit. Y directive Y YEAR or (deprecated backward-compatible forms): year YEAR apply year YEAR The space is optional. This sets a default year to be used for subse- quent dates which don't specify a year. Eg: Y2009 ; set default year to 2009 12/15 ; equivalent to 2009/12/15 expenses 1 assets year 2010 ; change default year to 2010 2009/1/30 ; specifies the year, not affected expenses 1 assets 1/31 ; equivalent to 2010/1/31 expenses 1 assets Downsides: omitting the year (from primary transaction dates, at least) makes your financial data less explicit, less portable, and less trust- worthy in an audit. Such dates can get separated from their corre- sponding Y directive, eg when evaluating a region of the journal in your editor. A missing Y directive makes reports dependent on today's date. Secondary dates A secondary date is written after the primary date, following an equals sign. If the year is omitted, the primary date's year is assumed. When running reports, the primary (left) date is used by default, but with the --date2 flag (or --aux-date or --effective), the secondary (right) date will be used instead. The meaning of secondary dates is up to you, but it's best to follow a consistent rule. Eg "primary = the bank's clearing date, secondary = date the transaction was initiated, if different". Downsides: makes your financial data more complicated, less portable, and less trustworthy in an audit. Keeping the meaning of the two dates consistent requires discipline, and you have to remember which report- ing mode is appropriate for a given report. Posting dates are simpler and better. Star comments Lines beginning with * (star/asterisk) are also comment lines. This feature allows Emacs users to insert org headings in their journal, al- lowing them to fold/unfold/navigate it like an outline when viewed with org mode. Downsides: another, unconventional comment syntax to learn. Decreases your journal's portability. And switching to Emacs org mode just for folding/unfolding meant losing the benefits of ledger mode; nowadays you can add outshine mode to ledger mode to get folding without losing ledger mode's features. Valuation expressions Ledger allows a valuation function or value to be written in double parentheses after an amount. hledger ignores these. Virtual postings A posting with parentheses around the account name ((some:account)) is called a unbalanced virtual posting. Such postings do not participate in transaction balancing. (And if you write them without an amount, a zero amount is always inferred.) These can occasionally be convenient for special circumstances, but they violate double entry bookkeeping and make your data less portable across applications, so many people avoid using them at all. A posting with brackets around the account name ([some:account]) is called a balanced virtual posting. The balanced virtual postings in a transaction must add up to zero, just like ordinary postings, but sepa- rately from them. These are not part of double entry bookkeeping ei- ther, but they are at least balanced. An example: 2022-01-01 buy food with cash, update budget envelope subaccounts, & something else assets:cash $-10 ; <- these balance each other expenses:food $7 ; <- expenses:food $3 ; <- [assets:checking:budget:food] $-10 ; <- and these balance each other [assets:checking:available] $10 ; <- (something:else) $5 ; <- this is not required to balance Ordinary postings, whose account names are neither parenthesised nor bracketed, are called real postings. You can exclude virtual postings from reports with the -R/--real flag or a real:1 query. Other Ledger directives These other Ledger directives are currently accepted but ignored. This allows hledger to read more Ledger files, but be aware that hledger's reports may differ from Ledger's if you use these. apply fixed COMM AMT apply tag TAG assert EXPR bucket / A ACCT capture ACCT REGEX check EXPR define VAR=EXPR end apply fixed end apply tag end apply year end tag eval / expr EXPR python PYTHONCODE tag NAME value EXPR --command-line-flags See also https://hledger.org/ledger.html for a detailed hledger/Ledger syntax comparison. CSV hledger can read CSV files (Character Separated Value - usually comma, semicolon, or tab) containing dated records, automatically converting each record into a transaction. (To learn about writing CSV, see CSV output.) For best error messages when reading CSV/TSV/SSV files, make sure they have a corresponding .csv, .tsv or .ssv file extension or use a hledger file prefix (see File Extension below). Each CSV file must be described by a corresponding rules file. This contains rules describing the CSV data (header line, fields lay- out, date format etc.), how to construct hledger transactions from it, and how to categorise transactions based on description or other at- tributes. By default hledger looks for a rules file named like the CSV file with an extra .rules extension, in the same directory. Eg when asked to read foo/FILE.csv, hledger looks for foo/FILE.csv.rules. You can spec- ify a different rules file with the --rules-file option. If no rules file is found, hledger will create a sample rules file, which you'll need to adjust. At minimum, the rules file must identify the date and amount fields, and often it also specifies the date format and how many header lines there are. Here's a simple CSV file and a rules file for it: Date, Description, Id, Amount 12/11/2019, Foo, 123, 10.23 # basic.csv.rules skip 1 fields date, description, , amount date-format %d/%m/%Y $ hledger print -f basic.csv 2019-11-12 Foo expenses:unknown 10.23 income:unknown -10.23 There's an introductory Importing CSV data tutorial on hledger.org, and more CSV rules examples below, and a larger collection at https://github.com/simonmichael/hledger/tree/master/examples/csv. CSV rules cheatsheet The following kinds of rule can appear in the rules file, in any order. (Blank lines and lines beginning with # or ; or * are ignored.) source optionally declare which file to read data from separator declare the field separator, instead of rely- ing on file extension skip skip one or more header lines at start of file date-format declare how to parse CSV dates/date-times timezone declare the time zone of ambiguous CSV date-times newest-first improve txn order when: there are multiple records, newest first, all with the same date intra-day-reversed improve txn order when: same-day txns are in opposite order to the overall file decimal-mark declare the decimal mark used in CSV amounts, when ambiguous fields list name CSV fields for easy reference, and op- tionally assign their values to hledger fields Field assignment assign a CSV value or interpolated text value to a hledger field if block conditionally assign values to hledger fields, or skip a record or end (skip rest of file) if table conditionally assign values to hledger fields, using compact syntax balance-type select which type of balance assertions/as- signments to generate include inline another CSV rules file Working with CSV tips can be found below, including How CSV rules are evaluated. source If you tell hledger to read a csv file with -f foo.csv, it will look for rules in foo.csv.rules. Or, you can tell it to read the rules file, with -f foo.csv.rules, and it will look for data in foo.csv (since 1.30). These are mostly equivalent, but the second method provides some extra features. For one, the data file can be missing, without causing an error; it is just considered empty. And, you can specify a different data file by adding a "source" rule: source ./Checking1.csv If you specify just a file name with no path, hledger will look for it in your system's downloads directory (~/Downloads, currently): source Checking1.csv And if you specify a glob pattern, hledger will read the most recent of the matched files (useful with repeated downloads): source Checking1*.csv See also "Working with CSV > Reading files specified by rule". separator You can use the separator rule to read other kinds of character-sepa- rated data. The argument is any single separator character, or the words tab or space (case insensitive). Eg, for comma-separated values (CSV): separator , or for semicolon-separated values (SSV): separator ; or for tab-separated values (TSV): separator TAB If the input file has a .csv, .ssv or .tsv file extension (or a csv:, ssv:, tsv: prefix), the appropriate separator will be inferred automat- ically, and you won't need this rule. skip skip N The word skip followed by a number (or no number, meaning 1) tells hledger to ignore this many non-empty lines at the start of the input data. You'll need this whenever your CSV data contains header lines. Note, empty and blank lines are skipped automatically, so you don't need to count those. skip has a second meaning: it can be used inside if blocks (described below), to skip one or more records whenever the condition is true. Records skipped in this way are ignored, except they are still required to be valid CSV. date-format date-format DATEFMT This is a helper for the date (and date2) fields. If your CSV dates are not formatted like YYYY-MM-DD, YYYY/MM/DD or YYYY.MM.DD, you'll need to add a date-format rule describing them with a strptime-style date parsing pattern - see https://hackage.haskell.org/pack- age/time/docs/Data-Time-Format.html#v:formatTime. The pattern must parse the CSV date value completely. Some examples: # MM/DD/YY date-format %m/%d/%y # D/M/YYYY # The - makes leading zeros optional. date-format %-d/%-m/%Y # YYYY-Mmm-DD date-format %Y-%h-%d # M/D/YYYY HH:MM AM some other junk # Note the time and junk must be fully parsed, though only the date is used. date-format %-m/%-d/%Y %l:%M %p some other junk timezone timezone TIMEZONE When CSV contains date-times that are implicitly in some time zone other than yours, but containing no explicit time zone information, you can use this rule to declare the CSV's native time zone, which helps prevent off-by-one dates. When the CSV date-times do contain time zone information, you don't need this rule; instead, use %Z in date-format (or %z, %EZ, %Ez; see the formatTime link above). In either of these cases, hledger will do a time-zone-aware conversion, localising the CSV date-times to your current system time zone. If you prefer to localise to some other time zone, eg for reproducibility, you can (on unix at least) set the output timezone with the TZ environment variable, eg: $ TZ=-1000 hledger print -f foo.csv # or TZ=-1000 hledger import foo.csv timezone currently does not understand timezone names, except "UTC", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", "PST", or "PDT". For others, use numeric format: +HHMM or -HHMM. newest-first hledger tries to ensure that the generated transactions will be ordered chronologically, including same-day transactions. Usually it can auto-detect how the CSV records are ordered. But if it encounters CSV where all records are on the same date, it assumes that the records are oldest first. If in fact the CSV's records are normally newest first, like: 2022-10-01, txn 3... 2022-10-01, txn 2... 2022-10-01, txn 1... you can add the newest-first rule to help hledger generate the transac- tions in correct order. # same-day CSV records are newest first newest-first intra-day-reversed If CSV records within a single day are ordered opposite to the overall record order, you can add the intra-day-reversed rule to improve the order of journal entries. Eg, here the overall record order is newest first, but same-day records are oldest first: 2022-10-02, txn 3... 2022-10-02, txn 4... 2022-10-01, txn 1... 2022-10-01, txn 2... # transactions within each day are reversed with respect to the overall date order intra-day-reversed decimal-mark decimal-mark . or: decimal-mark , hledger automatically accepts either period or comma as a decimal mark when parsing numbers (cf Amounts). However if any numbers in the CSV contain digit group marks, such as thousand-separating commas, you should declare the decimal mark explicitly with this rule, to avoid misparsed numbers. fields list fields FIELDNAME1, FIELDNAME2, ... A fields list (the word fields followed by comma-separated field names) is optional, but convenient. It does two things: 1. It names the CSV field in each column. This can be convenient if you are referencing them in other rules, so you can say %SomeField instead of remembering %13. 2. Whenever you use one of the special hledger field names (described below), it assigns the CSV value in this position to that hledger field. This is the quickest way to populate hledger's fields and build a transaction. Here's an example that says "use the 1st, 2nd and 4th fields as the transaction's date, description and amount; name the last two fields for later reference; and ignore the others": fields date, description, , amount, , , somefield, anotherfield In a fields list, the separator is always comma; it is unrelated to the CSV file's separator. Also: o There must be least two items in the list (at least one comma). o Field names may not contain spaces. Spaces before/after field names are optional. o Field names may contain _ (underscore) or - (hyphen). o Fields you don't care about can be given a dummy name or an empty name. If the CSV contains column headings, it's convenient to use these for your field names, suitably modified (eg lower-cased with spaces re- placed by underscores). Sometimes you may want to alter a CSV field name to avoid assigning to a hledger field with the same name. Eg you could call the CSV's "bal- ance" field balance_ to avoid directly setting hledger's balance field (and generating a balance assertion). Field assignment HLEDGERFIELD FIELDVALUE Field assignments are the more flexible way to assign CSV values to hledger fields. They can be used instead of or in addition to a fields list (see above). To assign a value to a hledger field, write the field name (any of the standard hledger field/pseudo-field names, defined below), a space, followed by a text value on the same line. This text value may inter- polate CSV fields, referenced either by their 1-based position in the CSV record (%N) or by the name they were given in the fields list (%CSVFIELD), and regular expression match groups (\N). Some examples: # set the amount to the 4th CSV field, with " USD" appended amount %4 USD # combine three fields to make a comment, containing note: and date: tags comment note: %somefield - %anotherfield, date: %1 Tips: o Interpolation strips outer whitespace (so a CSV value like " 1 " be- comes 1 when interpolated) (#1051). o Interpolations always refer to a CSV field - you can't interpolate a hledger field. (See Referencing other fields below). Field names Note the two kinds of field names mentioned here, and used only in hledger CSV rules files: 1. CSV field names (CSVFIELD in these docs): you can optionally name the CSV columns for easy reference (since hledger doesn't yet auto- matically recognise column headings in a CSV file), by writing arbi- trary names in a fields list, eg: fields When, What, Some_Id, Net, Total, Foo, Bar 2. Special hledger field names (HLEDGERFIELD in these docs): you must set at least some of these to generate the hledger transaction from a CSV record, by writing them as the left hand side of a field as- signment, eg: date %When code %Some_Id description %What comment %Foo %Bar amount1 $ %Total or directly in a fields list: fields date, description, code, , amount1, Foo, Bar currency $ comment %Foo %Bar Here are all the special hledger field names available, and what hap- pens when you assign values to them: date field Assigning to date sets the transaction date. date2 field date2 sets the transaction's secondary date, if any. status field status sets the transaction's status, if any. code field code sets the transaction's code, if any. description field description sets the transaction's description, if any. comment field comment sets the transaction's comment, if any. commentN, where N is a number, sets the Nth posting's comment. You can assign multi-line comments by writing literal \n in the code. A comment starting with \n will begin on a new line. Comments can contain tags, as usual. account field Assigning to accountN, where N is 1 to 99, sets the account name of the Nth posting, and causes that posting to be generated. Most often there are two postings, so you'll want to set account1 and account2. Typically account1 is associated with the CSV file, and is set once with a top-level assignment, while account2 is set based on each transaction's description, in conditional rules. If a posting's account name is left unset but its amount is set (see below), a default account name will be chosen (like "expenses:unknown" or "income:unknown"). amount field There are several ways to set posting amounts from CSV, useful in dif- ferent situations. 1. amount is the oldest and simplest. Assigning to this sets the amount of the first and second postings. In the second posting, the amount will be negated; also, if it has a cost attached, it will be converted to cost. 2. amount-in and amount-out work exactly like the above, but should be used when the CSV has two amount fields (such as "Debit" and "Credit", or "Inflow" and "Outflow"). Whichever field has a non-zero value will be used as the amount of the first and second postings. Here are some tips to avoid confusion: o It's not "amount-in for posting 1 and amount-out for posting 2", it is "extract a single amount from the amount-in or amount-out field, and use that for posting 1 and (negated) for posting 2". o Don't use both amount and amount-in/amount-out in the same rules file; choose based on whether the amount is in a single CSV field or spread across two fields. o In each record, at most one of the two CSV fields should contain a non-zero amount; the other field must contain a zero or noth- ing. o hledger assumes both CSV fields contain unsigned numbers, and it automatically negates the amount-out values. o If the data doesn't fit these requirements, you'll probably need an if rule (see below). 3. amountN (where N is a number from 1 to 99) sets the amount of only a single posting: the Nth posting in the transaction. You'll usually need at least two such assignments to make a balanced transaction. You can also generate more than two postings, to represent more com- plex transactions. The posting numbers don't have to be consecu- tive; with if rules, higher posting numbers can be useful to ensure a certain order of postings. 4. amountN-in and amountN-out work exactly like the above, but should be used when the CSV has two amount fields. This is analogous to amount-in and amount-out, and those tips also apply here. 5. Remember that a fields list can also do assignments. So in a fields list if you name a CSV field "amount", that counts as assigning to amount. (If you don't want that, call it something else in the fields list, like "amount_".) 6. The above don't handle every situation; if you need more flexibil- ity, use an if rule to set amounts conditionally. See "Working with CSV > Setting amounts" below for more on this and on amount-setting generally. currency field currency sets a currency symbol, to be prepended to all postings' amounts. You can use this if the CSV amounts do not have a currency symbol, eg if it is in a separate column. currencyN prepends a currency symbol to just the Nth posting's amount. balance field balanceN sets a balance assertion amount (or if the posting amount is left empty, a balance assignment) on posting N. balance is a compatibility spelling for hledger <1.17; it is equivalent to balance1. You can adjust the type of assertion/assignment with the balance-type rule (see below). See Tips below for more about setting amounts and currency. if block Rules can be applied conditionally, depending on patterns in the CSV data. This allows flexibility; in particular, it is how you can cate- gorise transactions, selecting an appropriate account name based on their description (for example). There are two ways to write condi- tional rules: "if blocks", described here, and "if tables", described below. An if block is the word if and one or more "matcher" expressions (can be a word or phrase), one per line, starting either on the same or next line; followed by one or more indented rules. Eg, if MATCHER RULE or if MATCHER MATCHER MATCHER RULE RULE If any of the matchers succeeds, all of the indented rules will be ap- plied. They are usually field assignments, but the following special rules may also be used within an if block: o skip - skips the matched CSV record (generating no transaction from it) o end - skips the rest of the current CSV file. Some examples: # if the record contains "groceries", set account2 to "expenses:groceries" if groceries account2 expenses:groceries # if the record contains any of these phrases, set account2 and a transaction comment as shown if monthly service fee atm transaction fee banking thru software account2 expenses:business:banking comment XXX deductible ? check it # if an empty record is seen (assuming five fields), ignore the rest of the CSV file if ,,,, end Matchers There are two kinds: 1. A record matcher is a word or single-line text fragment or regular expression (REGEX), which hledger will try to match case-insensi- tively anywhere within the CSV record. Eg: whole foods 2. A field matcher is preceded with a percent sign and CSV field name (%CSVFIELD REGEX). hledger will try to match these just within the named CSV field. Eg: %date 2023 The regular expression is (as usual in hledger) a POSIX extended regu- lar expression, that also supports GNU word boundaries (\b, \B, \<, \>), and nothing else. If you have trouble, see "Regular expressions" in the hledger manual (https://hledger.org/hledger.html#regular-expres- sions). What matchers match With record matchers, it's important to know that the record matched is not the original CSV record, but a modified one: separators will be converted to commas, and enclosing double quotes (but not enclosing whitespace) are removed. So for example, when reading an SSV file, if the original record was: 2023-01-01; "Acme, Inc."; 1,000 the regex would see, and try to match, this modified record text: 2023-01-01,Acme, Inc., 1,000 Combining matchers When an if block has multiple matchers, they are combined as follows: o By default they are OR'd (any one of them can match) o When a matcher is preceded by ampersand (&) it will be AND'ed with the previous matcher (both of them must match) o When a matcher is preceded by an exclamation mark (!), the matcher is negated (it may not match). Currently there is a limitation: you can't use both & and ! on the same line (you can't AND a negated matcher). Match groups Matchers can define match groups: parenthesised portions of the regular expression which are available for reference in field assignments. Groups are enclosed in regular parentheses (( and )) and can be nested. Each group is available in field assignments using the token \N, where N is an index into the match groups for this conditional block (e.g. \1, \2, etc.). Example: Warp credit card payment postings to the beginning of the billing period (Month start), to match how they are presented in state- ments, using posting dates: if %date (....-..)-.. comment2 date:\1-01 Another example: Read the expense account from the CSV field, but throw away a prefix: if %account1 liabilities:family:(expenses:.*) account1 \1 if table "if tables" are an alternative to if blocks; they can express many matchers and field assignments in a more compact tabular format, like this: if,HLEDGERFIELD1,HLEDGERFIELD2,... MATCHERA,VALUE1,VALUE2,... MATCHERB,VALUE1,VALUE2,... MATCHERC,VALUE1,VALUE2,... The first character after if is taken to be this if table's field sepa- rator. It is unrelated to the separator used in the CSV file. It should be a non-alphanumeric character like , or | that does not appear anywhere else in the table (it should not be used in field names or matchers or values, and it cannot be escaped with a backslash). Each line must contain the same number of separators; empty values are allowed. Whitespace can be used in the matcher lines for readability (but not in the if line, currently). The table must be terminated by an empty line (or end of file). An if table like the above is interpreted as follows: try all of the matchers; whenever a matcher succeeds, assign all of the values on that line to the corresponding hledger fields; later lines can overrider earlier ones. It is equivalent to this sequence of if blocks: if MATCHERA HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERB HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERC HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... Example: if,account2,comment atm transaction fee,expenses:business:banking,deductible? check it %description groceries,expenses:groceries, 2023/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call-out balance-type Balance assertions generated by assigning to balanceN are of the simple = type by default, which is a single-commodity, subaccount-excluding assertion. You may find the subaccount-including variants more useful, eg if you have created some virtual subaccounts of checking to help with budgeting. You can select a different type of assertion with the balance-type rule: # balance assertions will consider all commodities and all subaccounts balance-type ==* Here are the balance assertion types for quick reference: = single commodity, exclude subaccounts =* single commodity, include subaccounts == multi commodity, exclude subaccounts ==* multi commodity, include subaccounts include include RULESFILE This includes the contents of another CSV rules file at this point. RULESFILE is an absolute file path or a path relative to the current file's directory. This can be useful for sharing common rules between several rules files, eg: # someaccount.csv.rules ## someaccount-specific rules fields date,description,amount account1 assets:someaccount account2 expenses:misc ## common rules include categorisation.rules Working with CSV Some tips: Rapid feedback It's a good idea to get rapid feedback while creating/troubleshooting CSV rules. Here's a good way, using entr from eradman.com/entrproject: $ ls foo.csv* | entr bash -c 'echo ----; hledger -f foo.csv print desc:SOMEDESC' A desc: query (eg) is used to select just one, or a few, transactions of interest. "bash -c" is used to run multiple commands, so we can echo a separator each time the command re-runs, making it easier to read the output. Valid CSV Note that hledger will only accept valid CSV conforming to RFC 4180, and equivalent SSV and TSV formats (like RFC 4180 but with semicolon or tab as separators). This means, eg: o Values may be enclosed in double quotes, or not. Enclosing in single quotes is not allowed. (Eg 'A','B' is rejected.) o When values are enclosed in double quotes, spaces outside the quotes are not allowed. (Eg "A", "B" is rejected.) o When values are not enclosed in quotes, they may not contain double quotes. (Eg A"A, B is rejected.) If your CSV/SSV/TSV is not valid in this sense, you'll need to trans- form it before reading with hledger. Try using sed, or a more permis- sive CSV parser like python's csv lib. File Extension To help hledger choose the CSV file reader and show the right error messages (and choose the right field separator character by default), it's best if CSV/SSV/TSV files are named with a .csv, .ssv or .tsv filename extension. (More about this at Data formats.) When reading files with the "wrong" extension, you can ensure the CSV reader (and the default field separator) by prefixing the file path with csv:, ssv: or tsv:: Eg: $ hledger -f ssv:foo.dat print You can also override the default field separator with a separator rule if needed. Reading CSV from standard input You'll need the file format prefix when reading CSV from stdin also, since hledger assumes journal format by default. Eg: $ cat foo.dat | hledger -f ssv:- print Reading multiple CSV files If you use multiple -f options to read multiple CSV files at once, hledger will look for a correspondingly-named rules file for each CSV file. But if you use the --rules-file option, that rules file will be used for all the CSV files. Reading files specified by rule Instead of specifying a CSV file in the command line, you can specify a rules file, as in hledger -f foo.csv.rules CMD. By default this will read data from foo.csv in the same directory, but you can add a source rule to specify a different data file, perhaps located in your web browser's download directory. This feature was added in hledger 1.30, so you won't see it in most CSV rules examples. But it helps remove some of the busywork of managing CSV downloads. Most of your financial institutions's default CSV file- names are different and can be recognised by a glob pattern. So you can put a rule like source Checking1*.csv in foo-checking.csv.rules, and then periodically follow a workflow like: 1. Download CSV from Foo's website, using your browser's defaults 2. Run hledger import foo-checking.csv.rules to import any new transac- tions After import, you can: discard the CSV, or leave it where it is for a while, or move it into your archives, as you prefer. If you do noth- ing, next time your browser will save something like Checking1-2.csv, and hledger will use that because of the * wild card and because it is the most recent. Valid transactions After reading a CSV file, hledger post-processes and validates the gen- erated journal entries as it would for a journal file - balancing them, applying balance assignments, and canonicalising amount styles. Any errors at this stage will be reported in the usual way, displaying the problem entry. There is one exception: balance assertions, if you have generated them, will not be checked, since normally these will work only when the CSV data is part of the main journal. If you do need to check balance as- sertions generated from CSV right away, pipe into another hledger: $ hledger -f file.csv print | hledger -f- print Deduplicating, importing When you download a CSV file periodically, eg to get your latest bank transactions, the new file may overlap with the old one, containing some of the same records. The import command will (a) detect the new transactions, and (b) append just those transactions to your main journal. It is idempotent, so you don't have to remember how many times you ran it or with which version of the CSV. (It keeps state in a hidden .latest.FILE.csv file.) This is the easiest way to import CSV data. Eg: # download the latest CSV files, then run this command. # Note, no -f flags needed here. $ hledger import *.csv [--dry] This method works for most CSV files. (Where records have a stable chronological order, and new records appear only at the new end.) A number of other tools and workflows, hledger-specific and otherwise, exist for converting, deduplicating, classifying and managing CSV data. See: o https://hledger.org/cookbook.html#setups-and-workflows o https://plaintextaccounting.org -> data import/conversion Setting amounts Continuing from amount field above, here are more tips for amount-set- ting: 1. If the amount is in a single CSV field: a. If its sign indicates direction of flow: Assign it to amountN, to set the Nth posting's amount. N is usu- ally 1 or 2 but can go up to 99. b. If another field indicates direction of flow: Use one or more conditional rules to set the appropriate amount sign. Eg: # assume a withdrawal unless Type contains "deposit": amount1 -%Amount if %Type deposit amount1 %Amount 2. If the amount is in two CSV fields (such as Debit and Credit, or In and Out): a. If both fields are unsigned: Assign one field to amountN-in and the other to amountN-out. hledger will automatically negate the "out" field, and will use whichever field value is non-zero as posting N's amount. b. If either field is signed: You will probably need to override hledger's sign for one or the other field, as in the following example: # Negate the -out value, but only if it is not empty: fields date, description, amount1-in, amount1-out if %amount1-out [1-9] amount1-out -%amount1-out c. If both fields can contain a non-zero value (or both can be empty): The -in/-out rules normally choose the value which is non-zero/non-empty. Some value pairs can be ambiguous, such as 1 and none. For such cases, use conditional rules to help select the amount. Eg, to handle the above you could select the value con- taining non-zero digits: fields date, description, in, out if %in [1-9] amount1 %in if %out [1-9] amount1 %out 3. If you want posting 2's amount converted to cost: Use the unnumbered amount (or amount-in and amount-out) syntax. 4. If the CSV has only balance amounts, not transaction amounts: Assign to balanceN, to set a balance assignment on the Nth posting, causing the posting's amount to be calculated automatically. balance with no number is equivalent to balance1. In this situation hledger is more likely to guess the wrong default account name, so you may need to set that explicitly. Amount signs There is some special handling making it easier to parse and to reverse amount signs. (This only works for whole amounts, not for cost amounts such as COST in amount1 AMT @ COST): o If an amount value begins with a plus sign: that will be removed: +AMT becomes AMT o If an amount value is parenthesised: it will be de-parenthesised and sign-flipped: (AMT) becomes -AMT o If an amount value has two minus signs (or two sets of parentheses, or a minus sign and parentheses): they cancel out and will be removed: --AMT or -(AMT) becomes AMT o If an amount value contains just a sign (or just a set of parenthe- ses): that is removed, making it an empty value. "+" or "-" or "()" becomes "". It's not possible (without preprocessing the CSV) to set an amount to its absolute value, ie discard its sign. Setting currency/commodity If the currency/commodity symbol is included in the CSV's amount field(s): 2023-01-01,foo,$123.00 you don't have to do anything special for the commodity symbol, it will be assigned as part of the amount. Eg: fields date,description,amount 2023-01-01 foo expenses:unknown $123.00 income:unknown $-123.00 If the currency is provided as a separate CSV field: 2023-01-01,foo,USD,123.00 You can assign that to the currency pseudo-field, which has the special effect of prepending itself to every amount in the transaction (on the left, with no separating space): fields date,description,currency,amount 2023-01-01 foo expenses:unknown USD123.00 income:unknown USD-123.00 Or, you can use a field assignment to construct the amount yourself, with more control. Eg to put the symbol on the right, and separated by a space: fields date,description,cur,amt amount %amt %cur 2023-01-01 foo expenses:unknown 123.00 USD income:unknown -123.00 USD Note we used a temporary field name (cur) that is not currency - that would trigger the prepending effect, which we don't want here. Amount decimal places Like amounts in a journal file, the amounts generated by CSV rules like amount1 influence commodity display styles, such as the number of deci- mal places displayed in reports. The original amounts as written in the CSV file do not affect display style (because we don't yet reliably know their commodity). Referencing other fields In field assignments, you can interpolate only CSV fields, not hledger fields. In the example below, there's both a CSV field and a hledger field named amount1, but %amount1 always means the CSV field, not the hledger field: # Name the third CSV field "amount1" fields date,description,amount1 # Set hledger's amount1 to the CSV amount1 field followed by USD amount1 %amount1 USD # Set comment to the CSV amount1 (not the amount1 assigned above) comment %amount1 Here, since there's no CSV amount1 field, %amount1 will produce a lit- eral "amount1": fields date,description,csvamount amount1 %csvamount USD # Can't interpolate amount1 here comment %amount1 When there are multiple field assignments to the same hledger field, only the last one takes effect. Here, comment's value will be be B, or C if "something" is matched, but never A: comment A comment B if something comment C How CSV rules are evaluated Here's how to think of CSV rules being evaluated (if you really need to). First, o include - all includes are inlined, from top to bottom, depth first. (At each include point the file is inlined and scanned for further includes, recursively, before proceeding.) Then "global" rules are evaluated, top to bottom. If a rule is re- peated, the last one wins: o skip (at top level) o date-format o newest-first o fields - names the CSV fields, optionally sets up initial assignments to hledger fields Then for each CSV record in turn: o test all if blocks. If any of them contain a end rule, skip all re- maining CSV records. Otherwise if any of them contain a skip rule, skip that many CSV records. If there are multiple matched skip rules, the first one wins. o collect all field assignments at top level and in matched if blocks. When there are multiple assignments for a field, keep only the last one. o compute a value for each hledger field - either the one that was as- signed to it (and interpolate the %CSVFIELD references), or a default o generate a hledger transaction (journal entry) from these values. This is all part of the CSV reader, one of several readers hledger can use to parse input files. When all files have been read successfully, the transactions are passed as input to whichever hledger command the user specified. Well factored rules Some things than can help reduce duplication and complexity in rules files: o Extracting common rules usable with multiple CSV files into a com- mon.rules, and adding include common.rules to each CSV's rules file. o Splitting if blocks into smaller if blocks, extracting the frequently used parts. CSV rules examples Bank of Ireland Here's a CSV with two amount fields (Debit and Credit), and a balance field, which we can use to add balance assertions, which is not neces- sary but provides extra error checking: Date,Details,Debit,Credit,Balance 07/12/2012,LODGMENT 529898,,10.0,131.21 07/12/2012,PAYMENT,5,,126 # bankofireland-checking.csv.rules # skip the header line skip # name the csv fields, and assign some of them as journal entry fields fields date, description, amount-out, amount-in, balance # We generate balance assertions by assigning to "balance" # above, but you may sometimes need to remove these because: # # - the CSV balance differs from the true balance, # by up to 0.0000000000005 in my experience # # - it is sometimes calculated based on non-chronological ordering, # eg when multiple transactions clear on the same day # date is in UK/Ireland format date-format %d/%m/%Y # set the currency currency EUR # set the base account for all txns account1 assets:bank:boi:checking $ hledger -f bankofireland-checking.csv print 2012-12-07 LODGMENT 529898 assets:bank:boi:checking EUR10.0 = EUR131.2 income:unknown EUR-10.0 2012-12-07 PAYMENT assets:bank:boi:checking EUR-5.0 = EUR126.0 expenses:unknown EUR5.0 The balance assertions don't raise an error above, because we're read- ing directly from CSV, but they will be checked if these entries are imported into a journal file. Coinbase A simple example with some CSV from Coinbase. The spot price is recorded using cost notation. The legacy amount field name conve- niently sets amount 2 (posting 2's amount) to the total cost. # Timestamp,Transaction Type,Asset,Quantity Transacted,Spot Price Currency,Spot Price at Transaction,Subtotal,Total (inclusive of fees and/or spread),Fees and/or Spread,Notes # 2021-12-30T06:57:59Z,Receive,USDC,100,GBP,0.740000,"","","","Received 100.00 USDC from an external account" # coinbase.csv.rules skip 1 fields Timestamp,Transaction_Type,Asset,Quantity_Transacted,Spot_Price_Currency,Spot_Price_at_Transaction,Subtotal,Total,Fees_Spread,Notes date %Timestamp date-format %Y-%m-%dT%T%Z description %Notes account1 assets:coinbase:cc amount %Quantity_Transacted %Asset @ %Spot_Price_at_Transaction %Spot_Price_Currency $ hledger print -f coinbase.csv 2021-12-30 Received 100.00 USDC from an external account assets:coinbase:cc 100 USDC @ 0.740000 GBP income:unknown -74.000000 GBP Amazon Here we convert amazon.com order history, and use an if block to gener- ate a third posting if there's a fee. (In practice you'd probably get this data from your bank instead, but it's an example.) "Date","Type","To/From","Name","Status","Amount","Fees","Transaction ID" "Jul 29, 2012","Payment","To","Foo.","Completed","$20.00","$0.00","16000000000000DGLNJPI1P9B8DKPVHL" "Jul 30, 2012","Payment","To","Adapteva, Inc.","Completed","$25.00","$1.00","17LA58JSKRD4HDGLNJPI1P9B8DKPVHL" # amazon-orders.csv.rules # skip one header line skip 1 # name the csv fields, and assign the transaction's date, amount and code. # Avoided the "status" and "amount" hledger field names to prevent confusion. fields date, _, toorfrom, name, amzstatus, amzamount, fees, code # how to parse the date date-format %b %-d, %Y # combine two fields to make the description description %toorfrom %name # save the status as a tag comment status:%amzstatus # set the base account for all transactions account1 assets:amazon # leave amount1 blank so it can balance the other(s). # I'm assuming amzamount excludes the fees, don't remember # set a generic account2 account2 expenses:misc amount2 %amzamount # and maybe refine it further: #include categorisation.rules # add a third posting for fees, but only if they are non-zero. if %fees [1-9] account3 expenses:fees amount3 %fees $ hledger -f amazon-orders.csv print 2012-07-29 (16000000000000DGLNJPI1P9B8DKPVHL) To Foo. ; status:Completed assets:amazon expenses:misc $20.00 2012-07-30 (17LA58JSKRD4HDGLNJPI1P9B8DKPVHL) To Adapteva, Inc. ; status:Completed assets:amazon expenses:misc $25.00 expenses:fees $1.00 Paypal Here's a real-world rules file for (customised) Paypal CSV, with some Paypal-specific rules, and a second rules file included: "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" "10/01/2019","03:46:20","PDT","Calm Radio","Subscription Payment","Completed","USD","-6.99","0.00","-6.99","simon@joyful.com","memberships@calmradio.com","60P57143A8206782E","MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month","","I-R8YLY094FJYR","","-6.99","" "10/01/2019","03:46:20","PDT","","Bank Deposit to PP Account ","Pending","USD","6.99","0.00","6.99","","simon@joyful.com","0TU1544T080463733","","","60P57143A8206782E","","0.00","" "10/01/2019","08:57:01","PDT","Patreon","PreApproved Payment Bill User Payment","Completed","USD","-7.00","0.00","-7.00","simon@joyful.com","support@patreon.com","2722394R5F586712G","Patreon* Membership","","B-0PG93074E7M86381M","","-7.00","" "10/01/2019","08:57:01","PDT","","Bank Deposit to PP Account ","Pending","USD","7.00","0.00","7.00","","simon@joyful.com","71854087RG994194F","Patreon* Membership","","2722394R5F586712G","","0.00","" "10/19/2019","03:02:12","PDT","Wikimedia Foundation, Inc.","Subscription Payment","Completed","USD","-2.00","0.00","-2.00","simon@joyful.com","tle@wikimedia.org","K9U43044RY432050M","Monthly donation to the Wikimedia Foundation","","I-R5C3YUS3285L","","-2.00","" "10/19/2019","03:02:12","PDT","","Bank Deposit to PP Account ","Pending","USD","2.00","0.00","2.00","","simon@joyful.com","3XJ107139A851061F","","","K9U43044RY432050M","","0.00","" "10/22/2019","05:07:06","PDT","Noble Benefactor","Subscription Payment","Completed","USD","10.00","-0.59","9.41","noble@bene.fac.tor","simon@joyful.com","6L8L1662YP1334033","Joyful Systems","","I-KC9VBGY2GWDB","","9.41","" # paypal-custom.csv.rules # Tips: # Export from Activity -> Statements -> Custom -> Activity download # Suggested transaction type: "Balance affecting" # Paypal's default fields in 2018 were: # "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Shipping Address","Address Status","Item Title","Item ID","Shipping and Handling Amount","Insurance Amount","Sales Tax","Option 1 Name","Option 1 Value","Option 2 Name","Option 2 Value","Reference Txn ID","Invoice Number","Custom Number","Quantity","Receipt ID","Balance","Address Line 1","Address Line 2/District/Neighborhood","Town/City","State/Province/Region/County/Territory/Prefecture/Republic","Zip/Postal Code","Country","Contact Phone Number","Subject","Note","Country Code","Balance Impact" # This rules file assumes the following more detailed fields, configured in "Customize report fields": # "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" fields date, time, timezone, description_, type, status_, currency, grossamount, feeamount, netamount, fromemail, toemail, code, itemtitle, itemid, referencetxnid, receiptid, balance, note skip 1 date-format %-m/%-d/%Y # ignore some paypal events if In Progress Temporary Hold Update to skip # add more fields to the description description %description_ %itemtitle # save some other fields as tags comment itemid:%itemid, fromemail:%fromemail, toemail:%toemail, time:%time, type:%type, status:%status_ # convert to short currency symbols if %currency USD currency $ if %currency EUR currency E if %currency GBP currency P # generate postings # the first posting will be the money leaving/entering my paypal account # (negative means leaving my account, in all amount fields) account1 assets:online:paypal amount1 %netamount # the second posting will be money sent to/received from other party # (account2 is set below) amount2 -%grossamount # if there's a fee, add a third posting for the money taken by paypal. if %feeamount [1-9] account3 expenses:banking:paypal amount3 -%feeamount comment3 business: # choose an account for the second posting # override the default account names: # if the amount is positive, it's income (a debit) if %grossamount ^[^-] account2 income:unknown # if negative, it's an expense (a credit) if %grossamount ^- account2 expenses:unknown # apply common rules for setting account2 & other tweaks include common.rules # apply some overrides specific to this csv # Transfers from/to bank. These are usually marked Pending, # which can be disregarded in this case. if Bank Account Bank Deposit to PP Account description %type for %referencetxnid %itemtitle account2 assets:bank:wf:pchecking account1 assets:online:paypal # Currency conversions if Currency Conversion account2 equity:currency conversion # common.rules if darcs noble benefactor account2 revenues:foss donations:darcshub comment2 business: if Calm Radio account2 expenses:online:apps if electronic frontier foundation Patreon wikimedia Advent of Code account2 expenses:dues if Google account2 expenses:online:apps description google | music $ hledger -f paypal-custom.csv print 2019-10-01 (60P57143A8206782E) Calm Radio MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month ; itemid:, fromemail:simon@joyful.com, toemail:memberships@calmradio.com, time:03:46:20, type:Subscription Payment, status:Completed assets:online:paypal $-6.99 = $-6.99 expenses:online:apps $6.99 2019-10-01 (0TU1544T080463733) Bank Deposit to PP Account for 60P57143A8206782E ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:46:20, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $6.99 = $0.00 assets:bank:wf:pchecking $-6.99 2019-10-01 (2722394R5F586712G) Patreon Patreon* Membership ; itemid:, fromemail:simon@joyful.com, toemail:support@patreon.com, time:08:57:01, type:PreApproved Payment Bill User Payment, status:Completed assets:online:paypal $-7.00 = $-7.00 expenses:dues $7.00 2019-10-01 (71854087RG994194F) Bank Deposit to PP Account for 2722394R5F586712G Patreon* Membership ; itemid:, fromemail:, toemail:simon@joyful.com, time:08:57:01, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $7.00 = $0.00 assets:bank:wf:pchecking $-7.00 2019-10-19 (K9U43044RY432050M) Wikimedia Foundation, Inc. Monthly donation to the Wikimedia Foundation ; itemid:, fromemail:simon@joyful.com, toemail:tle@wikimedia.org, time:03:02:12, type:Subscription Payment, status:Completed assets:online:paypal $-2.00 = $-2.00 expenses:dues $2.00 expenses:banking:paypal ; business: 2019-10-19 (3XJ107139A851061F) Bank Deposit to PP Account for K9U43044RY432050M ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:02:12, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $2.00 = $0.00 assets:bank:wf:pchecking $-2.00 2019-10-22 (6L8L1662YP1334033) Noble Benefactor Joyful Systems ; itemid:, fromemail:noble@bene.fac.tor, toemail:simon@joyful.com, time:05:07:06, type:Subscription Payment, status:Completed assets:online:paypal $9.41 = $9.41 revenues:foss donations:darcshub $-10.00 ; business: expenses:banking:paypal $0.59 ; business: Timeclock The time logging format of timeclock.el, as read by hledger. hledger can read time logs in timeclock format. As with Ledger, these are (a subset of) timeclock.el's format, containing clock-in and clock-out entries as in the example below. The date is a simple date. The time format is HH:MM[:SS][+-ZZZZ]. Seconds and timezone are op- tional. The timezone, if present, must be four digits and is ignored (currently the time is always interpreted as a local time). Lines be- ginning with # or ; or *, and blank lines, are ignored. i 2015/03/30 09:00:00 some account optional description after 2 spaces ; optional comment, tags: o 2015/03/30 09:20:00 i 2015/03/31 22:21:45 another:account o 2015/04/01 02:00:34 hledger treats each clock-in/clock-out pair as a transaction posting some number of hours to an account. Or if the session spans more than one day, it is split into several transactions, one for each day. For the above time log, hledger print generates these journal entries: $ hledger -f t.timeclock print 2015-03-30 * optional description after 2 spaces ; optional comment, tags: (some account) 0.33h 2015-03-31 * 22:21-23:59 (another:account) 1.64h 2015-04-01 * 00:00-02:00 (another:account) 2.01h Here is a sample.timeclock to download and some queries to try: $ hledger -f sample.timeclock balance # current time balances $ hledger -f sample.timeclock register -p 2009/3 # sessions in march 2009 $ hledger -f sample.timeclock register -p weekly --depth 1 --empty # time summary by week To generate time logs, ie to clock in and clock out, you could: o use emacs and the built-in timeclock.el, or the extended time- clock-x.el and perhaps the extras in ledgerutils.el o at the command line, use these bash aliases: shell alias ti="echo i `date '+%Y-%m-%d %H:%M:%S'` \$* >>$TIMELOG" alias to="echo o `date '+%Y-%m-%d %H:%M:%S'` >>$TIMELOG" o or use the old ti and to scripts in the ledger 2.x repository. These rely on a "timeclock" executable which I think is just the ledger 2 executable renamed. Timedot timedot format is hledger's human-friendly time logging format. Com- pared to timeclock format, it is more convenient for quick, approxi- mate, and retroactive time logging, and more human-readable (you can see at a glance where time was spent). A quick example: 2023-05-01 hom:errands .... .... ; two hours; the space is ignored fos:hledger:timedot .. ; half an hour per:admin:finance ; no time spent yet hledger reads this as a transaction on this day with three (unbalanced) postings, where each dot represents "0.25". No commodity symbol is as- sumed, but we typically interpret it as hours. $ hledger -f a.timedot print # .timedot file extension (or timedot: prefix) is required 2023-05-01 * (hom:errands) 2.00 ; two hours (fos:hledger:timedot) 0.50 ; half an hour (per:admin:finance) 0 A timedot file contains a series of transactions (usually one per day). Each begins with a simple date (Y-M-D, Y/M/D, or Y.M.D), optionally be followed on the same line by a transaction description, and/or a trans- action comment following a semicolon. After the date line are zero or more time postings, consisting of: o An account name - any hledger-style account name, optionally in- dented. o Two or more spaces - required if there is an amount (as in journal format). o A timedot amount, which can be o empty (representing zero) o a number, optionally followed by a unit s, m, h, d, w, mo, or y, representing a precise number of seconds, minutes, hours, days weeks, months or years (hours is assumed by default), which will be converted to hours according to 60s = 1m, 60m = 1h, 24h = 1d, 7d = 1w, 30d = 1mo, 365d = 1y. o one or more dots (period characters), each representing 0.25. These are the dots in "timedot". Spaces are ignored and can be used for grouping/alignment. o one or more letters. These are like dots but they also generate a tag t: (short for "type") with the letter as its value, and a sepa- rate posting for each of the values. This provides a second dimen- sion of categorisation, viewable in reports with --pivot t. o An optional comment following a semicolon (a hledger-style posting comment). There is some flexibility to help with keeping time log data and notes in the same file: o Blank lines and lines beginning with # or ; are ignored. o After the first date line, lines which do not contain a double space are parsed as postings with zero amount. (hledger's register reports will show these if you add -E). o Before the first date line, lines beginning with * (eg org headings) are ignored. And from the first date line onward, Emacs org mode heading prefixes at the start of lines (one or more *'s followed by a space) will be ignored. This means the time log can also be a org outline. Timedot examples Numbers: 2016/2/3 inc:client1 4 fos:hledger 3h biz:research 60m Dots: # on this day, 6h was spent on client work, 1.5h on haskell FOSS work, etc. 2016/2/1 inc:client1 .... .... .... .... .... .... fos:haskell .... .. biz:research . 2016/2/2 inc:client1 .... .... biz:research . $ hledger -f a.timedot print date:2016/2/2 2016-02-02 * (inc:client1) 2.00 2016-02-02 * (biz:research) 0.25 $ hledger -f a.timedot bal --daily --tree Balance changes in 2016-02-01-2016-02-03: || 2016-02-01d 2016-02-02d 2016-02-03d ============++======================================== biz || 0.25 0.25 1.00 research || 0.25 0.25 1.00 fos || 1.50 0 3.00 haskell || 1.50 0 0 hledger || 0 0 3.00 inc || 6.00 2.00 4.00 client1 || 6.00 2.00 4.00 ------------++---------------------------------------- || 7.75 2.25 8.00 Letters: # Activity types: # c cleanup/catchup/repair # e enhancement # s support # l learning/research 2023-11-01 work:adm ccecces $ hledger -f a.timedot print 2023-11-01 (work:adm) 1 ; t:c (work:adm) 0.5 ; t:e (work:adm) 0.25 ; t:s $ hledger -f a.timedot bal 1.75 work:adm -------------------- 1.75 $ hledger -f a.timedot bal --pivot t 1.00 c 0.50 e 0.25 s -------------------- 1.75 Org: * 2023 Work Diary ** Q1 *** 2023-02-29 **** DONE 0700 yoga **** UNPLANNED **** BEGUN hom:chores cleaning ... water plants outdoor - one full watering can indoor - light watering **** TODO adm:planning: trip *** LATER Using . as account name separator: 2016/2/4 fos.hledger.timedot 4h fos.ledger .. $ hledger -f a.timedot --alias '/\./=:' bal -t 4.50 fos 4.00 hledger:timedot 0.50 ledger -------------------- 4.50 PART 3: REPORTING CONCEPTS Amount formatting, parseability If you're wondering why your print report sometimes shows trailing dec- imal marks, with no decimal digits; it does this when showing amounts that have digit group marks but no decimal digits, to disambiguate them and allow them to be re-parsed reliably (see also Decimal marks, digit group marks. Eg: commodity $1,000.00 2023-01-02 (a) $1000 $ hledger print 2023-01-02 (a) $1,000. If this is a problem (eg when exporting to Ledger), you can avoid it by disabling digit group marks, eg with -c/--commodity (for each affected commodity): $ hledger print -c '$1000.00' 2023-01-02 (a) $1000 or by forcing print to always show decimal digits, with --round: $ hledger print -c '$1,000.00' --round=soft 2023-01-02 (a) $1,000.00 More generally: hledger output falls into three rough categories, which format amounts a little bit differently to suit different consumers: 1. "hledger-readable output" - should be readable by hledger (and by humans) o This is produced by reports that show full journal entries: print, import, close, rewrite etc. o It shows amounts with their original journal precisions, which may not be consistent. o It adds a trailing decimal mark when needed to avoid showing ambigu- ous amounts. o It can be parsed reliably (by hledger and ledger2beancount at least, but perhaps not by Ledger..) 2. "human-readable output" - usually for humans o This is produced by all other reports. o It shows amounts with standard display precisions, which will be con- sistent within each commodity. o It shows ambiguous amounts unmodified. o It can be parsed reliably in the context of a known report (when you know decimals are consistently not being shown, you can assume a sin- gle mark is a digit group mark). 3. "machine-readable output" - usually for other software o This is produced by all reports when an output format like csv, tsv, json, or sql is selected. o It shows amounts as 1 or 2 do, but without digit group marks. o It can be parsed reliably (if needed, the decimal mark can be changed with -c/--commodity-style). Time periods Report start & end date By default, most hledger reports will show the full span of time repre- sented by the journal. The report start date will be the earliest transaction or posting date, and the report end date will be the latest transaction, posting, or market price date. Often you will want to see a shorter time span, such as the current month. You can specify a start and/or end date using -b/--begin, -e/--end, -p/--period or a date: query (described below). All of these accept the smart date syntax (below). Some notes: o End dates are exclusive, as in Ledger, so you should write the date after the last day you want to see in the report. o As noted in reporting options: among start/end dates specified with options, the last (i.e. right-most) option takes precedence. o The effective report start and end dates are the intersection of the start/end dates from options and that from date: queries. That is, date:2019-01 date:2019 -p'2000 to 2030' yields January 2019, the smallest common time span. o In some cases a report interval will adjust start/end dates to fall on interval boundaries (see below). Examples: -b 2016/3/17 begin on St. Patrick's day 2016 -e 12/1 end at the start of december 1st of the current year (11/30 will be the last date included) -b thismonth all transactions on or after the 1st of the current month -p thismonth all transactions in the current month date:2016/3/17.. the above written as queries instead (.. can also be re- placed with -) date:..12/1 date:thismonth.. date:thismonth Smart dates hledger's user interfaces accept a "smart date" syntax for added conve- nience. Smart dates optionally can be relative to today's date, be written with english words, and have less-significant parts omitted (missing parts are inferred as 1). Some examples: 2004/10/1, 2004-01-01, exact date, several separators allowed. Year 2004.9.1 is 4+ digits, month is 1-12, day is 1-31 2004 start of year 2004/10 start of month 10/1 month and day in current year 21 day in current month october, oct start of month in current year yesterday, today, tomor- -1, 0, 1 days from today row last/this/next -1, 0, 1 periods from the current period day/week/month/quar- ter/year in n n periods from the current period days/weeks/months/quar- ters/years n n periods from the current period days/weeks/months/quar- ters/years ahead n -n periods from the current period days/weeks/months/quar- ters/years ago 20181201 8 digit YYYYMMDD with valid year month and day 201812 6 digit YYYYMM with valid year and month Some counterexamples - malformed digit sequences might give surprising results: 201813 6 digits with an invalid month is parsed as start of 6-digit year 20181301 8 digits with an invalid month is parsed as start of 8-digit year 20181232 8 digits with an invalid day gives an error 201801012 9+ digits beginning with a valid YYYYMMDD gives an error "Today's date" can be overridden with the --today option, in case it's needed for testing or for recreating old reports. (Except for periodic transaction rules, which are not affected by --today.) Report intervals A report interval can be specified so that reports like register, bal- ance or activity become multi-period, showing each subperiod as a sepa- rate row or column. The following standard intervals can be enabled with command-line flags: o -D/--daily o -W/--weekly o -M/--monthly o -Q/--quarterly o -Y/--yearly More complex intervals can be specified using -p/--period, described below. Date adjustment When there is a report interval (other than daily), report start/end dates which have been inferred, eg from the journal, are automatically adjusted to natural period boundaries. This is convenient for produc- ing simple periodic reports. More precisely: o an inferred start date will be adjusted earlier if needed to fall on a natural period boundary o an inferred end date will be adjusted later if needed to make the last period the same length as the others. By contrast, start/end dates which have been specified explicitly, with -b, -e, -p or date:, will not be adjusted (since hledger 1.29). This makes it possible to specify non-standard report periods, but it also means that if you are specifying a start date, you should pick one that's on a period boundary if you want to see simple report period headings. Period expressions The -p/--period option specifies a period expression, which is a com- pact way of expressing a start date, end date, and/or report interval. Here's a period expression with a start and end date (specifying the first quarter of 2009): -p "from 2009/1/1 to 2009/4/1" Several keywords like "from" and "to" are supported for readability; these are optional. "to" can also be written as ".." or "-". The spaces are also optional, as long as you don't run two dates together. So the following are equivalent to the above: -p "2009/1/1 2009/4/1" -p2009/1/1to2009/4/1 -p2009/1/1..2009/4/1 Dates are smart dates, so if the current year is 2009, these are also equivalent to the above: -p "1/1 4/1" -p "jan-apr" -p "this year to 4/1" If you specify only one date, the missing start or end date will be the earliest or latest transaction date in the journal: -p "from 2009/1/1" everything after january 1, 2009 -p "since 2009/1" the same, since is a syn- onym -p "from 2009" the same -p "to 2009" everything before january 1, 2009 You can also specify a period by writing a single partial or full date: -p "2009" the year 2009; equivalent to "2009/1/1 to 2010/1/1" -p "2009/1" the month of january 2009; equivalent to "2009/1/1 to 2009/2/1" -p "2009/1/1" the first day of 2009; equivalent to "2009/1/1 to 2009/1/2" or by using the "Q" quarter-year syntax (case insensitive): -p "2009Q1" first quarter of 2009, equivalent to "2009/1/1 to 2009/4/1" -p "q4" fourth quarter of the current year Period expressions with a report interval A period expression can also begin with a report interval, separated from the start/end dates (if any) by a space or the word in: -p "weekly from 2009/1/1 to 2009/4/1" -p "monthly in 2008" -p "quarterly" More complex report intervals Some more complex intervals can be specified within period expressions, such as: o biweekly (every two weeks) o fortnightly o bimonthly (every two months) o every day|week|month|quarter|year o every N days|weeks|months|quarters|years Weekly on a custom day: o every Nth day of week (th, nd, rd, or st are all accepted after the number) o every WEEKDAYNAME (full or three-letter english weekday name, case insensitive) Monthly on a custom day: o every Nth day [of month] o every Nth WEEKDAYNAME [of month] Yearly on a custom day: o every MM/DD [of year] (month number and day of month number) o every MONTHNAME DDth [of year] (full or three-letter english month name, case insensitive, and day of month number) o every DDth MONTHNAME [of year] (equivalent to the above) Examples: -p "bimonthly from 2008" -p "every 2 weeks" -p "every 5 months from 2009/03" -p "every 2nd day of week" periods will go from Tue to Tue -p "every Tue" same -p "every 15th day" period boundaries will be on 15th of each month -p "every 2nd Monday" period boundaries will be on second Monday of each month -p "every 11/05" yearly periods with boundaries on 5th of November -p "every 5th November" same -p "every Nov 5th" same Show historical balances at end of the 15th day of each month (N is an end date, exclusive as always): $ hledger balance -H -p "every 16th day" Group postings from the start of wednesday to end of the following tuesday (N is both (inclusive) start date and (exclusive) end date): $ hledger register checking -p "every 3rd day of week" Multiple weekday intervals This special form is also supported: o every WEEKDAYNAME,WEEKDAYNAME,... (full or three-letter english week- day names, case insensitive) Also, weekday and weekendday are shorthand for mon,tue,wed,thu,fri and sat,sun. This is mainly intended for use with --forecast, to generate periodic transactions on arbitrary days of the week. It may be less useful with -p, since it divides each week into subperiods of unequal length, which is unusual. (Related: #1632) Examples: -p "every dates will be Mon, Wed, Fri; periods will be mon,wed,fri" Mon-Tue, Wed-Thu, Fri-Sun -p "every weekday" dates will be Mon, Tue, Wed, Thu, Fri; periods will be Mon, Tue, Wed, Thu, Fri-Sun -p "every weekend- dates will be Sat, Sun; periods will be Sat, Sun-Fri day" Depth With the --depth NUM option (short form: -NUM), reports will show ac- counts only to the specified depth, hiding deeper subaccounts. Use this when you want a summary with less detail. This flag has the same effect as a depth: query argument: depth:2, --depth=2 or -2 are equiva- lent. Queries One of hledger's strengths is being able to quickly report on a precise subset of your data. Most hledger commands accept query arguments, to restrict their scope. Multiple query terms can be provided to build up a more complex query. o By default, a query term is interpreted as a case-insensitive sub- string pattern for matching account names: car:fuel dining groceries o Patterns containing spaces or other special characters must be en- closed in single or double quotes: 'personal care' o These patterns are actually regular expressions, so you can add reg- exp metacharacters for more precision (see "Regular expressions" above for details): '^expenses\b' 'food$' 'fuel|repair' 'accounts (payable|receivable)' o To match something other than account name, add one of the query type prefixes described in "Query types" below: date:202312- status: desc:amazon cur:USD cur:\\$ amt:'>0' o Add a not: prefix to negate a term: not:status:'*' not:desc:'opening|closing' not:cur:USD o Terms with different types are AND-ed, terms with the same type are OR-ed (mostly; see "Combining query terms" below). The following query: date:2022 desc:amazon desc:amzn is interpreted as: date is in 2022 AND ( transaction description contains "amazon" OR "amzn" ) Query types Here are the types of query term available. Remember these can also be prefixed with not: to convert them into a negative match. acct:REGEX or REGEX Match account names containing this case insensitive regular expres- sion. This is the default query type, so we usually don't bother writ- ing the "acct:" prefix. amt:N, amt:N, amt:>=N Match postings with a single-commodity amount equal to, less than, or greater than N. (Postings with multi-commodity amounts are not tested and will always match.) The comparison has two modes: if N is preceded by a + or - sign (or is 0), the two signed numbers are compared. Oth- erwise, the absolute magnitudes are compared, ignoring sign. code:REGEX Match by transaction code (eg check number). cur:REGEX Match postings or transactions including any amounts whose cur- rency/commodity symbol is fully matched by REGEX. (For a partial match, use .*REGEX.*). Note, to match special characters which are regex-significant, you need to escape them with \. And for characters which are significant to your shell you may need one more level of es- caping. So eg to match the dollar sign: hledger print cur:\\$. desc:REGEX Match transaction descriptions. date:PERIODEXPR Match dates (or with the --date2 flag, secondary dates) within the specified period. PERIODEXPR is a period expression with no report in- terval. Examples: date:2016, date:thismonth, date:2/1-2/15, date:2021-07-27..nextquarter. date2:PERIODEXPR Match secondary dates within the specified period (independent of the --date2 flag). depth:N Match (or display, depending on command) accounts at or above this depth. expr:"TERM AND NOT (TERM OR TERM)" (eg) Match with a boolean combination of queries (which must be enclosed in quotes). See Combining query terms below. note:REGEX Match transaction notes (the part of the description right of |, or the whole description if there's no |). payee:REGEX Match transaction payee/payer names (the part of the description left of |, or the whole description if there's no |). real:, real:0 Match real or virtual postings respectively. status:, status:!, status:* Match unmarked, pending, or cleared transactions respectively. type:TYPECODES Match by account type (see Declaring accounts > Account types). TYPE- CODES is one or more of the single-letter account type codes ALERXCV, case insensitive. Note type:A and type:E will also match their respec- tive subtypes C (Cash) and V (Conversion). Certain kinds of account alias can disrupt account types, see Rewriting accounts > Aliases and account types. tag:REGEX[=REGEX] Match by tag name, and optionally also by tag value. (To match only by value, use tag:.=REGEX.) When querying by tag, note that: o Accounts also inherit the tags of their parent accounts o Postings also inherit the tags of their account and their transaction o Transactions also acquire the tags of their postings. (inacct:ACCTNAME A special query term used automatically in hledger-web only: tells hledger-web to show the transaction register for an account.) Combining query terms When given multiple space-separated query terms, most commands select things which match: o any of the description terms AND o any of the account terms AND o any of the status terms AND o all the other terms. The print command is a little different, showing transactions which: o match any of the description terms AND o have any postings matching any of the positive account terms AND o have no postings matching any of the negative account terms AND o match all the other terms. We also support more complex boolean queries with the 'expr:' prefix. This allows one to combine queries using one of three operators: AND, OR, and NOT, where NOT is different syntax for 'not:'. Examples of such queries are: o Match transactions with 'cool' in the description AND with the 'A' tag expr:"desc:cool AND tag:A" o Match transactions NOT to the 'expenses:food' account OR with the 'A' tag expr:"NOT expenses:food OR tag:A" o Match transactions NOT involving the 'expenses:food' account OR with the 'A' tag AND involving the 'expenses:drink' account. (the AND is implicitly added by space-separation, following the rules above) expr:"expenses:food OR (tag:A expenses:drink)" Queries and command options Some queries can also be expressed as command-line options: depth:2 is equivalent to --depth 2, date:2023 is equivalent to -p 2023, etc. When you mix command options and query arguments, generally the resulting query is their intersection. Queries and valuation When amounts are converted to other commodities in cost or value re- ports, cur: and amt: match the old commodity symbol and the old amount quantity, not the new ones (except in hledger 1.22.0 where it's re- versed, see #1625). Querying with account aliases When account names are rewritten with --alias or alias, note that acct: will match either the old or the new account name. Querying with cost or value When amounts are converted to other commodities in cost or value re- ports, note that cur: matches the new commodity symbol, and not the old one, and amt: matches the new quantity, and not the old one. Note: this changed in hledger 1.22, previously it was the reverse, see the discussion at #1625. Pivoting Normally, hledger groups and sums amounts within each account. The --pivot FIELD option substitutes some other transaction field for ac- count names, causing amounts to be grouped and summed by that field's value instead. FIELD can be any of the transaction fields acct, sta- tus, code, desc, payee, note, or a tag name. When pivoting on a tag and a posting has multiple values of that tag, only the first value is displayed. Values containing colon:separated:parts will be displayed hierarchically, like account names. Multiple, colon-delimited fields can be pivoted simultaneously, generating a hierarchical account name. Some examples: 2016/02/16 Yearly Dues Payment assets:bank account 2 EUR income:dues -2 EUR ; member: John Doe, kind: Lifetime Normal balance report showing account names: $ hledger balance 2 EUR assets:bank account -2 EUR income:dues -------------------- 0 Pivoted balance report, using member: tag values instead: $ hledger balance --pivot member 2 EUR -2 EUR John Doe -------------------- 0 One way to show only amounts with a member: value (using a query): $ hledger balance --pivot member tag:member=. -2 EUR John Doe -------------------- -2 EUR Another way (the acct: query matches against the pivoted "account name"): $ hledger balance --pivot member acct:. -2 EUR John Doe -------------------- -2 EUR Hierarchical reports can be generated with multiple pivots: $ hledger balance Income:Dues --pivot kind:member -2 EUR Lifetime:John Doe -------------------- -2 EUR Generating data hledger has several features for generating data, such as: o Periodic transaction rules can generate single or repeating transac- tions following a template. These are usually dated in the future, eg to help with forecasting. They are activated by the --forecast option. o The balance command's --budget option uses these same periodic rules to generate goals for the budget report. o Auto posting rules can generate extra postings on certain matched transactions. They are always applied to forecast transactions; with the --auto flag they are applied to transactions recorded in the journal as well. o The --infer-equity flag infers missing conversion equity postings from @/@@ costs. And the inverse --infer-costs flag infers missing @/@@ costs from conversion equity postings. Generated data of this kind is temporary, existing only at report time. But you can see it in the output of hledger print, and you can save that to your journal, in effect converting it from temporary generated data to permanent recorded data. This could be useful as a data entry aid. If you are wondering what data is being generated and why, add the --verbose-tags flag. In hledger print output you will see extra tags like generated-transaction, generated-posting, and modified on gener- ated/modified data. Also, even without --verbose-tags, generated data always has equivalen hidden tags (with an underscore prefix), so eg you could match generated transactions with tag:_generated-transaction. Forecasting Forecasting, or speculative future reporting, can be useful for esti- mating future balances, or for exploring different future scenarios. The simplest and most flexible way to do it with hledger is to manually record a bunch of future-dated transactions. You could keep these in a separate future.journal and include that with -f only when you want to see them. --forecast There is another way: with the --forecast option, hledger can generate temporary "forecast transactions" for reporting purposes, according to periodic transaction rules defined in the journal. Each rule can gen- erate multiple recurring transactions, so by changing one rule you can change many forecasted transactions. Forecast transactions usually start after ordinary transactions end. By default, they begin after your latest-dated ordinary transaction, or today, whichever is later, and they end six months from today. (The exact rules are a little more complicated, and are given below.) This is the "forecast period", which need not be the same as the report period. You can override it - eg to forecast farther into the future, or to force forecast transactions to overlap your ordinary transactions - by giving the --forecast option a period expression argument, like --forecast=..2099 or --forecast=2023-02-15... Note that the = is re- quired. Inspecting forecast transactions print is the best command for inspecting and troubleshooting forecast transactions. Eg: ~ monthly from 2022-12-20 rent assets:bank:checking expenses:rent $1000 $ hledger print --forecast --today=2023/4/21 2023-05-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-06-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-07-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-08-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-09-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 Here there are no ordinary transactions, so the forecasted transactions begin on the first occurence after today's date. (You won't normally use --today; it's just to make these examples reproducible.) Forecast reports Forecast transactions affect all reports, as you would expect. Eg: $ hledger areg rent --forecast --today=2023/4/21 Transactions in expenses:rent and subaccounts: 2023-05-20 rent as:ba:checking $1000 $1000 2023-06-20 rent as:ba:checking $1000 $2000 2023-07-20 rent as:ba:checking $1000 $3000 2023-08-20 rent as:ba:checking $1000 $4000 2023-09-20 rent as:ba:checking $1000 $5000 $ hledger bal -M expenses --forecast --today=2023/4/21 Balance changes in 2023-05-01..2023-09-30: || May Jun Jul Aug Sep ===============++=================================== expenses:rent || $1000 $1000 $1000 $1000 $1000 ---------------++----------------------------------- || $1000 $1000 $1000 $1000 $1000 Forecast tags Forecast transactions generated by --forecast have a hidden tag, _gen- erated-transaction. So if you ever need to match forecast transac- tions, you could use tag:_generated-transaction (or just tag:generated) in a query. For troubleshooting, you can add the --verbose-tags flag. Then, visi- ble generated-transaction tags will be added also, so you can view them with the print command. Their value indicates which periodic rule was responsible. Forecast period, in detail Forecast start/end dates are chosen so as to do something useful by de- fault in almost all situations, while also being flexible. Here are (with luck) the exact rules, to help with troubleshooting: The forecast period starts on: o the later of o the start date in the periodic transaction rule o the start date in --forecast's argument o otherwise (if those are not available): the later of o the report start date specified with -b/-p/date: o the day after the latest ordinary transaction in the journal o otherwise (if none of these are available): today. The forecast period ends on: o the earlier of o the end date in the periodic transaction rule o the end date in --forecast's argument o otherwise: the report end date specified with -e/-p/date: o otherwise: 180 days (~6 months) from today. Forecast troubleshooting When --forecast is not doing what you expect, one of these tips should help: o Remember to use the --forecast option. o Remember to have at least one periodic transaction rule in your jour- nal. o Test with print --forecast. o Check for typos or too-restrictive start/end dates in your periodic transaction rule. o Leave at least 2 spaces between the rule's period expression and de- scription fields. o Check for future-dated ordinary transactions suppressing forecasted transactions. o Try setting explicit report start and/or end dates with -b, -e, -p or date: o Try adding the -E flag to encourage display of empty periods/zero transactions. o Try setting explicit forecast start and/or end dates with --fore- cast=START..END o Consult Forecast period, in detail, above. o Check inside the engine: add --debug=2 (eg). Budgeting With the balance command's --budget report, each periodic transaction rule generates recurring budget goals in specified accounts, and goals and actual performance can be compared. See the balance command's doc below. You can generate budget goals and forecast transactions at the same time, from the same or different periodic transaction rules: hledger bal -M --budget --forecast ... See also: Budgeting and Forecasting. Cost reporting In some transactions - for example a currency conversion, or a purchase or sale of stock - one commodity is exchanged for another. In these transactions there is a conversion rate, also called the cost (when buying) or selling price (when selling). In hledger docs we just say "cost", for convenience; feel free to mentally translate to "conversion rate" or "selling price" if helpful. Recording costs We'll explore several ways of recording transactions involving costs. These are also summarised at hledger Cookbook > Cost notation. Costs can be recorded explicitly in the journal, using the @ UNITCOST or @@ TOTALCOST notation described in Journal > Costs: Variant 1 2022-01-01 assets:dollars $-135 assets:euros 100 @ $1.35 ; $1.35 per euro (unit cost) Variant 2 2022-01-01 assets:dollars $-135 assets:euros 100 @@ $135 ; $135 total cost Typically, writing the unit cost (variant 1) is preferable; it can be more effort, requiring more attention to decimal digits; but it reveals the per-unit cost basis, and makes stock sales easier. Costs can also be left implicit, and hledger will infer the cost that is consistent with a balanced transaction: Variant 3 2022-01-01 assets:dollars $-135 assets:euros 100 Here, hledger will attach a @@ 100 cost to the first amount (you can see it with hledger print -x). This form looks convenient, but there are downsides: o It sacrifices some error checking. For example, if you accidentally wrote 10 instead of 100, hledger would not be able to detect the mis- take. o It is sensitive to the order of postings - if they were reversed, a different entry would be inferred and reports would be different. o The per-unit cost basis is not easy to read. So generally this kind of entry is not recommended. You can make sure you have none of these by using -s (strict mode), or by running hledger check balanced. Reporting at cost Now when you add the -B/--cost flag to reports ("B" is from Ledger's -B/--basis/--cost flag), any amounts which have been annotated with costs will be converted to their cost's commodity (in the report out- put). Ie they will be displayed "at cost" or "at sale price". Some things to note: o Costs are attached to specific posting amounts in specific transac- tions, and once recorded they do not change. This contrasts with market prices, which are ambient and fluctuating. o Conversion to cost is performed before conversion to market value (described below). Equity conversion postings There is a problem with the entries above - they are not conventional Double Entry Bookkeeping (DEB) notation, and because of the "magical" transformation of one commodity into another, they cause an imbalance in the Accounting Equation. This shows up as a non-zero grand total in balance reports like hledger bse. For most hledger users, this doesn't matter in practice and can safely be ignored ! But if you'd like to learn more, keep reading. Conventional DEB uses an extra pair of equity postings to balance the transaction. Of course you can do this in hledger as well: Variant 4 2022-01-01 assets:dollars $-135 assets:euros 100 equity:conversion $135 equity:conversion -100 Now the transaction is perfectly balanced according to standard DEB, and hledger bse's total will not be disrupted. And, hledger can still infer the cost for cost reporting, but it's not done by default - you must add the --infer-costs flag like so: $ hledger print --infer-costs 2022-01-01 one hundred euros purchased at $1.35 each assets:dollars $-135 @@ 100 assets:euros 100 equity:conversion $135 equity:conversion -100 $ hledger bal --infer-costs -B -100 assets:dollars 100 assets:euros -------------------- 0 Here are some downsides of this kind of entry: o The per-unit cost basis is not easy to read. o Instead of -B you must remember to type -B --infer-costs. o --infer-costs works only where hledger can identify the two eq- uity:conversion postings and match them up with the two non-equity postings. So writing the journal entry in a particular format be- comes more important. More on this below. Inferring equity conversion postings Can we go in the other direction ? Yes, if you have transactions writ- ten with the @/@@ cost notation, hledger can infer the missing equity postings, if you add the --infer-equity flag. Eg: 2022-01-01 assets:dollars -$135 assets:euros 100 @ $1.35 $ hledger print --infer-equity 2022-01-01 assets:dollars $-135 assets:euros 100 @ $1.35 equity:conversion:$-: -100 equity:conversion:$-:$ $135.00 The equity account names will be "equity:conversion:A-B:A" and "eq- uity:conversion:A-B:B" where A is the alphabetically first commodity symbol. You can customise the "equity:conversion" part by declaring an account with the V/Conversion account type. Combining costs and equity conversion postings Finally, you can use both the @/@@ cost notation and equity postings at the same time. This in theory gives the best of all worlds - preserv- ing the accounting equation, revealing the per-unit cost basis, and providing more flexibility in how you write the entry: Variant 5 2022-01-01 one hundred euros purchased at $1.35 each assets:dollars $-135 equity:conversion $135 equity:conversion -100 assets:euros 100 @ $1.35 All the other variants above can (usually) be rewritten to this final form with: $ hledger print -x --infer-costs --infer-equity Downsides: o This was added in hledger-1.29 and is still somewhat experimental. o The precise format of the journal entry becomes more important. If hledger can't detect and match up the cost and equity postings, it will give a transaction balancing error. o The add command does not yet accept this kind of entry (#2056). o This is the most verbose form. Requirements for detecting equity conversion postings --infer-costs has certain requirements (unlike --infer-equity, which always works). It will infer costs only in transactions with: o Two non-equity postings, in different commodities. Their order is significant: the cost will be added to the first of them. o Two postings to equity conversion accounts, next to one another, which balance the two non-equity postings. This balancing is checked to the same precision (number of decimal places) used in the conver- sion posting's amount. Equity conversion accounts are: o any accounts declared with account type V/Conversion, or their sub- accounts o otherwise, accounts named equity:conversion, equity:trade, or eq- uity:trading, or their subaccounts. And multiple such four-posting groups can coexist within a single transaction. When --infer-costs fails, it does not infer a cost in that transaction, and does not raise an error (ie, it infers costs where it can). Reading variant 5 journal entries, combining cost notation and equity postings, has all the same requirements. When reading such an entry fails, hledger raises an "unbalanced transaction" error. Infer cost and equity by default ? Should --infer-costs and --infer-equity be enabled by default ? Try using them always, eg with a shell alias: alias h="hledger --infer-equity --infer-costs" and let us know what problems you find. Value reporting Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), and/or to market value (using some market price on a certain date). This is controlled by the --value=TYPE[,COMMODITY] op- tion, which will be described below. We also provide the simpler -V and -X COMMODITY options, and often one of these is all you need: -V: Value The -V/--market flag converts amounts to market value in their default valuation commodity, using the market prices in effect on the valuation date(s), if any. More on these in a minute. -X: Value in specified commodity The -X/--exchange=COMM option is like -V, except you tell it which cur- rency you want to convert to, and it tries to convert everything to that. Valuation date Market prices can change from day to day. hledger will use the prices on a particular valuation date (or on more than one date). By default hledger uses "end" dates for valuation. More specifically: o For single period reports (including normal print and register re- ports): o If an explicit report end date is specified, that is used o Otherwise the latest transaction date or P directive date is used (even if it's in the future) o For multiperiod reports, each period is valued on its last day. This can be customised with the --value option described below, which can select either "then", "end", "now", or "custom" dates. (Note, this has a bug in hledger-ui <=1.31: turning on valuation with the V key al- ways resets it to "end".) Finding market price To convert a commodity A to its market value in another commodity B, hledger looks for a suitable market price (exchange rate) as follows, in this order of preference: 1. A declared market price or inferred market price: A's latest market price in B on or before the valuation date as declared by a P direc- tive, or (with the --infer-market-prices flag) inferred from costs. 2. A reverse market price: the inverse of a declared or inferred market price from B to A. 3. A forward chain of market prices: a synthetic price formed by com- bining the shortest chain of "forward" (only 1 above) market prices, leading from A to B. 4. Any chain of market prices: a chain of any market prices, including both forward and reverse prices (1 and 2 above), leading from A to B. There is a limit to the length of these price chains; if hledger reaches that length without finding a complete chain or exhausting all possibilities, it will give up (with a "gave up" message visible in --debug=2 output). That limit is currently 1000. Amounts for which no suitable market price can be found, are not con- verted. --infer-market-prices: market prices from transactions Normally, market value in hledger is fully controlled by, and requires, P directives in your journal. Since adding and updating those can be a chore, and since transactions usually take place at close to market value, why not use the recorded costs as additional market prices (as Ledger does) ? Adding the --infer-market-prices flag to -V, -X or --value enables this. So for example, hledger bs -V --infer-market-prices will get market prices both from P directives and from transactions. If both occur on the same day, the P directive takes precedence. There is a downside: value reports can sometimes be affected in confus- ing/undesired ways by your journal entries. If this happens to you, read all of this Value reporting section carefully, and try adding --debug or --debug=2 to troubleshoot. --infer-market-prices can infer market prices from: o multicommodity transactions with explicit prices (@/@@) o multicommodity transactions with implicit prices (no @, two commodi- ties, unbalanced). (With these, the order of postings matters. hledger print -x can be useful for troubleshooting.) o multicommodity transactions with equity postings, if cost is inferred with --infer-costs. There is a limitation (bug) currently: when a valuation commodity is not specified, prices inferred with --infer-market-prices do not help select a default valuation commodity, as P prices would. So conversion might not happen because no valuation commodity was detected (--debug=2 will show this). To be safe, specify the valuation commmodity, eg: o -X EUR --infer-market-prices, not -V --infer-market-prices o --value=then,EUR --infer-market-prices, not --value=then --infer-mar- ket-prices Signed costs and market prices can be confusing. For reference, here is the current behaviour, since hledger 1.25. (If you think it should work differently, see #1870.) 2022-01-01 Positive Unit prices a A 1 b B -1 @ A 1 2022-01-01 Positive Total prices a A 1 b B -1 @@ A 1 2022-01-02 Negative unit prices a A 1 b B 1 @ A -1 2022-01-02 Negative total prices a A 1 b B 1 @@ A -1 2022-01-03 Double Negative unit prices a A -1 b B -1 @ A -1 2022-01-03 Double Negative total prices a A -1 b B -1 @@ A -1 All of the transactions above are considered balanced (and on each day, the two transactions are considered equivalent). Here are the market prices inferred for B: $ hledger -f- --infer-market-prices prices P 2022-01-01 B A 1 P 2022-01-01 B A 1.0 P 2022-01-02 B A -1 P 2022-01-02 B A -1.0 P 2022-01-03 B A -1 P 2022-01-03 B A -1.0 Valuation commodity When you specify a valuation commodity (-X COMM or --value TYPE,COMM): hledger will convert all amounts to COMM, wherever it can find a suit- able market price (including by reversing or chaining prices). When you leave the valuation commodity unspecified (-V or --value TYPE): For each commodity A, hledger picks a default valuation commodity as follows, in this order of preference: 1. The price commodity from the latest P-declared market price for A on or before valuation date. 2. The price commodity from the latest P-declared market price for A on any date. (Allows conversion to proceed when there are inferred prices before the valuation date.) 3. If there are no P directives at all (any commodity or date) and the --infer-market-prices flag is used: the price commodity from the latest transaction-inferred price for A on or before valuation date. This means: o If you have P directives, they determine which commodities -V will convert, and to what. o If you have no P directives, and use the --infer-market-prices flag, costs determine it. Amounts for which no valuation commodity can be found are not con- verted. Simple valuation examples Here are some quick examples of -V: ; one euro is worth this many dollars from nov 1 P 2016/11/01 $1.10 ; purchase some euros on nov 3 2016/11/3 assets:euros 100 assets:checking ; the euro is worth fewer dollars by dec 21 P 2016/12/21 $1.03 How many euros do I have ? $ hledger -f t.j bal -N euros 100 assets:euros What are they worth at end of nov 3 ? $ hledger -f t.j bal -N euros -V -e 2016/11/4 $110.00 assets:euros What are they worth after 2016/12/21 ? (no report end date specified, defaults to today) $ hledger -f t.j bal -N euros -V $103.00 assets:euros --value: Flexible valuation -V and -X are special cases of the more general --value option: --value=TYPE[,COMM] TYPE is then, end, now or YYYY-MM-DD. COMM is an optional commodity symbol. Shows amounts converted to: - default valuation commodity (or COMM) using market prices at posting dates - default valuation commodity (or COMM) using market prices at period end(s) - default valuation commodity (or COMM) using current market prices - default valuation commodity (or COMM) using market prices at some date The TYPE part selects cost or value and valuation date: --value=then Convert amounts to their value in the default valuation commod- ity, using market prices on each posting's date. --value=end Convert amounts to their value in the default valuation commod- ity, using market prices on the last day of the report period (or if unspecified, the journal's end date); or in multiperiod reports, market prices on the last day of each subperiod. --value=now Convert amounts to their value in the default valuation commod- ity using current market prices (as of when report is gener- ated). --value=YYYY-MM-DD Convert amounts to their value in the default valuation commod- ity using market prices on this date. To select a different valuation commodity, add the optional ,COMM part: a comma, then the target commodity's symbol. Eg: --value=now,EUR. hledger will do its best to convert amounts to this commodity, deducing market prices as described above. More valuation examples Here are some examples showing the effect of --value, as seen with print: P 2000-01-01 A 1 B P 2000-02-01 A 2 B P 2000-03-01 A 3 B P 2000-04-01 A 4 B 2000-01-01 (a) 1 A @ 5 B 2000-02-01 (a) 1 A @ 6 B 2000-03-01 (a) 1 A @ 7 B Show the cost of each posting: $ hledger -f- print --cost 2000-01-01 (a) 5 B 2000-02-01 (a) 6 B 2000-03-01 (a) 7 B Show the value as of the last day of the report period (2000-02-29): $ hledger -f- print --value=end date:2000/01-2000/03 2000-01-01 (a) 2 B 2000-02-01 (a) 2 B With no report period specified, that shows the value as of the last day of the journal (2000-03-01): $ hledger -f- print --value=end 2000-01-01 (a) 3 B 2000-02-01 (a) 3 B 2000-03-01 (a) 3 B Show the current value (the 2000-04-01 price is still in effect today): $ hledger -f- print --value=now 2000-01-01 (a) 4 B 2000-02-01 (a) 4 B 2000-03-01 (a) 4 B Show the value on 2000/01/15: $ hledger -f- print --value=2000-01-15 2000-01-01 (a) 1 B 2000-02-01 (a) 1 B 2000-03-01 (a) 1 B Interaction of valuation and queries When matching postings based on queries in the presence of valuation, the following happens. 1. The query is separated into two parts: 1. the currency (cur:) or amount (amt:). 2. all other parts. 2. The postings are matched to the currency and amount queries based on pre-valued amounts. 3. Valuation is applied to the postings. 4. The postings are matched to the other parts of the query based on post-valued amounts. See: 1625 Effect of valuation on reports Here is a reference for how valuation is supposed to affect each part of hledger's reports (and a glossary). (It's wide, you'll have to scroll sideways.) It may be useful when troubleshooting. If you find problems, please report them, ideally with a reproducible example. Re- lated: #329, #1083. Report -B, --cost -V, -X --value=then --value=end --value=DATE, type --value=now -------------------------------------------------------------------------------------------- print posting cost value at re- value at posting value at re- value at amounts port end or date port or DATE/today today journal end balance unchanged unchanged unchanged unchanged unchanged asser- tions/as- signments register starting cost value at re- valued at day value at re- value at balance port or each historical port or DATE/today (-H) journal end posting was made journal end starting cost value at day valued at day value at day value at balance before re- each historical before re- DATE/today (-H) with port or posting was made port or report journal journal interval start start posting cost value at re- value at posting value at re- value at amounts port or date port or DATE/today journal end journal end summary summarised value at pe- sum of postings value at pe- value at posting cost riod ends in interval, val- riod ends DATE/today amounts ued at interval with re- start port in- terval running sum/average sum/average sum/average of sum/average sum/average total/av- of displayed of displayed displayed values of displayed of displayed erage values values values values balance (bs, bse, cf, is) balance sums of value at re- value at posting value at re- value at changes costs port end or date port or DATE/today of today of journal end sums of post- sums of of sums of ings postings postings budget like balance like balance like balance like bal- like balance amounts changes changes changes ances changes (--bud- get) grand to- sum of dis- sum of dis- sum of displayed sum of dis- sum of dis- tal played val- played val- valued played val- played values ues ues ues balance (bs, bse, cf, is) with re- port in- terval starting sums of value at re- sums of values of value at re- sums of post- balances costs of port start postings before port start ings before (-H) postings be- of sums of report start at of sums of report start fore report all postings respective post- all postings start before re- ing dates before re- port start port start balance sums of same as sums of values of balance value at changes costs of --value=end postings in pe- change in DATE/today of (bal, is, postings in riod at respec- each period, sums of post- bs period tive posting valued at ings --change, dates period ends cf --change) end bal- sums of same as sums of values of period end value at ances costs of --value=end postings from be- balances, DATE/today of (bal -H, postings fore period start valued at sums of post- is --H, from before to period end at period ends ings bs, cf) report start respective post- to period ing dates end budget like balance like balance like balance like bal- like balance amounts changes/end changes/end changes/end bal- ances changes/end (--bud- balances balances ances balances get) row to- sums, aver- sums, aver- sums, averages of sums, aver- sums, aver- tals, row ages of dis- ages of dis- displayed values ages of dis- ages of dis- averages played val- played val- played val- played values (-T, -A) ues ues ues column sums of dis- sums of dis- sums of displayed sums of dis- sums of dis- totals played val- played val- values played val- played values ues ues ues grand to- sum, average sum, average sum, average of sum, average sum, average tal, of column of column column totals of column of column to- grand av- totals totals totals tals erage --cumulative is omitted to save space, it works like -H but with a zero starting balance. Glossary: cost calculated using price(s) recorded in the transaction(s). value market value using available market price declarations, or the unchanged amount if no conversion rate can be found. report start the first day of the report period specified with -b or -p or date:, otherwise today. report or journal start the first day of the report period specified with -b or -p or date:, otherwise the earliest transaction date in the journal, otherwise today. report end the last day of the report period specified with -e or -p or date:, otherwise today. report or journal end the last day of the report period specified with -e or -p or date:, otherwise the latest transaction date in the journal, otherwise today. report interval a flag (-D/-W/-M/-Q/-Y) or period expression that activates the report's multi-period mode (whether showing one or many subperi- ods). PART 4: COMMANDS Commands overview Here are the built-in commands: DATA ENTRY These data entry commands are the only ones which can modify your jour- nal file. o add - add transactions using terminal prompts o import - add new transactions from other files, eg CSV files DATA CREATION o close - generate balance-zeroing/restoring transactions o rewrite - generate auto postings, like print --auto DATA MANAGEMENT o check - check for various kinds of error in the data o diff - compare account transactions in two journal files REPORTS, FINANCIAL o aregister (areg) - show transactions in a particular account o balancesheet (bs) - show assets, liabilities and net worth o balancesheetequity (bse) - show assets, liabilities and equity o cashflow (cf) - show changes in liquid assets o incomestatement (is) - show revenues and expenses REPORTS, VERSATILE o balance (bal) - show balance changes, end balances, budgets, gains.. o print - show transactions or export journal data o register (reg) - show postings in one or more accounts & running to- tal o roi - show return on investments REPORTS, BASIC o accounts - show account names o activity - show bar charts of posting counts per period o codes - show transaction codes o commodities - show commodity/currency symbols o descriptions - show transaction descriptions o files - show input file paths o notes - show note parts of transaction descriptions o payees - show payee parts of transaction descriptions o prices - show market prices o stats - show journal statistics o tags - show tag names o test - run self tests HELP o help - show the hledger manual with info/man/pager o demo - show small hledger demos in the terminal ADD-ONS And here are some typical add-on commands. Some of these are installed by the hledger-install script. If installed, they will appear in hledger's commands list: o ui - run hledger's terminal UI o web - run hledger's web UI o iadd - add transactions using a TUI (currently hard to build) o interest - generate interest transactions o stockquotes - download market prices from AlphaVantage o Scripts and add-ons - check-fancyassertions, edit, fifo, git, move, pijul, plot, and more.. Next, each command is described in detail, in alphabetical order. accounts Show account names. This command lists account names. By default it shows all known ac- counts, either used in transactions or declared with account direc- tives. With query arguments, only matched account names and account names ref- erenced by matched postings are shown. Or it can show just the used accounts (--used/-u), the declared ac- counts (--declared/-d), the accounts declared but not used (--unused), the accounts used but not declared (--undeclared), or the first account matched by an account name pattern, if any (--find). It shows a flat list by default. With --tree, it uses indentation to show the account hierarchy. In flat mode you can add --drop N to omit the first few account name components. Account names can be depth-clipped with depth:N or --depth N or -N. With --types, it also shows each account's type, if it's known. (See Declaring accounts > Account types.) With --positions, it also shows the file and line number of each ac- count's declaration, if any, and the account's overall declaration or- der; these may be useful when troubleshooting account display order. With --directives, it adds the account keyword, showing valid account directives which can be pasted into a journal file. This is useful to- gether with --undeclared when updating your account declarations to satisfy hledger check accounts. The --find flag can be used to look up a single account name, in the same way that the aregister command does. It returns the alphanumeri- cally-first matched account name, or if none can be found, it fails with a non-zero exit code. Examples: $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts $ hledger accounts --undeclared --directives >> $LEDGER_FILE $ hledger check accounts activity Show an ascii barchart of posting counts per interval. The activity command displays an ascii histogram showing transaction counts by day, week, month or other reporting interval (by day is the default). With query arguments, it counts only matched transactions. Examples: $ hledger activity --quarterly 2008-01-01 ** 2008-04-01 ******* 2008-07-01 2008-10-01 ** add Prompt for transactions and add them to the journal. Any arguments will be used as default inputs for the first N prompts. Many hledger users edit their journals directly with a text editor, or generate them from CSV. For more interactive data entry, there is the add command, which prompts interactively on the console for new trans- actions, and appends them to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also import). To use it, just run hledger add and follow the prompts. You can add as many transactions as you like; when you are finished, enter . or press control-d or control-c to exit. Features: o add tries to provide useful defaults, using the most similar (by de- scription) recent transaction (filtered by the query, if any) as a template. o You can also set the initial defaults with command line arguments. o Readline-style edit keys can be used during data entry. o The tab key will auto-complete whenever possible - accounts, pay- ees/descriptions, dates (yesterday, today, tomorrow). If the input area is empty, it will insert the default value. o If the journal defines a default commodity, it will be added to any bare numbers entered. o A parenthesised transaction code may be entered following a date. o Comments and tags may be entered following a description or amount. o If you make a mistake, enter < at any prompt to go one step backward. o Input prompts are displayed in a different colour when the terminal supports it. Example (see https://hledger.org/add.html for a detailed tutorial): $ hledger add Adding transactions to journal file /src/hledger/examples/sample.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control-d or control-c. Date [2015/05/22]: Description: supermarket Account 1: expenses:food Amount 1: $10 Account 2: assets:checking Amount 2 [$-10.0]: Account 3 (or . or enter to finish this transaction): . 2015/05/22 supermarket expenses:food $10 assets:checking $-10.0 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl-D/ctrl-C to quit) Date [2015/05/22]: $ On Microsoft Windows, the add command makes sure that no part of the file path ends with a period, as that would cause problems (#1056). aregister (areg) Show the transactions and running historical balance of a single ac- count, with each transaction displayed as one line. aregister shows the overall transactions affecting a particular account (and any subaccounts). Each report line represents one transaction in this account. Transactions before the report start date are always in- cluded in the running balance (--historical mode is always on). This is a more "real world", bank-like view than the register command (which shows individual postings, possibly from multiple accounts, not necessarily in historical mode). As a quick rule of thumb: - use areg- ister for reviewing and reconciling real-world asset/liability accounts - use register for reviewing detailed revenues/expenses. aregister requires one argument: the account to report on. You can write either the full account name, or a case-insensitive regular ex- pression which will select the alphabetically first matched account. When there are multiple matches, the alphabetically-first choice can be surprising; eg if you have assets:per:checking 1 and assets:biz:check- ing 2 accounts, hledger areg checking would select assets:biz:checking 2. It's just a convenience to save typing, so if in doubt, write the full account name, or a distinctive substring that matches uniquely. Transactions involving subaccounts of this account will also be shown. aregister ignores depth limits, so its final total will always match a balance report with similar arguments. Any additional arguments form a query which will filter the transac- tions shown. Note some queries will disturb the running balance, caus- ing it to be different from the account's real-world running balance. An example: this shows the transactions and historical running balance during july, in the first account whose name contains "checking": $ hledger areg checking date:jul Each aregister line item shows: o the transaction's date (or the relevant posting's date if different, see below) o the names of all the other account(s) involved in this transaction (probably abbreviated) o the total change to this account's balance from this transaction o the account's historical running balance after this transaction. Transactions making a net change of zero are not shown by default; add the -E/--empty flag to show them. For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the --align-all flag. This command also supports the output destination and output format op- tions. The output formats supported are txt, csv, tsv, and json. aregister and posting dates aregister always shows one line (and date and amount) per transaction. But sometimes transactions have postings with different dates. Also, not all of a transaction's postings may be within the report period. To resolve this, aregister shows the earliest of the transaction's date and posting dates that is in-period, and the sum of the in-period post- ings. In other words it will show a combined line item with just the earliest date, and the running balance will (temporarily, until the transaction's last posting) be inaccurate. Use register -H if you need to see the individual postings. There is also a --txn-dates flag, which filters strictly by transaction date, ignoring posting dates. This too can cause an inaccurate running balance. balance (bal) Show accounts and their balances. balance is one of hledger's oldest and most versatile commands, for listing account balances, balance changes, values, value changes and more, during one time period or many. Generally it shows a table, with rows representing accounts, and columns representing periods. Note there are some higher-level variants of the balance command with convenient defaults, which can be simpler to use: balancesheet, bal- ancesheetequity, cashflow and incomestatement. When you need more con- trol, then use balance. balance features Here's a quick overview of the balance command's features, followed by more detailed descriptions and examples. Many of these work with the higher-level commands as well. balance can show.. o accounts as a list (-l) or a tree (-t) o optionally depth-limited (-[1-9]) o sorted by declaration order and name, or by amount ..and their.. o balance changes (the default) o or actual and planned balance changes (--budget) o or value of balance changes (-V) o or change of balance values (--valuechange) o or unrealised capital gain/loss (--gain) o or postings count (--count) ..in.. o one time period (the whole journal period by default) o or multiple periods (-D, -W, -M, -Q, -Y, -p INTERVAL) ..either.. o per period (the default) o or accumulated since report start date (--cumulative) o or accumulated since account creation (--historical/-H) ..possibly converted to.. o cost (--value=cost[,COMM]/--cost/-B) o or market value, as of transaction dates (--value=then[,COMM]) o or at period ends (--value=end[,COMM]) o or now (--value=now) o or at some other date (--value=YYYY-MM-DD) ..with.. o totals (-T), averages (-A), percentages (-%), inverted sign (--in- vert) o rows and columns swapped (--transpose) o another field used as account name (--pivot) o custom-formatted line items (single-period reports only) (--format) o commodities displayed on the same line or multiple lines (--layout) This command supports the output destination and output format options, with output formats txt, csv, tsv, json, and (multi-period reports only:) html. In txt output in a colour-supporting terminal, negative amounts are shown in red. The --related/-r flag shows the balance of the other postings in the transactions of the postings which would normally be shown. Simple balance report With no arguments, balance shows a list of all accounts and their change of balance - ie, the sum of posting amounts, both inflows and outflows - during the entire period of the journal. ("Simple" here means just one column of numbers, covering a single period. You can also have multi-period reports, described later.) For real-world accounts, these numbers will normally be their end bal- ance at the end of the journal period; more on this below. Accounts are sorted by declaration order if any, and then alphabeti- cally by account name. For instance (using examples/sample.journal): $ hledger -f examples/sample.journal bal $1 assets:bank:saving $-2 assets:cash $1 expenses:food $1 expenses:supplies $-1 income:gifts $-1 income:salary $1 liabilities:debts -------------------- 0 Accounts with a zero balance (and no non-zero subaccounts, in tree mode - see below) are hidden by default. Use -E/--empty to show them (re- vealing assets:bank:checking here): $ hledger -f examples/sample.journal bal -E 0 assets:bank:checking $1 assets:bank:saving $-2 assets:cash $1 expenses:food $1 expenses:supplies $-1 income:gifts $-1 income:salary $1 liabilities:debts -------------------- 0 The total of the amounts displayed is shown as the last line, unless -N/--no-total is used. Balance report line format For single-period balance reports displayed in the terminal (only), you can use --format FMT to customise the format and content of each line. Eg: $ hledger -f examples/sample.journal balance --format "%20(account) %12(total)" assets $-1 bank:saving $1 cash $-2 expenses $2 food $1 supplies $1 income $-2 gifts $-1 salary $-1 liabilities:debts $1 --------------------------------- 0 The FMT format string specifies the formatting applied to each ac- count/balance pair. It may contain any suitable text, with data fields interpolated like so: %[MIN][.MAX](FIELDNAME) o MIN pads with spaces to at least this width (optional) o MAX truncates at this width (optional) o FIELDNAME must be enclosed in parentheses, and can be one of: o depth_spacer - a number of spaces equal to the account's depth, or if MIN is specified, MIN * depth spaces. o account - the account's name o total - the account's balance/posted total, right justified Also, FMT can begin with an optional prefix to control how multi-com- modity amounts are rendered: o %_ - render on multiple lines, bottom-aligned (the default) o %^ - render on multiple lines, top-aligned o %, - render on one line, comma-separated There are some quirks. Eg in one-line mode, %(depth_spacer) has no ef- fect, instead %(account) has indentation built in. Experimentation may be needed to get pleasing results. Some example formats: o %(total) - the account's total o %-20.20(account) - the account's name, left justified, padded to 20 characters and clipped at 20 characters o %,%-50(account) %25(total) - account name padded to 50 characters, total padded to 20 characters, with multiple commodities rendered on one line o %20(total) %2(depth_spacer)%-(account) - the default format for the single-column balance report Filtered balance report You can show fewer accounts, a different time period, totals from cleared transactions only, etc. by using query arguments or options to limit the postings being matched. Eg: $ hledger -f examples/sample.journal bal --cleared assets date:200806 $-2 assets:cash -------------------- $-2 List or tree mode By default, or with -l/--flat, accounts are shown as a flat list with their full names visible, as in the examples above. With -t/--tree, the account hierarchy is shown, with subaccounts' "leaf" names indented below their parent: $ hledger -f examples/sample.journal balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 Notes: o "Boring" accounts are combined with their subaccount for more compact output, unless --no-elide is used. Boring accounts have no balance of their own and just one subaccount (eg assets:bank and liabilities above). o All balances shown are "inclusive", ie including the balances from all subaccounts. Note this means some repetition in the output, which requires explanation when sharing reports with non-plaintextac- counting-users. A tree mode report's final total is the sum of the top-level balances shown, not of all the balances shown. o Each group of sibling accounts (ie, under a common parent) is sorted separately. Depth limiting With a depth:NUM query, or --depth NUM option, or just -NUM (eg: -3) balance reports will show accounts only to the specified depth, hiding the deeper subaccounts. This can be useful for getting an overview without too much detail. Account balances at the depth limit always include the balances from any deeper subaccounts (even in list mode). Eg, limiting to depth 1: $ hledger -f examples/sample.journal balance -1 $-1 assets $2 expenses $-2 income $1 liabilities -------------------- 0 Dropping top-level accounts You can also hide one or more top-level account name parts, using --drop NUM. This can be useful for hiding repetitive top-level account names: $ hledger -f examples/sample.journal bal expenses --drop 1 $1 food $1 supplies -------------------- $2 Showing declared accounts With --declared, accounts which have been declared with an account di- rective will be included in the balance report, even if they have no transactions. (Since they will have a zero balance, you will also need -E/--empty to see them.) More precisely, leaf declared accounts (with no subaccounts) will be included, since those are usually the more useful in reports. The idea of this is to be able to see a useful "complete" balance re- port, even when you don't have transactions in all of your declared ac- counts yet. Sorting by amount With -S/--sort-amount, accounts with the largest (most positive) bal- ances are shown first. Eg: hledger bal expenses -MAS shows your biggest averaged monthly expenses first. When more than one commodity is present, they will be sorted by the alphabetically earliest commod- ity first, and then by subsequent commodities (if an amount is missing a commodity, it is treated as 0). Revenues and liability balances are typically negative, however, so -S shows these in reverse order. To work around this, you can add --in- vert to flip the signs. (Or, use one of the higher-level reports, which flip the sign automatically. Eg: hledger incomestatement -MAS). Percentages With -%/--percent, balance reports show each account's value expressed as a percentage of the (column) total. Note it is not useful to calculate percentages if the amounts in a col- umn have mixed signs. In this case, make a separate report for each sign, eg: $ hledger bal -% amt:`>0` $ hledger bal -% amt:`<0` Similarly, if the amounts in a column have mixed commodities, convert them to one commodity with -B, -V, -X or --value, or make a separate report for each commodity: $ hledger bal -% cur:\\$ $ hledger bal -% cur: Multi-period balance report With a report interval (set by the -D/--daily, -W/--weekly, -M/--monthly, -Q/--quarterly, -Y/--yearly, or -p/--period flag), bal- ance shows a tabular report, with columns representing successive time periods (and a title): $ hledger -f examples/sample.journal bal --quarterly income expenses -E Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 ===================++================================= expenses:food || 0 $1 0 0 expenses:supplies || 0 $1 0 0 income:gifts || 0 $-1 0 0 income:salary || $-1 0 0 0 -------------------++--------------------------------- || $-1 $1 0 0 Notes: o The report's start/end dates will be expanded, if necessary, to fully encompass the displayed subperiods (so that the first and last subpe- riods have the same duration as the others). o Leading and trailing periods (columns) containing all zeroes are not shown, unless -E/--empty is used. o Accounts (rows) containing all zeroes are not shown, unless -E/--empty is used. o Amounts with many commodities are shown in abbreviated form, unless --no-elide is used. (experimental) o Average and/or total columns can be added with the -A/--average and -T/--row-total flags. o The --transpose flag can be used to exchange rows and columns. o The --pivot FIELD option causes a different transaction field to be used as "account name". See PIVOTING. Multi-period reports with many periods can be too wide for easy viewing in the terminal. Here are some ways to handle that: o Hide the totals row with -N/--no-total o Convert to a single currency with -V o Maximize the terminal window o Reduce the terminal's font size o View with a pager like less, eg: hledger bal -D --color=yes | less -RS o Output as CSV and use a CSV viewer like visidata (hledger bal -D -O csv | vd -f csv), Emacs' csv-mode (M-x csv-mode, C-c C-a), or a spreadsheet (hledger bal -D -o a.csv && open a.csv) o Output as HTML and view with a browser: hledger bal -D -o a.html && open a.html Balance change, end balance It's important to be clear on the meaning of the numbers shown in bal- ance reports. Here is some terminology we use: A balance change is the net amount added to, or removed from, an ac- count during some period. An end balance is the amount accumulated in an account as of some date (and some time, but hledger doesn't store that; assume end of day in your timezone). It is the sum of previous balance changes. We call it a historical end balance if it includes all balance changes since the account was created. For a real world account, this means it will match the "historical record", eg the balances reported in your bank statements or bank web UI. (If they are correct!) In general, balance changes are what you want to see when reviewing revenues and expenses, and historical end balances are what you want to see when reviewing or reconciling asset, liability and equity accounts. balance shows balance changes by default. To see accurate historical end balances: 1. Initialise account starting balances with an "opening balances" transaction (a transfer from equity to the account), unless the journal covers the account's full lifetime. 2. Include all of of the account's prior postings in the report, by not specifying a report start date, or by using the -H/--historical flag. (-H causes report start date to be ignored when summing post- ings.) Balance report types The balance command is quite flexible; here is the full detail on how to control what it reports. If the following seems complicated, don't worry - this is for advanced reporting, and it does take time and ex- perimentation to get familiar with all the report modes. There are three important option groups: hledger balance [CALCULATIONTYPE] [ACCUMULATIONTYPE] [VALUATIONTYPE] ... Calculation type The basic calculation to perform for each table cell. It is one of: o --sum : sum the posting amounts (default) o --budget : sum the amounts, but also show the budget goal amount (for each account/period) o --valuechange : show the change in period-end historical balance val- ues (caused by deposits, withdrawals, and/or market price fluctua- tions) o --gain : show the unrealised capital gain/loss, (the current valued balance minus each amount's original cost) o --count : show the count of postings Accumulation type How amounts should accumulate across report periods. Another way to say it: which time period's postings should contribute to each cell's calculation. It is one of: o --change : calculate with postings from column start to column end, ie "just this column". Typically used to see revenues/expenses. (default for balance, incomestatement) o --cumulative : calculate with postings from report start to column end, ie "previous columns plus this column". Typically used to show changes accumulated since the report's start date. Not often used. o --historical/-H : calculate with postings from journal start to col- umn end, ie "all postings from before report start date until this column's end". Typically used to see historical end balances of as- sets/liabilities/equity. (default for balancesheet, balancesheete- quity, cashflow) Valuation type Which kind of value or cost conversion should be applied, if any, be- fore displaying the report. It is one of: o no valuation type : don't convert to cost or value (default) o --value=cost[,COMM] : convert amounts to cost (then optionally to some other commodity) o --value=then[,COMM] : convert amounts to market value on transaction dates o --value=end[,COMM] : convert amounts to market value on period end date(s) (default with --valuechange, --gain) o --value=now[,COMM] : convert amounts to market value on today's date o --value=YYYY-MM-DD[,COMM] : convert amounts to market value on an- other date or one of the equivalent simpler flags: o -B/--cost : like --value=cost (though, note --cost and --value are independent options which can both be used at once) o -V/--market : like --value=end o -X COMM/--exchange COMM : like --value=end,COMM See Cost reporting and Value reporting for more about these. Combining balance report types Most combinations of these options should produce reasonable reports, but if you find any that seem wrong or misleading, let us know. The following restrictions are applied: o --valuechange implies --value=end o --valuechange makes --change the default when used with the bal- ancesheet/balancesheetequity commands o --cumulative or --historical disables --row-total/-T For reference, here is what the combinations of accumulation and valua- tion show: Valua- no valuation --value= then --value= end --value= tion:> YYYY-MM-DD Accumu- /now lation:v ----------------------------------------------------------------------------------- --change change in period sum of post- period-end DATE-value of ing-date market value of change change in pe- values in period in period riod --cumu- change from re- sum of post- period-end DATE-value of lative port start to ing-date market value of change change from period end values from re- from report report start port start to pe- start to period to period end riod end end --his- change from sum of post- period-end DATE-value of torical journal start to ing-date market value of change change from /-H period end (his- values from jour- from journal journal start torical end bal- nal start to pe- start to period to period end ance) riod end end Budget report The --budget report type is like a regular balance report, but with two main differences: o Budget goals and performance percentages are also shown, in brackets o Accounts which don't have budget goals are hidden by default. This is useful for comparing planned and actual income, expenses, time usage, etc. Periodic transaction rules are used to define budget goals. For exam- ple, here's a periodic rule defining monthly goals for bus travel and food expenses: ;; Budget ~ monthly (expenses:bus) $30 (expenses:food) $400 After recording some actual expenses, ;; Two months worth of expenses 2017-11-01 income $-1950 expenses:bus $35 expenses:food:groceries $310 expenses:food:dining $42 expenses:movies $38 assets:bank:checking 2017-12-01 income $-2100 expenses:bus $53 expenses:food:groceries $380 expenses:food:dining $32 expenses:gifts $100 assets:bank:checking we can see a budget report like this: $ hledger bal -M --budget Budget performance in 2017-11-01..2017-12-31: || Nov Dec ===============++============================================ || $-425 $-565 expenses || $425 [ 99% of $430] $565 [131% of $430] expenses:bus || $35 [117% of $30] $53 [177% of $30] expenses:food || $352 [ 88% of $400] $412 [103% of $400] ---------------++-------------------------------------------- || 0 [ 0% of $430] 0 [ 0% of $430] This is "goal-based budgeting"; you define goals for accounts and peri- ods, often recurring, and hledger shows performance relative to the goals. This contrasts with "envelope budgeting", which is more de- tailed and strict - useful when cash is tight, but also quite a bit more work. https://plaintextaccounting.org/Budgeting has more on this topic. Using the budget report Historically this report has been confusing and fragile. hledger's version should be relatively robust and intuitive, but you may still find surprises. Here are more notes to help with learning and trou- bleshooting. o In the above example, expenses:bus and expenses:food are shown be- cause they have budget goals during the report period. o Their parent expenses is also shown, with budget goals aggregated from the children. o The subaccounts expenses:food:groceries and expenses:food:dining are not shown since they have no budget goal of their own, but they con- tribute to expenses:food's actual amount. o Unbudgeted accounts expenses:movies and expenses:gifts are also not shown, but they contribute to expenses's actual amount. o The other unbudgeted accounts income and assets:bank:checking are grouped as . o --depth or depth: can be used to limit report depth in the usual way (but will not reveal unbudgeted subaccounts). o Amounts are always inclusive of subaccounts (even in -l/--list mode). o Numbers displayed in a --budget report will not always agree with the totals, because of hidden unbudgeted accounts; this is normal. -E/--empty can be used to reveal the hidden accounts. o In the periodic rules used for setting budget goals, unbalanced post- ings are convenient. o You can filter budget reports with the usual queries, eg to focus on particular accounts. It's common to restrict them to just expenses. (The account is occasionally hard to exclude; this is because of date surprises, discussed below.) o When you have multiple currencies, you may want to convert them to one (-X COMM --infer-market-prices) and/or show just one at a time (cur:COMM). If you do need to show multiple currencies at once, --layout bare can be helpful. o You can "roll over" amounts (actual and budgeted) to the next period with --cumulative. See also: https://hledger.org/budgeting.html. Budget date surprises With small data, or when starting out, some of the generated budget goal transaction dates might fall outside the report periods. Eg with the following journal and report, the first period appears to have no expenses:food budget. (Also the account should be ex- cluded by the expenses query, but isn't.): ~ monthly in 2020 (expenses:food) $500 2020-01-15 expenses:food $400 assets:checking $ hledger bal --budget expenses Budget performance in 2020-01-15: || 2020-01-15 ===============++==================== || $400 expenses:food || 0 [ 0% of $500] ---------------++-------------------- || $400 [80% of $500] In this case, the budget goal transactions are generated on first days of of month (this can be seen with hledger print --forecast tag:gener- ated expenses). Whereas the report period defaults to just the 15th day of january (this can be seen from the report table's column head- ings). To fix this kind of thing, be more explicit about the report period (and/or the periodic rules' dates). In this case, adding -b 2020 does the trick. Selecting budget goals By default, the budget report uses all available periodic transaction rules to generate goals. This includes rules with a different report interval from your report. Eg if you have daily, weekly and monthly periodic rules, all of these will contribute to the goals in a monthly budget report. You can select a subset of periodic rules by providing an argument to the --budget flag. --budget=DESCPAT will match all periodic rules whose description contains DESCPAT, a case-insensitive substring (not a regular expression or query). This means you can give your periodic rules descriptions (remember that two spaces are needed between period expression and description), and then select from multiple budgets de- fined in your journal. Budgeting vs forecasting --budget and --forecast both use the periodic transaction rules in the journal to generate temporary transactions for reporting purposes. However they are separate features - though you can use both at the same time if you want. Here are some differences between them: 1. --budget is a command-specific option; it selects the budget report. --forecast is a general option; forecasting works with all reports. 2. --budget uses all periodic rules; --budget=DESCPAT uses just the rules matched by DESCPAT. --forecast uses all periodic rules. 3. --budget's budget goal transactions are invisible, except that they produce goal amounts. --forecast's forecast transactions are visible, and appear in re- ports. 4. --budget generates budget goal transactions throughout the report period, optionally restricted by periods specified in the periodic transaction rules. --forecast generates forecast transactions from after the last reg- ular transaction, to the end of the report period; while --fore- cast=PERIODEXPR generates them throughout the specified period; both optionally restricted by periods specified in the periodic transaction rules. Balance report layout The --layout option affects how balance reports show multi-commodity amounts and commodity symbols, which can improve readability. It can also normalise the data for easy consumption by other programs. It has four possible values: o --layout=wide[,WIDTH]: commodities are shown on a single line, op- tionally elided to WIDTH o --layout=tall: each commodity is shown on a separate line o --layout=bare: commodity symbols are in their own column, amounts are bare numbers o --layout=tidy: data is normalised to easily-consumed "tidy" form, with one row per data value Here are the --layout modes supported by each output format; note only CSV output supports all of them: - txt csv html json sql ------------------------------------- wide Y Y Y tall Y Y Y bare Y Y Y tidy Y Examples: o Wide layout. With many commodities, reports can be very wide: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=wide Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++==================================================================================================================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, -98.12 USD, 10.00 VEA, 18.00 VHT -11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT ------------------++-------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------- || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, -98.12 USD, 10.00 VEA, 18.00 VHT -11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT o Limited wide layout. A width limit reduces the width, but some com- modities will be hidden: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=wide,32 Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++=========================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. -11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. ------------------++--------------------------------------------------------------------------------------------------------------------------- || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. -11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. o Tall layout. Each commodity gets a new line (may be different in each column), and account names are repeated: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=tall Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++================================================== Assets:US:ETrade || 10.00 ITOT 70.00 GLD -11.00 ITOT 70.00 GLD Assets:US:ETrade || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT Assets:US:ETrade || 12.00 VEA -98.12 USD 14.00 VEA 5120.50 USD Assets:US:ETrade || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA Assets:US:ETrade || 18.00 VHT 294.00 VHT ------------------++-------------------------------------------------- || 10.00 ITOT 70.00 GLD -11.00 ITOT 70.00 GLD || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT || 12.00 VEA -98.12 USD 14.00 VEA 5120.50 USD || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA || 18.00 VHT 294.00 VHT o Bare layout. Commodity symbols are kept in one column, each commod- ity gets its own report row, account names are repeated: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=bare Balance changes in 2012-01-01..2014-12-31: || Commodity 2012 2013 2014 Total ==================++============================================= Assets:US:ETrade || GLD 0 70.00 0 70.00 Assets:US:ETrade || ITOT 10.00 18.00 -11.00 17.00 Assets:US:ETrade || USD 337.18 -98.12 4881.44 5120.50 Assets:US:ETrade || VEA 12.00 10.00 14.00 36.00 Assets:US:ETrade || VHT 106.00 18.00 170.00 294.00 ------------------++--------------------------------------------- || GLD 0 70.00 0 70.00 || ITOT 10.00 18.00 -11.00 17.00 || USD 337.18 -98.12 4881.44 5120.50 || VEA 12.00 10.00 14.00 36.00 || VHT 106.00 18.00 170.00 294.00 o Bare layout also affects CSV output, which is useful for producing data that is easier to consume, eg for making charts: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -O csv --layout=bare "account","commodity","balance" "Assets:US:ETrade","GLD","70.00" "Assets:US:ETrade","ITOT","17.00" "Assets:US:ETrade","USD","5120.50" "Assets:US:ETrade","VEA","36.00" "Assets:US:ETrade","VHT","294.00" "total","GLD","70.00" "total","ITOT","17.00" "total","USD","5120.50" "total","VEA","36.00" "total","VHT","294.00" o Note: bare layout will sometimes display an extra row for the no-sym- bol commodity, because of zero amounts (hledger treats zeroes as com- modity-less, usually). This can break hledger-bar confusingly (workaround: add a cur: query to exclude the no-symbol row). o Tidy layout produces normalised "tidy data", where every variable has its own column and each row represents a single data point. See https://cran.r-project.org/web/packages/tidyr/vi- gnettes/tidy-data.html for more. This is the easiest kind of data for other software to consume. Here's how it looks: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -Y -O csv --layout=tidy "account","period","start_date","end_date","commodity","value" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","GLD","0" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","ITOT","10.00" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","USD","337.18" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","VEA","12.00" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","VHT","106.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","GLD","70.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","ITOT","18.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","USD","-98.12" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","VEA","10.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","VHT","18.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","GLD","0" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","ITOT","-11.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","USD","4881.44" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","VEA","14.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","VHT","170.00" Useful balance reports Some frequently used balance options/reports are: o bal -M revenues expenses Show revenues/expenses in each month. Also available as the incomes- tatement command. o bal -M -H assets liabilities Show historical asset/liability balances at each month end. Also available as the balancesheet command. o bal -M -H assets liabilities equity Show historical asset/liability/equity balances at each month end. Also available as the balancesheetequity command. o bal -M assets not:receivable Show changes to liquid assets in each month. Also available as the cashflow command. Also: o bal -M expenses -2 -SA Show monthly expenses summarised to depth 2 and sorted by average amount. o bal -M --budget expenses Show monthly expenses and budget goals. o bal -M --valuechange investments Show monthly change in market value of investment assets. o bal investments --valuechange -D date:lastweek amt:'>1000' -STA [--invert] Show top gainers [or losers] last week balancesheet (bs) This command displays a balance sheet, showing historical ending bal- ances of asset and liability accounts. (To see equity as well, use the balancesheetequity command.) Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the Asset, Cash or Liability type (see account types). Or if no such accounts are declared, it shows top-level accounts named asset or liability (case insensitive, plurals allowed) and their subaccounts. Example: $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 This command is a higher-level variant of the balance command, and sup- ports many of that command's features, such as multi-period reports. It is similar to hledger balance -H assets liabilities, but with smarter account detection, and liabilities displayed with their sign flipped. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, tsv, html, and (exper- imental) json. balancesheetequity (bse) This command displays a balance sheet, showing historical ending bal- ances of asset, liability and equity accounts. Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the Asset, Cash, Liability or Equity type (see account types). Or if no such accounts are declared, it shows top-level accounts named asset, liability or equity (case in- sensitive, plurals allowed) and their subaccounts. Example: $ hledger balancesheetequity Balance Sheet With Equity Assets: $-2 assets $1 bank:saving $-3 cash -------------------- $-2 Liabilities: $1 liabilities:debts -------------------- $1 Equity: $1 equity:owner -------------------- $1 Total: -------------------- 0 This command is a higher-level variant of the balance command, and sup- ports many of that command's features, such as multi-period reports. It is similar to hledger balance -H assets liabilities equity, but with smarter account detection, and liabilities/equity displayed with their sign flipped. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, tsv, html, and (exper- imental) json. cashflow (cf) This command displays a cashflow statement, showing the inflows and outflows affecting "cash" (ie, liquid, easily convertible) assets. Amounts are shown with normal positive sign, as in conventional finan- cial statements. This report shows accounts declared with the Cash type (see account types). Or if no such accounts are declared, it shows accounts o under a top-level account named asset (case insensitive, plural al- lowed) o whose name contains some variation of cash, bank, checking or saving. More precisely: all accounts matching this case insensitive regular ex- pression: ^assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|currentcash)(:|$) and their subaccounts. An example cashflow report: $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 This command is a higher-level variant of the balance command, and sup- ports many of that command's features, such as multi-period reports. It is similar to hledger balance assets not:fixed not:investment not:receivable, but with smarter account detection. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, tsv, html, and (exper- imental) json. check Check for various kinds of errors in your data. hledger provides a number of built-in error checks to help prevent problems in your data. Some of these are run automatically; or, you can use this check command to run them on demand, with no output and a zero exit code if all is well. Specify their names (or a prefix) as argument(s). Some examples: hledger check # basic checks hledger check -s # basic + strict checks hledger check ordereddates payees # basic + two other checks If you are an Emacs user, you can also configure flycheck-hledger to run these checks, providing instant feedback as you edit the journal. Here are the checks currently available: Default checks These checks are run automatically by (almost) all hledger commands: o parseable - data files are in a supported format, with no syntax er- rors and no invalid include directives. o autobalanced - all transactions are balanced, after converting to cost. Missing amounts and missing costs are inferred automatically where possible. o assertions - all balance assertions in the journal are passing. (This check can be disabled with -I/--ignore-assertions.) Strict checks These additional checks are run when the -s/--strict (strict mode) flag is used. Or, they can be run by giving their names as arguments to check: o balanced - all transactions are balanced after converting to cost, without inferring missing costs. If conversion costs are required, they must be explicit. o accounts - all account names used by transactions have been declared o commodities - all commodity symbols used have been declared Other checks These checks can be run only by giving their names as arguments to check. They are more specialised and not desirable for everyone: o ordereddates - transactions are ordered by date within each file o payees - all payees used by transactions have been declared o recentassertions - all accounts with balance assertions have a bal- ance assertion within 7 days of their latest posting o tags - all tags used by transactions have been declared o uniqueleafnames - all account leaf names are unique Custom checks A few more checks are are available as separate add-on commands, in https://github.com/simonmichael/hledger/tree/master/bin: o hledger-check-tagfiles - all tag values containing / (a forward slash) exist as file paths o hledger-check-fancyassertions - more complex balance assertions are passing You could make similar scripts to perform your own custom checks. See: Cookbook -> Scripting. More about specific checks hledger check recentassertions will complain if any balance-asserted account has postings more than 7 days after its latest balance asser- tion. This aims to prevent the situation where you are regularly up- dating your journal, but forgetting to check your balances against the real world, then one day must dig back through months of data to find an error. It assumes that adding a balance assertion requires/reminds you to check the real-world balance. (That may not be true if you auto-generate balance assertions from bank data; in that case, I recom- mend to import transactions uncleared, and when you manually review and clear them, also check the latest assertion against the real-world bal- ance.) close (equity) Generate transactions which transfer account balances to and/or from another account (typically equity). This can be useful for migrating balances to a new journal file, or for merging earnings into equity at end of accounting period. By default, it prints a transaction that zeroes out ALE accounts (as- set, liability, equity accounts; this requires account types to be con- figured); or if ACCTQUERY is provided, the accounts matched by that. (experimental) This command has four main modes, corresponding to the most common use cases: 1. With --close (default), it prints a "closing balances" transaction that zeroes out ALE (asset, liability, equity) accounts by default (this requires account types to be inferred or declared); or, the accounts matched by the provided ACCTQUERY arguments. 2. With --open, it prints an opposite "opening balances" transaction that restores those balances from zero. This is similar to Ledger's equity command. 3. With --migrate, it prints both the closing and opening transactions. This is the preferred way to migrate balances to a new file: run hledger close --migrate, add the closing transaction at the end of the old file, and add the opening transaction at the start of the new file. The matching closing/opening transactions cancel each other out, preserving correct balances during multi-file reporting. 4. With --retain, it prints a "retain earnings" transaction that trans- fers RX (revenue and expense) balances to equity:retained earnings. Businesses traditionally do this at the end of each accounting pe- riod; it is less necessary with computer-based accounting, but it could still be useful if you want to see the accounting equation (A=L+E) satisfied. In all modes, the defaults can be overridden: o the transaction descriptions can be changed with --close-desc=DESC and --open-desc=DESC o the account to transfer to/from can be changed with --close-acct=ACCT and --open-acct=ACCT o the accounts to be closed/opened can be changed with ACCTQUERY (ac- count query arguments). o the closing/opening dates can be changed with -e DATE (a report end date) By default just one destination/source posting will be used, with its amount left implicit. With --x/--explicit, the amount will be shown explicitly, and if it involves multiple commodities, a separate posting will be generated for each of them (similar to print -x). With --show-costs, any amount costs are shown, with separate postings for each cost. This is currently the best way to view investment lots. If you have many currency conversion or investment transactions, it can generate very large journal entries. With --interleaved, each individual transfer is shown with source and destination postings next to each other. This could be useful for troubleshooting. The default closing date is yesterday, or the journal's end date, whichever is later. You can change this by specifying a report end date with -e. The last day of the report period will be the closing date, eg -e 2024 means "close on 2023-12-31". The opening date is al- ways the day after the closing date. close and balance assertions Balance assertions will be generated, verifying that the accounts have been reset to zero (and then restored to their previous balances, if there is an opening transaction). These provide useful error checking, but you can ignore them temporar- ily with -I, or remove them if you prefer. You probably should avoid filtering transactions by status or realness (-C, -R, status:), or generating postings (--auto), with this command, since the balance assertions would depend on these. Note custom posting dates spanning the file boundary will disrupt the balance assertions: 2023-12-30 a purchase made in december, cleared in january expenses:food 5 assets:bank:checking -5 ; date: 2023-01-02 To solve that you can transfer the money to and from a temporary ac- count, in effect splitting the multi-day transaction into two sin- gle-day transactions: ; in 2022.journal: 2022-12-30 a purchase made in december, cleared in january expenses:food 5 equity:pending -5 ; in 2023.journal: 2023-01-02 last year's transaction cleared equity:pending 5 = 0 assets:bank:checking -5 Example: retain earnings Record 2022's revenues/expenses as retained earnings on 2022-12-31, ap- pending the generated transaction to the journal: $ hledger close --retain -f 2022.journal -p 2022 >> 2022.journal Note 2022's income statement will now show only zeroes, because rev- enues and expenses have been moved entirely to equity. To see them again, you could exclude the retain transaction: $ hledger -f 2022.journal is not:desc:'retain earnings' Example: migrate balances to a new file Close assets/liabilities/equity on 2022-12-31 and re-open them on 2023-01-01: $ hledger close --migrate -f 2022.journal -p 2022 # copy/paste the closing transaction to the end of 2022.journal # copy/paste the opening transaction to the start of 2023.journal Now 2022's balance sheet will show only zeroes, indicating a balanced accounting equation. (Unless you are using @/@@ notation - in that case, try adding --infer-equity.) To see the end-of-year balances again, you could exclude the closing transaction: $ hledger -f 2022.journal bs not:desc:'closing balances' Example: excluding closing/opening transactions When combining many files for multi-year reports, the closing/opening transactions cause some noise in transaction-oriented reports like print and register. You can exclude them as shown above, but not:desc:... is not ideal as it depends on consistent descriptions; also you will want to avoid excluding the very first opening transac- tion, which could be awkward. Here is one alternative, using tags: Add clopen: tags to all opening/closing balances transactions except the first, like this: ; 2021.journal 2021-06-01 first opening balances ... 2021-12-31 closing balances ; clopen:2022 ... ; 2022.journal 2022-01-01 opening balances ; clopen:2022 ... 2022-12-31 closing balances ; clopen:2023 ... ; 2023.journal 2023-01-01 opening balances ; clopen:2023 ... Now, assuming a combined journal like: ; all.journal include 2021.journal include 2022.journal include 2023.journal The clopen: tag can exclude all but the first opening transaction. To show a clean multi-year checking register: $ hledger -f all.journal areg checking not:tag:clopen And the year values allow more precision. To show 2022's year-end bal- ance sheet: $ hledger -f all.journal bs -e2023 not:tag:clopen=2023 codes List the codes seen in transactions, in the order parsed. This command prints the value of each transaction's code field, in the order transactions were parsed. The transaction code is an optional value written in parentheses between the date and description, often used to store a cheque number, order number or similar. Transactions aren't required to have a code, and missing or empty codes will not be shown by default. With the -E/--empty flag, they will be printed as blank lines. You can add a query to select a subset of transactions. Examples: 2022/1/1 (123) Supermarket Food $5.00 Checking 2022/1/2 (124) Post Office Postage $8.32 Checking 2022/1/3 Supermarket Food $11.23 Checking 2022/1/4 (126) Post Office Postage $3.21 Checking $ hledger codes 123 124 126 $ hledger codes -E 123 124 126 commodities List all commodity/currency symbols used or declared in the journal. demo Play demos of hledger usage in the terminal, if asciinema is installed. Run this command with no argument to list the demos. To play a demo, write its number or a prefix or substring of its title. Tips: Make your terminal window large enough to see the demo clearly. Use the -s/--speed SPEED option to set your preferred playback speed, eg -s4 to play at 4x original speed or -s.5 to play at half speed. The default speed is 2x. Other asciinema options can be added following a double dash, eg -- -i.1 to limit pauses or -- -h to list asciinema's other options. During playback, several keys are available: SPACE to pause/unpause, . to step forward (while paused), CTRL-c quit. Examples: $ hledger demo # list available demos $ hledger demo 1 # play the first demo at default speed (2x) $ hledger demo install -s4 # play the "install" demo at 4x speed descriptions List the unique descriptions that appear in transactions. This command lists the unique descriptions that appear in transactions, in alphabetic order. You can add a query to select a subset of trans- actions. Example: $ hledger descriptions Store Name Gas Station | Petrol Person A diff Compares a particular account's transactions in two input files. It shows any transactions to this account which are in one file but not in the other. More precisely, for each posting affecting this account in either file, it looks for a corresponding posting in the other file which posts the same amount to the same account (ignoring date, description, etc.) Since postings not transactions are compared, this also works when mul- tiple bank transactions have been combined into a single journal entry. This is useful eg if you have downloaded an account's transactions from your bank (eg as CSV data). When hledger and your bank disagree about the account balance, you can compare the bank data with your journal to find out the cause. Examples: $ hledger diff -f $LEDGER_FILE -f bank.csv assets:bank:giro These transactions are in the first file only: 2014/01/01 Opening Balances assets:bank:giro EUR ... ... equity:opening balances EUR -... These transactions are in the second file only: files List all files included in the journal. With a REGEX argument, only file names matching the regular expression (case sensitive) are shown. help Show the hledger user manual in the terminal, with info, man, or a pager. With a TOPIC argument, open it at that topic if possible. TOPIC can be any heading in the manual, or a heading prefix, case in- sensitive. Eg: commands, print, forecast, journal, amount, "auto post- ings". This command shows the hledger manual built in to your hledger version. It can be useful when offline, or when you prefer the terminal to a web browser, or when the appropriate hledger manual or viewing tools are not installed on your system. By default it chooses the best viewer found in $PATH, trying (in this order): info, man, $PAGER, less, more. You can force the use of info, man, or a pager with the -i, -m, or -p flags, If no viewer can be found, or the command is run non-interactively, it just prints the man- ual to stdout. If using info, note that version 6 or greater is needed for TOPIC lookup. If you are on mac you will likely have info 4.8, and should consider installing a newer version, eg with brew install texinfo (#1770). Examples $ hledger help --help # show how the help command works $ hledger help # show the hledger manual with info, man or $PAGER $ hledger help journal # show the journal topic in the hledger manual $ hledger help -m journal # show it with man, even if info is installed import Read new transactions added to each FILE provided as arguments since last run, and add them to the journal. Or with --dry-run, just print the transactions that would be added. Or with --catchup, just mark all of the FILEs' current transactions as imported, without importing them. This command may append new transactions to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also add). Unlike other hledger commands, with import the journal file is an out- put file, and will be modified, though only by appending (existing data will not be changed). The input files are specified as arguments, so to import one or more CSV files to your main journal, you will run hledger import bank.csv or perhaps hledger import *.csv. Note you can import from any file format, though CSV files are the most common import source, and these docs focus on that case. Deduplication import does time-based deduplication, to detect only the new transac- tions since the last successful import. (This does not mean "ignore transactions that look the same", but rather "ignore transactions that have been seen before".) This is intended for when you are periodi- cally importing downloaded data, which may overlap with previous down- loads. Eg if every week (or every day) you download a bank's last three months of CSV data, you can safely run hledger import thebank.csv each time and only new transactions will be imported. Since the items being read (CSV records, eg) often do not come with unique identifiers, hledger detects new transactions by date, assuming that: 1. new items always have the newest dates 2. item dates do not change across reads 3. and items with the same date remain in the same relative order across reads. These are often true of CSV files representing transactions, or true enough so that it works pretty well in practice. 1 is important, but violations of 2 and 3 amongst the old transactions won't matter (and if you import often, the new transactions will be few, so less likely to be the ones affected). hledger remembers the latest date processed in each input file by sav- ing a hidden ".latest.FILE" file in FILE's directory (after a succesful import). Eg when reading finance/bank.csv, it will look for and update the fi- nance/.latest.bank.csv state file. The format is simple: one or more lines containing the same ISO-format date (YYYY-MM-DD), meaning "I have processed transactions up to this date, and this many of them on that date." Normally you won't see or manipulate these state files yourself. But if needed, you can delete them to reset the state (making all transactions "new"), or you can construct them to "catch up" to a cer- tain date. Note deduplication (and updating of state files) can also be done by print --new, but this is less often used. Related: CSV > Working with CSV > Deduplicating, importing. Import testing With --dry-run, the transactions that will be imported are printed to the terminal, without updating your journal or state files. The output is valid journal format, like the print command, so you can re-parse it. Eg, to see any importable transactions which CSV rules have not categorised: $ hledger import --dry bank.csv | hledger -f- -I print unknown or (live updating): $ ls bank.csv* | entr bash -c 'echo ====; hledger import --dry bank.csv | hledger -f- -I print unknown' Note: when importing from multiple files at once, it's currently possi- ble for some .latest files to be updated successfully, while the actual import fails because of a problem in one of the files, leaving them out of sync (and causing some transactions to be missed). To prevent this, do a --dry-run first and fix any problems before the real import. Importing balance assignments Entries added by import will have their posting amounts made explicit (like hledger print -x). This means that any balance assignments in imported files must be evaluated; but, imported files don't get to see the main file's account balances. As a result, importing entries with balance assignments (eg from an institution that provides only balances and not posting amounts) will probably generate incorrect posting amounts. To avoid this problem, use print instead of import: $ hledger print IMPORTFILE [--new] >> $LEDGER_FILE (If you think import should leave amounts implicit like print does, please test it and send a pull request.) Commodity display styles Imported amounts will be formatted according to the canonical commodity styles (declared or inferred) in the main journal file. incomestatement (is) This command displays an income statement, showing revenues and ex- penses during one or more periods. Amounts are shown with normal posi- tive sign, as in conventional financial statements. This report shows accounts declared with the Revenue or Expense type (see account types). Or if no such accounts are declared, it shows top-level accounts named revenue or income or expense (case insensi- tive, plurals allowed) and their subaccounts. Example: $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 This command is a higher-level variant of the balance command, and sup- ports many of that command's features, such as multi-period reports. It is similar to hledger balance '(revenues|income)' expenses, but with smarter account detection, and revenues/income displayed with their sign flipped. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, tsv, html, and (exper- imental) json. notes List the unique notes that appear in transactions. This command lists the unique notes that appear in transactions, in al- phabetic order. You can add a query to select a subset of transac- tions. The note is the part of the transaction description after a | character (or if there is no |, the whole description). Example: $ hledger notes Petrol Snacks payees List the unique payee/payer names that appear in transactions. This command lists unique payee/payer names which have been declared with payee directives (--declared), used in transaction descriptions (--used), or both (the default). The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). You can add query arguments to select a subset of transactions. This implies --used. Example: $ hledger payees Store Name Gas Station Person A prices Print the market prices declared with P directives. With --infer-mar- ket-prices, also show any additional prices inferred from costs. With --show-reverse, also show additional prices inferred by reversing known prices. Price amounts are always displayed with their full precision, except for reverse prices which are limited to 8 decimal digits. Prices can be filtered by a date:, cur: or amt: query. Generally if you run this command with --infer-market-prices --show-re- verse, it will show the same prices used internally to calculate value reports. But if in doubt, you can inspect those directly by running the value report with --debug=2. print Show transaction journal entries, sorted by date. The print command displays full journal entries (transactions) from the journal file, sorted by date (or with --date2, by secondary date). Directives and inter-transaction comments are not shown, currently. This means the print command is somewhat lossy, and if you are using it to reformat/regenerate your journal you should take care to also copy over the directives and inter-transaction comments. Eg: $ hledger print -f examples/sample.journal date:200806 2008/06/01 gift assets:bank:checking $1 income:gifts $-1 2008/06/02 save assets:bank:saving $1 assets:bank:checking $-1 2008/06/03 * eat & shop expenses:food $1 expenses:supplies $1 assets:cash $-2 print explicitness Normally, whether posting amounts are implicit or explicit is pre- served. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, if a conversion cost is implied but not written, it will not appear in the output. You can use the -x/--explicit flag to force explicit display of all amounts and costs. This can be useful for troubleshooting or for mak- ing your journal more readable and robust against data entry errors. -x is also implied by using any of -B,-V,-X,--value. The -x/--explicit flag will cause any postings with a multi-commodity amount (which can arise when a multi-commodity transaction has an im- plicit amount) to be split into multiple single-commodity postings, keeping the output parseable. print amount style Amounts are shown right-aligned within each transaction (but not aligned across all transactions; you can do that with ledger-mode in Emacs). Amounts will be (mostly) normalised to their commodity display style: their symbol placement, decimal mark, and digit group marks will be made consistent. By default, decimal digits are shown as they are written in the journal. With the --round option, print will try increasingly hard to display decimal digits according to the commodity display styles: o --round=none show amounts with original precisions (default) o --round=soft add/remove decimal zeros in amounts (except costs) o --round=hard round amounts (except costs), possibly hiding signifi- cant digits o --round=all round all amounts and costs soft is good for non-lossy cleanup, formatting amounts more consis- tently where it's safe to do so. hard and all can cause print to show invalid unbalanced journal en- tries; they may be useful eg for stronger cleanup, with manual fixups when needed. print parseability print's output is usually a valid hledger journal, and you can process it again with a second hledger command. This can be useful for certain kinds of search (though the same can be achieved with expr: queries now): # Show running total of food expenses paid from cash. # -f- reads from stdin. -I/--ignore-assertions is sometimes needed. $ hledger print assets:cash | hledger -f- -I reg expenses:food There are some situations where print's output can become unparseable: o Value reporting affects posting amounts but not balance assertion or balance assignment amounts, potentially causing those to fail. o Auto postings can generate postings with too many missing amounts. o Account aliases can generate bad account names. print, other features With -B/--cost, amounts with costs are shown converted to cost. With --new, print shows only transactions it has not seen on a previous run. This uses the same deduplication system as the import command. (See import's docs for details.) With -m DESC/--match=DESC, print shows one recent transaction whose de- scription is most similar to DESC. DESC should contain at least two characters. If there is no similar-enough match, no transaction will be shown and the program exit code will be non-zero. print output format This command also supports the output destination and output format op- tions The output formats supported are txt, beancount, csv, tsv, json and sql. Experimental: The beancount format tries to produce Beancount-compati- ble output, as follows: o Transaction and postings with unmarked status are converted to cleared (*) status. o Transactions' payee and note are backslash-escaped and dou- ble-quote-escaped and wrapped in double quotes. o Transaction tags are copied to Beancount #tag format. o Commodity symbols are converted to upper case, and a small number of currency symbols like $ are converted to the corresponding currency names. o Account name parts are capitalised and unsupported characters are re- placed with -. If an account name part does not begin with a letter, or if the first part is not Assets, Liabilities, Equity, Income, or Expenses, an error is raised. (Use --alias options to bring your ac- counts into compliance.) o An open directive is generated for each account used, on the earliest transaction date. Some limitations: o Balance assertions are removed. o Balance assignments become missing amounts. o Virtual and balanced virtual postings become regular postings. o Directives are not converted. Here's an example of print's CSV output: $ hledger print -Ocsv "txnidx","date","date2","status","code","description","comment","account","amount","commodity","credit","debit","posting-status","posting-comment" "1","2008/01/01","","","","income","","assets:bank:checking","1","$","","1","","" "1","2008/01/01","","","","income","","income:salary","-1","$","1","","","" "2","2008/06/01","","","","gift","","assets:bank:checking","1","$","","1","","" "2","2008/06/01","","","","gift","","income:gifts","-1","$","1","","","" "3","2008/06/02","","","","save","","assets:bank:saving","1","$","","1","","" "3","2008/06/02","","","","save","","assets:bank:checking","-1","$","1","","","" "4","2008/06/03","","*","","eat & shop","","expenses:food","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","expenses:supplies","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","assets:cash","-2","$","2","","","" "5","2008/12/31","","*","","pay off","","liabilities:debts","1","$","","1","","" "5","2008/12/31","","*","","pay off","","assets:bank:checking","-1","$","1","","","" o There is one CSV record per posting, with the parent transaction's fields repeated. o The "txnidx" (transaction index) field shows which postings belong to the same transaction. (This number might change if transactions are reordered within the file, files are parsed/included in a different order, etc.) o The amount is separated into "commodity" (the symbol) and "amount" (numeric quantity) fields. o The numeric amount is repeated in either the "credit" or "debit" col- umn, for convenience. (Those names are not accurate in the account- ing sense; it just puts negative amounts under credit and zero or greater amounts under debit.) register (reg) Show postings and their running total. The register command displays matched postings, across all accounts, in date order, with their running total or running historical balance. (See also the aregister command, which shows matched transactions in a specific account.) register normally shows line per posting, but note that multi-commodity amounts will occupy multiple lines (one line per commodity). It is typically used with a query selecting a particular account, to see that account's activity: $ hledger register checking 2008/01/01 income assets:bank:checking $1 $1 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $-1 $1 2008/12/31 pay off assets:bank:checking $-1 0 With --date2, it shows and sorts by secondary date instead. For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the --align-all flag. The --historical/-H flag adds the balance from any undisplayed prior postings to the running total. This is useful when you want to see only recent activity, with a historically accurate running balance: $ hledger register checking -b 2008/6 --historical 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $-1 $1 2008/12/31 pay off assets:bank:checking $-1 0 The --depth option limits the amount of sub-account detail displayed. The --average/-A flag shows the running average posting amount instead of the running total (so, the final number displayed is the average for the whole report period). This flag implies --empty (see below). It is affected by --historical. It works best when showing just one ac- count and one commodity. The --related/-r flag shows the other postings in the transactions of the postings which would normally be shown. The --invert flag negates all amounts. For example, it can be used on an income account where amounts are normally displayed as negative num- bers. It's also useful to show postings on the checking account to- gether with the related account: $ hledger register --related --invert assets:checking With a reporting interval, register shows summary postings, one per in- terval, aggregating the postings to each account: $ hledger register --monthly income 2008/01 income:salary $-1 $-1 2008/06 income:gifts $-1 $-2 Periods with no activity, and summary postings with a zero amount, are not shown by default; use the --empty/-E flag to see them: $ hledger register --monthly income -E 2008/01 income:salary $-1 $-1 2008/02 0 $-1 2008/03 0 $-1 2008/04 0 $-1 2008/05 0 $-1 2008/06 income:gifts $-1 $-2 2008/07 0 $-2 2008/08 0 $-2 2008/09 0 $-2 2008/10 0 $-2 2008/11 0 $-2 2008/12 0 $-2 Often, you'll want to see just one line per interval. The --depth op- tion helps with this, causing subaccounts to be aggregated: $ hledger register --monthly assets --depth 1h 2008/01 assets $1 $1 2008/06 assets $-1 0 2008/12 assets $-1 $-1 Note when using report intervals, if you specify start/end dates these will be adjusted outward if necessary to contain a whole number of in- tervals. This ensures that the first and last intervals are full length and comparable to the others in the report. With -m DESC/--match=DESC, register does a fuzzy search for one recent posting whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar-enough match, no post- ing will be shown and the program exit code will be non-zero. Custom register output register uses the full terminal width by default, except on windows. You can override this by setting the COLUMNS environment variable (not a bash shell variable) or by using the --width/-w option. The description and account columns normally share the space equally (about half of (width - 40) each). You can adjust this by adding a de- scription width as part of --width's argument, comma-separated: --width W,D . Here's a diagram (won't display correctly in --help): <--------------------------------- width (W) ----------------------------------> date (10) description (D) account (W-41-D) amount (12) balance (12) DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA and some examples: $ hledger reg # use terminal width (or 80 on windows) $ hledger reg -w 100 # use width 100 $ COLUMNS=100 hledger reg # set with one-time environment variable $ export COLUMNS=100; hledger reg # set till session end (or window resize) $ hledger reg -w 100,40 # set overall width 100, description width 40 $ hledger reg -w $COLUMNS,40 # use terminal width, & description width 40 This command also supports the output destination and output format op- tions The output formats supported are txt, csv, tsv, and (experimen- tal) json. rewrite Print all transactions, rewriting the postings of matched transactions. For now the only rewrite available is adding new postings, like print --auto. This is a start at a generic rewriter of transaction entries. It reads the default journal and prints the transactions, like print, but adds one or more specified postings to any transactions matching QUERY. The posting amounts can be fixed, or a multiplier of the existing transac- tion's first posting amount. Examples: $ hledger-rewrite.hs ^income --add-posting '(liabilities:tax) *.33 ; income tax' --add-posting '(reserve:gifts) $100' $ hledger-rewrite.hs expenses:gifts --add-posting '(reserve:gifts) *-1"' $ hledger-rewrite.hs -f rewrites.hledger rewrites.hledger may consist of entries like: = ^income amt:<0 date:2017 (liabilities:tax) *0.33 ; tax on income (reserve:grocery) *0.25 ; reserve 25% for grocery (reserve:) *0.25 ; reserve 25% for grocery Note the single quotes to protect the dollar sign from bash, and the two spaces between account and amount. More: $ hledger rewrite -- [QUERY] --add-posting "ACCT AMTEXPR" ... $ hledger rewrite -- ^income --add-posting '(liabilities:tax) *.33' $ hledger rewrite -- expenses:gifts --add-posting '(budget:gifts) *-1"' $ hledger rewrite -- ^income --add-posting '(budget:foreign currency) *0.25 JPY; diversify' Argument for --add-posting option is a usual posting of transaction with an exception for amount specification. More precisely, you can use '*' (star symbol) before the amount to indicate that that this is a factor for an amount of original matched posting. If the amount in- cludes a commodity name, the new posting amount will be in the new com- modity; otherwise, it will be in the matched posting amount's commod- ity. Re-write rules in a file During the run this tool will execute so called "Automated Transac- tions" found in any journal it process. I.e instead of specifying this operations in command line you can put them in a journal file. $ rewrite-rules.journal Make contents look like this: = ^income (liabilities:tax) *.33 = expenses:gifts budget:gifts *-1 assets:budget *1 Note that '=' (equality symbol) that is used instead of date in trans- actions you usually write. It indicates the query by which you want to match the posting to add new ones. $ hledger rewrite -- -f input.journal -f rewrite-rules.journal > rewritten-tidy-output.journal This is something similar to the commands pipeline: $ hledger rewrite -- -f input.journal '^income' --add-posting '(liabilities:tax) *.33' \ | hledger rewrite -- -f - expenses:gifts --add-posting 'budget:gifts *-1' \ --add-posting 'assets:budget *1' \ > rewritten-tidy-output.journal It is important to understand that relative order of such entries in journal is important. You can re-use result of previously added post- ings. Diff output format To use this tool for batch modification of your journal files you may find useful output in form of unified diff. $ hledger rewrite -- --diff -f examples/sample.journal '^income' --add-posting '(liabilities:tax) *.33' Output might look like: --- /tmp/examples/sample.journal +++ /tmp/examples/sample.journal @@ -18,3 +18,4 @@ 2008/01/01 income - assets:bank:checking $1 + assets:bank:checking $1 income:salary + (liabilities:tax) 0 @@ -22,3 +23,4 @@ 2008/06/01 gift - assets:bank:checking $1 + assets:bank:checking $1 income:gifts + (liabilities:tax) 0 If you'll pass this through patch tool you'll get transactions contain- ing the posting that matches your query be updated. Note that multiple files might be update according to list of input files specified via --file options and include directives inside of these files. Be careful. Whole transaction being re-formatted in a style of output from hledger print. See also: https://github.com/simonmichael/hledger/issues/99 rewrite vs. print --auto This command predates print --auto, and currently does much the same thing, but with these differences: o with multiple files, rewrite lets rules in any file affect all other files. print --auto uses standard directive scoping; rules affect only child files. o rewrite's query limits which transactions can be rewritten; all are printed. print --auto's query limits which transactions are printed. o rewrite applies rules specified on command line or in the journal. print --auto applies rules specified in the journal. roi Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. At a minimum, you need to supply a query (which could be just an ac- count name) to select your investment(s) with --inv, and another query to identify your profit and loss transactions with --pnl. If you do not record changes in the value of your investment manually, or do not require computation of time-weighted return (TWR), --pnl could be an empty query (--pnl "" or --pnl STR where STR does not match any of your accounts). This command will compute and display the internalized rate of return (IRR, also known as money-weighted rate of return) and time-weighted rate of return (TWR) for your investments for the time period re- quested. IRR is always annualized due to the way it is computed, but TWR is reported both as a rate over the chosen reporting period and as an annual rate. Price directives will be taken into account if you supply appropriate --cost or --value flags (see VALUATION). Note, in some cases this report can fail, for these reasons: o Error (NotBracketed): No solution for Internal Rate of Return (IRR). Possible causes: IRR is huge (>1000000%), balance of investment be- comes negative at some point in time. o Error (SearchFailed): Failed to find solution for Internal Rate of Return (IRR). Either search does not converge to a solution, or con- verges too slowly. Examples: o Using roi to compute total return of investment in stocks: https://github.com/simonmichael/hledger/blob/master/examples/invest- ing/roi-unrealised.ledger o Cookbook > Return on Investment: https://hledger.org/roi.html Spaces and special characters in --inv and --pnl Note that --inv and --pnl's argument is a query, and queries could have several space-separated terms (see QUERIES). To indicate that all search terms form single command-line argument, you will need to put them in quotes (see Special characters): $ hledger roi --inv 'term1 term2 term3 ...' If any query terms contain spaces themselves, you will need an extra level of nested quoting, eg: $ hledger roi --inv="'Assets:Test 1'" --pnl="'Equity:Unrealized Profit and Loss'" Semantics of --inv and --pnl Query supplied to --inv has to match all transactions that are related to your investment. Transactions not matching --inv will be ignored. In these transactions, ROI will conside postings that match --inv to be "investment postings" and other postings (not matching --inv) will be sorted into two categories: "cash flow" and "profit and loss", as ROI needs to know which part of the investment value is your contributions and which is due to the return on investment. o "Cash flow" is depositing or withdrawing money, buying or selling as- sets, or otherwise converting between your investment commodity and any other commodity. Example: 2019-01-01 Investing in Snake Oil assets:cash -$100 investment:snake oil 2020-01-01 Selling my Snake Oil assets:cash $10 investment:snake oil = 0 o "Profit and loss" is change in the value of your investment: 2019-06-01 Snake Oil falls in value investment:snake oil = $57 equity:unrealized profit or loss All non-investment postings are assumed to be "cash flow", unless they match --pnl query. Changes in value of your investment due to "profit and loss" postings will be considered as part of your investment re- turn. Example: if you use --inv snake --pnl equity:unrealized, then postings in the example below would be classifed as: 2019-01-01 Snake Oil #1 assets:cash -$100 ; cash flow posting investment:snake oil ; investment posting 2019-03-01 Snake Oil #2 equity:unrealized pnl -$100 ; profit and loss posting snake oil ; investment posting 2019-07-01 Snake Oil #3 equity:unrealized pnl ; profit and loss posting cash -$100 ; cash flow posting snake oil $50 ; investment posting IRR and TWR explained "ROI" stands for "return on investment". Traditionally this was com- puted as a difference between current value of investment and its ini- tial value, expressed in percentage of the initial value. However, this approach is only practical in simple cases, where invest- ments receives no in-flows or out-flows of money, and where rate of growth is fixed over time. For more complex scenarios you need differ- ent ways to compute rate of return, and this command implements two of them: IRR and TWR. Internal rate of return, or "IRR" (also called "money-weighted rate of return") takes into account effects of in-flows and out-flows, and the time between them. Investment at a particular fixed interest rate is going to give you more interest than the same amount invested at the same interest rate, but made later in time. If you are withdrawing from your investment, your future gains would be smaller (in absolute numbers), and will be a smaller percentage of your initial investment, so your IRR will be smaller. And if you are adding to your investment, you will receive bigger absolute gains, which will be a bigger percent- age of your initial investment, so your IRR will be larger. As mentioned before, in-flows and out-flows would be any cash that you personally put in or withdraw, and for the "roi" command, these are the postings that match the query in the--inv argument and NOT match the query in the--pnl argument. If you manually record changes in the value of your investment as transactions that balance them against "profit and loss" (or "unreal- ized gains") account or use price directives, then in order for IRR to compute the precise effect of your in-flows and out-flows on the rate of return, you will need to record the value of your investement on or close to the days when in- or out-flows occur. In technical terms, IRR uses the same approach as computation of net present value, and tries to find a discount rate that makes net present value of all the cash flows of your investment to add up to zero. This could be hard to wrap your head around, especially if you haven't done discounted cash flow analysis before. Implementation of IRR in hledger should produce results that match the =XIRR formula in Excel. Second way to compute rate of return that roi command implements is called "time-weighted rate of return" or "TWR". Like IRR, it will ac- count for the effect of your in-flows and out-flows, but unlike IRR it will try to compute the true rate of return of the underlying asset, compensating for the effect that deposits and withdrawas have on the apparent rate of growth of your investment. TWR represents your investment as an imaginary "unit fund" where in-flows/ out-flows lead to buying or selling "units" of your invest- ment and changes in its value change the value of "investment unit". Change in "unit price" over the reporting period gives you rate of re- turn of your investment, and make TWR less sensitive than IRR to the effects of cash in-flows and out-flows. References: o Explanation of rate of return o Explanation of IRR o Explanation of TWR o IRR vs TWR o Examples of computing IRR and TWR and discussion of the limitations of both metrics stats Show journal and performance statistics. The stats command displays summary information for the whole journal, or a matched part of it. With a reporting interval, it shows a report for each report period. At the end, it shows (in the terminal) the overall run time and number of transactions processed per second. Note these are approximate and will vary based on machine, current load, data size, hledger version, haskell lib versions, GHC version.. but they may be of interest. The stats command's run time is similar to that of a single-column balance report. Example: $ hledger stats -f examples/1000x1000x10.journal Main file : /Users/simon/src/hledger/examples/1000x1000x10.journal Included files : Transactions span : 2000-01-01 to 2002-09-27 (1000 days) Last transaction : 2002-09-26 (6995 days ago) Transactions : 1000 (1.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 1000 Accounts : 1000 (depth 10) Commodities : 26 (A, B, C, D, E, F, G, H, I, J, K, L, M, N, O, P, Q, R, S, T, U, V, W, X, Y, Z) Market prices : 1000 (A) Run time : 0.12 s Throughput : 8342 txns/s This command supports the -o/--output-file option (but not -O/--out- put-format selection). tags List the tags used in the journal, or their values. This command lists the tag names used in the journal, whether on trans- actions, postings, or account declarations. With a TAGREGEX argument, only tag names matching this regular expres- sion (case insensitive, infix matched) are shown. With QUERY arguments, only transactions and accounts matching this query are considered. If the query involves transaction fields (date:, desc:, amt:, ...), the search is restricted to the matched transactions and their accounts. With the --values flag, the tags' unique non-empty values are listed instead. With -E/--empty, blank/empty values are also shown. With --parsed, tags or values are shown in the order they were parsed, with duplicates included. (Except, tags from account declarations are always shown first.) Tip: remember, accounts also acquire tags from their parents, postings also acquire tags from their account and transaction, transactions also acquire tags from their postings. test Run built-in unit tests. This command runs the unit tests built in to hledger and hledger-lib, printing the results on stdout. If any test fails, the exit code will be non-zero. This is mainly used by hledger developers, but you can also use it to sanity-check the installed hledger executable on your platform. All tests are expected to pass - if you ever see a failure, please report as a bug! This command also accepts tasty test runner options, written after a -- (double hyphen). Eg to run only the tests in Hledger.Data.Amount, with ANSI colour codes disabled: $ hledger test -- -pData.Amount --color=never For help on these, see https://github.com/feuerbach/tasty#options (-- --help currently doesn't show them). PART 5: COMMON TASKS Here are some quick examples of how to do some basic tasks with hledger. Getting help Here's how to list commands and view options and command docs: $ hledger # show available commands $ hledger --help # show common options $ hledger CMD --help # show CMD's options, common options and CMD's documentation You can also view your hledger version's manual in several formats by using the help command. Eg: $ hledger help # show the hledger manual with info, man or $PAGER (best available) $ hledger help journal # show the journal topic in the hledger manual $ hledger help --help # find out more about the help command To view manuals and introductory docs on the web, visit https://hledger.org. Chat and mail list support and discussion archives can be found at https://hledger.org/support. Constructing command lines hledger has a flexible command line interface. We strive to keep it simple and ergonomic, but if you run into one of the sharp edges de- scribed in OPTIONS, here are some tips that might help: o command-specific options must go after the command (it's fine to put common options there too: hledger CMD OPTS ARGS) o running add-on executables directly simplifies command line parsing (hledger-ui OPTS ARGS) o enclose "problematic" args in single quotes o if needed, also add a backslash to hide regular expression metachar- acters from the shell o to see how a misbehaving command line is being parsed, add --debug=2. Starting a journal file hledger looks for your accounting data in a journal file, $HOME/.hledger.journal by default: $ hledger stats The hledger journal file "/Users/simon/.hledger.journal" was not found. Please create it first, eg with "hledger add" or a text editor. Or, specify an existing journal file with -f or LEDGER_FILE. You can override this by setting the LEDGER_FILE environment variable (see below). It's a good practice to keep this important file under version control, and to start a new file each year. So you could do something like this: $ mkdir ~/finance $ cd ~/finance $ git init Initialized empty Git repository in /Users/simon/finance/.git/ $ touch 2023.journal $ echo "export LEDGER_FILE=$HOME/finance/2023.journal" >> ~/.profile $ source ~/.profile $ hledger stats Main file : /Users/simon/finance/2023.journal Included files : Transactions span : to (0 days) Last transaction : none Transactions : 0 (0.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 0 Accounts : 0 (depth 0) Commodities : 0 () Market prices : 0 () Setting LEDGER_FILE How to set LEDGER_FILE permanently depends on your setup: On unix and mac, running these commands in the terminal will work for many people; adapt as needed: $ echo 'export LEDGER_FILE=~/finance/2023.journal' >> ~/.profile $ source ~/.profile When correctly configured, in a new terminal window env | grep LEDGER_FILE will show your file, and so will hledger files. On mac, this additional step might be helpful for GUI applications (like Emacs started from the dock): add an entry to ~/.MacOSX/environ- ment.plist like { "LEDGER_FILE" : "~/finance/2023.journal" } and then run killall Dock in a terminal window (or restart the ma- chine). On Windows, see https://www.java.com/en/download/help/path.html, or try running these commands in a powershell window (let us know if it per- sists across a reboot, and if you need to be an Administrator): > CD > MKDIR finance > SETX LEDGER_FILE "C:\Users\USERNAME\finance\2023.journal" Setting opening balances Pick a starting date for which you can look up the balances of some real-world assets (bank accounts, wallet..) and liabilities (credit cards..). To avoid a lot of data entry, you may want to start with just one or two accounts, like your checking account or cash wallet; and pick a re- cent starting date, like today or the start of the week. You can al- ways come back later and add more accounts and older transactions, eg going back to january 1st. Add an opening balances transaction to the journal, declaring the bal- ances on this date. Here are two ways to do it: o The first way: open the journal in any text editor and save an entry like this: 2023-01-01 * opening balances assets:bank:checking $1000 = $1000 assets:bank:savings $2000 = $2000 assets:cash $100 = $100 liabilities:creditcard $-50 = $-50 equity:opening/closing balances These are start-of-day balances, ie whatever was in the account at the end of the previous day. The * after the date is an optional status flag. Here it means "cleared & confirmed". The currency symbols are optional, but usually a good idea as you'll be dealing with multiple currencies sooner or later. The = amounts are optional balance assertions, providing extra error checking. o The second way: run hledger add and follow the prompts to record a similar transaction: $ hledger add Adding transactions to journal file /Users/simon/finance/2023.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control-d or control-c. Date [2023-02-07]: 2023-01-01 Description: * opening balances Account 1: assets:bank:checking Amount 1: $1000 Account 2: assets:bank:savings Amount 2 [$-1000]: $2000 Account 3: assets:cash Amount 3 [$-3000]: $100 Account 4: liabilities:creditcard Amount 4 [$-3100]: $-50 Account 5: equity:opening/closing balances Amount 5 [$-3050]: Account 6 (or . or enter to finish this transaction): . 2023-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl-D/ctrl-C to quit) Date [2023-01-01]: . If you're using version control, this could be a good time to commit the journal. Eg: $ git commit -m 'initial balances' 2023.journal Recording transactions As you spend or receive money, you can record these transactions using one of the methods above (text editor, hledger add) or by using the hledger-iadd or hledger-web add-ons, or by using the import command to convert CSV data downloaded from your bank. Here are some simple transactions, see the hledger_journal(5) manual and hledger.org for more ideas: 2023/1/10 * gift received assets:cash $20 income:gifts 2023.1.12 * farmers market expenses:food $13 assets:cash 2023-01-15 paycheck income:salary assets:bank:checking $1000 Reconciling Periodically you should reconcile - compare your hledger-reported bal- ances against external sources of truth, like bank statements or your bank's website - to be sure that your ledger accurately represents the real-world balances (and, that the real-world institutions have not made a mistake!). This gets easy and fast with (1) practice and (2) frequency. If you do it daily, it can take 2-10 minutes. If you let it pile up, expect it to take longer as you hunt down errors and dis- crepancies. A typical workflow: 1. Reconcile cash. Count what's in your wallet. Compare with what hledger reports (hledger bal cash). If they are different, try to remember the missing transaction, or look for the error in the al- ready-recorded transactions. A register report can be helpful (hledger reg cash). If you can't find the error, add an adjustment transaction. Eg if you have $105 after the above, and can't explain the missing $2, it could be: 2023-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc 2. Reconcile checking. Log in to your bank's website. Compare today's (cleared) balance with hledger's cleared balance (hledger bal check- ing -C). If they are different, track down the error or record the missing transaction(s) or add an adjustment transaction, similar to the above. Unlike the cash case, you can usually compare the trans- action history and running balance from your bank with the one re- ported by hledger reg checking -C. This will be easier if you gen- erally record transaction dates quite similar to your bank's clear- ing dates. 3. Repeat for other asset/liability accounts. Tip: instead of the register command, use hledger-ui to see a live-up- dating register while you edit the journal: hledger-ui --watch --regis- ter checking -C After reconciling, it could be a good time to mark the reconciled transactions' status as "cleared and confirmed", if you want to track that, by adding the * marker. Eg in the paycheck transaction above, insert * between 2023-01-15 and paycheck If you're using version control, this can be another good time to com- mit: $ git commit -m 'txns' 2023.journal Reporting Here are some basic reports. Show all transactions: $ hledger print 2023-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 2023-01-10 * gift received assets:cash $20 income:gifts 2023-01-12 * farmers market expenses:food $13 assets:cash 2023-01-15 * paycheck income:salary assets:bank:checking $1000 2023-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc Show account names, and their hierarchy: $ hledger accounts --tree assets bank checking savings cash equity opening/closing balances expenses food misc income gifts salary liabilities creditcard Show all account totals: $ hledger balance $4105 assets $4000 bank $2000 checking $2000 savings $105 cash $-3050 equity:opening/closing balances $15 expenses $13 food $2 misc $-1020 income $-20 gifts $-1000 salary $-50 liabilities:creditcard -------------------- 0 Show only asset and liability balances, as a flat list, limited to depth 2: $ hledger bal assets liabilities -2 $4000 assets:bank $105 assets:cash $-50 liabilities:creditcard -------------------- $4055 Show the same thing without negative numbers, formatted as a simple balance sheet: $ hledger bs -2 Balance Sheet 2023-01-16 || 2023-01-16 ========================++============ Assets || ------------------------++------------ assets:bank || $4000 assets:cash || $105 ------------------------++------------ || $4105 ========================++============ Liabilities || ------------------------++------------ liabilities:creditcard || $50 ------------------------++------------ || $50 ========================++============ Net: || $4055 The final total is your "net worth" on the end date. (Or use bse for a full balance sheet with equity.) Show income and expense totals, formatted as an income statement: hledger is Income Statement 2023-01-01-2023-01-16 || 2023-01-01-2023-01-16 ===============++======================= Revenues || ---------------++----------------------- income:gifts || $20 income:salary || $1000 ---------------++----------------------- || $1020 ===============++======================= Expenses || ---------------++----------------------- expenses:food || $13 expenses:misc || $2 ---------------++----------------------- || $15 ===============++======================= Net: || $1005 The final total is your net income during this period. Show transactions affecting your wallet, with running total: $ hledger register cash 2023-01-01 opening balances assets:cash $100 $100 2023-01-10 gift received assets:cash $20 $120 2023-01-12 farmers market assets:cash $-13 $107 2023-01-16 adjust cash assets:cash $-2 $105 Show weekly posting counts as a bar chart: $ hledger activity -W 2019-12-30 ***** 2023-01-06 **** 2023-01-13 **** Migrating to a new file At the end of the year, you may want to continue your journal in a new file, so that old transactions don't slow down or clutter your reports, and to help ensure the integrity of your accounting history. See the close command. If using version control, don't forget to git add the new file. BUGS We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). Some known issues and limitations: The need to precede add-on command options with -- when invoked from hledger is awkward. (See Command options, Constructing command lines.) A UTF-8-aware system locale must be configured to work with non-ascii data. (See Unicode characters, Troubleshooting.) On Microsoft Windows, depending whether you are running in a CMD window or a Cygwin/MSYS/Mintty window and how you installed hledger, non-ascii characters and colours may not be supported, and the tab key may not be supported by hledger add. (Running in a WSL window should resolve these.) When processing large data files, hledger uses more memory than Ledger. Troubleshooting Here are some common issues you might encounter when you run hledger, and how to resolve them (and remember also you can usually get quick Support): PATH issues: I get an error like "No command 'hledger' found" Depending how you installed hledger, the executables may not be in your shell's PATH. Eg on unix systems, stack installs hledger in ~/.lo- cal/bin and cabal installs it in ~/.cabal/bin. You may need to add one of these directories to your shell's PATH, and/or open a new terminal window. LEDGER_FILE issues: I configured LEDGER_FILE but hledger is not using it o LEDGER_FILE should be a real environment variable, not just a shell variable. Eg on unix, the command env | grep LEDGER_FILE should show it. You may need to use export (see https://stackover- flow.com/a/7411509). o You may need to force your shell to see the new configuration. A simple way is to close your terminal window and open a new one. LANG issues: I get errors like "Illegal byte sequence" or "Invalid or incomplete multibyte or wide character" or "commitAndReleaseBuffer: in- valid argument (invalid character)" Programs compiled with GHC (hledger, haskell build tools, etc.) need the system locale to be UTF-8-aware, or they will fail when they en- counter non-ascii characters. To fix it, set the LANG environment variable to a locale which supports UTF-8 and which is installed on your system. On unix, locale -a lists the installed locales. Look for one which mentions utf8, UTF-8 or similar. Some examples: C.UTF-8, en_US.utf-8, fr_FR.utf8. If necessary, use your system package manager to install one. Then select it by setting the LANG environment variable. Note, exact spelling and capitalisation of the locale name may be important: Here's one common way to configure this permanently for your shell: $ echo "export LANG=en_US.utf8" >>~/.profile # close and re-open terminal window If you are using Nix (not NixOS) for GHC and Hledger, you might need to set the LOCALE_ARCHIVE variable: $ echo "export LOCALE_ARCHIVE=${glibcLocales}/lib/locale/locale-archive" >>~/.profile # close and re-open terminal window COMPATIBILITY ISSUES: hledger gives an error with my Ledger file Not all of Ledger's journal file syntax or feature set is supported. See hledger and Ledger for full details. AUTHORS Simon Michael and contributors. See http://hledger.org/CREDITS.html COPYRIGHT Copyright 2007-2023 Simon Michael and contributors. LICENSE Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), ledger(1) hledger-1.32.3 January 2024 HLEDGER(1) hledger-1.32.3/embeddedfiles/hledger.info0000644000000000000000000144755314555433336016501 0ustar0000000000000000This is hledger.info, produced by makeinfo version 7.1 from stdin. INFO-DIR-SECTION User Applications START-INFO-DIR-ENTRY * hledger: (hledger). Command-line plain text accounting tool. END-INFO-DIR-ENTRY  File: hledger.info, Node: Top, Next: PART 1 USER INTERFACE, Up: (dir) hledger(1) ********** hledger - robust, friendly plain text accounting (CLI version) 'hledger' 'hledger COMMAND [OPTS] [ARGS]' 'hledger ADDONCMD -- [OPTS] [ARGS]' hledger is a robust, user-friendly, cross-platform set of programs for tracking money, time, or any other commodity, using double-entry accounting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). This manual is for hledger's command line interface, version 1.32.3. It also describes the common options, file formats and concepts used by all hledger programs. It might accidentally teach you some bookkeeping/accounting as well! You don't need to know everything in here to use hledger productively, but when you have a question about functionality, this doc should answer it. It is detailed, so do skip ahead or skim when needed. You can read it on hledger.org, or as an info manual or man page on your system. You can also get it from hledger itself with 'hledger --man', 'hledger --info' or 'hledger help [TOPIC]'. The main function of the hledger CLI is to read plain text files describing financial transactions, crunch the numbers, and print a useful report on the terminal (or save it as HTML, CSV, JSON or SQL). Many reports are available, as subcommands. hledger will also detect other 'hledger-*' executables as extra subcommands. hledger usually reads from (and appends to) a journal file specified by the 'LEDGER_FILE' environment variable (defaulting to '$HOME/.hledger.journal'); or you can specify files with '-f' options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. Here is a small journal file describing one transaction: 2015-10-16 bought food expenses:food $10 assets:cash Transactions are dated movements of money (etc.) between two or more _accounts_: bank accounts, your wallet, revenue/expense categories, people, etc. You can choose any account names you wish, using ':' to indicate subaccounts. There must be at least two spaces between account name and amount. Positive amounts are inflow to that account (_debit_), negatives are outflow from it (_credit_). (Some reports show revenue, liability and equity account balances as negative numbers as a result; this is normal.) hledger's add command can help you add transactions, or you can install other data entry UIs like hledger-web or hledger-iadd. For more extensive/efficient changes, use a text editor: Emacs + ledger-mode, VIM + vim-ledger, or VS Code + hledger-vscode are some good choices (see https://hledger.org/editors.html). To get started, run 'hledger add' and follow the prompts, or save some entries like the above in '$HOME/.hledger.journal', then try commands like: 'hledger print -x' 'hledger aregister assets' 'hledger balance' 'hledger balancesheet' 'hledger incomestatement'. Run 'hledger' to list the commands. See also the "Starting a journal file" and "Setting opening balances" sections in PART 5: COMMON TASKS. * Menu: * PART 1 USER INTERFACE:: * Input:: * Commands:: * Options:: * Command line tips:: * Output:: * Environment:: * PART 2 DATA FORMATS:: * Journal:: * CSV:: * Timeclock:: * Timedot:: * PART 3 REPORTING CONCEPTS:: * Amount formatting parseability:: * Time periods:: * Depth:: * Queries:: * Pivoting:: * Generating data:: * Forecasting:: * Budgeting:: * Cost reporting:: * Value reporting:: * PART 4 COMMANDS:: * PART 5 COMMON TASKS:: * BUGS::  File: hledger.info, Node: PART 1 USER INTERFACE, Next: Input, Prev: Top, Up: Top 1 PART 1: USER INTERFACE ************************  File: hledger.info, Node: Input, Next: Commands, Prev: PART 1 USER INTERFACE, Up: Top 2 Input ******* hledger reads one or more data files, each time you run it. You can specify a file with '-f', like so $ hledger -f FILE print Files are most often in hledger's journal format, with the '.journal' file extension ('.hledger' or '.j' also work); these files describe transactions, like an accounting general journal. When no file is specified, hledger looks for '.hledger.journal' in your home directory. But most people prefer to keep financial files in a dedicated folder, perhaps with version control. Also, starting a new journal file each year is common (it's not required, but helps keep things fast and organised). So we usually configure a different journal file, by setting the 'LEDGER_FILE' environment variable, to something like '~/finance/2023.journal'. For more about how to do that on your system, see Common tasks > Setting LEDGER_FILE. * Menu: * Data formats:: * Standard input:: * Multiple files:: * Strict mode::  File: hledger.info, Node: Data formats, Next: Standard input, Up: Input 2.1 Data formats ================ Usually the data file is in hledger's journal format, but it can be in any of the supported file formats, which currently are: Reader: Reads: Used for file extensions: ---------------------------------------------------------------------------- 'journal' hledger journal files and '.journal' '.j' '.hledger' some Ledger journals, for '.ledger' transactions 'timeclock' timeclock files, for precise '.timeclock' time logging 'timedot' timedot files, for '.timedot' approximate time logging 'csv' CSV/SSV/TSV/character-separated '.csv' '.ssv' '.tsv' values, for data import '.csv.rules' '.ssv.rules' '.tsv.rules' These formats are described in more detail below. hledger detects the format automatically based on the file extensions shown above. If it can't recognise the file extension, it assumes 'journal' format. So for non-journal files, it's important to use a recognised file extension, so as to either read successfully or to show relevant error messages. You can also force a specific reader/format by prefixing the file path with the format and a colon. Eg, to read a .dat file as csv format: $ hledger -f csv:/some/csv-file.dat stats  File: hledger.info, Node: Standard input, Next: Multiple files, Prev: Data formats, Up: Input 2.2 Standard input ================== The file name '-' means standard input: $ cat FILE | hledger -f- print If reading non-journal data in this way, you'll need to add a file format prefix, like: $ echo 'i 2009/13/1 08:00:00' | hledger print -f timeclock:-  File: hledger.info, Node: Multiple files, Next: Strict mode, Prev: Standard input, Up: Input 2.3 Multiple files ================== You can specify multiple '-f' options, to read multiple files as one big journal. When doing this, note that certain features (described below) will be affected: * Balance assertions will not see the effect of transactions in previous files. (Usually this doesn't matter as each file will set the corresponding opening balances.) * Some directives will not affect previous or subsequent files. If needed, you can work around these by using a single parent file which includes the others, or concatenating the files into one, eg: 'cat a.journal b.journal | hledger -f- CMD'.  File: hledger.info, Node: Strict mode, Prev: Multiple files, Up: Input 2.4 Strict mode =============== hledger checks input files for valid data. By default, the most important errors are detected, while still accepting easy journal files without a lot of declarations: * Are the input files parseable, with valid syntax ? * Are all transactions balanced ? * Do all balance assertions pass ? With the '-s'/'--strict' flag, additional checks are performed: * Are all accounts posted to, declared with an 'account' directive ? (Account error checking) * Are all commodities declared with a 'commodity' directive ? (Commodity error checking) * Are all commodity conversions declared explicitly ? You can use the check command to run individual checks - the ones listed above and some more.  File: hledger.info, Node: Commands, Next: Options, Prev: Input, Up: Top 3 Commands ********** hledger provides various subcommands for getting things done. Most of these commands do not change the journal file; they just read it and output a report. A few commands assist with adding data and file management. To show the commands list, run 'hledger' with no arguments. The commands are described in detail in PART 4: COMMANDS, below. To use a particular command, run 'hledger CMD [CMDOPTS] [CMDARGS]', * CMD is the full command name, or its standard abbreviation shown in the commands list, or any unambiguous prefix of the name. * CMDOPTS are command-specific options, if any. Command-specific options must be written after the command name. Eg: 'hledger print -x'. * CMDARGS are additional arguments to the command, if any. Most hledger commands accept arguments representing a query, to limit the data in some way. Eg: 'hledger reg assets:checking'. To list a command's options, arguments, and documentation in the terminal, run 'hledger CMD -h'. Eg: 'hledger bal -h'. * Menu: * Add-on commands::  File: hledger.info, Node: Add-on commands, Up: Commands 3.1 Add-on commands =================== In addition to the built-in commands, you can install _add-on commands_: programs or scripts named "hledger-SOMETHING", which will also appear in hledger's commands list. If you used the hledger-install script, you will have several add-ons installed already. Some more can be found in hledger's bin/ directory, documented at https://hledger.org/scripts.html. More precisely, add-on commands are programs or scripts in your shell's PATH, whose name starts with "hledger-" and ends with no extension or a recognised extension (".bat", ".com", ".exe", ".hs", ".js", ".lhs", ".lua", ".php", ".pl", ".py", ".rb", ".rkt", or ".sh"), and (on unix and mac) which has executable permission for the current user. You can run add-on commands using hledger, much like built-in commands: 'hledger ADDONCMD [-- ADDONCMDOPTS] [ADDONCMDARGS]'. But note the double hyphen argument, required before add-on-specific options. Eg: 'hledger ui -- --watch' or 'hledger web -- --serve'. If this causes difficulty, you can always run the add-on directly, without using 'hledger': 'hledger-ui --watch' or 'hledger-web --serve'.  File: hledger.info, Node: Options, Next: Command line tips, Prev: Commands, Up: Top 4 Options ********* Run 'hledger -h' to see general command line help, and general options which are common to most hledger commands. These options can be written anywhere on the command line. They can be grouped into help, input, and reporting options: * Menu: * General help options:: * General input options:: * General reporting options::  File: hledger.info, Node: General help options, Next: General input options, Up: Options 4.1 General help options ======================== '-h --help' show general or COMMAND help '--man' show general or COMMAND user manual with man '--info' show general or COMMAND user manual with info '--version' show general or ADDONCMD version '--debug[=N]' show debug output (levels 1-9, default: 1)  File: hledger.info, Node: General input options, Next: General reporting options, Prev: General help options, Up: Options 4.2 General input options ========================= '-f FILE --file=FILE' use a different input file. For stdin, use - (default: '$LEDGER_FILE' or '$HOME/.hledger.journal') '--rules-file=RULESFILE' Conversion rules file to use when reading CSV (default: FILE.rules) '--separator=CHAR' Field separator to expect when reading CSV (default: ',') '--alias=OLD=NEW' rename accounts named OLD to NEW '--pivot FIELDNAME' use some other field or tag for the account name '-I --ignore-assertions' disable balance assertion checks (note: does not disable balance assignments) '-s --strict' do extra error checking (check that all posted accounts are declared)  File: hledger.info, Node: General reporting options, Prev: General input options, Up: Options 4.3 General reporting options ============================= '-b --begin=DATE' include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) '-e --end=DATE' include postings/txns before this date (will be adjusted to following subperiod end when using a report interval) '-D --daily' multiperiod/multicolumn report by day '-W --weekly' multiperiod/multicolumn report by week '-M --monthly' multiperiod/multicolumn report by month '-Q --quarterly' multiperiod/multicolumn report by quarter '-Y --yearly' multiperiod/multicolumn report by year '-p --period=PERIODEXP' set start date, end date, and/or reporting interval all at once using period expressions syntax '--date2' match the secondary date instead (see command help for other effects) '--today=DATE' override today's date (affects relative smart dates, for tests/examples) '-U --unmarked' include only unmarked postings/txns (can combine with -P or -C) '-P --pending' include only pending postings/txns '-C --cleared' include only cleared postings/txns '-R --real' include only non-virtual postings '-NUM --depth=NUM' hide/aggregate accounts or postings more than NUM levels deep '-E --empty' show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) '-B --cost' convert amounts to their cost/selling amount at transaction time '-V --market' convert amounts to their market value in default valuation commodities '-X --exchange=COMM' convert amounts to their market value in commodity COMM '--value' convert amounts to cost or market value, more flexibly than -B/-V/-X '--infer-equity' infer conversion equity postings from costs '--infer-costs' infer costs from conversion equity postings '--infer-market-prices' use costs as additional market prices, as if they were P directives '--forecast' generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger-ui make future-dated transactions visible. '--auto' generate extra postings by applying auto posting rules to all txns (not just forecast txns) '--verbose-tags' add visible tags indicating transactions or postings which have been generated/modified '--commodity-style' Override the commodity style in the output for the specified commodity. For example 'EUR1.000,00'. '--color=WHEN (or --colour=WHEN)' Should color-supporting commands use ANSI color codes in text output. 'auto' (default): whenever stdout seems to be a color-supporting terminal. 'always' or 'yes': always, useful eg when piping output into 'less -R'. 'never' or 'no': never. A NO_COLOR environment variable overrides this. '--pretty[=WHEN]' Show prettier output, e.g. using unicode box-drawing characters. Accepts 'yes' (the default) or 'no' ('y', 'n', 'always', 'never' also work). If you provide an argument you must use '=', e.g. '-pretty=yes'. When a reporting option appears more than once in the command line, the last one takes precedence. Some reporting options can also be written as query arguments.  File: hledger.info, Node: Command line tips, Next: Output, Prev: Options, Up: Top 5 Command line tips ******************* Here are some details useful to know about for hledger command lines (and elsewhere). Feel free to skip this section until you need it. * Menu: * Option repetition:: * Special characters:: * Unicode characters:: * Regular expressions:: * Argument files::  File: hledger.info, Node: Option repetition, Next: Special characters, Up: Command line tips 5.1 Option repetition ===================== If options are repeated in a command line, hledger will generally use the last (right-most) occurence.  File: hledger.info, Node: Special characters, Next: Unicode characters, Prev: Option repetition, Up: Command line tips 5.2 Special characters ====================== * Menu: * Single escaping shell metacharacters:: * Double escaping regular expression metacharacters:: * Triple escaping for add-on commands:: * Less escaping::  File: hledger.info, Node: Single escaping shell metacharacters, Next: Double escaping regular expression metacharacters, Up: Special characters 5.2.1 Single escaping (shell metacharacters) -------------------------------------------- In shell command lines, characters significant to your shell - such as spaces, '<', '>', '(', ')', '|', '$' and '\' - should be "shell-escaped" if you want hledger to see them. This is done by enclosing them in single or double quotes, or by writing a backslash before them. Eg to match an account name containing a space: $ hledger register 'credit card' or: $ hledger register credit\ card Windows users should keep in mind that 'cmd' treats single quote as a regular character, so you should be using double quotes exclusively. PowerShell treats both single and double quotes as quotes.  File: hledger.info, Node: Double escaping regular expression metacharacters, Next: Triple escaping for add-on commands, Prev: Single escaping shell metacharacters, Up: Special characters 5.2.2 Double escaping (regular expression metacharacters) --------------------------------------------------------- Characters significant in regular expressions (described below) - such as '.', '^', '$', '[', ']', '(', ')', '|', and '\' - may need to be "regex-escaped" if you don't want them to be interpreted by hledger's regular expression engine. This is done by writing backslashes before them, but since backslash is typically also a shell metacharacter, both shell-escaping and regex-escaping will be needed. Eg to match a literal '$' sign while using the bash shell: $ hledger balance cur:'\$' or: $ hledger balance cur:\\$  File: hledger.info, Node: Triple escaping for add-on commands, Next: Less escaping, Prev: Double escaping regular expression metacharacters, Up: Special characters 5.2.3 Triple escaping (for add-on commands) ------------------------------------------- When you use hledger to run an external add-on command (described below), one level of shell-escaping is lost from any options or arguments intended for by the add-on command, so those need an extra level of shell-escaping. Eg to match a literal '$' sign while using the bash shell and running an add-on command ('ui'): $ hledger ui cur:'\\$' or: $ hledger ui cur:\\\\$ If you wondered why _four_ backslashes, perhaps this helps: unescaped: '$' escaped: '\$' double-escaped: '\\$' triple-escaped: '\\\\$' Or, you can avoid the extra escaping by running the add-on executable directly: $ hledger-ui cur:\\$  File: hledger.info, Node: Less escaping, Prev: Triple escaping for add-on commands, Up: Special characters 5.2.4 Less escaping ------------------- Options and arguments are sometimes used in places other than the shell command line, where shell-escaping is not needed, so there you should use one less level of escaping. Those places include: * an @argumentfile * hledger-ui's filter field * hledger-web's search form * GHCI's prompt (used by developers).  File: hledger.info, Node: Unicode characters, Next: Regular expressions, Prev: Special characters, Up: Command line tips 5.3 Unicode characters ====================== hledger is expected to handle non-ascii characters correctly: * they should be parsed correctly in input files and on the command line, by all hledger tools (add, iadd, hledger-web's search/add/edit forms, etc.) * they should be displayed correctly by all hledger tools, and on-screen alignment should be preserved. This requires a well-configured environment. Here are some tips: * A system locale must be configured, and it must be one that can decode the characters being used. In bash, you can set a locale like this: 'export LANG=en_US.UTF-8'. There are some more details in Troubleshooting. This step is essential - without it, hledger will quit on encountering a non-ascii character (as with all GHC-compiled programs). * your terminal software (eg Terminal.app, iTerm, CMD.exe, xterm..) must support unicode * the terminal must be using a font which includes the required unicode glyphs * the terminal should be configured to display wide characters as double width (for report alignment) * on Windows, for best results you should run hledger in the same kind of environment in which it was built. Eg hledger built in the standard CMD.EXE environment (like the binaries on our download page) might show display problems when run in a cygwin or msys terminal, and vice versa. (See eg #961).  File: hledger.info, Node: Regular expressions, Next: Argument files, Prev: Unicode characters, Up: Command line tips 5.4 Regular expressions ======================= A regular expression (regexp) is a small piece of text where certain characters (like '.', '^', '$', '+', '*', '()', '|', '[]', '\') have special meanings, forming a tiny language for matching text precisely - very useful in hledger and elsewhere. To learn all about them, visit regular-expressions.info. hledger supports regexps whenever you are entering a pattern to match something, eg in query arguments, account aliases, CSV if rules, hledger-web's search form, hledger-ui's '/' search, etc. You may need to wrap them in quotes, especially at the command line (see Special characters above). Here are some examples: Account name queries (quoted for command line use): Regular expression: Matches: ------------------- ------------------------------------------------------------ bank assets:bank, assets:bank:savings, expenses:art:banksy, ... :bank assets:bank:savings, expenses:art:banksy :bank: assets:bank:savings '^bank' none of those ( ^ matches beginning of text ) 'bank$' assets:bank ( $ matches end of text ) 'big \$ bank' big $ bank ( \ disables following character's special meaning ) '\bbank\b' assets:bank, assets:bank:savings ( \b matches word boundaries ) '(sav|check)ing' saving or checking ( (|) matches either alternative ) 'saving|checking' saving or checking ( outer parentheses are not needed ) 'savings?' saving or savings ( ? matches 0 or 1 of the preceding thing ) 'my +bank' my bank, my bank, ... ( + matches 1 or more of the preceding thing ) 'my *bank' mybank, my bank, my bank, ... ( * matches 0 or more of the preceding thing ) 'b.nk' bank, bonk, b nk, ... ( . matches any character ) Some other queries: desc:'amazon|amzn|audible' Amazon transactions cur:EUR amounts with commodity symbol containing EUR cur:'\$' amounts with commodity symbol containing $ cur:'^\$$' only $ amounts, not eg AU$ or CA$ cur:....? amounts with 4-or-more-character symbols tag:.=202[1-3] things with any tag whose value contains 2021, 2022 or 2023 Account name aliases: accept '.' instead of ':' as account separator: alias /\./=: replaces all periods in account names with colons Show multiple top-level accounts combined as one: --alias='/^[^:]+/=combined' ( [^:] matches any character other than : ) Show accounts with the second-level part removed: --alias '/^([^:]+):[^:]+/ = \1' match a top-level account and a second-level account and replace those with just the top-level account ( \1 in the replacement text means "whatever was matched by the first parenthesised part of the regexp" CSV rules: match CSV records containing dining-related MCC codes: if \?MCC581[124] Match CSV records with a specific amount around the end/start of month: if %amount \b3\.99 & %date (29|30|31|01|02|03)$ * Menu: * hledger's regular expressions::  File: hledger.info, Node: hledger's regular expressions, Up: Regular expressions 5.4.1 hledger's regular expressions ----------------------------------- hledger's regular expressions come from the regex-tdfa library. If they're not doing what you expect, it's important to know exactly what they support: 1. they are case insensitive 2. they are infix matching (they do not need to match the entire thing being matched) 3. they are POSIX ERE (extended regular expressions) 4. they also support GNU word boundaries ('\b', '\B', '\<', '\>') 5. backreferences are supported when doing text replacement in account aliases or CSV rules, where backreferences can be used in the replacement string to reference capturing groups in the search regexp. Otherwise, if you write '\1', it will match the digit '1'. 6. they do not support mode modifiers ('(?s)'), character classes ('\w', '\d'), or anything else not mentioned above. Some things to note: * In the 'alias' directive and '--alias' option, regular expressions must be enclosed in forward slashes ('/REGEX/'). Elsewhere in hledger, these are not required. * In queries, to match a regular expression metacharacter like '$' as a literal character, prepend a backslash. Eg to search for amounts with the dollar sign in hledger-web, write 'cur:\$'. * On the command line, some metacharacters like '$' have a special meaning to the shell and so must be escaped at least once more. See Special characters.  File: hledger.info, Node: Argument files, Prev: Regular expressions, Up: Command line tips 5.5 Argument files ================== You can save a set of command line options and arguments in a file, and then reuse them by writing '@FILENAME' as a command line argument. Eg: 'hledger bal @foo.args'. Inside the argument file, each line should contain just one option or argument. Don't use spaces except inside quotes (or you'll see a confusing error); write '=' (or nothing) between a flag and its argument. For the special characters mentioned above, use one less level of quoting than you would at the command prompt.  File: hledger.info, Node: Output, Next: Environment, Prev: Command line tips, Up: Top 6 Output ******** * Menu: * Output destination:: * Output format:: * Commodity styles:: * Colour:: * Box-drawing:: * Paging:: * Debug output::  File: hledger.info, Node: Output destination, Next: Output format, Up: Output 6.1 Output destination ====================== hledger commands send their output to the terminal by default. You can of course redirect this, eg into a file, using standard shell syntax: $ hledger print > foo.txt Some commands (print, register, stats, the balance commands) also provide the '-o/--output-file' option, which does the same thing without needing the shell. Eg: $ hledger print -o foo.txt $ hledger print -o - # write to stdout (the default)  File: hledger.info, Node: Output format, Next: Commodity styles, Prev: Output destination, Up: Output 6.2 Output format ================= Some commands offer other kinds of output, not just text on the terminal. Here are those commands and the formats currently supported: - txt csv/tsv html json sql ------------------------------------------------------------------------------- aregister Y Y Y Y balance Y _1_ Y _1_ Y _1,2_ Y balancesheet Y _1_ Y _1_ Y _1_ Y balancesheetequityY _1_ Y _1_ Y _1_ Y cashflow Y _1_ Y _1_ Y _1_ Y incomestatement Y _1_ Y _1_ Y _1_ Y print Y Y Y Y register Y Y Y * _1 Also affected by the balance commands' '--layout' option._ * _2 'balance' does not support html output without a report interval or with '--budget'._ The output format is selected by the '-O/--output-format=FMT' option: $ hledger print -O csv # print CSV on stdout or by the filename extension of an output file specified with the '-o/--output-file=FILE.FMT' option: $ hledger balancesheet -o foo.csv # write CSV to foo.csv The '-O' option can be combined with '-o' to override the file extension, if needed: $ hledger balancesheet -o foo.txt -O csv # write CSV to foo.txt Some notes about the various output formats: * Menu: * CSV output:: * HTML output:: * JSON output:: * SQL output::  File: hledger.info, Node: CSV output, Next: HTML output, Up: Output format 6.2.1 CSV output ---------------- * In CSV output, digit group marks (such as thousands separators) are disabled automatically.  File: hledger.info, Node: HTML output, Next: JSON output, Prev: CSV output, Up: Output format 6.2.2 HTML output ----------------- * HTML output can be styled by an optional 'hledger.css' file in the same directory.  File: hledger.info, Node: JSON output, Next: SQL output, Prev: HTML output, Up: Output format 6.2.3 JSON output ----------------- * This is not yet much used; real-world feedback is welcome. * Our JSON is rather large and verbose, since it is a faithful representation of hledger's internal data types. To understand the JSON, read the Haskell type definitions, which are mostly in https://github.com/simonmichael/hledger/blob/master/hledger-lib/Hledger/Data/Types.hs. * hledger represents quantities as Decimal values storing up to 255 significant digits, eg for repeating decimals. Such numbers can arise in practice (from automatically-calculated transaction prices), and would break most JSON consumers. So in JSON, we show quantities as simple Numbers with at most 10 decimal places. We don't limit the number of integer digits, but that part is under your control. We hope this approach will not cause problems in practice; if you find otherwise, please let us know. (Cf #1195)  File: hledger.info, Node: SQL output, Prev: JSON output, Up: Output format 6.2.4 SQL output ---------------- * This is not yet much used; real-world feedback is welcome. * SQL output is expected to work at least with SQLite, MySQL and Postgres. * For SQLite, it will be more useful if you modify the generated 'id' field to be a PRIMARY KEY. Eg: $ hledger print -O sql | sed 's/id serial/id INTEGER PRIMARY KEY AUTOINCREMENT NOT NULL/g' | ... * SQL output is structured with the expectations that statements will be executed in the empty database. If you already have tables created via SQL output of hledger, you would probably want to either clear tables of existing data (via 'delete' or 'truncate' SQL statements) or drop tables completely as otherwise your postings will be duped.  File: hledger.info, Node: Commodity styles, Next: Colour, Prev: Output format, Up: Output 6.3 Commodity styles ==================== When displaying amounts, hledger infers a standard display style for each commodity/currency, as described below in Commodity display style. If needed, this can be overridden by a '-c/--commodity-style' option (except for cost amounts and amounts displayed by the 'print' command, which are always displayed with all decimal digits). For example, the following will force dollar amounts to be displayed as shown: $ hledger print -c '$1.000,0' This option can repeated to set the display style for multiple commodities/currencies. Its argument is as described in the commodity directive.  File: hledger.info, Node: Colour, Next: Box-drawing, Prev: Commodity styles, Up: Output 6.4 Colour ========== In terminal output, some commands can produce colour when the terminal supports it: * if the '--color/--colour' option is given a value of 'yes' or 'always' (or 'no' or 'never'), colour will (or will not) be used; * otherwise, if the 'NO_COLOR' environment variable is set, colour will not be used; * otherwise, colour will be used if the output (terminal or file) supports it.  File: hledger.info, Node: Box-drawing, Next: Paging, Prev: Colour, Up: Output 6.5 Box-drawing =============== In terminal output, you can enable unicode box-drawing characters to render prettier tables: * if the '--pretty' option is given a value of 'yes' or 'always' (or 'no' or 'never'), unicode characters will (or will not) be used; * otherwise, unicode characters will not be used.  File: hledger.info, Node: Paging, Next: Debug output, Prev: Box-drawing, Up: Output 6.6 Paging ========== When showing long output in the terminal, hledger will try to use the pager specified by the 'PAGER' environment variable, or 'less', or 'more'. (A pager is a helper program that shows one page at a time rather than scrolling everything off screen). Currently it does this only for help output, not for reports; specifically, * when listing commands, with 'hledger' * when showing help with 'hledger [CMD] --help', * when viewing manuals with 'hledger help' or 'hledger --man'. Note the pager is expected to handle ANSI codes, which hledger uses eg for bold emphasis. For the common pager 'less' (and its 'more' compatibility mode), we add 'R' to the 'LESS' and 'MORE' environment variables to make this work. If you use a different pager, you might need to configure it similarly, to avoid seeing junk on screen (let us know). Otherwise, you can set the 'NO_COLOR' environment variable to 1 to disable all ANSI output (see Colour).  File: hledger.info, Node: Debug output, Prev: Paging, Up: Output 6.7 Debug output ================ We intend hledger to be relatively easy to troubleshoot, introspect and develop. You can add '--debug[=N]' to any hledger command line to see additional debug output. N ranges from 1 (least output, the default) to 9 (maximum output). Typically you would start with 1 and increase until you are seeing enough. Debug output goes to stderr, and is not affected by '-o/--output-file' (unless you redirect stderr to stdout, eg: '2>&1'). It will be interleaved with normal output, which can help reveal when parts of the code are evaluated. To capture debug output in a log file instead, you can usually redirect stderr, eg: hledger bal --debug=3 2>hledger.log  File: hledger.info, Node: Environment, Next: PART 2 DATA FORMATS, Prev: Output, Up: Top 7 Environment ************* These environment variables affect hledger: *COLUMNS* This is normally set by your terminal; some hledger commands ('register') will format their output to this width. If not set, they will try to use the available terminal width. *LEDGER_FILE* The main journal file to use when not specified with '-f/--file'. Default: '$HOME/.hledger.journal'. *NO_COLOR* If this environment variable is set (with any value), hledger will not use ANSI color codes in terminal output, unless overridden by an explicit '--color/--colour' option.  File: hledger.info, Node: PART 2 DATA FORMATS, Next: Journal, Prev: Environment, Up: Top 8 PART 2: DATA FORMATS **********************  File: hledger.info, Node: Journal, Next: CSV, Prev: PART 2 DATA FORMATS, Up: Top 9 Journal ********* hledger's default file format, representing a General Journal. Here's a cheatsheet/mini-tutorial, or you can skip ahead to About journal format. * Menu: * Journal cheatsheet:: * About journal format:: * Comments:: * Transactions:: * Dates:: * Status:: * Code:: * Description:: * Transaction comments:: * Postings:: * Account names:: * Amounts:: * Costs:: * Balance assertions:: * Posting comments:: * Tags:: * Directives:: * account directive:: * alias directive:: * commodity directive:: * decimal-mark directive:: * include directive:: * P directive:: * payee directive:: * tag directive:: * Periodic transactions:: * Auto postings:: * Other syntax::  File: hledger.info, Node: Journal cheatsheet, Next: About journal format, Up: Journal 9.1 Journal cheatsheet ====================== # Here is the main syntax of hledger's journal format # (omitting extra Ledger compatibility syntax). # hledger journals contain comments, directives, and transactions, in any order: ############################################################################### # 1. Comment lines are for notes or temporarily disabling things. # They begin with #, ;, or a line containing the word "comment". # hash comment line ; semicolon comment line comment These lines are commented. end comment # Some but not all hledger entries can have same-line comments attached to them, # from ; (semicolon) to end of line. ############################################################################### # 2. Directives modify parsing or reports in some way. # They begin with a word or letter (or symbol). account actifs ; type:A, declare an account that is an Asset. 2+ spaces before ;. account passifs ; type:L, declare an account that is a Liability, and so on.. (ALERX) alias chkg = assets:checking commodity $0.00 decimal-mark . include /dev/null payee Whole Foods P 2022-01-01 AAAA $1.40 ~ monthly budget goals ; <- 2+ spaces between period expression and description expenses:food $400 expenses:home $1000 budgeted ############################################################################### # 3. Transactions are what it's all about; they are dated events, # usually describing movements of money. # They begin with a date. # DATE DESCRIPTION ; This is a transaction comment. # ACCOUNT NAME 1 AMOUNT1 ; <- posting 1. This is a posting comment. # ACCOUNT NAME 2 AMOUNT2 ; <- posting 2. Postings must be indented. # ; ^^ At least 2 spaces between account and amount. # ... ; Any number of postings is allowed. The amounts must balance (sum to 0). 2022-01-01 opening balances are declared this way assets:checking $1000 ; Account names can be anything. lower case is easy to type. assets:savings $1000 ; assets, liabilities, equity, revenues, expenses are common. assets:cash:wallet $100 ; : indicates subaccounts. liabilities:credit card $-200 ; liabilities, equity, revenues balances are usually negative. equity ; One amount can be left blank; $-1900 is inferred here. 2022-04-15 * (#12345) pay taxes ; There can be a ! or * after the date meaning "pending" or "cleared". ; There can be a transaction code (text in parentheses) after the date/status. ; Amounts' sign represents direction of flow, or credit/debit: assets:checking $-500 ; minus means removed from this account (credit) expenses:tax:us:2021 $500 ; plus means added to this account (debit) ; revenue/expense categories are also "accounts" 2022-01-01 ; The description is optional. ; Any currency/commodity symbols are allowed, on either side. assets:cash:wallet GBP -10 expenses:clothing GBP 10 assets:gringotts -10 gold assets:pouch 10 gold revenues:gifts -2 "Liquorice Wands" ; Complex symbols assets:bag 2 "Liquorice Wands" ; must be double-quoted. 2022-01-01 Cost in another commodity can be noted with @ or @@ assets:investments 2.0 AAAA @ $1.50 ; @ means per-unit cost assets:investments 3.0 AAAA @@ $4 ; @@ means total cost assets:checking $-7.00 2022-01-02 assert balances ; Balances can be asserted for extra error checking, in any transaction. assets:investments 0 AAAA = 5.0 AAAA assets:pouch 0 gold = 10 gold assets:savings $0 = $1000 1999-12-31 Ordering transactions by date is recommended but not required. ; Postings are not required. 2022.01.01 These date 2022/1/1 formats are 12/31 also allowed (but consistent YYYY-MM-DD is recommended).  File: hledger.info, Node: About journal format, Next: Comments, Prev: Journal cheatsheet, Up: Journal 9.2 About journal format ======================== hledger's usual data source is a plain text file containing journal entries in hledger journal format. This file represents a standard accounting general journal. I use file names ending in '.journal', but that's not required. The journal file contains a number of transaction entries, each describing a transfer of money (or any commodity) between two or more named accounts, in a simple format readable by both hledger and humans. hledger's journal format is compatible with most of Ledger's journal format, but not all of it. The differences and interoperation tips are described at hledger and Ledger. With some care, and by avoiding incompatible features, you can keep your hledger journal readable by Ledger and vice versa. This can useful eg for comparing the behaviour of one app against the other. You can use hledger without learning any more about this file; just use the add or web or import commands to create and update it. Many users, though, edit the journal file with a text editor, and track changes with a version control system such as git. Editor addons such as ledger-mode or hledger-mode for Emacs, vim-ledger for Vim, and hledger-vscode for Visual Studio Code, make this easier, adding colour, formatting, tab completion, and useful commands. See Editor configuration at hledger.org for the full list. Here's a description of each part of the file format (and hledger's data model). A hledger journal file can contain three kinds of thing: file comments, transactions, and/or directives (counting periodic transaction rules and auto posting rules as directives).  File: hledger.info, Node: Comments, Next: Transactions, Prev: About journal format, Up: Journal 9.3 Comments ============ Lines in the journal will be ignored if they begin with a hash ('#') or a semicolon (';'). (See also Other syntax.) hledger will also ignore regions beginning with a 'comment' line and ending with an 'end comment' line (or file end). Here's a suggestion for choosing between them: * '#' for top-level notes * ';' for commenting out things temporarily * 'comment' for quickly commenting large regions (remember it's there, or you might get confused) Eg: # a comment line ; another commentline comment A multi-line comment block, continuing until "end comment" directive or the end of the current file. end comment Some hledger entries can have same-line comments attached to them, from ; (semicolon) to end of line. See Transaction comments, Posting comments, and Account comments below.  File: hledger.info, Node: Transactions, Next: Dates, Prev: Comments, Up: Journal 9.4 Transactions ================ Transactions are the main unit of information in a journal file. They represent events, typically a movement of some quantity of commodities between two or more named accounts. Each transaction is recorded as a journal entry, beginning with a simple date in column 0. This can be followed by any of the following optional fields, separated by spaces: * a status character (empty, '!', or '*') * a code (any short number or text, enclosed in parentheses) * a description (any remaining text until end of line or a semicolon) * a comment (any remaining text following a semicolon until end of line, and any following indented lines beginning with a semicolon) * 0 or more indented _posting_ lines, describing what was transferred and the accounts involved (indented comment lines are also allowed, but not blank lines or non-indented lines). Here's a simple journal file containing one transaction: 2008/01/01 income assets:bank:checking $1 income:salary $-1  File: hledger.info, Node: Dates, Next: Status, Prev: Transactions, Up: Journal 9.5 Dates ========= * Menu: * Simple dates:: * Posting dates::  File: hledger.info, Node: Simple dates, Next: Posting dates, Up: Dates 9.5.1 Simple dates ------------------ Dates in the journal file use _simple dates_ format: 'YYYY-MM-DD' or 'YYYY/MM/DD' or 'YYYY.MM.DD', with leading zeros optional. The year may be omitted, in which case it will be inferred from the context: the current transaction, the default year set with a 'Y' directive, or the current date when the command is run. Some examples: '2010-01-31', '2010/01/31', '2010.1.31', '1/31'. (The UI also accepts simple dates, as well as the more flexible smart dates documented in the hledger manual.)  File: hledger.info, Node: Posting dates, Prev: Simple dates, Up: Dates 9.5.2 Posting dates ------------------- You can give individual postings a different date from their parent transaction, by adding a posting comment containing a tag (see below) like 'date:DATE'. This is probably the best way to control posting dates precisely. Eg in this example the expense should appear in May reports, and the deduction from checking should be reported on 6/1 for easy bank reconciliation: 2015/5/30 expenses:food $10 ; food purchased on saturday 5/30 assets:checking ; bank cleared it on monday, date:6/1 $ hledger -f t.j register food 2015-05-30 expenses:food $10 $10 $ hledger -f t.j register checking 2015-06-01 assets:checking $-10 $-10 DATE should be a simple date; if the year is not specified it will use the year of the transaction's date. The 'date:' tag must have a valid simple date value if it is present, eg a 'date:' tag with no value is not allowed.  File: hledger.info, Node: Status, Next: Code, Prev: Dates, Up: Journal 9.6 Status ========== Transactions, or individual postings within a transaction, can have a status mark, which is a single character before the transaction description or posting account name, separated from it by a space, indicating one of three statuses: mark status ----------------- unmarked '!' pending '*' cleared When reporting, you can filter by status with the '-U/--unmarked', '-P/--pending', and '-C/--cleared' flags; or the 'status:', 'status:!', and 'status:*' queries; or the U, P, C keys in hledger-ui. Note, in Ledger and in older versions of hledger, the "unmarked" state is called "uncleared". As of hledger 1.3 we have renamed it to unmarked for clarity. To replicate Ledger and old hledger's behaviour of also matching pending, combine -U and -P. Status marks are optional, but can be helpful eg for reconciling with real-world accounts. Some editor modes provide highlighting and shortcuts for working with status. Eg in Emacs ledger-mode, you can toggle transaction status with C-c C-e, or posting status with C-c C-c. What "uncleared", "pending", and "cleared" actually mean is up to you. Here's one suggestion: status meaning -------------------------------------------------------------------------- uncleared recorded but not yet reconciled; needs review pending tentatively reconciled (if needed, eg during a big reconciliation) cleared complete, reconciled as far as possible, and considered correct With this scheme, you would use '-PC' to see the current balance at your bank, '-U' to see things which will probably hit your bank soon (like uncashed checks), and no flags to see the most up-to-date state of your finances.  File: hledger.info, Node: Code, Next: Description, Prev: Status, Up: Journal 9.7 Code ======== After the status mark, but before the description, you can optionally write a transaction "code", enclosed in parentheses. This is a good place to record a check number, or some other important transaction id or reference number.  File: hledger.info, Node: Description, Next: Transaction comments, Prev: Code, Up: Journal 9.8 Description =============== A transaction's description is the rest of the line following the date and status mark (or until a comment begins). Sometimes called the "narration" in traditional bookkeeping, it can be used for whatever you wish, or left blank. Transaction descriptions can be queried, unlike comments. * Menu: * Payee and note::  File: hledger.info, Node: Payee and note, Up: Description 9.8.1 Payee and note -------------------- You can optionally include a '|' (pipe) character in descriptions to subdivide the description into separate fields for payee/payer name on the left (up to the first '|') and an additional note field on the right (after the first '|'). This may be worthwhile if you need to do more precise querying and pivoting by payee or by note.  File: hledger.info, Node: Transaction comments, Next: Postings, Prev: Description, Up: Journal 9.9 Transaction comments ======================== Text following ';', after a transaction description, and/or on indented lines immediately below it, form comments for that transaction. They are reproduced by 'print' but otherwise ignored, except they may contain tags, which are not ignored. 2012-01-01 something ; a transaction comment ; a second line of transaction comment expenses 1 assets  File: hledger.info, Node: Postings, Next: Account names, Prev: Transaction comments, Up: Journal 9.10 Postings ============= A posting is an addition of some amount to, or removal of some amount from, an account. Each posting line begins with at least one space or tab (2 or 4 spaces is common), followed by: * (optional) a status character (empty, '!', or '*'), followed by a space * (required) an account name (any text, optionally containing *single spaces*, until end of line or a double space) * (optional) *two or more spaces* or tabs followed by an amount. Positive amounts are being added to the account, negative amounts are being removed. The amounts within a transaction must always sum up to zero. As a convenience, one amount may be left blank; it will be inferred so as to balance the transaction. Be sure to note the unusual two-space delimiter between account name and amount. This makes it easy to write account names containing spaces. But if you accidentally leave only one space (or tab) before the amount, the amount will be considered part of the account name.  File: hledger.info, Node: Account names, Next: Amounts, Prev: Postings, Up: Journal 9.11 Account names ================== Accounts are the main way of categorising things in hledger. As in Double Entry Bookkeeping, they can represent real world accounts (such as a bank account), or more abstract categories such as "money borrowed from Frank" or "money spent on electricity". You can use any account names you like, but we usually start with the traditional accounting categories, which in english are 'assets', 'liabilities', 'equity', 'revenues', 'expenses'. (You might see these referred to as A, L, E, R, X for short.) For more precise reporting, we usually divide the top level accounts into more detailed subaccounts, by writing a full colon between account name parts. For example, from the account names 'assets:bank:checking' and 'expenses:food', hledger will infer this hierarchy of five accounts: assets assets:bank assets:bank:checking expenses expenses:food Shown as an outline, the hierarchical tree structure is more clear: assets bank checking expenses food hledger reports can summarise the account tree to any depth, so you can go as deep as you like with subcategories, but keeping your account names relatively simple may be best when starting out. Account names may be capitalised or not; they may contain letters, numbers, symbols, or single spaces. Note, when an account name and an amount are written on the same line, they must be separated by *two or more spaces* (or tabs). Parentheses or brackets enclosing the full account name indicate virtual postings, described below. Parentheses or brackets internal to the account name have no special meaning. Account names can be altered temporarily or permanently by account aliases.  File: hledger.info, Node: Amounts, Next: Costs, Prev: Account names, Up: Journal 9.12 Amounts ============ After the account name, there is usually an amount. (Important: between account name and amount, there must be *two or more spaces*.) hledger's amount format is flexible, supporting several international formats. Here are some examples. Amounts have a number (the "quantity"): 1 ..and usually a currency symbol or commodity name (more on this below), to the left or right of the quantity, with or without a separating space: $1 4000 AAPL 3 "green apples" Amounts can be preceded by a minus sign (or a plus sign, though plus is the default), The sign can be written before or after a left-side commodity symbol: -$1 $-1 One or more spaces between the sign and the number are acceptable when parsing (but they won't be displayed in output): + $1 $- 1 Scientific E notation is allowed: 1E-6 EUR 1E3 * Menu: * Decimal marks digit group marks:: * Commodity:: * Directives influencing number parsing and display:: * Commodity display style:: * Rounding::  File: hledger.info, Node: Decimal marks digit group marks, Next: Commodity, Up: Amounts 9.12.1 Decimal marks, digit group marks --------------------------------------- A _decimal mark_ can be written as a period or a comma: 1.23 1,23 In the integer part of the quantity (left of the decimal mark), groups of digits can optionally be separated by a _digit group mark_ - a space, comma, or period (different from the decimal mark): $1,000,000.00 EUR 2.000.000,00 INR 9,99,99,999.00 1 000 000.9455 hledger is not biased towards period or comma decimal marks, so a number containing just one period or comma, like '1,000' or '1.000', is ambiguous. In such cases hledger assumes it is a decimal mark, parsing both of these as 1. To disambiguate these and ensure accurate number parsing, especially if you use digit group marks, we recommend declaring the decimal mark. You can declare it for each file with 'decimal-mark' directives, or for each commodity with 'commodity' directives (described below).  File: hledger.info, Node: Commodity, Next: Directives influencing number parsing and display, Prev: Decimal marks digit group marks, Up: Amounts 9.12.2 Commodity ---------------- Amounts in hledger have both a "quantity", which is a signed decimal number, and a "commodity", which is a currency symbol, stock ticker, or any word or phrase describing something you are tracking. If the commodity name contains non-letters (spaces, numbers, or punctuation), you must always write it inside double quotes ('"green apples"', '"ABC123"'). If you write just a bare number, that too will have a commodity, with name '""'; we call that the "no-symbol commodity". Actually, hledger combines these single-commodity amounts into more powerful multi-commodity amounts, which are what it works with most of the time. A multi-commodity amount could be, eg: '1 USD, 2 EUR, 3.456 TSLA'. In practice, you will only see multi-commodity amounts in hledger's output; you can't write them directly in the journal file. (If you are writing scripts or working with hledger's internals, these are the 'Amount' and 'MixedAmount' types.)  File: hledger.info, Node: Directives influencing number parsing and display, Next: Commodity display style, Prev: Commodity, Up: Amounts 9.12.3 Directives influencing number parsing and display -------------------------------------------------------- You can add 'decimal-mark' and 'commodity' directives to the journal, to declare and control these things more explicitly and precisely. These are described below, but here's a quick example: # the decimal mark character used by all amounts in this file (all commodities) decimal-mark . # display styles for the $, EUR, INR and no-symbol commodities: commodity $1,000.00 commodity EUR 1.000,00 commodity INR 9,99,99,999.00 commodity 1 000 000.9455  File: hledger.info, Node: Commodity display style, Next: Rounding, Prev: Directives influencing number parsing and display, Up: Amounts 9.12.4 Commodity display style ------------------------------ For the amounts in each commodity, hledger chooses a consistent display style (symbol placement, decimal mark and digit group marks, number of decimal digits) to use in most reports. This is inferred as follows: First, if there's a 'D' directive declaring a default commodity, that commodity symbol and amount format is applied to all no-symbol amounts in the journal. Then each commodity's display style is determined from its 'commodity' directive. We recommend always declaring commodities with 'commodity' directives, since they help ensure consistent display styles and precisions, and bring other benefits such as error checking for commodity symbols. But if a 'commodity' directive is not present, hledger infers a commodity's display styles from its amounts as they are written in the journal (excluding cost amounts and amounts in periodic transaction rules or auto posting rules). It uses * the symbol placement and decimal mark of the first amount seen * the digit group marks of the first amount with digit group marks * and the maximum number of decimal digits seen across all amounts. And as fallback if no applicable amounts are found, it would use a default style, like '$1000.00' (symbol on the left with no space, period as decimal mark, and two decimal digits). Finally, commodity styles can be overridden by the '-c/--commodity-style' command line option.  File: hledger.info, Node: Rounding, Prev: Commodity display style, Up: Amounts 9.12.5 Rounding --------------- Amounts are stored internally as decimal numbers with up to 255 decimal places. They are displayed with their original journal precisions by print and print-like reports, and rounded to their display precision (the number of decimal digits specified by the commodity display style) by other reports. When rounding, hledger uses banker's rounding (it rounds to the nearest even digit). So eg 0.5 displayed with zero decimal digits appears as "0".  File: hledger.info, Node: Costs, Next: Balance assertions, Prev: Amounts, Up: Journal 9.13 Costs ========== After a posting amount, you can note its cost (when buying) or selling price (when selling) in another commodity, by writing either '@ UNITPRICE' or '@@ TOTALPRICE' after it. This indicates a conversion transaction, where one commodity is exchanged for another. (You might also see this called "transaction price" in hledger docs, discussions, or code; that term was directionally neutral and reminded that it is a price specific to a transaction, but we now just call it "cost", with the understanding that the transaction could be a purchase or a sale.) Costs are usually written explicitly with '@' or '@@', but can also be inferred automatically for simple multi-commodity transactions. Note, if costs are inferred, the order of postings is significant; the first posting will have a cost attached, in the commodity of the second. As an example, here are several ways to record purchases of a foreign currency in hledger, using the cost notation either explicitly or implicitly: 1. Write the price per unit, as '@ UNITPRICE' after the amount: 2009/1/1 assets:euros €100 @ $1.35 ; one hundred euros purchased at $1.35 each assets:dollars ; balancing amount is -$135.00 2. Write the total price, as '@@ TOTALPRICE' after the amount: 2009/1/1 assets:euros €100 @@ $135 ; one hundred euros purchased at $135 for the lot assets:dollars 3. Specify amounts for all postings, using exactly two commodities, and let hledger infer the price that balances the transaction. Note the effect of posting order: the price is added to first posting, making it '€100 @@ $135', as in example 2: 2009/1/1 assets:euros €100 ; one hundred euros purchased assets:dollars $-135 ; for $135 Amounts can be converted to cost at report time using the '-B/--cost' flag; this is discussed more in the Cost reporting section. Note that the cost normally should be a positive amount, though it's not required to be. This can be a little confusing, see discussion at -infer-market-prices: market prices from transactions. * Menu: * Other cost/lot notations::  File: hledger.info, Node: Other cost/lot notations, Up: Costs 9.13.1 Other cost/lot notations ------------------------------- A slight digression for Ledger and Beancount users. Ledger has a number of cost/lot-related notations: * '@ UNITCOST' and '@@ TOTALCOST' * expresses a conversion rate, as in hledger * when buying, also creates a lot than can be selected at selling time * '(@) UNITCOST' and '(@@) TOTALCOST' (virtual cost) * like the above, but also means "this cost was exceptional, don't use it when inferring market prices". Currently, hledger treats the above like '@' and '@@'; the parentheses are ignored. * '{=FIXEDUNITCOST}' and '{{=FIXEDTOTALCOST}}' (fixed price) * when buying, means "this cost is also the fixed price, don't let it fluctuate in value reports" * '{UNITCOST}' and '{{TOTALCOST}}' (lot price) * can be used identically to '@ UNITCOST' and '@@ TOTALCOST', also creates a lot * when selling, combined with '@ ...', specifies an investment lot by its cost basis; does not check if that lot is present * and related: '[YYYY/MM/DD]' (lot date) * when buying, attaches this acquisition date to the lot * when selling, selects a lot by its acquisition date * '(SOME TEXT)' (lot note) * when buying, attaches this note to the lot * when selling, selects a lot by its note Currently, hledger accepts any or all of the above in any order after the posting amount, but ignores them. (This can break transaction balancing.) For Beancount users, the notation and behaviour is different: * '@ UNITCOST' and '@@ TOTALCOST' * expresses a cost without creating a lot, as in hledger * when buying (augmenting) or selling (reducing) a lot, combined with '{...}': documents the cost/selling price (not used for transaction balancing) * '{UNITCOST}' and '{{TOTALCOST}}' * when buying (augmenting), expresses the cost for transaction balancing, and also creates a lot with this cost basis attached * when selling (reducing), * selects a lot by its cost basis * raises an error if that lot is not present or can not be selected unambiguously (depending on booking method configured) * expresses the selling price for transaction balancing Currently, hledger accepts the '{UNITCOST}'/'{{TOTALCOST}}' notation but ignores it. * variations: '{}', '{YYYY-MM-DD}', '{"LABEL"}', '{UNITCOST, "LABEL"}', '{UNITCOST, YYYY-MM-DD, "LABEL"}' etc. Currently, hledger rejects these.  File: hledger.info, Node: Balance assertions, Next: Posting comments, Prev: Costs, Up: Journal 9.14 Balance assertions ======================= hledger supports Ledger-style balance assertions in journal files. These look like, for example, '= EXPECTEDBALANCE' following a posting's amount. Eg here we assert the expected dollar balance in accounts a and b after each posting: 2013/1/1 a $1 =$1 b =$-1 2013/1/2 a $1 =$2 b $-1 =$-2 After reading a journal file, hledger will check all balance assertions and report an error if any of them fail. Balance assertions can protect you from, eg, inadvertently disrupting reconciled balances while cleaning up old entries. You can disable them temporarily with the '-I/--ignore-assertions' flag, which can be useful for troubleshooting or for reading Ledger files. (Note: this flag currently does not disable balance assignments, described below). * Menu: * Assertions and ordering:: * Assertions and multiple included files:: * Assertions and multiple -f files:: * Assertions and commodities:: * Assertions and costs:: * Assertions and subaccounts:: * Assertions and virtual postings:: * Assertions and auto postings:: * Assertions and precision::  File: hledger.info, Node: Assertions and ordering, Next: Assertions and multiple included files, Up: Balance assertions 9.14.1 Assertions and ordering ------------------------------ hledger sorts an account's postings and assertions first by date and then (for postings on the same day) by parse order. Note this is different from Ledger, which sorts assertions only by parse order. (Also, Ledger assertions do not see the accumulated effect of repeated postings to the same account within a transaction.) So, hledger balance assertions keep working if you reorder differently-dated transactions within the journal. But if you reorder same-dated transactions or postings, assertions might break and require updating. This order dependence does bring an advantage: precise control over the order of postings and assertions within a day, so you can assert intra-day balances.  File: hledger.info, Node: Assertions and multiple included files, Next: Assertions and multiple -f files, Prev: Assertions and ordering, Up: Balance assertions 9.14.2 Assertions and multiple included files --------------------------------------------- Multiple files included with the 'include' directive are processed as if concatenated into one file, preserving their order and the posting order within each file. It means that balance assertions in later files will see balance from earlier files. And if you have multiple postings to an account on the same day, split across multiple files, and you want to assert the account's balance on that day, you'll need to put the assertion in the right file - the last one in the sequence, probably.  File: hledger.info, Node: Assertions and multiple -f files, Next: Assertions and commodities, Prev: Assertions and multiple included files, Up: Balance assertions 9.14.3 Assertions and multiple -f files --------------------------------------- Unlike 'include', when multiple files are specified on the command line with multiple '-f/--file' options, balance assertions will not see balance from earlier files. This can be useful when you do not want problems in earlier files to disrupt valid assertions in later files. If you do want assertions to see balance from earlier files, use 'include', or concatenate the files temporarily.  File: hledger.info, Node: Assertions and commodities, Next: Assertions and costs, Prev: Assertions and multiple -f files, Up: Balance assertions 9.14.4 Assertions and commodities --------------------------------- The asserted balance must be a simple single-commodity amount, and in fact the assertion checks only this commodity's balance within the (possibly multi-commodity) account balance. This is how assertions work in Ledger also. We could call this a "partial" balance assertion. To assert the balance of more than one commodity in an account, you can write multiple postings, each asserting one commodity's balance. You can make a stronger "total" balance assertion by writing a double equals sign ('== EXPECTEDBALANCE'). This asserts that there are no other commodities in the account besides the asserted one (or at least, that their balance is 0). 2013/1/1 a $1 a 1€ b $-1 c -1€ 2013/1/2 ; These assertions succeed a 0 = $1 a 0 = 1€ b 0 == $-1 c 0 == -1€ 2013/1/3 ; This assertion fails as 'a' also contains 1€ a 0 == $1 It's not yet possible to make a complete assertion about a balance that has multiple commodities. One workaround is to isolate each commodity into its own subaccount: 2013/1/1 a:usd $1 a:euro 1€ b 2013/1/2 a 0 == 0 a:usd 0 == $1 a:euro 0 == 1€  File: hledger.info, Node: Assertions and costs, Next: Assertions and subaccounts, Prev: Assertions and commodities, Up: Balance assertions 9.14.5 Assertions and costs --------------------------- Balance assertions ignore costs, and should normally be written without one: 2019/1/1 (a) $1 @ €1 = $1 We do allow costs to be written in balance assertion amounts, however, and print shows them, but they don't affect whether the assertion passes or fails. This is for backward compatibility (hledger's close command used to generate balance assertions with costs), and because balance _assignments_ do use costs (see below).  File: hledger.info, Node: Assertions and subaccounts, Next: Assertions and virtual postings, Prev: Assertions and costs, Up: Balance assertions 9.14.6 Assertions and subaccounts --------------------------------- The balance assertions above ('=' and '==') do not count the balance from subaccounts; they check the account's exclusive balance only. You can assert the balance including subaccounts by writing '=*' or '==*', eg: 2019/1/1 equity:opening balances checking:a 5 checking:b 5 checking 1 ==* 11  File: hledger.info, Node: Assertions and virtual postings, Next: Assertions and auto postings, Prev: Assertions and subaccounts, Up: Balance assertions 9.14.7 Assertions and virtual postings -------------------------------------- Balance assertions always consider both real and virtual postings; they are not affected by the '--real/-R' flag or 'real:' query.  File: hledger.info, Node: Assertions and auto postings, Next: Assertions and precision, Prev: Assertions and virtual postings, Up: Balance assertions 9.14.8 Assertions and auto postings ----------------------------------- Balance assertions _are_ affected by the '--auto' flag, which generates auto postings, which can alter account balances. Because auto postings are optional in hledger, accounts affected by them effectively have two balances. But balance assertions can only test one or the other of these. So to avoid making fragile assertions, either: * assert the balance calculated with '--auto', and always use '--auto' with that file * or assert the balance calculated without '--auto', and never use '--auto' with that file * or avoid balance assertions on accounts affected by auto postings (or avoid auto postings entirely).  File: hledger.info, Node: Assertions and precision, Prev: Assertions and auto postings, Up: Balance assertions 9.14.9 Assertions and precision ------------------------------- Balance assertions compare the exactly calculated amounts, which are not always what is shown by reports. Eg a commodity directive may limit the display precision, but this will not affect balance assertions. Balance assertion failure messages show exact amounts.  File: hledger.info, Node: Posting comments, Next: Tags, Prev: Balance assertions, Up: Journal 9.15 Posting comments ===================== Text following ';', at the end of a posting line, and/or on indented lines immediately below it, form comments for that posting. They are reproduced by 'print' but otherwise ignored, except they may contain tags, which are not ignored. 2012-01-01 expenses 1 ; a comment for posting 1 assets ; a comment for posting 2 ; a second comment line for posting 2  File: hledger.info, Node: Tags, Next: Directives, Prev: Posting comments, Up: Journal 9.16 Tags ========= Tags are a way to add extra labels or labelled data to transactions, postings, or accounts, which you can then search or pivot on. They are written as a word (optionally hyphenated) immediately followed by a full colon, in a transaction or posting or account directive's comment. (This is an exception to the usual rule that things in comments are ignored.) Eg, here four different tags are recorded: one on the checking account, two on the transaction, and one on the expenses posting: account assets:checking ; accounttag: 2017/1/16 bought groceries ; transactiontag-1: ; transactiontag-2: assets:checking $-1 expenses:food $1 ; postingtag: Postings also inherit tags from their transaction and their account. And transactions also acquire tags from their postings (and postings' accounts). So in the example above, the expenses posting effectively has all four tags (by inheriting from account and transaction), and the transaction also has all four tags (by acquiring from the expenses posting). You can list tag names with 'hledger tags [NAMEREGEX]', or match by tag name with a 'tag:NAMEREGEX' query. * Menu: * Tag values::  File: hledger.info, Node: Tag values, Up: Tags 9.16.1 Tag values ----------------- Tags can have a value, which is any text after the colon up until a comma or end of line (with surrounding whitespace removed). Note this means that hledger tag values can not contain commas. Eg in the following posting, the three tags' values are "value 1", "value 2", and "" (empty) respectively: expenses:food $10 ; foo, tag1: value 1 , tag2:value 2, bar tag3: , baz Note that tags can be repeated, and are additive rather than overriding: when the same tag name is seen again with a new value, the new name:value pair is added to the tags. (It is not possible to override a tag's value or remove a tag.) You can list a tag's values with 'hledger tags TAGNAME --values', or match by tag value with a 'tag:NAMEREGEX=VALUEREGEX' query.  File: hledger.info, Node: Directives, Next: account directive, Prev: Tags, Up: Journal 9.17 Directives =============== Besides transactions, there is something else you can put in a 'journal' file: directives. These are declarations, beginning with a keyword, that modify hledger's behaviour. Some directives can have more specific subdirectives, indented below them. hledger's directives are similar to Ledger's in many cases, but there are also many differences. Directives are not required, but can be useful. Here are the main directives: purpose directive -------------------------------------------------------------------------- *READING DATA:* Rewrite account names 'alias' Comment out sections of the file 'comment' Declare file's decimal mark, to help 'decimal-mark' parse amounts accurately Include other data files 'include' *GENERATING DATA:* Generate recurring transactions or '~' budget goals Generate extra postings on existing '=' transactions *CHECKING FOR ERRORS:* Define valid entities to provide more 'account', 'commodity', error checking 'payee', 'tag' *REPORTING:* Declare accounts' type and display 'account' order Declare commodity display styles 'commodity' Declare market prices 'P' * Menu: * Directives and multiple files:: * Directive effects::  File: hledger.info, Node: Directives and multiple files, Next: Directive effects, Up: Directives 9.17.1 Directives and multiple files ------------------------------------ Directives vary in their scope, ie which journal entries and which input files they affect. Most often, a directive will affect the following entries and included files if any, until the end of the current file - and no further. You might find this inconvenient! For example, 'alias' directives do not affect parent or sibling files. But there are usually workarounds; for example, put 'alias' directives in your top-most file, before including other files. The restriction, though it may be annoying at first, is in a good cause; it allows reports to be stable and deterministic, independent of the order of input. Without it, reports could show different numbers depending on the order of -f options, or the positions of include directives in your files.  File: hledger.info, Node: Directive effects, Prev: Directives and multiple files, Up: Directives 9.17.2 Directive effects ------------------------ Here are all hledger's directives, with their effects and scope summarised - nine main directives, plus four others which we consider non-essential: directivewhat it does ends at file end? --------------------------------------------------------------------------- *'account'*Declares an account, for checking all entries in all files; andN its display order and type. Subdirectives: any text, ignored. *'alias'*Rewrites account names, in following entries until end of Y current file or 'end aliases'. Command line equivalent: '--alias' *'comment'*Ignores part of the journal file, until end of current file orY 'end comment'. *'commodity'*Declares up to four things: 1. a commodity symbol, for checkingN,Y,N,N all amounts in all files 2. the decimal mark for parsing amounts of this commodity, in the following entries until end of current file (if there is no 'decimal-mark' directive) 3. and the display style for amounts of this commodity 4. which is also the precision to use for balanced-transaction checking in this commodity. Takes precedence over 'D'. Subdirectives: 'format' (Ledger-compatible syntax). Command line equivalent: '-c/--commodity-style' *'decimal-mark'*Declares the decimal mark, for parsing amounts of all Y commodities in following entries until next 'decimal-mark' or end of current file. Included files can override. Takes precedence over 'commodity' and 'D'. *'include'*Includes entries and directives from another file, as if theyN were written inline. Command line alternative: multiple '-f/--file' *'payee'*Declares a payee name, for checking all entries in all files. N *'P'*Declares the market price of a commodity on some date, for value N reports. *'~'*Declares a periodic transaction rule that generates future N (tilde)transactions with '--forecast' and budget goals with 'balance --budget'. Other syntax: *'applyPrepends a common parent account to all account names, in Y account'*following entries until end of current file or 'end apply account'. *'D'*Sets a default commodity to use for no-symbol amounts;and, if Y,Y,N,N there is no 'commodity' directive for this commodity: its decimal mark, balancing precision, and display style, as above. *'Y'*Sets a default year to use for any yearless dates, in following Y entries until end of current file. *'='*Declares an auto posting rule that generates extra postings on partly (equals)matched transactions with '--auto', in current, parent, and child files (but not sibling files, see #1212). *OtherOther directives from Ledger's file format are accepted but Ledgerignored. directives*  File: hledger.info, Node: account directive, Next: alias directive, Prev: Directives, Up: Journal 9.18 'account' directive ======================== 'account' directives can be used to declare accounts (ie, the places that amounts are transferred from and to). Though not required, these declarations can provide several benefits: * They can document your intended chart of accounts, providing a reference. * In strict mode, they restrict which accounts may be posted to by transactions, which helps detect typos. * They control account display order in reports, allowing non-alphabetic sorting (eg Revenues to appear above Expenses). * They help with account name completion (in hledger add, hledger-web, hledger-iadd, ledger-mode, etc.) * They can store additional account information as comments, or as tags which can be used to filter or pivot reports. * They can help hledger know your accounts' types (asset, liability, equity, revenue, expense), affecting reports like balancesheet and incomestatement. They are written as the word 'account' followed by a hledger-style account name, eg: account assets:bank:checking Note, however, that accounts declared in account directives are not allowed to have surrounding brackets and parentheses, unlike accounts used in postings. So the following journal will not parse: account (assets:bank:checking) * Menu: * Account comments:: * Account subdirectives:: * Account error checking:: * Account display order:: * Account types::  File: hledger.info, Node: Account comments, Next: Account subdirectives, Up: account directive 9.18.1 Account comments ----------------------- Text following *two or more spaces* and ';' at the end of an account directive line, and/or following ';' on indented lines immediately below it, form comments for that account. They are ignored except they may contain tags, which are not ignored. The two-space requirement for same-line account comments is because ';' is allowed in account names. account assets:bank:checking ; same-line comment, at least 2 spaces before the semicolon ; next-line comment ; some tags - type:A, acctnum:12345  File: hledger.info, Node: Account subdirectives, Next: Account error checking, Prev: Account comments, Up: account directive 9.18.2 Account subdirectives ---------------------------- Ledger-style indented subdirectives are also accepted, but currently ignored: account assets:bank:checking format subdirective is ignored  File: hledger.info, Node: Account error checking, Next: Account display order, Prev: Account subdirectives, Up: account directive 9.18.3 Account error checking ----------------------------- By default, accounts need not be declared; they come into existence when a posting references them. This is convenient, but it means hledger can't warn you when you mis-spell an account name in the journal. Usually you'll find that error later, as an extra account in balance reports, or an incorrect balance when reconciling. In strict mode, enabled with the '-s'/'--strict' flag, hledger will report an error if any transaction uses an account name that has not been declared by an account directive. Some notes: * The declaration is case-sensitive; transactions must use the correct account name capitalisation. * The account directive's scope is "whole file and below" (see directives). This means it affects all of the current file, and any files it includes, but not parent or sibling files. The position of account directives within the file does not matter, though it's usual to put them at the top. * Accounts can only be declared in 'journal' files, but will affect included files of all types. * It's currently not possible to declare "all possible subaccounts" with a wildcard; every account posted to must be declared.  File: hledger.info, Node: Account display order, Next: Account types, Prev: Account error checking, Up: account directive 9.18.4 Account display order ---------------------------- The order in which account directives are written influences the order in which accounts appear in reports, hledger-ui, hledger-web etc. By default accounts appear in alphabetical order, but if you add these account directives to the journal file: account assets account liabilities account equity account revenues account expenses those accounts will be displayed in declaration order: $ hledger accounts -1 assets liabilities equity revenues expenses Any undeclared accounts are displayed last, in alphabetical order. Sorting is done at each level of the account tree, within each group of sibling accounts under the same parent. And currently, this directive: account other:zoo would influence the position of 'zoo' among 'other''s subaccounts, but not the position of 'other' among the top-level accounts. This means: * you will sometimes declare parent accounts (eg 'account other' above) that you don't intend to post to, just to customize their display order * sibling accounts stay together (you couldn't display 'x:y' in between 'a:b' and 'a:c').  File: hledger.info, Node: Account types, Prev: Account display order, Up: account directive 9.18.5 Account types -------------------- hledger knows that accounts come in several types: assets, liabilities, expenses and so on. This enables easy reports like balancesheet and incomestatement, and filtering by account type with the 'type:' query. As a convenience, hledger will detect these account types automatically if you are using common english-language top-level account names (described below). But generally we recommend you declare types explicitly, by adding a 'type:' tag to your top-level account directives. Subaccounts will inherit the type of their parent. The tag's value should be one of the five main account types: * 'A' or 'Asset' (things you own) * 'L' or 'Liability' (things you owe) * 'E' or 'Equity' (investment/ownership; balanced counterpart of assets & liabilities) * 'R' or 'Revenue' (what you received money from, AKA income; technically part of Equity) * 'X' or 'Expense' (what you spend money on; technically part of Equity) or, it can be (these are used less often): * 'C' or 'Cash' (a subtype of Asset, indicating liquid assets for the cashflow report) * 'V' or 'Conversion' (a subtype of Equity, for conversions (see Cost reporting).) Here is a typical set of account type declarations: account assets ; type: A account liabilities ; type: L account equity ; type: E account revenues ; type: R account expenses ; type: X account assets:bank ; type: C account assets:cash ; type: C account equity:conversion ; type: V Here are some tips for working with account types. * The rules for inferring types from account names are as follows. These are just a convenience that sometimes help new users get going; if they don't work for you, just ignore them and declare your account types. See also Regular expressions. If account's name contains this (CI) regular expression: | its type is: --------------------------------------------------------------------|------------- ^assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|current)(:|$) | Cash ^assets?(:|$) | Asset ^(debts?|liabilit(y|ies))(:|$) | Liability ^equity:(trad(e|ing)|conversion)s?(:|$) | Conversion ^equity(:|$) | Equity ^(income|revenue)s?(:|$) | Revenue ^expenses?(:|$) | Expense * If you declare any account types, it's a good idea to declare an account for all of the account types, because a mixture of declared and name-inferred types can disrupt certain reports. * Certain uses of account aliases can disrupt account types. See Rewriting accounts > Aliases and account types. * As mentioned above, subaccounts will inherit a type from their parent account. More precisely, an account's type is decided by the first of these that exists: 1. A 'type:' declaration for this account. 2. A 'type:' declaration in the parent accounts above it, preferring the nearest. 3. An account type inferred from this account's name. 4. An account type inferred from a parent account's name, preferring the nearest parent. 5. Otherwise, it will have no type. * For troubleshooting, you can list accounts and their types with: $ hledger accounts --types [ACCTPAT] [-DEPTH] [type:TYPECODES]  File: hledger.info, Node: alias directive, Next: commodity directive, Prev: account directive, Up: Journal 9.19 'alias' directive ====================== You can define account alias rules which rewrite your account names, or parts of them, before generating reports. This can be useful for: * expanding shorthand account names to their full form, allowing easier data entry and a less verbose journal * adapting old journals to your current chart of accounts * experimenting with new account organisations, like a new hierarchy * combining two accounts into one, eg to see their sum or difference on one line * customising reports Account aliases also rewrite account names in account directives. They do not affect account names being entered via hledger add or hledger-web. Account aliases are very powerful. They are generally easy to use correctly, but you can also generate invalid account names with them; more on this below. See also Rewrite account names. * Menu: * Basic aliases:: * Regex aliases:: * Combining aliases:: * Aliases and multiple files:: * end aliases directive:: * Aliases can generate bad account names:: * Aliases and account types::  File: hledger.info, Node: Basic aliases, Next: Regex aliases, Up: alias directive 9.19.1 Basic aliases -------------------- To set an account alias, use the 'alias' directive in your journal file. This affects all subsequent journal entries in the current file or its included files (but note: not sibling or parent files). The spaces around the = are optional: alias OLD = NEW Or, you can use the '--alias 'OLD=NEW'' option on the command line. This affects all entries. It's useful for trying out aliases interactively. OLD and NEW are case sensitive full account names. hledger will replace any occurrence of the old account name with the new one. Subaccounts are also affected. Eg: alias checking = assets:bank:wells fargo:checking ; rewrites "checking" to "assets:bank:wells fargo:checking", or "checking:a" to "assets:bank:wells fargo:checking:a"  File: hledger.info, Node: Regex aliases, Next: Combining aliases, Prev: Basic aliases, Up: alias directive 9.19.2 Regex aliases -------------------- There is also a more powerful variant that uses a regular expression, indicated by wrapping the pattern in forward slashes. (This is the only place where hledger requires forward slashes around a regular expression.) Eg: alias /REGEX/ = REPLACEMENT or: $ hledger --alias '/REGEX/=REPLACEMENT' ... Any part of an account name matched by REGEX will be replaced by REPLACEMENT. REGEX is case-insensitive as usual. If you need to match a forward slash, escape it with a backslash, eg '/\/=:'. If REGEX contains parenthesised match groups, these can be referenced by the usual backslash and number in REPLACEMENT: alias /^(.+):bank:([^:]+):(.*)/ = \1:\2 \3 ; rewrites "assets:bank:wells fargo:checking" to "assets:wells fargo checking" REPLACEMENT continues to the end of line (or on command line, to end of option argument), so it can contain trailing whitespace.  File: hledger.info, Node: Combining aliases, Next: Aliases and multiple files, Prev: Regex aliases, Up: alias directive 9.19.3 Combining aliases ------------------------ You can define as many aliases as you like, using journal directives and/or command line options. Recursive aliases - where an account name is rewritten by one alias, then by another alias, and so on - are allowed. Each alias sees the effect of previously applied aliases. In such cases it can be important to understand which aliases will be applied and in which order. For (each account name in) each journal entry, we apply: 1. 'alias' directives preceding the journal entry, most recently parsed first (ie, reading upward from the journal entry, bottom to top) 2. '--alias' options, in the order they appeared on the command line (left to right). In other words, for (an account name in) a given journal entry: * the nearest alias declaration before/above the entry is applied first * the next alias before/above that will be be applied next, and so on * aliases defined after/below the entry do not affect it. This gives nearby aliases precedence over distant ones, and helps provide semantic stability - aliases will keep working the same way independent of which files are being read and in which order. In case of trouble, adding '--debug=6' to the command line will show which aliases are being applied when.  File: hledger.info, Node: Aliases and multiple files, Next: end aliases directive, Prev: Combining aliases, Up: alias directive 9.19.4 Aliases and multiple files --------------------------------- As explained at Directives and multiple files, 'alias' directives do not affect parent or sibling files. Eg in this command, hledger -f a.aliases -f b.journal account aliases defined in a.aliases will not affect b.journal. Including the aliases doesn't work either: include a.aliases 2023-01-01 ; not affected by a.aliases foo 1 bar This means that account aliases should usually be declared at the start of your top-most file, like this: alias foo=Foo alias bar=Bar 2023-01-01 ; affected by aliases above foo 1 bar include c.journal ; also affected  File: hledger.info, Node: end aliases directive, Next: Aliases can generate bad account names, Prev: Aliases and multiple files, Up: alias directive 9.19.5 'end aliases' directive ------------------------------ You can clear (forget) all currently defined aliases (seen in the journal so far, or defined on the command line) with this directive: end aliases  File: hledger.info, Node: Aliases can generate bad account names, Next: Aliases and account types, Prev: end aliases directive, Up: alias directive 9.19.6 Aliases can generate bad account names --------------------------------------------- Be aware that account aliases can produce malformed account names, which could cause confusing reports or invalid 'print' output. For example, you could erase all account names: 2021-01-01 a:aa 1 b $ hledger print --alias '/.*/=' 2021-01-01 1 The above 'print' output is not a valid journal. Or you could insert an illegal double space, causing 'print' output that would give a different journal when reparsed: 2021-01-01 old 1 other $ hledger print --alias old="new USD" | hledger -f- print 2021-01-01 new USD 1 other  File: hledger.info, Node: Aliases and account types, Prev: Aliases can generate bad account names, Up: alias directive 9.19.7 Aliases and account types -------------------------------- If an account with a type declaration (see Declaring accounts > Account types) is renamed by an alias, normally the account type remains in effect. However, renaming in a way that reshapes the account tree (eg renaming parent accounts but not their children, or vice versa) could prevent child accounts from inheriting the account type of their parents. Secondly, if an account's type is being inferred from its name, renaming it by an alias could prevent or alter that. If you are using account aliases and the 'type:' query is not matching accounts as you expect, try troubleshooting with the accounts command, eg something like: $ hledger accounts --alias assets=bassetts type:a  File: hledger.info, Node: commodity directive, Next: decimal-mark directive, Prev: alias directive, Up: Journal 9.20 'commodity' directive ========================== The 'commodity' directive performs several functions: 1. It declares which commodity symbols may be used in the journal, enabling useful error checking with strict mode or the check command. (See Commodity error checking below.) 2. It declares the precision with which this commodity's amounts should be compared when checking for balanced transactions. 3. It declares how this commodity's amounts should be displayed, eg their symbol placement, digit group mark if any, digit group sizes, decimal mark (period or comma), and the number of decimal places. (See Commodity display style above.) 4. It sets which decimal mark (period or comma) to expect when parsing subsequent amounts in this commodity (if there is no 'decimal-mark' directive in effect. See Decimal marks, digit group marks above. For related dev discussion, see #793.) Declaring commodities solves several common parsing/display problems, so we recommend it. Generally you should put 'commodity' directives at the top of your journal file (because function 4 is position-sensitive). * Menu: * Commodity directive syntax:: * Commodity error checking::  File: hledger.info, Node: Commodity directive syntax, Next: Commodity error checking, Up: commodity directive 9.20.1 Commodity directive syntax --------------------------------- A commodity directive is normally the word 'commodity' followed by a sample amount (and optionally a comment). Only the amount's symbol and format is significant. Eg: commodity $1000.00 commodity 1.000,00 EUR commodity 1 000 000.0000 ; the no-symbol commodity Commodities do not have tags (tags in the comment will be ignored). A commodity directive's sample amount must always include a period or comma decimal mark (this rule helps disambiguate decimal marks and digit group marks). If you don't want to show any decimal digits, write the decimal mark at the end: commodity 1000. AAAA ; show AAAA with no decimals Commodity symbols containing spaces, numbers, or punctuation must be enclosed in double quotes, as usual: commodity 1.0000 "AAAA 2023" Commodity directives normally include a sample amount, but can declare only a symbol (ie, just function 1 above): commodity $ commodity INR commodity "AAAA 2023" commodity "" ; the no-symbol commodity Commodity directives may also be written with an indented 'format' subdirective, as in Ledger. The symbol is repeated and must be the same in both places. Other subdirectives are currently ignored: ; display indian rupees with currency name on the left, ; thousands, lakhs and crores comma-separated, ; period as decimal point, and two decimal places. commodity INR format INR 1,00,00,000.00 an unsupported subdirective ; ignored by hledger  File: hledger.info, Node: Commodity error checking, Prev: Commodity directive syntax, Up: commodity directive 9.20.2 Commodity error checking ------------------------------- In strict mode ('-s'/'--strict') (or when you run 'hledger check commodities'), hledger will report an error if an undeclared commodity symbol is used. (With one exception: zero amounts are always allowed to have no commodity symbol.) It works like account error checking (described above).  File: hledger.info, Node: decimal-mark directive, Next: include directive, Prev: commodity directive, Up: Journal 9.21 'decimal-mark' directive ============================= You can use a 'decimal-mark' directive - usually one per file, at the top of the file - to declare which character represents a decimal mark when parsing amounts in this file. It can look like decimal-mark . or decimal-mark , This prevents any ambiguity when parsing numbers in the file, so we recommend it, especially if the file contains digit group marks (eg thousands separators).  File: hledger.info, Node: include directive, Next: P directive, Prev: decimal-mark directive, Up: Journal 9.22 'include' directive ======================== You can pull in the content of additional files by writing an include directive, like this: include FILEPATH Only journal files can include, and only journal, timeclock or timedot files can be included (not CSV files, currently). If the file path does not begin with a slash, it is relative to the current file's folder. A tilde means home directory, eg: 'include ~/main.journal'. The path may contain glob patterns to match multiple files, eg: 'include *.journal'. There is limited support for recursive wildcards: '**/' (the slash is required) matches 0 or more subdirectories. It's not super convenient since you have to avoid include cycles and including directories, but this can be done, eg: 'include */**/*.journal'. The path may also be prefixed to force a specific file format, overriding the file extension (as described in Data formats): 'include timedot:~/notes/2023*.md'.  File: hledger.info, Node: P directive, Next: payee directive, Prev: include directive, Up: Journal 9.23 'P' directive ================== The 'P' directive declares a market price, which is a conversion rate between two commodities on a certain date. This allows value reports to convert amounts of one commodity to their value in another, on or after that date. These prices are often obtained from a stock exchange, cryptocurrency exchange, the or foreign exchange market. The format is: P DATE COMMODITY1SYMBOL COMMODITY2AMOUNT DATE is a simple date, COMMODITY1SYMBOL is the symbol of the commodity being priced, and COMMODITY2AMOUNT is the amount (symbol and quantity) of commodity 2 that one unit of commodity 1 is worth on this date. Examples: # one euro was worth $1.35 from 2009-01-01 onward: P 2009-01-01 € $1.35 # and $1.40 from 2010-01-01 onward: P 2010-01-01 € $1.40 The '-V', '-X' and '--value' flags use these market prices to show amount values in another commodity. See Value reporting.  File: hledger.info, Node: payee directive, Next: tag directive, Prev: P directive, Up: Journal 9.24 'payee' directive ====================== 'payee PAYEE NAME' This directive can be used to declare a limited set of payees which may appear in transaction descriptions. The "payees" check will report an error if any transaction refers to a payee that has not been declared. Eg: payee Whole Foods ; a comment Payees do not have tags (tags in the comment will be ignored). To declare the empty payee name, use '""'. payee "" Ledger-style indented subdirectives, if any, are currently ignored.  File: hledger.info, Node: tag directive, Next: Periodic transactions, Prev: payee directive, Up: Journal 9.25 'tag' directive ==================== 'tag TAGNAME' This directive can be used to declare a limited set of tag names allowed in tags. TAGNAME should be a valid tag name (no spaces). Eg: tag item-id Any indented subdirectives are currently ignored. The "tags" check will report an error if any undeclared tag name is used. It is quite easy to accidentally create a tag through normal use of colons in comments(#comments]; if you want to prevent this, you can declare and check your tags .  File: hledger.info, Node: Periodic transactions, Next: Auto postings, Prev: tag directive, Up: Journal 9.26 Periodic transactions ========================== The '~' directive declares a "periodic rule" which generates temporary extra transactions, usually recurring at some interval, when hledger is run with the '--forecast' flag. These "forecast transactions" are useful for forecasting future activity. They exist only for the duration of the report, and only when '--forecast' is used; they are not saved in the journal file by hledger. Periodic rules also have a second use: with the '--budget' flag they set budget goals for budgeting. Periodic rules can be a little tricky, so before you use them, read this whole section, or at least the following tips: 1. Two spaces accidentally added or omitted will cause you trouble - read about this below. 2. For troubleshooting, show the generated transactions with 'hledger print --forecast tag:generated' or 'hledger register --forecast tag:generated'. 3. Forecasted transactions will begin only after the last non-forecasted transaction's date. 4. Forecasted transactions will end 6 months from today, by default. See below for the exact start/end rules. 5. period expressions can be tricky. Their documentation needs improvement, but is worth studying. 6. Some period expressions with a repeating interval must begin on a natural boundary of that interval. Eg in 'weekly from DATE', DATE must be a monday. '~ weekly from 2019/10/1' (a tuesday) will give an error. 7. Other period expressions with an interval are automatically expanded to cover a whole number of that interval. (This is done to improve reports, but it also affects periodic transactions. Yes, it's a bit inconsistent with the above.) Eg: '~ every 10th day of month from 2023/01', which is equivalent to '~ every 10th day of month from 2023/01/01', will be adjusted to start on 2019/12/10. * Menu: * Periodic rule syntax:: * Periodic rules and relative dates:: * Two spaces between period expression and description!::  File: hledger.info, Node: Periodic rule syntax, Next: Periodic rules and relative dates, Up: Periodic transactions 9.26.1 Periodic rule syntax --------------------------- A periodic transaction rule looks like a normal journal entry, with the date replaced by a tilde ('~') followed by a period expression (mnemonic: '~' looks like a recurring sine wave.): # every first of month ~ monthly expenses:rent $2000 assets:bank:checking # every 15th of month in 2023's first quarter: ~ monthly from 2023-04-15 to 2023-06-16 expenses:utilities $400 assets:bank:checking The period expression is the same syntax used for specifying multi-period reports, just interpreted differently; there, it specifies report periods; here it specifies recurrence dates (the periods' start dates).  File: hledger.info, Node: Periodic rules and relative dates, Next: Two spaces between period expression and description!, Prev: Periodic rule syntax, Up: Periodic transactions 9.26.2 Periodic rules and relative dates ---------------------------------------- Partial or relative dates (like '12/31', '25', 'tomorrow', 'last week', 'next quarter') are usually not recommended in periodic rules, since the results will change as time passes. If used, they will be interpreted relative to, in order of preference: 1. the first day of the default year specified by a recent 'Y' directive 2. or the date specified with '--today' 3. or the date on which you are running the report. They will not be affected at all by report period or forecast period dates.  File: hledger.info, Node: Two spaces between period expression and description!, Prev: Periodic rules and relative dates, Up: Periodic transactions 9.26.3 Two spaces between period expression and description! ------------------------------------------------------------ If the period expression is followed by a transaction description, these must be separated by *two or more spaces*. This helps hledger know where the period expression ends, so that descriptions can not accidentally alter their meaning, as in this example: ; 2 or more spaces needed here, so the period is not understood as "every 2 months in 2023" ; || ; vv ~ every 2 months in 2023, we will review assets:bank:checking $1500 income:acme inc So, * Do write two spaces between your period expression and your transaction description, if any. * Don't accidentally write two spaces in the middle of your period expression.  File: hledger.info, Node: Auto postings, Next: Other syntax, Prev: Periodic transactions, Up: Journal 9.27 Auto postings ================== The '=' directive declares an "auto posting rule" which generates temporary extra postings on existing transactions, when hledger is run with the '--auto' flag. (Remember, postings are the account name & amount lines.) The rule contains a query and one or more posting templates. Wherever the query matches an existing posting, the new posting(s) will be generated and added below that one. Optionally the generated amount(s) can depend on the matched posting's amount. These auto postings can be useful for, eg, adding tax postings with a standard percentage. They exist only for the duration of the report, and only when '--auto' is used; they are not saved in the journal file by hledger. Note that depending fully on generated data such as this has some drawbacks - it's less portable, less future-proof, less auditable by others, and less robust (eg your balance assertions will depend on whether you use or don't use '--auto'). An alternative is to use auto postings in "one time" fashion - use them to help build a complex journal entry, view it with 'hledger print --auto', and then copy that output into the journal file to make it permanent. Here's the journal file syntax. An auto posting rule looks a bit like a transaction: = QUERY ACCOUNT AMOUNT ... ACCOUNT [AMOUNT] except the first line is an equals sign (mnemonic: '=' suggests matching), followed by a query (which matches existing postings), and each "posting" line describes a posting to be generated, and the posting amounts can be: * a normal amount with a commodity symbol, eg '$2'. This will be used as-is. * a number, eg '2'. The commodity symbol (if any) from the matched posting will be added to this. * a numeric multiplier, eg '*2' (a star followed by a number N). The matched posting's amount (and total price, if any) will be multiplied by N. * a multiplier with a commodity symbol, eg '*$2' (a star, number N, and symbol S). The matched posting's amount will be multiplied by N, and its commodity symbol will be replaced with S. Any query term containing spaces must be enclosed in single or double quotes, as on the command line. Eg, note the quotes around the second query term below: = expenses:groceries 'expenses:dining out' (budget:funds:dining out) *-1 Some examples: ; every time I buy food, schedule a dollar donation = expenses:food (liabilities:charity) $-1 ; when I buy a gift, also deduct that amount from a budget envelope subaccount = expenses:gifts assets:checking:gifts *-1 assets:checking *1 2017/12/1 expenses:food $10 assets:checking 2017/12/14 expenses:gifts $20 assets:checking $ hledger print --auto 2017-12-01 expenses:food $10 assets:checking (liabilities:charity) $-1 2017-12-14 expenses:gifts $20 assets:checking assets:checking:gifts -$20 assets:checking $20 * Menu: * Auto postings and multiple files::  File: hledger.info, Node: Auto postings and multiple files, Up: Auto postings 9.27.1 Auto postings and multiple files --------------------------------------- An auto posting rule can affect any transaction in the current file, or in any parent file or child file. Note, currently it will not affect sibling files (when multiple '-f'/'--file' are used - see #1212). * Menu: * Auto postings and dates:: * Auto postings and transaction balancing / inferred amounts / balance assertions:: * Auto posting tags:: * Auto postings on forecast transactions only::  File: hledger.info, Node: Auto postings and dates, Next: Auto postings and transaction balancing / inferred amounts / balance assertions, Up: Auto postings and multiple files 9.27.1.1 Auto postings and dates ................................ A posting date (or secondary date) in the matched posting, or (taking precedence) a posting date in the auto posting rule itself, will also be used in the generated posting.  File: hledger.info, Node: Auto postings and transaction balancing / inferred amounts / balance assertions, Next: Auto posting tags, Prev: Auto postings and dates, Up: Auto postings and multiple files 9.27.1.2 Auto postings and transaction balancing / inferred ........................................................... amounts / balance assertions Currently, auto postings are added: * after missing amounts are inferred, and transactions are checked for balancedness, * but before balance assertions are checked. Note this means that journal entries must be balanced both before and after auto postings are added. This changed in hledger 1.12+; see #893 for background. This also means that you cannot have more than one auto-posting with a missing amount applied to a given transaction, as it will be unable to infer amounts.  File: hledger.info, Node: Auto posting tags, Next: Auto postings on forecast transactions only, Prev: Auto postings and transaction balancing / inferred amounts / balance assertions, Up: Auto postings and multiple files 9.27.1.3 Auto posting tags .......................... Automated postings will have some extra tags: * 'generated-posting:= QUERY' - shows this was generated by an auto posting rule, and the query * '_generated-posting:= QUERY' - a hidden tag, which does not appear in hledger's output. This can be used to match postings generated "just now", rather than generated in the past and saved to the journal. Also, any transaction that has been changed by auto posting rules will have these tags added: * 'modified:' - this transaction was modified * '_modified:' - a hidden tag not appearing in the comment; this transaction was modified "just now".  File: hledger.info, Node: Auto postings on forecast transactions only, Prev: Auto posting tags, Up: Auto postings and multiple files 9.27.1.4 Auto postings on forecast transactions only .................................................... Tip: you can can make auto postings that will apply to forecast transactions but not recorded transactions, by adding 'tag:_generated-transaction' to their QUERY. This can be useful when generating new journal entries to be saved in the journal.  File: hledger.info, Node: Other syntax, Prev: Auto postings, Up: Journal 9.28 Other syntax ================= hledger journal format supports quite a few other features, mainly to make interoperating with or converting from Ledger easier. Note some of the features below are powerful and can be useful in special cases, but in general, features in this section are considered less important or even not recommended for most users. Downsides are mentioned to help you decide if you want to use them. * Menu: * Balance assignments:: * Bracketed posting dates:: * D directive:: * apply account directive:: * Y directive:: * Secondary dates:: * Star comments:: * Valuation expressions:: * Virtual postings:: * Other Ledger directives::  File: hledger.info, Node: Balance assignments, Next: Bracketed posting dates, Up: Other syntax 9.28.1 Balance assignments -------------------------- Ledger-style balance assignments are also supported. These are like balance assertions, but with no posting amount on the left side of the equals sign; instead it is calculated automatically so as to satisfy the assertion. This can be a convenience during data entry, eg when setting opening balances: ; starting a new journal, set asset account balances 2016/1/1 opening balances assets:checking = $409.32 assets:savings = $735.24 assets:cash = $42 equity:opening balances or when adjusting a balance to reality: ; no cash left; update balance, record any untracked spending as a generic expense 2016/1/15 assets:cash = $0 expenses:misc The calculated amount depends on the account's balance in the commodity at that point (which depends on the previously-dated postings of the commodity to that account since the last balance assertion or assignment). Downsides: using balance assignments makes your journal less explicit; to know the exact amount posted, you have to run hledger or do the calculations yourself, instead of just reading it. Also balance assignments' forcing of balances can hide errors. These things make your financial data less portable, less future-proof, and less trustworthy in an audit. * Menu: * Balance assignments and prices:: * Balance assignments and multiple files::  File: hledger.info, Node: Balance assignments and prices, Next: Balance assignments and multiple files, Up: Balance assignments 9.28.1.1 Balance assignments and prices ....................................... A cost in a balance assignment will cause the calculated amount to have that price attached: 2019/1/1 (a) = $1 @ €2 $ hledger print --explicit 2019-01-01 (a) $1 @ €2 = $1 @ €2  File: hledger.info, Node: Balance assignments and multiple files, Prev: Balance assignments and prices, Up: Balance assignments 9.28.1.2 Balance assignments and multiple files ............................................... Balance assignments handle multiple files like balance assertions. They see balance from other files previously included from the current file, but not from previous sibling or parent files.  File: hledger.info, Node: Bracketed posting dates, Next: D directive, Prev: Balance assignments, Up: Other syntax 9.28.2 Bracketed posting dates ------------------------------ For setting posting dates and secondary posting dates, Ledger's bracketed date syntax is also supported: '[DATE]', '[DATE=DATE2]' or '[=DATE2]' in posting comments. hledger will attempt to parse any square-bracketed sequence of the '0123456789/-.=' characters in this way. With this syntax, DATE infers its year from the transaction and DATE2 infers its year from DATE. Downsides: another syntax to learn, redundant with hledger's 'date:'/'date2:' tags, and confusingly similar to Ledger's lot date syntax.  File: hledger.info, Node: D directive, Next: apply account directive, Prev: Bracketed posting dates, Up: Other syntax 9.28.3 'D' directive -------------------- 'D AMOUNT' This directive sets a default commodity, to be used for any subsequent commodityless amounts (ie, plain numbers) seen while parsing the journal. This effect lasts until the next 'D' directive, or the end of the journal. For compatibility/historical reasons, 'D' also acts like a 'commodity' directive (setting the commodity's decimal mark for parsing and display style for output). So its argument is not just a commodity symbol, but a full amount demonstrating the style. The amount must include a decimal mark (either period or comma). Eg: ; commodity-less amounts should be treated as dollars ; (and displayed with the dollar sign on the left, thousands separators and two decimal places) D $1,000.00 1/1 a 5 ; <- commodity-less amount, parsed as $5 and displayed as $5.00 b Interactions with other directives: For setting a commodity's display style, a 'commodity' directive has highest priority, then a 'D' directive. For detecting a commodity's decimal mark during parsing, 'decimal-mark' has highest priority, then 'commodity', then 'D'. For checking commodity symbols with the check command, a 'commodity' directive is required ('hledger check commodities' ignores 'D' directives). Downsides: omitting commodity symbols makes your financial data less explicit, less portable, and less trustworthy in an audit. It is usually an unsustainable shortcut; sooner or later you will want to track multiple commodities. D is overloaded with functions redundant with 'commodity' and 'decimal-mark'. And it works differently from Ledger's 'D'.  File: hledger.info, Node: apply account directive, Next: Y directive, Prev: D directive, Up: Other syntax 9.28.4 'apply account' directive -------------------------------- This directive sets a default parent account, which will be prepended to all accounts in following entries, until an 'end apply account' directive or end of current file. Eg: apply account home 2010/1/1 food $10 cash end apply account is equivalent to: 2010/01/01 home:food $10 home:cash $-10 'account' directives are also affected, and so is any 'include'd content. Account names entered via hledger add or hledger-web are not affected. Account aliases, if any, are applied after the parent account is prepended. Downsides: this can make your financial data less explicit, less portable, and less trustworthy in an audit.  File: hledger.info, Node: Y directive, Next: Secondary dates, Prev: apply account directive, Up: Other syntax 9.28.5 'Y' directive -------------------- 'Y YEAR' or (deprecated backward-compatible forms): 'year YEAR' 'apply year YEAR' The space is optional. This sets a default year to be used for subsequent dates which don't specify a year. Eg: Y2009 ; set default year to 2009 12/15 ; equivalent to 2009/12/15 expenses 1 assets year 2010 ; change default year to 2010 2009/1/30 ; specifies the year, not affected expenses 1 assets 1/31 ; equivalent to 2010/1/31 expenses 1 assets Downsides: omitting the year (from primary transaction dates, at least) makes your financial data less explicit, less portable, and less trustworthy in an audit. Such dates can get separated from their corresponding Y directive, eg when evaluating a region of the journal in your editor. A missing Y directive makes reports dependent on today's date.  File: hledger.info, Node: Secondary dates, Next: Star comments, Prev: Y directive, Up: Other syntax 9.28.6 Secondary dates ---------------------- A secondary date is written after the primary date, following an equals sign. If the year is omitted, the primary date's year is assumed. When running reports, the primary (left) date is used by default, but with the '--date2' flag (or '--aux-date' or '--effective'), the secondary (right) date will be used instead. The meaning of secondary dates is up to you, but it's best to follow a consistent rule. Eg "primary = the bank's clearing date, secondary = date the transaction was initiated, if different". Downsides: makes your financial data more complicated, less portable, and less trustworthy in an audit. Keeping the meaning of the two dates consistent requires discipline, and you have to remember which reporting mode is appropriate for a given report. Posting dates are simpler and better.  File: hledger.info, Node: Star comments, Next: Valuation expressions, Prev: Secondary dates, Up: Other syntax 9.28.7 Star comments -------------------- Lines beginning with '*' (star/asterisk) are also comment lines. This feature allows Emacs users to insert org headings in their journal, allowing them to fold/unfold/navigate it like an outline when viewed with org mode. Downsides: another, unconventional comment syntax to learn. Decreases your journal's portability. And switching to Emacs org mode just for folding/unfolding meant losing the benefits of ledger mode; nowadays you can add outshine mode to ledger mode to get folding without losing ledger mode's features.  File: hledger.info, Node: Valuation expressions, Next: Virtual postings, Prev: Star comments, Up: Other syntax 9.28.8 Valuation expressions ---------------------------- Ledger allows a valuation function or value to be written in double parentheses after an amount. hledger ignores these.  File: hledger.info, Node: Virtual postings, Next: Other Ledger directives, Prev: Valuation expressions, Up: Other syntax 9.28.9 Virtual postings ----------------------- A posting with parentheses around the account name ('(some:account)') is called a _unbalanced virtual posting_. Such postings do not participate in transaction balancing. (And if you write them without an amount, a zero amount is always inferred.) These can occasionally be convenient for special circumstances, but they violate double entry bookkeeping and make your data less portable across applications, so many people avoid using them at all. A posting with brackets around the account name ('[some:account]') is called a _balanced virtual posting_. The balanced virtual postings in a transaction must add up to zero, just like ordinary postings, but separately from them. These are not part of double entry bookkeeping either, but they are at least balanced. An example: 2022-01-01 buy food with cash, update budget envelope subaccounts, & something else assets:cash $-10 ; <- these balance each other expenses:food $7 ; <- expenses:food $3 ; <- [assets:checking:budget:food] $-10 ; <- and these balance each other [assets:checking:available] $10 ; <- (something:else) $5 ; <- this is not required to balance Ordinary postings, whose account names are neither parenthesised nor bracketed, are called _real postings_. You can exclude virtual postings from reports with the '-R/--real' flag or a 'real:1' query.  File: hledger.info, Node: Other Ledger directives, Prev: Virtual postings, Up: Other syntax 9.28.10 Other Ledger directives ------------------------------- These other Ledger directives are currently accepted but ignored. This allows hledger to read more Ledger files, but be aware that hledger's reports may differ from Ledger's if you use these. apply fixed COMM AMT apply tag TAG assert EXPR bucket / A ACCT capture ACCT REGEX check EXPR define VAR=EXPR end apply fixed end apply tag end apply year end tag eval / expr EXPR python PYTHONCODE tag NAME value EXPR --command-line-flags See also https://hledger.org/ledger.html for a detailed hledger/Ledger syntax comparison.  File: hledger.info, Node: CSV, Next: Timeclock, Prev: Journal, Up: Top 10 CSV ****** hledger can read CSV files (Character Separated Value - usually comma, semicolon, or tab) containing dated records, automatically converting each record into a transaction. (To learn about _writing_ CSV, see CSV output.) For best error messages when reading CSV/TSV/SSV files, make sure they have a corresponding '.csv', '.tsv' or '.ssv' file extension or use a hledger file prefix (see File Extension below). Each CSV file must be described by a corresponding _rules file_. This contains rules describing the CSV data (header line, fields layout, date format etc.), how to construct hledger transactions from it, and how to categorise transactions based on description or other attributes. By default hledger looks for a rules file named like the CSV file with an extra '.rules' extension, in the same directory. Eg when asked to read 'foo/FILE.csv', hledger looks for 'foo/FILE.csv.rules'. You can specify a different rules file with the '--rules-file' option. If no rules file is found, hledger will create a sample rules file, which you'll need to adjust. At minimum, the rules file must identify the date and amount fields, and often it also specifies the date format and how many header lines there are. Here's a simple CSV file and a rules file for it: Date, Description, Id, Amount 12/11/2019, Foo, 123, 10.23 # basic.csv.rules skip 1 fields date, description, , amount date-format %d/%m/%Y $ hledger print -f basic.csv 2019-11-12 Foo expenses:unknown 10.23 income:unknown -10.23 There's an introductory Importing CSV data tutorial on hledger.org, and more CSV rules examples below, and a larger collection at https://github.com/simonmichael/hledger/tree/master/examples/csv. * Menu: * CSV rules cheatsheet:: * source:: * separator:: * skip:: * date-format:: * timezone:: * newest-first:: * intra-day-reversed:: * decimal-mark:: * fields list:: * Field assignment:: * Field names:: * if block:: * Matchers:: * if table:: * balance-type:: * include:: * Working with CSV:: * CSV rules examples::  File: hledger.info, Node: CSV rules cheatsheet, Next: source, Up: CSV 10.1 CSV rules cheatsheet ========================= The following kinds of rule can appear in the rules file, in any order. (Blank lines and lines beginning with '#' or ';' or '*' are ignored.) *'source'* optionally declare which file to read data from *'separator'* declare the field separator, instead of relying on file extension *'skip'* skip one or more header lines at start of file *'date-format'* declare how to parse CSV dates/date-times *'timezone'* declare the time zone of ambiguous CSV date-times *'newest-first'* improve txn order when: there are multiple records, newest first, all with the same date *'intra-day-reversed'* improve txn order when: same-day txns are in opposite order to the overall file *'decimal-mark'* declare the decimal mark used in CSV amounts, when ambiguous *'fields' list* name CSV fields for easy reference, and optionally assign their values to hledger fields *Field assignment* assign a CSV value or interpolated text value to a hledger field *'if' block* conditionally assign values to hledger fields, or 'skip' a record or 'end' (skip rest of file) *'if' table* conditionally assign values to hledger fields, using compact syntax *'balance-type'* select which type of balance assertions/assignments to generate *'include'* inline another CSV rules file Working with CSV tips can be found below, including How CSV rules are evaluated.  File: hledger.info, Node: source, Next: separator, Prev: CSV rules cheatsheet, Up: CSV 10.2 'source' ============= If you tell hledger to read a csv file with '-f foo.csv', it will look for rules in 'foo.csv.rules'. Or, you can tell it to read the rules file, with '-f foo.csv.rules', and it will look for data in 'foo.csv' (since 1.30). These are mostly equivalent, but the second method provides some extra features. For one, the data file can be missing, without causing an error; it is just considered empty. And, you can specify a different data file by adding a "source" rule: source ./Checking1.csv If you specify just a file name with no path, hledger will look for it in your system's downloads directory ('~/Downloads', currently): source Checking1.csv And if you specify a glob pattern, hledger will read the most recent of the matched files (useful with repeated downloads): source Checking1*.csv See also "Working with CSV > Reading files specified by rule".  File: hledger.info, Node: separator, Next: skip, Prev: source, Up: CSV 10.3 'separator' ================ You can use the 'separator' rule to read other kinds of character-separated data. The argument is any single separator character, or the words 'tab' or 'space' (case insensitive). Eg, for comma-separated values (CSV): separator , or for semicolon-separated values (SSV): separator ; or for tab-separated values (TSV): separator TAB If the input file has a '.csv', '.ssv' or '.tsv' file extension (or a 'csv:', 'ssv:', 'tsv:' prefix), the appropriate separator will be inferred automatically, and you won't need this rule.  File: hledger.info, Node: skip, Next: date-format, Prev: separator, Up: CSV 10.4 'skip' =========== skip N The word 'skip' followed by a number (or no number, meaning 1) tells hledger to ignore this many non-empty lines at the start of the input data. You'll need this whenever your CSV data contains header lines. Note, empty and blank lines are skipped automatically, so you don't need to count those. 'skip' has a second meaning: it can be used inside if blocks (described below), to skip one or more records whenever the condition is true. Records skipped in this way are ignored, except they are still required to be valid CSV.  File: hledger.info, Node: date-format, Next: timezone, Prev: skip, Up: CSV 10.5 'date-format' ================== date-format DATEFMT This is a helper for the 'date' (and 'date2') fields. If your CSV dates are not formatted like 'YYYY-MM-DD', 'YYYY/MM/DD' or 'YYYY.MM.DD', you'll need to add a date-format rule describing them with a strptime-style date parsing pattern - see https://hackage.haskell.org/package/time/docs/Data-Time-Format.html#v:formatTime. The pattern must parse the CSV date value completely. Some examples: # MM/DD/YY date-format %m/%d/%y # D/M/YYYY # The - makes leading zeros optional. date-format %-d/%-m/%Y # YYYY-Mmm-DD date-format %Y-%h-%d # M/D/YYYY HH:MM AM some other junk # Note the time and junk must be fully parsed, though only the date is used. date-format %-m/%-d/%Y %l:%M %p some other junk  File: hledger.info, Node: timezone, Next: newest-first, Prev: date-format, Up: CSV 10.6 'timezone' =============== timezone TIMEZONE When CSV contains date-times that are implicitly in some time zone other than yours, but containing no explicit time zone information, you can use this rule to declare the CSV's native time zone, which helps prevent off-by-one dates. When the CSV date-times do contain time zone information, you don't need this rule; instead, use '%Z' in 'date-format' (or '%z', '%EZ', '%Ez'; see the formatTime link above). In either of these cases, hledger will do a time-zone-aware conversion, localising the CSV date-times to your current system time zone. If you prefer to localise to some other time zone, eg for reproducibility, you can (on unix at least) set the output timezone with the TZ environment variable, eg: $ TZ=-1000 hledger print -f foo.csv # or TZ=-1000 hledger import foo.csv 'timezone' currently does not understand timezone names, except "UTC", "GMT", "EST", "EDT", "CST", "CDT", "MST", "MDT", "PST", or "PDT". For others, use numeric format: +HHMM or -HHMM.  File: hledger.info, Node: newest-first, Next: intra-day-reversed, Prev: timezone, Up: CSV 10.7 'newest-first' =================== hledger tries to ensure that the generated transactions will be ordered chronologically, including same-day transactions. Usually it can auto-detect how the CSV records are ordered. But if it encounters CSV where all records are on the same date, it assumes that the records are oldest first. If in fact the CSV's records are normally newest first, like: 2022-10-01, txn 3... 2022-10-01, txn 2... 2022-10-01, txn 1... you can add the 'newest-first' rule to help hledger generate the transactions in correct order. # same-day CSV records are newest first newest-first  File: hledger.info, Node: intra-day-reversed, Next: decimal-mark, Prev: newest-first, Up: CSV 10.8 'intra-day-reversed' ========================= If CSV records within a single day are ordered opposite to the overall record order, you can add the 'intra-day-reversed' rule to improve the order of journal entries. Eg, here the overall record order is newest first, but same-day records are oldest first: 2022-10-02, txn 3... 2022-10-02, txn 4... 2022-10-01, txn 1... 2022-10-01, txn 2... # transactions within each day are reversed with respect to the overall date order intra-day-reversed  File: hledger.info, Node: decimal-mark, Next: fields list, Prev: intra-day-reversed, Up: CSV 10.9 'decimal-mark' =================== decimal-mark . or: decimal-mark , hledger automatically accepts either period or comma as a decimal mark when parsing numbers (cf Amounts). However if any numbers in the CSV contain digit group marks, such as thousand-separating commas, you should declare the decimal mark explicitly with this rule, to avoid misparsed numbers.  File: hledger.info, Node: fields list, Next: Field assignment, Prev: decimal-mark, Up: CSV 10.10 'fields' list =================== fields FIELDNAME1, FIELDNAME2, ... A fields list (the word 'fields' followed by comma-separated field names) is optional, but convenient. It does two things: 1. It names the CSV field in each column. This can be convenient if you are referencing them in other rules, so you can say '%SomeField' instead of remembering '%13'. 2. Whenever you use one of the special hledger field names (described below), it assigns the CSV value in this position to that hledger field. This is the quickest way to populate hledger's fields and build a transaction. Here's an example that says "use the 1st, 2nd and 4th fields as the transaction's date, description and amount; name the last two fields for later reference; and ignore the others": fields date, description, , amount, , , somefield, anotherfield In a fields list, the separator is always comma; it is unrelated to the CSV file's separator. Also: * There must be least two items in the list (at least one comma). * Field names may not contain spaces. Spaces before/after field names are optional. * Field names may contain '_' (underscore) or '-' (hyphen). * Fields you don't care about can be given a dummy name or an empty name. If the CSV contains column headings, it's convenient to use these for your field names, suitably modified (eg lower-cased with spaces replaced by underscores). Sometimes you may want to alter a CSV field name to avoid assigning to a hledger field with the same name. Eg you could call the CSV's "balance" field 'balance_' to avoid directly setting hledger's 'balance' field (and generating a balance assertion).  File: hledger.info, Node: Field assignment, Next: Field names, Prev: fields list, Up: CSV 10.11 Field assignment ====================== HLEDGERFIELD FIELDVALUE Field assignments are the more flexible way to assign CSV values to hledger fields. They can be used instead of or in addition to a fields list (see above). To assign a value to a hledger field, write the field name (any of the standard hledger field/pseudo-field names, defined below), a space, followed by a text value on the same line. This text value may interpolate CSV fields, referenced either by their 1-based position in the CSV record ('%N') or by the name they were given in the fields list ('%CSVFIELD'), and regular expression match groups ('\N'). Some examples: # set the amount to the 4th CSV field, with " USD" appended amount %4 USD # combine three fields to make a comment, containing note: and date: tags comment note: %somefield - %anotherfield, date: %1 Tips: * Interpolation strips outer whitespace (so a CSV value like '" 1 "' becomes '1' when interpolated) (#1051). * Interpolations always refer to a CSV field - you can't interpolate a hledger field. (See Referencing other fields below).  File: hledger.info, Node: Field names, Next: if block, Prev: Field assignment, Up: CSV 10.12 Field names ================= Note the two kinds of field names mentioned here, and used only in hledger CSV rules files: 1. *CSV field names* ('CSVFIELD' in these docs): you can optionally name the CSV columns for easy reference (since hledger doesn't yet automatically recognise column headings in a CSV file), by writing arbitrary names in a 'fields' list, eg: fields When, What, Some_Id, Net, Total, Foo, Bar 2. Special *hledger field names* ('HLEDGERFIELD' in these docs): you must set at least some of these to generate the hledger transaction from a CSV record, by writing them as the left hand side of a field assignment, eg: date %When code %Some_Id description %What comment %Foo %Bar amount1 $ %Total or directly in a 'fields' list: fields date, description, code, , amount1, Foo, Bar currency $ comment %Foo %Bar Here are all the special hledger field names available, and what happens when you assign values to them: * Menu: * date field:: * date2 field:: * status field:: * code field:: * description field:: * comment field:: * account field:: * amount field:: * currency field:: * balance field::  File: hledger.info, Node: date field, Next: date2 field, Up: Field names 10.12.1 date field ------------------ Assigning to 'date' sets the transaction date.  File: hledger.info, Node: date2 field, Next: status field, Prev: date field, Up: Field names 10.12.2 date2 field ------------------- 'date2' sets the transaction's secondary date, if any.  File: hledger.info, Node: status field, Next: code field, Prev: date2 field, Up: Field names 10.12.3 status field -------------------- 'status' sets the transaction's status, if any.  File: hledger.info, Node: code field, Next: description field, Prev: status field, Up: Field names 10.12.4 code field ------------------ 'code' sets the transaction's code, if any.  File: hledger.info, Node: description field, Next: comment field, Prev: code field, Up: Field names 10.12.5 description field ------------------------- 'description' sets the transaction's description, if any.  File: hledger.info, Node: comment field, Next: account field, Prev: description field, Up: Field names 10.12.6 comment field --------------------- 'comment' sets the transaction's comment, if any. 'commentN', where N is a number, sets the Nth posting's comment. You can assign multi-line comments by writing literal '\n' in the code. A comment starting with '\n' will begin on a new line. Comments can contain tags, as usual.  File: hledger.info, Node: account field, Next: amount field, Prev: comment field, Up: Field names 10.12.7 account field --------------------- Assigning to 'accountN', where N is 1 to 99, sets the account name of the Nth posting, and causes that posting to be generated. Most often there are two postings, so you'll want to set 'account1' and 'account2'. Typically 'account1' is associated with the CSV file, and is set once with a top-level assignment, while 'account2' is set based on each transaction's description, in conditional rules. If a posting's account name is left unset but its amount is set (see below), a default account name will be chosen (like "expenses:unknown" or "income:unknown").  File: hledger.info, Node: amount field, Next: currency field, Prev: account field, Up: Field names 10.12.8 amount field -------------------- There are several ways to set posting amounts from CSV, useful in different situations. 1. *'amount'* is the oldest and simplest. Assigning to this sets the amount of the first and second postings. In the second posting, the amount will be negated; also, if it has a cost attached, it will be converted to cost. 2. *'amount-in'* and *'amount-out'* work exactly like the above, but should be used when the CSV has two amount fields (such as "Debit" and "Credit", or "Inflow" and "Outflow"). Whichever field has a non-zero value will be used as the amount of the first and second postings. Here are some tips to avoid confusion: * It's not "amount-in for posting 1 and amount-out for posting 2", it is "extract a single amount from the amount-in or amount-out field, and use that for posting 1 and (negated) for posting 2". * Don't use both 'amount' and 'amount-in'/'amount-out' in the same rules file; choose based on whether the amount is in a single CSV field or spread across two fields. * In each record, at most one of the two CSV fields should contain a non-zero amount; the other field must contain a zero or nothing. * hledger assumes both CSV fields contain unsigned numbers, and it automatically negates the amount-out values. * If the data doesn't fit these requirements, you'll probably need an if rule (see below). 3. *'amountN'* (where N is a number from 1 to 99) sets the amount of only a single posting: the Nth posting in the transaction. You'll usually need at least two such assignments to make a balanced transaction. You can also generate more than two postings, to represent more complex transactions. The posting numbers don't have to be consecutive; with if rules, higher posting numbers can be useful to ensure a certain order of postings. 4. *'amountN-in'* and *'amountN-out'* work exactly like the above, but should be used when the CSV has two amount fields. This is analogous to 'amount-in' and 'amount-out', and those tips also apply here. 5. Remember that a 'fields' list can also do assignments. So in a fields list if you name a CSV field "amount", that counts as assigning to 'amount'. (If you don't want that, call it something else in the fields list, like "amount_".) 6. The above don't handle every situation; if you need more flexibility, use an 'if' rule to set amounts conditionally. See "Working with CSV > Setting amounts" below for more on this and on amount-setting generally.  File: hledger.info, Node: currency field, Next: balance field, Prev: amount field, Up: Field names 10.12.9 currency field ---------------------- 'currency' sets a currency symbol, to be prepended to all postings' amounts. You can use this if the CSV amounts do not have a currency symbol, eg if it is in a separate column. 'currencyN' prepends a currency symbol to just the Nth posting's amount.  File: hledger.info, Node: balance field, Prev: currency field, Up: Field names 10.12.10 balance field ---------------------- 'balanceN' sets a balance assertion amount (or if the posting amount is left empty, a balance assignment) on posting N. 'balance' is a compatibility spelling for hledger <1.17; it is equivalent to 'balance1'. You can adjust the type of assertion/assignment with the 'balance-type' rule (see below). See Tips below for more about setting amounts and currency.  File: hledger.info, Node: if block, Next: Matchers, Prev: Field names, Up: CSV 10.13 'if' block ================ Rules can be applied conditionally, depending on patterns in the CSV data. This allows flexibility; in particular, it is how you can categorise transactions, selecting an appropriate account name based on their description (for example). There are two ways to write conditional rules: "if blocks", described here, and "if tables", described below. An if block is the word 'if' and one or more "matcher" expressions (can be a word or phrase), one per line, starting either on the same or next line; followed by one or more indented rules. Eg, if MATCHER RULE or if MATCHER MATCHER MATCHER RULE RULE If any of the matchers succeeds, all of the indented rules will be applied. They are usually field assignments, but the following special rules may also be used within an if block: * 'skip' - skips the matched CSV record (generating no transaction from it) * 'end' - skips the rest of the current CSV file. Some examples: # if the record contains "groceries", set account2 to "expenses:groceries" if groceries account2 expenses:groceries # if the record contains any of these phrases, set account2 and a transaction comment as shown if monthly service fee atm transaction fee banking thru software account2 expenses:business:banking comment XXX deductible ? check it # if an empty record is seen (assuming five fields), ignore the rest of the CSV file if ,,,, end  File: hledger.info, Node: Matchers, Next: if table, Prev: if block, Up: CSV 10.14 Matchers ============== There are two kinds: 1. A record matcher is a word or single-line text fragment or regular expression ('REGEX'), which hledger will try to match case-insensitively anywhere within the CSV record. Eg: 'whole foods' 2. A field matcher is preceded with a percent sign and CSV field name ('%CSVFIELD REGEX'). hledger will try to match these just within the named CSV field. Eg: '%date 2023' The regular expression is (as usual in hledger) a POSIX extended regular expression, that also supports GNU word boundaries ('\b', '\B', '\<', '\>'), and nothing else. If you have trouble, see "Regular expressions" in the hledger manual (https://hledger.org/hledger.html#regular-expressions). * Menu: * What matchers match:: * Combining matchers:: * Match groups::  File: hledger.info, Node: What matchers match, Next: Combining matchers, Up: Matchers 10.14.1 What matchers match --------------------------- With record matchers, it's important to know that the record matched is not the original CSV record, but a modified one: separators will be converted to commas, and enclosing double quotes (but not enclosing whitespace) are removed. So for example, when reading an SSV file, if the original record was: 2023-01-01; "Acme, Inc."; 1,000 the regex would see, and try to match, this modified record text: 2023-01-01,Acme, Inc., 1,000  File: hledger.info, Node: Combining matchers, Next: Match groups, Prev: What matchers match, Up: Matchers 10.14.2 Combining matchers -------------------------- When an if block has multiple matchers, they are combined as follows: * By default they are OR'd (any one of them can match) * When a matcher is preceded by ampersand ('&') it will be AND'ed with the previous matcher (both of them must match) * When a matcher is preceded by an exclamation mark ('!'), the matcher is negated (it may not match). Currently there is a limitation: you can't use both '&' and '!' on the same line (you can't AND a negated matcher).  File: hledger.info, Node: Match groups, Prev: Combining matchers, Up: Matchers 10.14.3 Match groups -------------------- Matchers can define match groups: parenthesised portions of the regular expression which are available for reference in field assignments. Groups are enclosed in regular parentheses ('(' and ')') and can be nested. Each group is available in field assignments using the token '\N', where N is an index into the match groups for this conditional block (e.g. '\1', '\2', etc.). Example: Warp credit card payment postings to the beginning of the billing period (Month start), to match how they are presented in statements, using posting dates: if %date (....-..)-.. comment2 date:\1-01 Another example: Read the expense account from the CSV field, but throw away a prefix: if %account1 liabilities:family:(expenses:.*) account1 \1  File: hledger.info, Node: if table, Next: balance-type, Prev: Matchers, Up: CSV 10.15 'if' table ================ "if tables" are an alternative to if blocks; they can express many matchers and field assignments in a more compact tabular format, like this: if,HLEDGERFIELD1,HLEDGERFIELD2,... MATCHERA,VALUE1,VALUE2,... MATCHERB,VALUE1,VALUE2,... MATCHERC,VALUE1,VALUE2,... The first character after 'if' is taken to be this if table's field separator. It is unrelated to the separator used in the CSV file. It should be a non-alphanumeric character like ',' or '|' that does not appear anywhere else in the table (it should not be used in field names or matchers or values, and it cannot be escaped with a backslash). Each line must contain the same number of separators; empty values are allowed. Whitespace can be used in the matcher lines for readability (but not in the if line, currently). The table must be terminated by an empty line (or end of file). An if table like the above is interpreted as follows: try all of the matchers; whenever a matcher succeeds, assign all of the values on that line to the corresponding hledger fields; later lines can overrider earlier ones. It is equivalent to this sequence of if blocks: if MATCHERA HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERB HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... if MATCHERC HLEDGERFIELD1 VALUE1 HLEDGERFIELD2 VALUE2 ... Example: if,account2,comment atm transaction fee,expenses:business:banking,deductible? check it %description groceries,expenses:groceries, 2023/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call-out  File: hledger.info, Node: balance-type, Next: include, Prev: if table, Up: CSV 10.16 'balance-type' ==================== Balance assertions generated by assigning to balanceN are of the simple '=' type by default, which is a single-commodity, subaccount-excluding assertion. You may find the subaccount-including variants more useful, eg if you have created some virtual subaccounts of checking to help with budgeting. You can select a different type of assertion with the 'balance-type' rule: # balance assertions will consider all commodities and all subaccounts balance-type ==* Here are the balance assertion types for quick reference: = single commodity, exclude subaccounts =* single commodity, include subaccounts == multi commodity, exclude subaccounts ==* multi commodity, include subaccounts  File: hledger.info, Node: include, Next: Working with CSV, Prev: balance-type, Up: CSV 10.17 'include' =============== include RULESFILE This includes the contents of another CSV rules file at this point. 'RULESFILE' is an absolute file path or a path relative to the current file's directory. This can be useful for sharing common rules between several rules files, eg: # someaccount.csv.rules ## someaccount-specific rules fields date,description,amount account1 assets:someaccount account2 expenses:misc ## common rules include categorisation.rules  File: hledger.info, Node: Working with CSV, Next: CSV rules examples, Prev: include, Up: CSV 10.18 Working with CSV ====================== Some tips: * Menu: * Rapid feedback:: * Valid CSV:: * File Extension:: * Reading CSV from standard input:: * Reading multiple CSV files:: * Reading files specified by rule:: * Valid transactions:: * Deduplicating importing:: * Setting amounts:: * Amount signs:: * Setting currency/commodity:: * Amount decimal places:: * Referencing other fields:: * How CSV rules are evaluated:: * Well factored rules::  File: hledger.info, Node: Rapid feedback, Next: Valid CSV, Up: Working with CSV 10.18.1 Rapid feedback ---------------------- It's a good idea to get rapid feedback while creating/troubleshooting CSV rules. Here's a good way, using entr from eradman.com/entrproject: $ ls foo.csv* | entr bash -c 'echo ----; hledger -f foo.csv print desc:SOMEDESC' A desc: query (eg) is used to select just one, or a few, transactions of interest. "bash -c" is used to run multiple commands, so we can echo a separator each time the command re-runs, making it easier to read the output.  File: hledger.info, Node: Valid CSV, Next: File Extension, Prev: Rapid feedback, Up: Working with CSV 10.18.2 Valid CSV ----------------- Note that hledger will only accept valid CSV conforming to RFC 4180, and equivalent SSV and TSV formats (like RFC 4180 but with semicolon or tab as separators). This means, eg: * Values may be enclosed in double quotes, or not. Enclosing in single quotes is not allowed. (Eg ''A','B'' is rejected.) * When values are enclosed in double quotes, spaces outside the quotes are not allowed. (Eg '"A", "B"' is rejected.) * When values are not enclosed in quotes, they may not contain double quotes. (Eg 'A"A, B' is rejected.) If your CSV/SSV/TSV is not valid in this sense, you'll need to transform it before reading with hledger. Try using sed, or a more permissive CSV parser like python's csv lib.  File: hledger.info, Node: File Extension, Next: Reading CSV from standard input, Prev: Valid CSV, Up: Working with CSV 10.18.3 File Extension ---------------------- To help hledger choose the CSV file reader and show the right error messages (and choose the right field separator character by default), it's best if CSV/SSV/TSV files are named with a '.csv', '.ssv' or '.tsv' filename extension. (More about this at Data formats.) When reading files with the "wrong" extension, you can ensure the CSV reader (and the default field separator) by prefixing the file path with 'csv:', 'ssv:' or 'tsv:': Eg: $ hledger -f ssv:foo.dat print You can also override the default field separator with a separator rule if needed.  File: hledger.info, Node: Reading CSV from standard input, Next: Reading multiple CSV files, Prev: File Extension, Up: Working with CSV 10.18.4 Reading CSV from standard input --------------------------------------- You'll need the file format prefix when reading CSV from stdin also, since hledger assumes journal format by default. Eg: $ cat foo.dat | hledger -f ssv:- print  File: hledger.info, Node: Reading multiple CSV files, Next: Reading files specified by rule, Prev: Reading CSV from standard input, Up: Working with CSV 10.18.5 Reading multiple CSV files ---------------------------------- If you use multiple '-f' options to read multiple CSV files at once, hledger will look for a correspondingly-named rules file for each CSV file. But if you use the '--rules-file' option, that rules file will be used for all the CSV files.  File: hledger.info, Node: Reading files specified by rule, Next: Valid transactions, Prev: Reading multiple CSV files, Up: Working with CSV 10.18.6 Reading files specified by rule --------------------------------------- Instead of specifying a CSV file in the command line, you can specify a rules file, as in 'hledger -f foo.csv.rules CMD'. By default this will read data from foo.csv in the same directory, but you can add a source rule to specify a different data file, perhaps located in your web browser's download directory. This feature was added in hledger 1.30, so you won't see it in most CSV rules examples. But it helps remove some of the busywork of managing CSV downloads. Most of your financial institutions's default CSV filenames are different and can be recognised by a glob pattern. So you can put a rule like 'source Checking1*.csv' in foo-checking.csv.rules, and then periodically follow a workflow like: 1. Download CSV from Foo's website, using your browser's defaults 2. Run 'hledger import foo-checking.csv.rules' to import any new transactions After import, you can: discard the CSV, or leave it where it is for a while, or move it into your archives, as you prefer. If you do nothing, next time your browser will save something like Checking1-2.csv, and hledger will use that because of the '*' wild card and because it is the most recent.  File: hledger.info, Node: Valid transactions, Next: Deduplicating importing, Prev: Reading files specified by rule, Up: Working with CSV 10.18.7 Valid transactions -------------------------- After reading a CSV file, hledger post-processes and validates the generated journal entries as it would for a journal file - balancing them, applying balance assignments, and canonicalising amount styles. Any errors at this stage will be reported in the usual way, displaying the problem entry. There is one exception: balance assertions, if you have generated them, will not be checked, since normally these will work only when the CSV data is part of the main journal. If you do need to check balance assertions generated from CSV right away, pipe into another hledger: $ hledger -f file.csv print | hledger -f- print  File: hledger.info, Node: Deduplicating importing, Next: Setting amounts, Prev: Valid transactions, Up: Working with CSV 10.18.8 Deduplicating, importing -------------------------------- When you download a CSV file periodically, eg to get your latest bank transactions, the new file may overlap with the old one, containing some of the same records. The import command will (a) detect the new transactions, and (b) append just those transactions to your main journal. It is idempotent, so you don't have to remember how many times you ran it or with which version of the CSV. (It keeps state in a hidden '.latest.FILE.csv' file.) This is the easiest way to import CSV data. Eg: # download the latest CSV files, then run this command. # Note, no -f flags needed here. $ hledger import *.csv [--dry] This method works for most CSV files. (Where records have a stable chronological order, and new records appear only at the new end.) A number of other tools and workflows, hledger-specific and otherwise, exist for converting, deduplicating, classifying and managing CSV data. See: * https://hledger.org/cookbook.html#setups-and-workflows * https://plaintextaccounting.org -> data import/conversion  File: hledger.info, Node: Setting amounts, Next: Amount signs, Prev: Deduplicating importing, Up: Working with CSV 10.18.9 Setting amounts ----------------------- Continuing from amount field above, here are more tips for amount-setting: 1. *If the amount is in a single CSV field:* a. *If its sign indicates direction of flow:* Assign it to 'amountN', to set the Nth posting's amount. N is usually 1 or 2 but can go up to 99. b. *If another field indicates direction of flow:* Use one or more conditional rules to set the appropriate amount sign. Eg: # assume a withdrawal unless Type contains "deposit": amount1 -%Amount if %Type deposit amount1 %Amount 2. *If the amount is in two CSV fields (such as Debit and Credit, or In and Out):* a. *If both fields are unsigned:* Assign one field to 'amountN-in' and the other to 'amountN-out'. hledger will automatically negate the "out" field, and will use whichever field value is non-zero as posting N's amount. b. *If either field is signed:* You will probably need to override hledger's sign for one or the other field, as in the following example: # Negate the -out value, but only if it is not empty: fields date, description, amount1-in, amount1-out if %amount1-out [1-9] amount1-out -%amount1-out c. *If both fields can contain a non-zero value (or both can be empty):* The -in/-out rules normally choose the value which is non-zero/non-empty. Some value pairs can be ambiguous, such as '1' and 'none'. For such cases, use conditional rules to help select the amount. Eg, to handle the above you could select the value containing non-zero digits: fields date, description, in, out if %in [1-9] amount1 %in if %out [1-9] amount1 %out 3. *If you want posting 2's amount converted to cost:* Use the unnumbered 'amount' (or 'amount-in' and 'amount-out') syntax. 4. *If the CSV has only balance amounts, not transaction amounts:* Assign to 'balanceN', to set a balance assignment on the Nth posting, causing the posting's amount to be calculated automatically. 'balance' with no number is equivalent to 'balance1'. In this situation hledger is more likely to guess the wrong default account name, so you may need to set that explicitly.  File: hledger.info, Node: Amount signs, Next: Setting currency/commodity, Prev: Setting amounts, Up: Working with CSV 10.18.10 Amount signs --------------------- There is some special handling making it easier to parse and to reverse amount signs. (This only works for whole amounts, not for cost amounts such as COST in 'amount1 AMT @ COST'): * *If an amount value begins with a plus sign:* that will be removed: '+AMT' becomes 'AMT' * *If an amount value is parenthesised:* it will be de-parenthesised and sign-flipped: '(AMT)' becomes '-AMT' * *If an amount value has two minus signs (or two sets of parentheses, or a minus sign and parentheses):* they cancel out and will be removed: '--AMT' or '-(AMT)' becomes 'AMT' * *If an amount value contains just a sign (or just a set of parentheses):* that is removed, making it an empty value. '"+"' or '"-"' or '"()"' becomes '""'. It's not possible (without preprocessing the CSV) to set an amount to its absolute value, ie discard its sign.  File: hledger.info, Node: Setting currency/commodity, Next: Amount decimal places, Prev: Amount signs, Up: Working with CSV 10.18.11 Setting currency/commodity ----------------------------------- If the currency/commodity symbol is included in the CSV's amount field(s): 2023-01-01,foo,$123.00 you don't have to do anything special for the commodity symbol, it will be assigned as part of the amount. Eg: fields date,description,amount 2023-01-01 foo expenses:unknown $123.00 income:unknown $-123.00 If the currency is provided as a separate CSV field: 2023-01-01,foo,USD,123.00 You can assign that to the 'currency' pseudo-field, which has the special effect of prepending itself to every amount in the transaction (on the left, with no separating space): fields date,description,currency,amount 2023-01-01 foo expenses:unknown USD123.00 income:unknown USD-123.00 Or, you can use a field assignment to construct the amount yourself, with more control. Eg to put the symbol on the right, and separated by a space: fields date,description,cur,amt amount %amt %cur 2023-01-01 foo expenses:unknown 123.00 USD income:unknown -123.00 USD Note we used a temporary field name ('cur') that is not 'currency' - that would trigger the prepending effect, which we don't want here.  File: hledger.info, Node: Amount decimal places, Next: Referencing other fields, Prev: Setting currency/commodity, Up: Working with CSV 10.18.12 Amount decimal places ------------------------------ Like amounts in a journal file, the amounts generated by CSV rules like 'amount1' influence commodity display styles, such as the number of decimal places displayed in reports. The original amounts as written in the CSV file do not affect display style (because we don't yet reliably know their commodity).  File: hledger.info, Node: Referencing other fields, Next: How CSV rules are evaluated, Prev: Amount decimal places, Up: Working with CSV 10.18.13 Referencing other fields --------------------------------- In field assignments, you can interpolate only CSV fields, not hledger fields. In the example below, there's both a CSV field and a hledger field named amount1, but %amount1 always means the CSV field, not the hledger field: # Name the third CSV field "amount1" fields date,description,amount1 # Set hledger's amount1 to the CSV amount1 field followed by USD amount1 %amount1 USD # Set comment to the CSV amount1 (not the amount1 assigned above) comment %amount1 Here, since there's no CSV amount1 field, %amount1 will produce a literal "amount1": fields date,description,csvamount amount1 %csvamount USD # Can't interpolate amount1 here comment %amount1 When there are multiple field assignments to the same hledger field, only the last one takes effect. Here, comment's value will be be B, or C if "something" is matched, but never A: comment A comment B if something comment C  File: hledger.info, Node: How CSV rules are evaluated, Next: Well factored rules, Prev: Referencing other fields, Up: Working with CSV 10.18.14 How CSV rules are evaluated ------------------------------------ Here's how to think of CSV rules being evaluated (if you really need to). First, * 'include' - all includes are inlined, from top to bottom, depth first. (At each include point the file is inlined and scanned for further includes, recursively, before proceeding.) Then "global" rules are evaluated, top to bottom. If a rule is repeated, the last one wins: * 'skip' (at top level) * 'date-format' * 'newest-first' * 'fields' - names the CSV fields, optionally sets up initial assignments to hledger fields Then for each CSV record in turn: * test all 'if' blocks. If any of them contain a 'end' rule, skip all remaining CSV records. Otherwise if any of them contain a 'skip' rule, skip that many CSV records. If there are multiple matched 'skip' rules, the first one wins. * collect all field assignments at top level and in matched 'if' blocks. When there are multiple assignments for a field, keep only the last one. * compute a value for each hledger field - either the one that was assigned to it (and interpolate the %CSVFIELD references), or a default * generate a hledger transaction (journal entry) from these values. This is all part of the CSV reader, one of several readers hledger can use to parse input files. When all files have been read successfully, the transactions are passed as input to whichever hledger command the user specified.  File: hledger.info, Node: Well factored rules, Prev: How CSV rules are evaluated, Up: Working with CSV 10.18.15 Well factored rules ---------------------------- Some things than can help reduce duplication and complexity in rules files: * Extracting common rules usable with multiple CSV files into a 'common.rules', and adding 'include common.rules' to each CSV's rules file. * Splitting if blocks into smaller if blocks, extracting the frequently used parts.  File: hledger.info, Node: CSV rules examples, Prev: Working with CSV, Up: CSV 10.19 CSV rules examples ======================== * Menu: * Bank of Ireland:: * Coinbase:: * Amazon:: * Paypal::  File: hledger.info, Node: Bank of Ireland, Next: Coinbase, Up: CSV rules examples 10.19.1 Bank of Ireland ----------------------- Here's a CSV with two amount fields (Debit and Credit), and a balance field, which we can use to add balance assertions, which is not necessary but provides extra error checking: Date,Details,Debit,Credit,Balance 07/12/2012,LODGMENT 529898,,10.0,131.21 07/12/2012,PAYMENT,5,,126 # bankofireland-checking.csv.rules # skip the header line skip # name the csv fields, and assign some of them as journal entry fields fields date, description, amount-out, amount-in, balance # We generate balance assertions by assigning to "balance" # above, but you may sometimes need to remove these because: # # - the CSV balance differs from the true balance, # by up to 0.0000000000005 in my experience # # - it is sometimes calculated based on non-chronological ordering, # eg when multiple transactions clear on the same day # date is in UK/Ireland format date-format %d/%m/%Y # set the currency currency EUR # set the base account for all txns account1 assets:bank:boi:checking $ hledger -f bankofireland-checking.csv print 2012-12-07 LODGMENT 529898 assets:bank:boi:checking EUR10.0 = EUR131.2 income:unknown EUR-10.0 2012-12-07 PAYMENT assets:bank:boi:checking EUR-5.0 = EUR126.0 expenses:unknown EUR5.0 The balance assertions don't raise an error above, because we're reading directly from CSV, but they will be checked if these entries are imported into a journal file.  File: hledger.info, Node: Coinbase, Next: Amazon, Prev: Bank of Ireland, Up: CSV rules examples 10.19.2 Coinbase ---------------- A simple example with some CSV from Coinbase. The spot price is recorded using cost notation. The legacy 'amount' field name conveniently sets amount 2 (posting 2's amount) to the total cost. # Timestamp,Transaction Type,Asset,Quantity Transacted,Spot Price Currency,Spot Price at Transaction,Subtotal,Total (inclusive of fees and/or spread),Fees and/or Spread,Notes # 2021-12-30T06:57:59Z,Receive,USDC,100,GBP,0.740000,"","","","Received 100.00 USDC from an external account" # coinbase.csv.rules skip 1 fields Timestamp,Transaction_Type,Asset,Quantity_Transacted,Spot_Price_Currency,Spot_Price_at_Transaction,Subtotal,Total,Fees_Spread,Notes date %Timestamp date-format %Y-%m-%dT%T%Z description %Notes account1 assets:coinbase:cc amount %Quantity_Transacted %Asset @ %Spot_Price_at_Transaction %Spot_Price_Currency $ hledger print -f coinbase.csv 2021-12-30 Received 100.00 USDC from an external account assets:coinbase:cc 100 USDC @ 0.740000 GBP income:unknown -74.000000 GBP  File: hledger.info, Node: Amazon, Next: Paypal, Prev: Coinbase, Up: CSV rules examples 10.19.3 Amazon -------------- Here we convert amazon.com order history, and use an if block to generate a third posting if there's a fee. (In practice you'd probably get this data from your bank instead, but it's an example.) "Date","Type","To/From","Name","Status","Amount","Fees","Transaction ID" "Jul 29, 2012","Payment","To","Foo.","Completed","$20.00","$0.00","16000000000000DGLNJPI1P9B8DKPVHL" "Jul 30, 2012","Payment","To","Adapteva, Inc.","Completed","$25.00","$1.00","17LA58JSKRD4HDGLNJPI1P9B8DKPVHL" # amazon-orders.csv.rules # skip one header line skip 1 # name the csv fields, and assign the transaction's date, amount and code. # Avoided the "status" and "amount" hledger field names to prevent confusion. fields date, _, toorfrom, name, amzstatus, amzamount, fees, code # how to parse the date date-format %b %-d, %Y # combine two fields to make the description description %toorfrom %name # save the status as a tag comment status:%amzstatus # set the base account for all transactions account1 assets:amazon # leave amount1 blank so it can balance the other(s). # I'm assuming amzamount excludes the fees, don't remember # set a generic account2 account2 expenses:misc amount2 %amzamount # and maybe refine it further: #include categorisation.rules # add a third posting for fees, but only if they are non-zero. if %fees [1-9] account3 expenses:fees amount3 %fees $ hledger -f amazon-orders.csv print 2012-07-29 (16000000000000DGLNJPI1P9B8DKPVHL) To Foo. ; status:Completed assets:amazon expenses:misc $20.00 2012-07-30 (17LA58JSKRD4HDGLNJPI1P9B8DKPVHL) To Adapteva, Inc. ; status:Completed assets:amazon expenses:misc $25.00 expenses:fees $1.00  File: hledger.info, Node: Paypal, Prev: Amazon, Up: CSV rules examples 10.19.4 Paypal -------------- Here's a real-world rules file for (customised) Paypal CSV, with some Paypal-specific rules, and a second rules file included: "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" "10/01/2019","03:46:20","PDT","Calm Radio","Subscription Payment","Completed","USD","-6.99","0.00","-6.99","simon@joyful.com","memberships@calmradio.com","60P57143A8206782E","MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month","","I-R8YLY094FJYR","","-6.99","" "10/01/2019","03:46:20","PDT","","Bank Deposit to PP Account ","Pending","USD","6.99","0.00","6.99","","simon@joyful.com","0TU1544T080463733","","","60P57143A8206782E","","0.00","" "10/01/2019","08:57:01","PDT","Patreon","PreApproved Payment Bill User Payment","Completed","USD","-7.00","0.00","-7.00","simon@joyful.com","support@patreon.com","2722394R5F586712G","Patreon* Membership","","B-0PG93074E7M86381M","","-7.00","" "10/01/2019","08:57:01","PDT","","Bank Deposit to PP Account ","Pending","USD","7.00","0.00","7.00","","simon@joyful.com","71854087RG994194F","Patreon* Membership","","2722394R5F586712G","","0.00","" "10/19/2019","03:02:12","PDT","Wikimedia Foundation, Inc.","Subscription Payment","Completed","USD","-2.00","0.00","-2.00","simon@joyful.com","tle@wikimedia.org","K9U43044RY432050M","Monthly donation to the Wikimedia Foundation","","I-R5C3YUS3285L","","-2.00","" "10/19/2019","03:02:12","PDT","","Bank Deposit to PP Account ","Pending","USD","2.00","0.00","2.00","","simon@joyful.com","3XJ107139A851061F","","","K9U43044RY432050M","","0.00","" "10/22/2019","05:07:06","PDT","Noble Benefactor","Subscription Payment","Completed","USD","10.00","-0.59","9.41","noble@bene.fac.tor","simon@joyful.com","6L8L1662YP1334033","Joyful Systems","","I-KC9VBGY2GWDB","","9.41","" # paypal-custom.csv.rules # Tips: # Export from Activity -> Statements -> Custom -> Activity download # Suggested transaction type: "Balance affecting" # Paypal's default fields in 2018 were: # "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Shipping Address","Address Status","Item Title","Item ID","Shipping and Handling Amount","Insurance Amount","Sales Tax","Option 1 Name","Option 1 Value","Option 2 Name","Option 2 Value","Reference Txn ID","Invoice Number","Custom Number","Quantity","Receipt ID","Balance","Address Line 1","Address Line 2/District/Neighborhood","Town/City","State/Province/Region/County/Territory/Prefecture/Republic","Zip/Postal Code","Country","Contact Phone Number","Subject","Note","Country Code","Balance Impact" # This rules file assumes the following more detailed fields, configured in "Customize report fields": # "Date","Time","TimeZone","Name","Type","Status","Currency","Gross","Fee","Net","From Email Address","To Email Address","Transaction ID","Item Title","Item ID","Reference Txn ID","Receipt ID","Balance","Note" fields date, time, timezone, description_, type, status_, currency, grossamount, feeamount, netamount, fromemail, toemail, code, itemtitle, itemid, referencetxnid, receiptid, balance, note skip 1 date-format %-m/%-d/%Y # ignore some paypal events if In Progress Temporary Hold Update to skip # add more fields to the description description %description_ %itemtitle # save some other fields as tags comment itemid:%itemid, fromemail:%fromemail, toemail:%toemail, time:%time, type:%type, status:%status_ # convert to short currency symbols if %currency USD currency $ if %currency EUR currency E if %currency GBP currency P # generate postings # the first posting will be the money leaving/entering my paypal account # (negative means leaving my account, in all amount fields) account1 assets:online:paypal amount1 %netamount # the second posting will be money sent to/received from other party # (account2 is set below) amount2 -%grossamount # if there's a fee, add a third posting for the money taken by paypal. if %feeamount [1-9] account3 expenses:banking:paypal amount3 -%feeamount comment3 business: # choose an account for the second posting # override the default account names: # if the amount is positive, it's income (a debit) if %grossamount ^[^-] account2 income:unknown # if negative, it's an expense (a credit) if %grossamount ^- account2 expenses:unknown # apply common rules for setting account2 & other tweaks include common.rules # apply some overrides specific to this csv # Transfers from/to bank. These are usually marked Pending, # which can be disregarded in this case. if Bank Account Bank Deposit to PP Account description %type for %referencetxnid %itemtitle account2 assets:bank:wf:pchecking account1 assets:online:paypal # Currency conversions if Currency Conversion account2 equity:currency conversion # common.rules if darcs noble benefactor account2 revenues:foss donations:darcshub comment2 business: if Calm Radio account2 expenses:online:apps if electronic frontier foundation Patreon wikimedia Advent of Code account2 expenses:dues if Google account2 expenses:online:apps description google | music $ hledger -f paypal-custom.csv print 2019-10-01 (60P57143A8206782E) Calm Radio MONTHLY - $1 for the first 2 Months: Me - Order 99309. Item total: $1.00 USD first 2 months, then $6.99 / Month ; itemid:, fromemail:simon@joyful.com, toemail:memberships@calmradio.com, time:03:46:20, type:Subscription Payment, status:Completed assets:online:paypal $-6.99 = $-6.99 expenses:online:apps $6.99 2019-10-01 (0TU1544T080463733) Bank Deposit to PP Account for 60P57143A8206782E ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:46:20, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $6.99 = $0.00 assets:bank:wf:pchecking $-6.99 2019-10-01 (2722394R5F586712G) Patreon Patreon* Membership ; itemid:, fromemail:simon@joyful.com, toemail:support@patreon.com, time:08:57:01, type:PreApproved Payment Bill User Payment, status:Completed assets:online:paypal $-7.00 = $-7.00 expenses:dues $7.00 2019-10-01 (71854087RG994194F) Bank Deposit to PP Account for 2722394R5F586712G Patreon* Membership ; itemid:, fromemail:, toemail:simon@joyful.com, time:08:57:01, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $7.00 = $0.00 assets:bank:wf:pchecking $-7.00 2019-10-19 (K9U43044RY432050M) Wikimedia Foundation, Inc. Monthly donation to the Wikimedia Foundation ; itemid:, fromemail:simon@joyful.com, toemail:tle@wikimedia.org, time:03:02:12, type:Subscription Payment, status:Completed assets:online:paypal $-2.00 = $-2.00 expenses:dues $2.00 expenses:banking:paypal ; business: 2019-10-19 (3XJ107139A851061F) Bank Deposit to PP Account for K9U43044RY432050M ; itemid:, fromemail:, toemail:simon@joyful.com, time:03:02:12, type:Bank Deposit to PP Account, status:Pending assets:online:paypal $2.00 = $0.00 assets:bank:wf:pchecking $-2.00 2019-10-22 (6L8L1662YP1334033) Noble Benefactor Joyful Systems ; itemid:, fromemail:noble@bene.fac.tor, toemail:simon@joyful.com, time:05:07:06, type:Subscription Payment, status:Completed assets:online:paypal $9.41 = $9.41 revenues:foss donations:darcshub $-10.00 ; business: expenses:banking:paypal $0.59 ; business:  File: hledger.info, Node: Timeclock, Next: Timedot, Prev: CSV, Up: Top 11 Timeclock ************ The time logging format of timeclock.el, as read by hledger. hledger can read time logs in timeclock format. As with Ledger, these are (a subset of) timeclock.el's format, containing clock-in and clock-out entries as in the example below. The date is a simple date. The time format is HH:MM[:SS][+-ZZZZ]. Seconds and timezone are optional. The timezone, if present, must be four digits and is ignored (currently the time is always interpreted as a local time). Lines beginning with '#' or ';' or '*', and blank lines, are ignored. i 2015/03/30 09:00:00 some account optional description after 2 spaces ; optional comment, tags: o 2015/03/30 09:20:00 i 2015/03/31 22:21:45 another:account o 2015/04/01 02:00:34 hledger treats each clock-in/clock-out pair as a transaction posting some number of hours to an account. Or if the session spans more than one day, it is split into several transactions, one for each day. For the above time log, 'hledger print' generates these journal entries: $ hledger -f t.timeclock print 2015-03-30 * optional description after 2 spaces ; optional comment, tags: (some account) 0.33h 2015-03-31 * 22:21-23:59 (another:account) 1.64h 2015-04-01 * 00:00-02:00 (another:account) 2.01h Here is a sample.timeclock to download and some queries to try: $ hledger -f sample.timeclock balance # current time balances $ hledger -f sample.timeclock register -p 2009/3 # sessions in march 2009 $ hledger -f sample.timeclock register -p weekly --depth 1 --empty # time summary by week To generate time logs, ie to clock in and clock out, you could: * use emacs and the built-in timeclock.el, or the extended timeclock-x.el and perhaps the extras in ledgerutils.el * at the command line, use these bash aliases: 'shell alias ti="echo i `date '+%Y-%m-%d %H:%M:%S'` \$* >>$TIMELOG" alias to="echo o `date '+%Y-%m-%d %H:%M:%S'` >>$TIMELOG"' * or use the old 'ti' and 'to' scripts in the ledger 2.x repository. These rely on a "timeclock" executable which I think is just the ledger 2 executable renamed.  File: hledger.info, Node: Timedot, Next: PART 3 REPORTING CONCEPTS, Prev: Timeclock, Up: Top 12 Timedot ********** 'timedot' format is hledger's human-friendly time logging format. Compared to 'timeclock' format, it is more convenient for quick, approximate, and retroactive time logging, and more human-readable (you can see at a glance where time was spent). A quick example: 2023-05-01 hom:errands .... .... ; two hours; the space is ignored fos:hledger:timedot .. ; half an hour per:admin:finance ; no time spent yet hledger reads this as a transaction on this day with three (unbalanced) postings, where each dot represents "0.25". No commodity symbol is assumed, but we typically interpret it as hours. $ hledger -f a.timedot print # .timedot file extension (or timedot: prefix) is required 2023-05-01 * (hom:errands) 2.00 ; two hours (fos:hledger:timedot) 0.50 ; half an hour (per:admin:finance) 0 A timedot file contains a series of transactions (usually one per day). Each begins with a *simple date* (Y-M-D, Y/M/D, or Y.M.D), optionally be followed on the same line by a transaction description, and/or a transaction comment following a semicolon. After the date line are zero or more time postings, consisting of: * *An account name* - any hledger-style account name, optionally indented. * *Two or more spaces* - required if there is an amount (as in journal format). * *A timedot amount*, which can be * empty (representing zero) * a number, optionally followed by a unit 's', 'm', 'h', 'd', 'w', 'mo', or 'y', representing a precise number of seconds, minutes, hours, days weeks, months or years (hours is assumed by default), which will be converted to hours according to 60s = 1m, 60m = 1h, 24h = 1d, 7d = 1w, 30d = 1mo, 365d = 1y. * one or more dots (period characters), each representing 0.25. These are the dots in "timedot". Spaces are ignored and can be used for grouping/alignment. * one or more letters. These are like dots but they also generate a tag 't:' (short for "type") with the letter as its value, and a separate posting for each of the values. This provides a second dimension of categorisation, viewable in reports with '--pivot t'. * *An optional comment* following a semicolon (a hledger-style posting comment). There is some flexibility to help with keeping time log data and notes in the same file: * Blank lines and lines beginning with '#' or ';' are ignored. * After the first date line, lines which do not contain a double space are parsed as postings with zero amount. (hledger's register reports will show these if you add -E). * Before the first date line, lines beginning with '*' (eg org headings) are ignored. And from the first date line onward, Emacs org mode heading prefixes at the start of lines (one or more '*''s followed by a space) will be ignored. This means the time log can also be a org outline. * Menu: * Timedot examples::  File: hledger.info, Node: Timedot examples, Up: Timedot 12.1 Timedot examples ===================== Numbers: 2016/2/3 inc:client1 4 fos:hledger 3h biz:research 60m Dots: # on this day, 6h was spent on client work, 1.5h on haskell FOSS work, etc. 2016/2/1 inc:client1 .... .... .... .... .... .... fos:haskell .... .. biz:research . 2016/2/2 inc:client1 .... .... biz:research . $ hledger -f a.timedot print date:2016/2/2 2016-02-02 * (inc:client1) 2.00 2016-02-02 * (biz:research) 0.25 $ hledger -f a.timedot bal --daily --tree Balance changes in 2016-02-01-2016-02-03: || 2016-02-01d 2016-02-02d 2016-02-03d ============++======================================== biz || 0.25 0.25 1.00 research || 0.25 0.25 1.00 fos || 1.50 0 3.00 haskell || 1.50 0 0 hledger || 0 0 3.00 inc || 6.00 2.00 4.00 client1 || 6.00 2.00 4.00 ------------++---------------------------------------- || 7.75 2.25 8.00 Letters: # Activity types: # c cleanup/catchup/repair # e enhancement # s support # l learning/research 2023-11-01 work:adm ccecces $ hledger -f a.timedot print 2023-11-01 (work:adm) 1 ; t:c (work:adm) 0.5 ; t:e (work:adm) 0.25 ; t:s $ hledger -f a.timedot bal 1.75 work:adm -------------------- 1.75 $ hledger -f a.timedot bal --pivot t 1.00 c 0.50 e 0.25 s -------------------- 1.75 Org: * 2023 Work Diary ** Q1 *** 2023-02-29 **** DONE 0700 yoga **** UNPLANNED **** BEGUN hom:chores cleaning ... water plants outdoor - one full watering can indoor - light watering **** TODO adm:planning: trip *** LATER Using '.' as account name separator: 2016/2/4 fos.hledger.timedot 4h fos.ledger .. $ hledger -f a.timedot --alias '/\./=:' bal -t 4.50 fos 4.00 hledger:timedot 0.50 ledger -------------------- 4.50  File: hledger.info, Node: PART 3 REPORTING CONCEPTS, Next: Amount formatting parseability, Prev: Timedot, Up: Top 13 PART 3: REPORTING CONCEPTS *****************************  File: hledger.info, Node: Amount formatting parseability, Next: Time periods, Prev: PART 3 REPORTING CONCEPTS, Up: Top 14 Amount formatting, parseability ********************************** If you're wondering why your 'print' report sometimes shows trailing decimal marks, with no decimal digits; it does this when showing amounts that have digit group marks but no decimal digits, to disambiguate them and allow them to be re-parsed reliably (see also Decimal marks, digit group marks. Eg: commodity $1,000.00 2023-01-02 (a) $1000 $ hledger print 2023-01-02 (a) $1,000. If this is a problem (eg when exporting to Ledger), you can avoid it by disabling digit group marks, eg with -c/-commodity (for each affected commodity): $ hledger print -c '$1000.00' 2023-01-02 (a) $1000 or by forcing print to always show decimal digits, with -round: $ hledger print -c '$1,000.00' --round=soft 2023-01-02 (a) $1,000.00 More generally: hledger output falls into three rough categories, which format amounts a little bit differently to suit different consumers: *1. "hledger-readable output" - should be readable by hledger (and by humans)* * This is produced by reports that show full journal entries: 'print', 'import', 'close', 'rewrite' etc. * It shows amounts with their original journal precisions, which may not be consistent. * It adds a trailing decimal mark when needed to avoid showing ambiguous amounts. * It can be parsed reliably (by hledger and ledger2beancount at least, but perhaps not by Ledger..) *2. "human-readable output" - usually for humans* * This is produced by all other reports. * It shows amounts with standard display precisions, which will be consistent within each commodity. * It shows ambiguous amounts unmodified. * It can be parsed reliably in the context of a known report (when you know decimals are consistently not being shown, you can assume a single mark is a digit group mark). *3. "machine-readable output" - usually for other software* * This is produced by all reports when an output format like 'csv', 'tsv', 'json', or 'sql' is selected. * It shows amounts as 1 or 2 do, but without digit group marks. * It can be parsed reliably (if needed, the decimal mark can be changed with -c/-commodity-style).  File: hledger.info, Node: Time periods, Next: Depth, Prev: Amount formatting parseability, Up: Top 15 Time periods *************** * Menu: * Report start & end date:: * Smart dates:: * Report intervals:: * Date adjustment:: * Period expressions::  File: hledger.info, Node: Report start & end date, Next: Smart dates, Up: Time periods 15.1 Report start & end date ============================ By default, most hledger reports will show the full span of time represented by the journal. The report start date will be the earliest transaction or posting date, and the report end date will be the latest transaction, posting, or market price date. Often you will want to see a shorter time span, such as the current month. You can specify a start and/or end date using '-b/--begin', '-e/--end', '-p/--period' or a 'date:' query (described below). All of these accept the smart date syntax (below). Some notes: * End dates are exclusive, as in Ledger, so you should write the date _after_ the last day you want to see in the report. * As noted in reporting options: among start/end dates specified with _options_, the last (i.e. right-most) option takes precedence. * The effective report start and end dates are the intersection of the start/end dates from options and that from 'date:' queries. That is, 'date:2019-01 date:2019 -p'2000 to 2030'' yields January 2019, the smallest common time span. * In some cases a report interval will adjust start/end dates to fall on interval boundaries (see below). Examples: '-b begin on St. Patrick's day 2016 2016/3/17' '-e 12/1' end at the start of december 1st of the current year (11/30 will be the last date included) '-b all transactions on or after the 1st of the current month thismonth' '-p all transactions in the current month thismonth' 'date:2016/3/17..'the above written as queries instead ('..' can also be replaced with '-') 'date:..12/1' 'date:thismonth..' 'date:thismonth'  File: hledger.info, Node: Smart dates, Next: Report intervals, Prev: Report start & end date, Up: Time periods 15.2 Smart dates ================ hledger's user interfaces accept a "smart date" syntax for added convenience. Smart dates optionally can be relative to today's date, be written with english words, and have less-significant parts omitted (missing parts are inferred as 1). Some examples: '2004/10/1', exact date, several separators allowed. Year '2004-01-01', is 4+ digits, month is 1-12, day is 1-31 '2004.9.1' '2004' start of year '2004/10' start of month '10/1' month and day in current year '21' day in current month 'october, oct' start of month in current year 'yesterday, today, -1, 0, 1 days from today tomorrow' 'last/this/next -1, 0, 1 periods from the current period day/week/month/quarter/year' 'in n n periods from the current period days/weeks/months/quarters/years' 'n n periods from the current period days/weeks/months/quarters/years ahead' 'n -n periods from the current period days/weeks/months/quarters/years ago' '20181201' 8 digit YYYYMMDD with valid year month and day '201812' 6 digit YYYYMM with valid year and month Some counterexamples - malformed digit sequences might give surprising results: '201813' 6 digits with an invalid month is parsed as start of 6-digit year '20181301' 8 digits with an invalid month is parsed as start of 8-digit year '20181232' 8 digits with an invalid day gives an error '201801012' 9+ digits beginning with a valid YYYYMMDD gives an error "Today's date" can be overridden with the '--today' option, in case it's needed for testing or for recreating old reports. (Except for periodic transaction rules, which are not affected by '--today'.)  File: hledger.info, Node: Report intervals, Next: Date adjustment, Prev: Smart dates, Up: Time periods 15.3 Report intervals ===================== A report interval can be specified so that reports like register, balance or activity become multi-period, showing each subperiod as a separate row or column. The following standard intervals can be enabled with command-line flags: * '-D/--daily' * '-W/--weekly' * '-M/--monthly' * '-Q/--quarterly' * '-Y/--yearly' More complex intervals can be specified using '-p/--period', described below.  File: hledger.info, Node: Date adjustment, Next: Period expressions, Prev: Report intervals, Up: Time periods 15.4 Date adjustment ==================== When there is a report interval (other than daily), report start/end dates which have been inferred, eg from the journal, are automatically adjusted to natural period boundaries. This is convenient for producing simple periodic reports. More precisely: * an inferred start date will be adjusted earlier if needed to fall on a natural period boundary * an inferred end date will be adjusted later if needed to make the last period the same length as the others. By contrast, start/end dates which have been specified explicitly, with '-b', '-e', '-p' or 'date:', will not be adjusted (since hledger 1.29). This makes it possible to specify non-standard report periods, but it also means that if you are specifying a start date, you should pick one that's on a period boundary if you want to see simple report period headings.  File: hledger.info, Node: Period expressions, Prev: Date adjustment, Up: Time periods 15.5 Period expressions ======================= The '-p/--period' option specifies a period expression, which is a compact way of expressing a start date, end date, and/or report interval. Here's a period expression with a start and end date (specifying the first quarter of 2009): '-p "from 2009/1/1 to 2009/4/1"' Several keywords like "from" and "to" are supported for readability; these are optional. "to" can also be written as ".." or "-". The spaces are also optional, as long as you don't run two dates together. So the following are equivalent to the above: '-p "2009/1/1 2009/4/1"' '-p2009/1/1to2009/4/1' '-p2009/1/1..2009/4/1' Dates are smart dates, so if the current year is 2009, these are also equivalent to the above: '-p "1/1 4/1"' '-p "jan-apr"' '-p "this year to 4/1"' If you specify only one date, the missing start or end date will be the earliest or latest transaction date in the journal: '-p "from 2009/1/1"' everything after january 1, 2009 '-p "since 2009/1"' the same, since is a synonym '-p "from 2009"' the same '-p "to 2009"' everything before january 1, 2009 You can also specify a period by writing a single partial or full date: '-p "2009"' the year 2009; equivalent to “2009/1/1 to 2010/1/1” '-p "2009/1"' the month of january 2009; equivalent to “2009/1/1 to 2009/2/1” '-p the first day of 2009; equivalent to “2009/1/1 to "2009/1/1"' 2009/1/2” or by using the "Q" quarter-year syntax (case insensitive): '-p "2009Q1"' first quarter of 2009, equivalent to “2009/1/1 to 2009/4/1” '-p "q4"' fourth quarter of the current year * Menu: * Period expressions with a report interval:: * More complex report intervals:: * Multiple weekday intervals::  File: hledger.info, Node: Period expressions with a report interval, Next: More complex report intervals, Up: Period expressions 15.5.1 Period expressions with a report interval ------------------------------------------------ A period expression can also begin with a report interval, separated from the start/end dates (if any) by a space or the word 'in': '-p "weekly from 2009/1/1 to 2009/4/1"' '-p "monthly in 2008"' '-p "quarterly"'  File: hledger.info, Node: More complex report intervals, Next: Multiple weekday intervals, Prev: Period expressions with a report interval, Up: Period expressions 15.5.2 More complex report intervals ------------------------------------ Some more complex intervals can be specified within period expressions, such as: * 'biweekly' (every two weeks) * 'fortnightly' * 'bimonthly' (every two months) * 'every day|week|month|quarter|year' * 'every N days|weeks|months|quarters|years' Weekly on a custom day: * 'every Nth day of week' ('th', 'nd', 'rd', or 'st' are all accepted after the number) * 'every WEEKDAYNAME' (full or three-letter english weekday name, case insensitive) Monthly on a custom day: * 'every Nth day [of month]' * 'every Nth WEEKDAYNAME [of month]' Yearly on a custom day: * 'every MM/DD [of year]' (month number and day of month number) * 'every MONTHNAME DDth [of year]' (full or three-letter english month name, case insensitive, and day of month number) * 'every DDth MONTHNAME [of year]' (equivalent to the above) Examples: '-p "bimonthly from 2008"' '-p "every 2 weeks"' '-p "every 5 months from 2009/03"' '-p "every 2nd day of periods will go from Tue to Tue week"' '-p "every Tue"' same '-p "every 15th day"' period boundaries will be on 15th of each month '-p "every 2nd Monday"' period boundaries will be on second Monday of each month '-p "every 11/05"' yearly periods with boundaries on 5th of November '-p "every 5th November"' same '-p "every Nov 5th"' same Show historical balances at end of the 15th day of each month (N is an end date, exclusive as always): $ hledger balance -H -p "every 16th day" Group postings from the start of wednesday to end of the following tuesday (N is both (inclusive) start date and (exclusive) end date): $ hledger register checking -p "every 3rd day of week"  File: hledger.info, Node: Multiple weekday intervals, Prev: More complex report intervals, Up: Period expressions 15.5.3 Multiple weekday intervals --------------------------------- This special form is also supported: * 'every WEEKDAYNAME,WEEKDAYNAME,...' (full or three-letter english weekday names, case insensitive) Also, 'weekday' and 'weekendday' are shorthand for 'mon,tue,wed,thu,fri' and 'sat,sun'. This is mainly intended for use with '--forecast', to generate periodic transactions on arbitrary days of the week. It may be less useful with '-p', since it divides each week into subperiods of unequal length, which is unusual. (Related: #1632) Examples: '-p "every dates will be Mon, Wed, Fri; periods will be mon,wed,fri"' Mon-Tue, Wed-Thu, Fri-Sun '-p "every dates will be Mon, Tue, Wed, Thu, Fri; periods will weekday"' be Mon, Tue, Wed, Thu, Fri-Sun '-p "every dates will be Sat, Sun; periods will be Sat, Sun-Fri weekendday"'  File: hledger.info, Node: Depth, Next: Queries, Prev: Time periods, Up: Top 16 Depth ******** With the '--depth NUM' option (short form: '-NUM'), reports will show accounts only to the specified depth, hiding deeper subaccounts. Use this when you want a summary with less detail. This flag has the same effect as a 'depth:' query argument: 'depth:2', '--depth=2' or '-2' are equivalent.  File: hledger.info, Node: Queries, Next: Pivoting, Prev: Depth, Up: Top 17 Queries ********** One of hledger's strengths is being able to quickly report on a precise subset of your data. Most hledger commands accept query arguments, to restrict their scope. Multiple query terms can be provided to build up a more complex query. * By default, a query term is interpreted as a case-insensitive substring pattern for matching account names: 'car:fuel' 'dining groceries' * Patterns containing spaces or other special characters must be enclosed in single or double quotes: ''personal care'' * These patterns are actually regular expressions, so you can add regexp metacharacters for more precision (see "Regular expressions" above for details): ''^expenses\b'' ''food$'' ''fuel|repair'' ''accounts (payable|receivable)'' * To match something other than account name, add one of the query type prefixes described in "Query types" below: 'date:202312-' 'status:' 'desc:amazon' 'cur:USD' 'cur:\\$' 'amt:'>0'' * Add a 'not:' prefix to negate a term: 'not:status:'*'' 'not:desc:'opening|closing'' 'not:cur:USD' * Terms with different types are AND-ed, terms with the same type are OR-ed (mostly; see "Combining query terms" below). The following query: 'date:2022 desc:amazon desc:amzn' is interpreted as: _date is in 2022 AND ( transaction description contains "amazon" OR "amzn" )_ * Menu: * Query types:: * Combining query terms:: * Queries and command options:: * Queries and valuation:: * Querying with account aliases:: * Querying with cost or value::  File: hledger.info, Node: Query types, Next: Combining query terms, Up: Queries 17.1 Query types ================ Here are the types of query term available. Remember these can also be prefixed with *'not:'* to convert them into a negative match. *'acct:REGEX'* or *'REGEX'* Match account names containing this case insensitive regular expression. This is the default query type, so we usually don't bother writing the "acct:" prefix. *'amt:N, amt:N, amt:>=N'* Match postings with a single-commodity amount equal to, less than, or greater than N. (Postings with multi-commodity amounts are not tested and will always match.) The comparison has two modes: if N is preceded by a + or - sign (or is 0), the two signed numbers are compared. Otherwise, the absolute magnitudes are compared, ignoring sign. *'code:REGEX'* Match by transaction code (eg check number). *'cur:REGEX'* Match postings or transactions including any amounts whose currency/commodity symbol is fully matched by REGEX. (For a partial match, use '.*REGEX.*'). Note, to match special characters which are regex-significant, you need to escape them with '\'. And for characters which are significant to your shell you may need one more level of escaping. So eg to match the dollar sign: 'hledger print cur:\\$'. *'desc:REGEX'* Match transaction descriptions. *'date:PERIODEXPR'* Match dates (or with the '--date2' flag, secondary dates) within the specified period. PERIODEXPR is a period expression with no report interval. Examples: 'date:2016', 'date:thismonth', 'date:2/1-2/15', 'date:2021-07-27..nextquarter'. *'date2:PERIODEXPR'* Match secondary dates within the specified period (independent of the '--date2' flag). *'depth:N'* Match (or display, depending on command) accounts at or above this depth. *'expr:"TERM AND NOT (TERM OR TERM)"'* (eg) Match with a boolean combination of queries (which must be enclosed in quotes). See Combining query terms below. *'note:REGEX'* Match transaction notes (the part of the description right of '|', or the whole description if there's no '|'). *'payee:REGEX'* Match transaction payee/payer names (the part of the description left of '|', or the whole description if there's no '|'). *'real:, real:0'* Match real or virtual postings respectively. *'status:, status:!, status:*'* Match unmarked, pending, or cleared transactions respectively. *'type:TYPECODES'* Match by account type (see Declaring accounts > Account types). 'TYPECODES' is one or more of the single-letter account type codes 'ALERXCV', case insensitive. Note 'type:A' and 'type:E' will also match their respective subtypes 'C' (Cash) and 'V' (Conversion). Certain kinds of account alias can disrupt account types, see Rewriting accounts > Aliases and account types. *'tag:REGEX[=REGEX]'* Match by tag name, and optionally also by tag value. (To match only by value, use 'tag:.=REGEX'.) When querying by tag, note that: * Accounts also inherit the tags of their parent accounts * Postings also inherit the tags of their account and their transaction * Transactions also acquire the tags of their postings. (*'inacct:ACCTNAME'* A special query term used automatically in hledger-web only: tells hledger-web to show the transaction register for an account.)  File: hledger.info, Node: Combining query terms, Next: Queries and command options, Prev: Query types, Up: Queries 17.2 Combining query terms ========================== When given multiple space-separated query terms, most commands select things which match: * any of the description terms AND * any of the account terms AND * any of the status terms AND * all the other terms. The print command is a little different, showing transactions which: * match any of the description terms AND * have any postings matching any of the positive account terms AND * have no postings matching any of the negative account terms AND * match all the other terms. We also support more complex boolean queries with the 'expr:' prefix. This allows one to combine queries using one of three operators: AND, OR, and NOT, where NOT is different syntax for 'not:'. Examples of such queries are: * Match transactions with 'cool' in the description AND with the 'A' tag 'expr:"desc:cool AND tag:A"' * Match transactions NOT to the 'expenses:food' account OR with the 'A' tag 'expr:"NOT expenses:food OR tag:A"' * Match transactions NOT involving the 'expenses:food' account OR with the 'A' tag AND involving the 'expenses:drink' account. (the AND is implicitly added by space-separation, following the rules above) 'expr:"expenses:food OR (tag:A expenses:drink)"'  File: hledger.info, Node: Queries and command options, Next: Queries and valuation, Prev: Combining query terms, Up: Queries 17.3 Queries and command options ================================ Some queries can also be expressed as command-line options: 'depth:2' is equivalent to '--depth 2', 'date:2023' is equivalent to '-p 2023', etc. When you mix command options and query arguments, generally the resulting query is their intersection.  File: hledger.info, Node: Queries and valuation, Next: Querying with account aliases, Prev: Queries and command options, Up: Queries 17.4 Queries and valuation ========================== When amounts are converted to other commodities in cost or value reports, 'cur:' and 'amt:' match the old commodity symbol and the old amount quantity, not the new ones (except in hledger 1.22.0 where it's reversed, see #1625).  File: hledger.info, Node: Querying with account aliases, Next: Querying with cost or value, Prev: Queries and valuation, Up: Queries 17.5 Querying with account aliases ================================== When account names are rewritten with '--alias' or 'alias', note that 'acct:' will match either the old or the new account name.  File: hledger.info, Node: Querying with cost or value, Prev: Querying with account aliases, Up: Queries 17.6 Querying with cost or value ================================ When amounts are converted to other commodities in cost or value reports, note that 'cur:' matches the new commodity symbol, and not the old one, and 'amt:' matches the new quantity, and not the old one. Note: this changed in hledger 1.22, previously it was the reverse, see the discussion at #1625.  File: hledger.info, Node: Pivoting, Next: Generating data, Prev: Queries, Up: Top 18 Pivoting *********** Normally, hledger groups and sums amounts within each account. The '--pivot FIELD' option substitutes some other transaction field for account names, causing amounts to be grouped and summed by that field's value instead. FIELD can be any of the transaction fields 'acct', 'status', 'code', 'desc', 'payee', 'note', or a tag name. When pivoting on a tag and a posting has multiple values of that tag, only the first value is displayed. Values containing 'colon:separated:parts' will be displayed hierarchically, like account names. Multiple, colon-delimited fields can be pivoted simultaneously, generating a hierarchical account name. Some examples: 2016/02/16 Yearly Dues Payment assets:bank account 2 EUR income:dues -2 EUR ; member: John Doe, kind: Lifetime Normal balance report showing account names: $ hledger balance 2 EUR assets:bank account -2 EUR income:dues -------------------- 0 Pivoted balance report, using member: tag values instead: $ hledger balance --pivot member 2 EUR -2 EUR John Doe -------------------- 0 One way to show only amounts with a member: value (using a query): $ hledger balance --pivot member tag:member=. -2 EUR John Doe -------------------- -2 EUR Another way (the acct: query matches against the pivoted "account name"): $ hledger balance --pivot member acct:. -2 EUR John Doe -------------------- -2 EUR Hierarchical reports can be generated with multiple pivots: $ hledger balance Income:Dues --pivot kind:member -2 EUR Lifetime:John Doe -------------------- -2 EUR  File: hledger.info, Node: Generating data, Next: Forecasting, Prev: Pivoting, Up: Top 19 Generating data ****************** hledger has several features for generating data, such as: * Periodic transaction rules can generate single or repeating transactions following a template. These are usually dated in the future, eg to help with forecasting. They are activated by the '--forecast' option. * The balance command's '--budget' option uses these same periodic rules to generate goals for the budget report. * Auto posting rules can generate extra postings on certain matched transactions. They are always applied to forecast transactions; with the '--auto' flag they are applied to transactions recorded in the journal as well. * The '--infer-equity' flag infers missing conversion equity postings from @/@@ costs. And the inverse '--infer-costs' flag infers missing @/@@ costs from conversion equity postings. Generated data of this kind is temporary, existing only at report time. But you can see it in the output of 'hledger print', and you can save that to your journal, in effect converting it from temporary generated data to permanent recorded data. This could be useful as a data entry aid. If you are wondering what data is being generated and why, add the '--verbose-tags' flag. In 'hledger print' output you will see extra tags like 'generated-transaction', 'generated-posting', and 'modified' on generated/modified data. Also, even without '--verbose-tags', generated data always has equivalen hidden tags (with an underscore prefix), so eg you could match generated transactions with 'tag:_generated-transaction'.  File: hledger.info, Node: Forecasting, Next: Budgeting, Prev: Generating data, Up: Top 20 Forecasting ************** Forecasting, or speculative future reporting, can be useful for estimating future balances, or for exploring different future scenarios. The simplest and most flexible way to do it with hledger is to manually record a bunch of future-dated transactions. You could keep these in a separate 'future.journal' and include that with '-f' only when you want to see them. * Menu: * --forecast:: * Inspecting forecast transactions:: * Forecast reports:: * Forecast tags:: * Forecast period in detail:: * Forecast troubleshooting::  File: hledger.info, Node: --forecast, Next: Inspecting forecast transactions, Up: Forecasting 20.1 -forecast ============== There is another way: with the '--forecast' option, hledger can generate temporary "forecast transactions" for reporting purposes, according to periodic transaction rules defined in the journal. Each rule can generate multiple recurring transactions, so by changing one rule you can change many forecasted transactions. Forecast transactions usually start after ordinary transactions end. By default, they begin after your latest-dated ordinary transaction, or today, whichever is later, and they end six months from today. (The exact rules are a little more complicated, and are given below.) This is the "forecast period", which need not be the same as the report period. You can override it - eg to forecast farther into the future, or to force forecast transactions to overlap your ordinary transactions - by giving the -forecast option a period expression argument, like '--forecast=..2099' or '--forecast=2023-02-15..'. Note that the '=' is required.  File: hledger.info, Node: Inspecting forecast transactions, Next: Forecast reports, Prev: --forecast, Up: Forecasting 20.2 Inspecting forecast transactions ===================================== 'print' is the best command for inspecting and troubleshooting forecast transactions. Eg: ~ monthly from 2022-12-20 rent assets:bank:checking expenses:rent $1000 $ hledger print --forecast --today=2023/4/21 2023-05-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-06-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-07-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-08-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 2023-09-20 rent ; generated-transaction: ~ monthly from 2022-12-20 assets:bank:checking expenses:rent $1000 Here there are no ordinary transactions, so the forecasted transactions begin on the first occurence after today's date. (You won't normally use '--today'; it's just to make these examples reproducible.)  File: hledger.info, Node: Forecast reports, Next: Forecast tags, Prev: Inspecting forecast transactions, Up: Forecasting 20.3 Forecast reports ===================== Forecast transactions affect all reports, as you would expect. Eg: $ hledger areg rent --forecast --today=2023/4/21 Transactions in expenses:rent and subaccounts: 2023-05-20 rent as:ba:checking $1000 $1000 2023-06-20 rent as:ba:checking $1000 $2000 2023-07-20 rent as:ba:checking $1000 $3000 2023-08-20 rent as:ba:checking $1000 $4000 2023-09-20 rent as:ba:checking $1000 $5000 $ hledger bal -M expenses --forecast --today=2023/4/21 Balance changes in 2023-05-01..2023-09-30: || May Jun Jul Aug Sep ===============++=================================== expenses:rent || $1000 $1000 $1000 $1000 $1000 ---------------++----------------------------------- || $1000 $1000 $1000 $1000 $1000  File: hledger.info, Node: Forecast tags, Next: Forecast period in detail, Prev: Forecast reports, Up: Forecasting 20.4 Forecast tags ================== Forecast transactions generated by -forecast have a hidden tag, '_generated-transaction'. So if you ever need to match forecast transactions, you could use 'tag:_generated-transaction' (or just 'tag:generated') in a query. For troubleshooting, you can add the '--verbose-tags' flag. Then, visible 'generated-transaction' tags will be added also, so you can view them with the 'print' command. Their value indicates which periodic rule was responsible.  File: hledger.info, Node: Forecast period in detail, Next: Forecast troubleshooting, Prev: Forecast tags, Up: Forecasting 20.5 Forecast period, in detail =============================== Forecast start/end dates are chosen so as to do something useful by default in almost all situations, while also being flexible. Here are (with luck) the exact rules, to help with troubleshooting: The forecast period starts on: * the later of * the start date in the periodic transaction rule * the start date in '--forecast''s argument * otherwise (if those are not available): the later of * the report start date specified with '-b'/'-p'/'date:' * the day after the latest ordinary transaction in the journal * otherwise (if none of these are available): today. The forecast period ends on: * the earlier of * the end date in the periodic transaction rule * the end date in '--forecast''s argument * otherwise: the report end date specified with '-e'/'-p'/'date:' * otherwise: 180 days (~6 months) from today.  File: hledger.info, Node: Forecast troubleshooting, Prev: Forecast period in detail, Up: Forecasting 20.6 Forecast troubleshooting ============================= When -forecast is not doing what you expect, one of these tips should help: * Remember to use the '--forecast' option. * Remember to have at least one periodic transaction rule in your journal. * Test with 'print --forecast'. * Check for typos or too-restrictive start/end dates in your periodic transaction rule. * Leave at least 2 spaces between the rule's period expression and description fields. * Check for future-dated ordinary transactions suppressing forecasted transactions. * Try setting explicit report start and/or end dates with '-b', '-e', '-p' or 'date:' * Try adding the '-E' flag to encourage display of empty periods/zero transactions. * Try setting explicit forecast start and/or end dates with '--forecast=START..END' * Consult Forecast period, in detail, above. * Check inside the engine: add '--debug=2' (eg).  File: hledger.info, Node: Budgeting, Next: Cost reporting, Prev: Forecasting, Up: Top 21 Budgeting ************ With the balance command's '--budget' report, each periodic transaction rule generates recurring budget goals in specified accounts, and goals and actual performance can be compared. See the balance command's doc below. You can generate budget goals and forecast transactions at the same time, from the same or different periodic transaction rules: 'hledger bal -M --budget --forecast ...' See also: Budgeting and Forecasting.  File: hledger.info, Node: Cost reporting, Next: Value reporting, Prev: Budgeting, Up: Top 22 Cost reporting ***************** In some transactions - for example a currency conversion, or a purchase or sale of stock - one commodity is exchanged for another. In these transactions there is a conversion rate, also called the cost (when buying) or selling price (when selling). In hledger docs we just say "cost", for convenience; feel free to mentally translate to "conversion rate" or "selling price" if helpful. * Menu: * Recording costs:: * Reporting at cost:: * Equity conversion postings:: * Inferring equity conversion postings:: * Combining costs and equity conversion postings:: * Requirements for detecting equity conversion postings:: * Infer cost and equity by default ?::  File: hledger.info, Node: Recording costs, Next: Reporting at cost, Up: Cost reporting 22.1 Recording costs ==================== We'll explore several ways of recording transactions involving costs. These are also summarised at hledger Cookbook > Cost notation. Costs can be recorded explicitly in the journal, using the '@ UNITCOST' or '@@ TOTALCOST' notation described in Journal > Costs: *Variant 1* 2022-01-01 assets:dollars $-135 assets:euros €100 @ $1.35 ; $1.35 per euro (unit cost) *Variant 2* 2022-01-01 assets:dollars $-135 assets:euros €100 @@ $135 ; $135 total cost Typically, writing the unit cost (variant 1) is preferable; it can be more effort, requiring more attention to decimal digits; but it reveals the per-unit cost basis, and makes stock sales easier. Costs can also be left implicit, and hledger will infer the cost that is consistent with a balanced transaction: *Variant 3* 2022-01-01 assets:dollars $-135 assets:euros €100 Here, hledger will attach a '@@ €100' cost to the first amount (you can see it with 'hledger print -x'). This form looks convenient, but there are downsides: * It sacrifices some error checking. For example, if you accidentally wrote €10 instead of €100, hledger would not be able to detect the mistake. * It is sensitive to the order of postings - if they were reversed, a different entry would be inferred and reports would be different. * The per-unit cost basis is not easy to read. So generally this kind of entry is not recommended. You can make sure you have none of these by using '-s' (strict mode), or by running 'hledger check balanced'.  File: hledger.info, Node: Reporting at cost, Next: Equity conversion postings, Prev: Recording costs, Up: Cost reporting 22.2 Reporting at cost ====================== Now when you add the '-B'/'--cost' flag to reports ("B" is from Ledger's -B/-basis/-cost flag), any amounts which have been annotated with costs will be converted to their cost's commodity (in the report output). Ie they will be displayed "at cost" or "at sale price". Some things to note: * Costs are attached to specific posting amounts in specific transactions, and once recorded they do not change. This contrasts with market prices, which are ambient and fluctuating. * Conversion to cost is performed before conversion to market value (described below).  File: hledger.info, Node: Equity conversion postings, Next: Inferring equity conversion postings, Prev: Reporting at cost, Up: Cost reporting 22.3 Equity conversion postings =============================== There is a problem with the entries above - they are not conventional Double Entry Bookkeeping (DEB) notation, and because of the "magical" transformation of one commodity into another, they cause an imbalance in the Accounting Equation. This shows up as a non-zero grand total in balance reports like 'hledger bse'. For most hledger users, this doesn't matter in practice and can safely be ignored ! But if you'd like to learn more, keep reading. Conventional DEB uses an extra pair of equity postings to balance the transaction. Of course you can do this in hledger as well: *Variant 4* 2022-01-01 assets:dollars $-135 assets:euros €100 equity:conversion $135 equity:conversion €-100 Now the transaction is perfectly balanced according to standard DEB, and 'hledger bse''s total will not be disrupted. And, hledger can still infer the cost for cost reporting, but it's not done by default - you must add the '--infer-costs' flag like so: $ hledger print --infer-costs 2022-01-01 one hundred euros purchased at $1.35 each assets:dollars $-135 @@ €100 assets:euros €100 equity:conversion $135 equity:conversion €-100 $ hledger bal --infer-costs -B €-100 assets:dollars €100 assets:euros -------------------- 0 Here are some downsides of this kind of entry: * The per-unit cost basis is not easy to read. * Instead of '-B' you must remember to type '-B --infer-costs'. * '--infer-costs' works only where hledger can identify the two equity:conversion postings and match them up with the two non-equity postings. So writing the journal entry in a particular format becomes more important. More on this below.  File: hledger.info, Node: Inferring equity conversion postings, Next: Combining costs and equity conversion postings, Prev: Equity conversion postings, Up: Cost reporting 22.4 Inferring equity conversion postings ========================================= Can we go in the other direction ? Yes, if you have transactions written with the @/@@ cost notation, hledger can infer the missing equity postings, if you add the '--infer-equity' flag. Eg: 2022-01-01 assets:dollars -$135 assets:euros €100 @ $1.35 $ hledger print --infer-equity 2022-01-01 assets:dollars $-135 assets:euros €100 @ $1.35 equity:conversion:$-€:€ €-100 equity:conversion:$-€:$ $135.00 The equity account names will be "equity:conversion:A-B:A" and "equity:conversion:A-B:B" where A is the alphabetically first commodity symbol. You can customise the "equity:conversion" part by declaring an account with the 'V'/'Conversion' account type.  File: hledger.info, Node: Combining costs and equity conversion postings, Next: Requirements for detecting equity conversion postings, Prev: Inferring equity conversion postings, Up: Cost reporting 22.5 Combining costs and equity conversion postings =================================================== Finally, you can use both the @/@@ cost notation and equity postings at the same time. This in theory gives the best of all worlds - preserving the accounting equation, revealing the per-unit cost basis, and providing more flexibility in how you write the entry: *Variant 5* 2022-01-01 one hundred euros purchased at $1.35 each assets:dollars $-135 equity:conversion $135 equity:conversion €-100 assets:euros €100 @ $1.35 All the other variants above can (usually) be rewritten to this final form with: $ hledger print -x --infer-costs --infer-equity Downsides: * This was added in hledger-1.29 and is still somewhat experimental. * The precise format of the journal entry becomes more important. If hledger can't detect and match up the cost and equity postings, it will give a transaction balancing error. * The add command does not yet accept this kind of entry (#2056). * This is the most verbose form.  File: hledger.info, Node: Requirements for detecting equity conversion postings, Next: Infer cost and equity by default ?, Prev: Combining costs and equity conversion postings, Up: Cost reporting 22.6 Requirements for detecting equity conversion postings ========================================================== '--infer-costs' has certain requirements (unlike '--infer-equity', which always works). It will infer costs only in transactions with: * Two non-equity postings, in different commodities. Their order is significant: the cost will be added to the first of them. * Two postings to equity conversion accounts, next to one another, which balance the two non-equity postings. This balancing is checked to the same precision (number of decimal places) used in the conversion posting's amount. Equity conversion accounts are: * any accounts declared with account type 'V'/'Conversion', or their subaccounts * otherwise, accounts named 'equity:conversion', 'equity:trade', or 'equity:trading', or their subaccounts. And multiple such four-posting groups can coexist within a single transaction. When '--infer-costs' fails, it does not infer a cost in that transaction, and does not raise an error (ie, it infers costs where it can). Reading variant 5 journal entries, combining cost notation and equity postings, has all the same requirements. When reading such an entry fails, hledger raises an "unbalanced transaction" error.  File: hledger.info, Node: Infer cost and equity by default ?, Prev: Requirements for detecting equity conversion postings, Up: Cost reporting 22.7 Infer cost and equity by default ? ======================================= Should '--infer-costs' and '--infer-equity' be enabled by default ? Try using them always, eg with a shell alias: alias h="hledger --infer-equity --infer-costs" and let us know what problems you find.  File: hledger.info, Node: Value reporting, Next: PART 4 COMMANDS, Prev: Cost reporting, Up: Top 23 Value reporting ****************** Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), and/or to market value (using some market price on a certain date). This is controlled by the '--value=TYPE[,COMMODITY]' option, which will be described below. We also provide the simpler '-V' and '-X COMMODITY' options, and often one of these is all you need: * Menu: * -V Value:: * -X Value in specified commodity:: * Valuation date:: * Finding market price:: * --infer-market-prices market prices from transactions:: * Valuation commodity:: * Simple valuation examples:: * --value Flexible valuation:: * More valuation examples:: * Interaction of valuation and queries:: * Effect of valuation on reports::  File: hledger.info, Node: -V Value, Next: -X Value in specified commodity, Up: Value reporting 23.1 -V: Value ============== The '-V/--market' flag converts amounts to market value in their default _valuation commodity_, using the market prices in effect on the _valuation date(s)_, if any. More on these in a minute.  File: hledger.info, Node: -X Value in specified commodity, Next: Valuation date, Prev: -V Value, Up: Value reporting 23.2 -X: Value in specified commodity ===================================== The '-X/--exchange=COMM' option is like '-V', except you tell it which currency you want to convert to, and it tries to convert everything to that.  File: hledger.info, Node: Valuation date, Next: Finding market price, Prev: -X Value in specified commodity, Up: Value reporting 23.3 Valuation date =================== Market prices can change from day to day. hledger will use the prices on a particular valuation date (or on more than one date). By default hledger uses "end" dates for valuation. More specifically: * For single period reports (including normal print and register reports): * If an explicit report end date is specified, that is used * Otherwise the latest transaction date or P directive date is used (even if it's in the future) * For multiperiod reports, each period is valued on its last day. This can be customised with the -value option described below, which can select either "then", "end", "now", or "custom" dates. (Note, this has a bug in hledger-ui <=1.31: turning on valuation with the 'V' key always resets it to "end".)  File: hledger.info, Node: Finding market price, Next: --infer-market-prices market prices from transactions, Prev: Valuation date, Up: Value reporting 23.4 Finding market price ========================= To convert a commodity A to its market value in another commodity B, hledger looks for a suitable market price (exchange rate) as follows, in this order of preference: 1. A _declared market price_ or _inferred market price_: A's latest market price in B on or before the valuation date as declared by a P directive, or (with the '--infer-market-prices' flag) inferred from costs. 2. A _reverse market price_: the inverse of a declared or inferred market price from B to A. 3. A _forward chain of market prices_: a synthetic price formed by combining the shortest chain of "forward" (only 1 above) market prices, leading from A to B. 4. _Any chain of market prices_: a chain of any market prices, including both forward and reverse prices (1 and 2 above), leading from A to B. There is a limit to the length of these price chains; if hledger reaches that length without finding a complete chain or exhausting all possibilities, it will give up (with a "gave up" message visible in '--debug=2' output). That limit is currently 1000. Amounts for which no suitable market price can be found, are not converted.  File: hledger.info, Node: --infer-market-prices market prices from transactions, Next: Valuation commodity, Prev: Finding market price, Up: Value reporting 23.5 -infer-market-prices: market prices from transactions ========================================================== Normally, market value in hledger is fully controlled by, and requires, P directives in your journal. Since adding and updating those can be a chore, and since transactions usually take place at close to market value, why not use the recorded costs as additional market prices (as Ledger does) ? Adding the '--infer-market-prices' flag to '-V', '-X' or '--value' enables this. So for example, 'hledger bs -V --infer-market-prices' will get market prices both from P directives and from transactions. If both occur on the same day, the P directive takes precedence. There is a downside: value reports can sometimes be affected in confusing/undesired ways by your journal entries. If this happens to you, read all of this Value reporting section carefully, and try adding '--debug' or '--debug=2' to troubleshoot. '--infer-market-prices' can infer market prices from: * multicommodity transactions with explicit prices ('@'/'@@') * multicommodity transactions with implicit prices (no '@', two commodities, unbalanced). (With these, the order of postings matters. 'hledger print -x' can be useful for troubleshooting.) * multicommodity transactions with equity postings, if cost is inferred with '--infer-costs'. There is a limitation (bug) currently: when a valuation commodity is not specified, prices inferred with '--infer-market-prices' do not help select a default valuation commodity, as 'P' prices would. So conversion might not happen because no valuation commodity was detected ('--debug=2' will show this). To be safe, specify the valuation commmodity, eg: * '-X EUR --infer-market-prices', not '-V --infer-market-prices' * '--value=then,EUR --infer-market-prices', not '--value=then --infer-market-prices' Signed costs and market prices can be confusing. For reference, here is the current behaviour, since hledger 1.25. (If you think it should work differently, see #1870.) 2022-01-01 Positive Unit prices a A 1 b B -1 @ A 1 2022-01-01 Positive Total prices a A 1 b B -1 @@ A 1 2022-01-02 Negative unit prices a A 1 b B 1 @ A -1 2022-01-02 Negative total prices a A 1 b B 1 @@ A -1 2022-01-03 Double Negative unit prices a A -1 b B -1 @ A -1 2022-01-03 Double Negative total prices a A -1 b B -1 @@ A -1 All of the transactions above are considered balanced (and on each day, the two transactions are considered equivalent). Here are the market prices inferred for B: $ hledger -f- --infer-market-prices prices P 2022-01-01 B A 1 P 2022-01-01 B A 1.0 P 2022-01-02 B A -1 P 2022-01-02 B A -1.0 P 2022-01-03 B A -1 P 2022-01-03 B A -1.0  File: hledger.info, Node: Valuation commodity, Next: Simple valuation examples, Prev: --infer-market-prices market prices from transactions, Up: Value reporting 23.6 Valuation commodity ======================== *When you specify a valuation commodity ('-X COMM' or '--value TYPE,COMM'):* hledger will convert all amounts to COMM, wherever it can find a suitable market price (including by reversing or chaining prices). *When you leave the valuation commodity unspecified ('-V' or '--value TYPE'):* For each commodity A, hledger picks a default valuation commodity as follows, in this order of preference: 1. The price commodity from the latest P-declared market price for A on or before valuation date. 2. The price commodity from the latest P-declared market price for A on any date. (Allows conversion to proceed when there are inferred prices before the valuation date.) 3. If there are no P directives at all (any commodity or date) and the '--infer-market-prices' flag is used: the price commodity from the latest transaction-inferred price for A on or before valuation date. This means: * If you have P directives, they determine which commodities '-V' will convert, and to what. * If you have no P directives, and use the '--infer-market-prices' flag, costs determine it. Amounts for which no valuation commodity can be found are not converted.  File: hledger.info, Node: Simple valuation examples, Next: --value Flexible valuation, Prev: Valuation commodity, Up: Value reporting 23.7 Simple valuation examples ============================== Here are some quick examples of '-V': ; one euro is worth this many dollars from nov 1 P 2016/11/01 € $1.10 ; purchase some euros on nov 3 2016/11/3 assets:euros €100 assets:checking ; the euro is worth fewer dollars by dec 21 P 2016/12/21 € $1.03 How many euros do I have ? $ hledger -f t.j bal -N euros €100 assets:euros What are they worth at end of nov 3 ? $ hledger -f t.j bal -N euros -V -e 2016/11/4 $110.00 assets:euros What are they worth after 2016/12/21 ? (no report end date specified, defaults to today) $ hledger -f t.j bal -N euros -V $103.00 assets:euros  File: hledger.info, Node: --value Flexible valuation, Next: More valuation examples, Prev: Simple valuation examples, Up: Value reporting 23.8 -value: Flexible valuation =============================== '-V' and '-X' are special cases of the more general '--value' option: --value=TYPE[,COMM] TYPE is then, end, now or YYYY-MM-DD. COMM is an optional commodity symbol. Shows amounts converted to: - default valuation commodity (or COMM) using market prices at posting dates - default valuation commodity (or COMM) using market prices at period end(s) - default valuation commodity (or COMM) using current market prices - default valuation commodity (or COMM) using market prices at some date The TYPE part selects cost or value and valuation date: '--value=then' Convert amounts to their value in the default valuation commodity, using market prices on each posting's date. '--value=end' Convert amounts to their value in the default valuation commodity, using market prices on the last day of the report period (or if unspecified, the journal's end date); or in multiperiod reports, market prices on the last day of each subperiod. '--value=now' Convert amounts to their value in the default valuation commodity using current market prices (as of when report is generated). '--value=YYYY-MM-DD' Convert amounts to their value in the default valuation commodity using market prices on this date. To select a different valuation commodity, add the optional ',COMM' part: a comma, then the target commodity's symbol. Eg: *'--value=now,EUR'*. hledger will do its best to convert amounts to this commodity, deducing market prices as described above.  File: hledger.info, Node: More valuation examples, Next: Interaction of valuation and queries, Prev: --value Flexible valuation, Up: Value reporting 23.9 More valuation examples ============================ Here are some examples showing the effect of '--value', as seen with 'print': P 2000-01-01 A 1 B P 2000-02-01 A 2 B P 2000-03-01 A 3 B P 2000-04-01 A 4 B 2000-01-01 (a) 1 A @ 5 B 2000-02-01 (a) 1 A @ 6 B 2000-03-01 (a) 1 A @ 7 B Show the cost of each posting: $ hledger -f- print --cost 2000-01-01 (a) 5 B 2000-02-01 (a) 6 B 2000-03-01 (a) 7 B Show the value as of the last day of the report period (2000-02-29): $ hledger -f- print --value=end date:2000/01-2000/03 2000-01-01 (a) 2 B 2000-02-01 (a) 2 B With no report period specified, that shows the value as of the last day of the journal (2000-03-01): $ hledger -f- print --value=end 2000-01-01 (a) 3 B 2000-02-01 (a) 3 B 2000-03-01 (a) 3 B Show the current value (the 2000-04-01 price is still in effect today): $ hledger -f- print --value=now 2000-01-01 (a) 4 B 2000-02-01 (a) 4 B 2000-03-01 (a) 4 B Show the value on 2000/01/15: $ hledger -f- print --value=2000-01-15 2000-01-01 (a) 1 B 2000-02-01 (a) 1 B 2000-03-01 (a) 1 B  File: hledger.info, Node: Interaction of valuation and queries, Next: Effect of valuation on reports, Prev: More valuation examples, Up: Value reporting 23.10 Interaction of valuation and queries ========================================== When matching postings based on queries in the presence of valuation, the following happens. 1. The query is separated into two parts: 1. the currency ('cur:') or amount ('amt:'). 2. all other parts. 2. The postings are matched to the currency and amount queries based on pre-valued amounts. 3. Valuation is applied to the postings. 4. The postings are matched to the other parts of the query based on post-valued amounts. See: 1625  File: hledger.info, Node: Effect of valuation on reports, Prev: Interaction of valuation and queries, Up: Value reporting 23.11 Effect of valuation on reports ==================================== Here is a reference for how valuation is supposed to affect each part of hledger's reports (and a glossary). (It's wide, you'll have to scroll sideways.) It may be useful when troubleshooting. If you find problems, please report them, ideally with a reproducible example. Related: #329, #1083. Report '-B', '-V', '-X' '--value=then' '--value=end''--value=DATE', type '--cost' '--value=now' ------------------------------------------------------------------------------ *print* posting cost value at value at posting value at value amounts report end date report or at or today journal DATE/today end balance unchanged unchanged unchanged unchanged unchanged assertions/assignments *register* starting cost value at valued at day value at value balance report or each historical report or at (-H) journal posting was made journal DATE/today end end starting cost value at valued at day value at value balance day before each historical day before at (-H) report or posting was made report or DATE/today with journal journal report start start interval posting cost value at value at posting value at value amounts report or date report or at journal journal DATE/today end end summary summarised value at sum of postings value at value posting cost period in interval, period at amounts ends valued at ends DATE/today with interval start report interval running sum/average sum/average sum/average of sum/average sum/average total/averageof of displayed values of of displayed displayed displayed displayed values values values values *balance (bs, bse, cf, is)* balance sums of value at value at posting value at value changes costs report end date report or at or today journal DATE/today of sums of end of of postings sums of sums postings of postings budget like like like balance like like amounts balance balance changes balances balance (-budget) changes changes changes grand sum of sum of sum of displayed sum of sum of total displayed displayed valued displayed displayed values values values values *balance (bs, bse, cf, is) with report interval* starting sums of value at sums of values value at sums balances costs of report of postings report of (-H) postings start of before report start of postings before sums of start at sums of before report all respective all report start postings posting dates postings start before before report report start start balance sums of same as sums of values balance value changes costs of -value=end of postings in change in at (bal, postings period at each DATE/today is, bs in period respective period, of -change, posting dates valued at sums cf period of -change) ends postings end sums of same as sums of values period end value balances costs of -value=end of postings from balances, at (bal -H, postings before period valued at DATE/today is -H, from start to period period of bs, cf) before end at ends sums report respective of start to posting dates postings period end budget like like like balance like like amounts balance balance changes/end balances balance (-budget) changes/end changes/end balances changes/end balances balances balances row sums, sums, sums, averages sums, sums, totals, averages averages of displayed averages averages row of of values of of averages displayed displayed displayed displayed (-T, -A) values values values values column sums of sums of sums of sums of sums totals displayed displayed displayed values displayed of values values values displayed values grand sum, sum, sum, average of sum, sum, total, average of average of column totals average of average grand column column column of average totals totals totals column totals '--cumulative' is omitted to save space, it works like '-H' but with a zero starting balance. *Glossary:* _cost_ calculated using price(s) recorded in the transaction(s). _value_ market value using available market price declarations, or the unchanged amount if no conversion rate can be found. _report start_ the first day of the report period specified with -b or -p or date:, otherwise today. _report or journal start_ the first day of the report period specified with -b or -p or date:, otherwise the earliest transaction date in the journal, otherwise today. _report end_ the last day of the report period specified with -e or -p or date:, otherwise today. _report or journal end_ the last day of the report period specified with -e or -p or date:, otherwise the latest transaction date in the journal, otherwise today. _report interval_ a flag (-D/-W/-M/-Q/-Y) or period expression that activates the report's multi-period mode (whether showing one or many subperiods).  File: hledger.info, Node: PART 4 COMMANDS, Next: PART 5 COMMON TASKS, Prev: Value reporting, Up: Top 24 PART 4: COMMANDS ******************* * Menu: * Commands overview:: * accounts:: * activity:: * add:: * aregister:: * balance:: * balancesheet:: * balancesheetequity:: * cashflow:: * check:: * close:: * codes:: * commodities:: * demo:: * descriptions:: * diff:: * files:: * help:: * import:: * incomestatement:: * notes:: * payees:: * prices:: * print:: * register:: * rewrite:: * roi:: * stats:: * tags:: * test::  File: hledger.info, Node: Commands overview, Next: accounts, Up: PART 4 COMMANDS 24.1 Commands overview ====================== Here are the built-in commands: * Menu: * DATA ENTRY:: * DATA CREATION:: * DATA MANAGEMENT:: * REPORTS FINANCIAL:: * REPORTS VERSATILE:: * REPORTS BASIC:: * HELP:: * ADD-ONS::  File: hledger.info, Node: DATA ENTRY, Next: DATA CREATION, Up: Commands overview 24.1.1 DATA ENTRY ----------------- These data entry commands are the only ones which can modify your journal file. * add - add transactions using terminal prompts * import - add new transactions from other files, eg CSV files  File: hledger.info, Node: DATA CREATION, Next: DATA MANAGEMENT, Prev: DATA ENTRY, Up: Commands overview 24.1.2 DATA CREATION -------------------- * close - generate balance-zeroing/restoring transactions * rewrite - generate auto postings, like print -auto  File: hledger.info, Node: DATA MANAGEMENT, Next: REPORTS FINANCIAL, Prev: DATA CREATION, Up: Commands overview 24.1.3 DATA MANAGEMENT ---------------------- * check - check for various kinds of error in the data * diff - compare account transactions in two journal files  File: hledger.info, Node: REPORTS FINANCIAL, Next: REPORTS VERSATILE, Prev: DATA MANAGEMENT, Up: Commands overview 24.1.4 REPORTS, FINANCIAL ------------------------- * aregister (areg) - show transactions in a particular account * balancesheet (bs) - show assets, liabilities and net worth * balancesheetequity (bse) - show assets, liabilities and equity * cashflow (cf) - show changes in liquid assets * incomestatement (is) - show revenues and expenses  File: hledger.info, Node: REPORTS VERSATILE, Next: REPORTS BASIC, Prev: REPORTS FINANCIAL, Up: Commands overview 24.1.5 REPORTS, VERSATILE ------------------------- * balance (bal) - show balance changes, end balances, budgets, gains.. * print - show transactions or export journal data * register (reg) - show postings in one or more accounts & running total * roi - show return on investments  File: hledger.info, Node: REPORTS BASIC, Next: HELP, Prev: REPORTS VERSATILE, Up: Commands overview 24.1.6 REPORTS, BASIC --------------------- * accounts - show account names * activity - show bar charts of posting counts per period * codes - show transaction codes * commodities - show commodity/currency symbols * descriptions - show transaction descriptions * files - show input file paths * notes - show note parts of transaction descriptions * payees - show payee parts of transaction descriptions * prices - show market prices * stats - show journal statistics * tags - show tag names * test - run self tests  File: hledger.info, Node: HELP, Next: ADD-ONS, Prev: REPORTS BASIC, Up: Commands overview 24.1.7 HELP ----------- * help - show the hledger manual with info/man/pager * demo - show small hledger demos in the terminal  File: hledger.info, Node: ADD-ONS, Prev: HELP, Up: Commands overview 24.1.8 ADD-ONS -------------- And here are some typical add-on commands. Some of these are installed by the hledger-install script. If installed, they will appear in hledger's commands list: * ui - run hledger's terminal UI * web - run hledger's web UI * iadd - add transactions using a TUI (currently hard to build) * interest - generate interest transactions * stockquotes - download market prices from AlphaVantage * Scripts and add-ons - check-fancyassertions, edit, fifo, git, move, pijul, plot, and more.. Next, each command is described in detail, in alphabetical order.  File: hledger.info, Node: accounts, Next: activity, Prev: Commands overview, Up: PART 4 COMMANDS 24.2 accounts ============= Show account names. This command lists account names. By default it shows all known accounts, either used in transactions or declared with account directives. With query arguments, only matched account names and account names referenced by matched postings are shown. Or it can show just the used accounts ('--used'/'-u'), the declared accounts ('--declared'/'-d'), the accounts declared but not used ('--unused'), the accounts used but not declared ('--undeclared'), or the first account matched by an account name pattern, if any ('--find'). It shows a flat list by default. With '--tree', it uses indentation to show the account hierarchy. In flat mode you can add '--drop N' to omit the first few account name components. Account names can be depth-clipped with 'depth:N' or '--depth N' or '-N'. With '--types', it also shows each account's type, if it's known. (See Declaring accounts > Account types.) With '--positions', it also shows the file and line number of each account's declaration, if any, and the account's overall declaration order; these may be useful when troubleshooting account display order. With '--directives', it adds the 'account' keyword, showing valid account directives which can be pasted into a journal file. This is useful together with '--undeclared' when updating your account declarations to satisfy 'hledger check accounts'. The '--find' flag can be used to look up a single account name, in the same way that the 'aregister' command does. It returns the alphanumerically-first matched account name, or if none can be found, it fails with a non-zero exit code. Examples: $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts $ hledger accounts --undeclared --directives >> $LEDGER_FILE $ hledger check accounts  File: hledger.info, Node: activity, Next: add, Prev: accounts, Up: PART 4 COMMANDS 24.3 activity ============= Show an ascii barchart of posting counts per interval. The activity command displays an ascii histogram showing transaction counts by day, week, month or other reporting interval (by day is the default). With query arguments, it counts only matched transactions. Examples: $ hledger activity --quarterly 2008-01-01 ** 2008-04-01 ******* 2008-07-01 2008-10-01 **  File: hledger.info, Node: add, Next: aregister, Prev: activity, Up: PART 4 COMMANDS 24.4 add ======== Prompt for transactions and add them to the journal. Any arguments will be used as default inputs for the first N prompts. Many hledger users edit their journals directly with a text editor, or generate them from CSV. For more interactive data entry, there is the 'add' command, which prompts interactively on the console for new transactions, and appends them to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also 'import'). To use it, just run 'hledger add' and follow the prompts. You can add as many transactions as you like; when you are finished, enter '.' or press control-d or control-c to exit. Features: * add tries to provide useful defaults, using the most similar (by description) recent transaction (filtered by the query, if any) as a template. * You can also set the initial defaults with command line arguments. * Readline-style edit keys can be used during data entry. * The tab key will auto-complete whenever possible - accounts, payees/descriptions, dates ('yesterday', 'today', 'tomorrow'). If the input area is empty, it will insert the default value. * If the journal defines a default commodity, it will be added to any bare numbers entered. * A parenthesised transaction code may be entered following a date. * Comments and tags may be entered following a description or amount. * If you make a mistake, enter '<' at any prompt to go one step backward. * Input prompts are displayed in a different colour when the terminal supports it. Example (see https://hledger.org/add.html for a detailed tutorial): $ hledger add Adding transactions to journal file /src/hledger/examples/sample.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control-d or control-c. Date [2015/05/22]: Description: supermarket Account 1: expenses:food Amount 1: $10 Account 2: assets:checking Amount 2 [$-10.0]: Account 3 (or . or enter to finish this transaction): . 2015/05/22 supermarket expenses:food $10 assets:checking $-10.0 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl-D/ctrl-C to quit) Date [2015/05/22]: $ On Microsoft Windows, the add command makes sure that no part of the file path ends with a period, as that would cause problems (#1056).  File: hledger.info, Node: aregister, Next: balance, Prev: add, Up: PART 4 COMMANDS 24.5 aregister ============== (areg) Show the transactions and running historical balance of a single account, with each transaction displayed as one line. 'aregister' shows the overall transactions affecting a particular account (and any subaccounts). Each report line represents one transaction in this account. Transactions before the report start date are always included in the running balance ('--historical' mode is always on). This is a more "real world", bank-like view than the 'register' command (which shows individual postings, possibly from multiple accounts, not necessarily in historical mode). As a quick rule of thumb: - use 'aregister' for reviewing and reconciling real-world asset/liability accounts - use 'register' for reviewing detailed revenues/expenses. 'aregister' requires one argument: the account to report on. You can write either the full account name, or a case-insensitive regular expression which will select the alphabetically first matched account. When there are multiple matches, the alphabetically-first choice can be surprising; eg if you have 'assets:per:checking 1' and 'assets:biz:checking 2' accounts, 'hledger areg checking' would select 'assets:biz:checking 2'. It's just a convenience to save typing, so if in doubt, write the full account name, or a distinctive substring that matches uniquely. Transactions involving subaccounts of this account will also be shown. 'aregister' ignores depth limits, so its final total will always match a balance report with similar arguments. Any additional arguments form a query which will filter the transactions shown. Note some queries will disturb the running balance, causing it to be different from the account's real-world running balance. An example: this shows the transactions and historical running balance during july, in the first account whose name contains "checking": $ hledger areg checking date:jul Each 'aregister' line item shows: * the transaction's date (or the relevant posting's date if different, see below) * the names of all the other account(s) involved in this transaction (probably abbreviated) * the total change to this account's balance from this transaction * the account's historical running balance after this transaction. Transactions making a net change of zero are not shown by default; add the '-E/--empty' flag to show them. For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the '--align-all' flag. This command also supports the output destination and output format options. The output formats supported are 'txt', 'csv', 'tsv', and 'json'. * Menu: * aregister and posting dates::  File: hledger.info, Node: aregister and posting dates, Up: aregister 24.5.1 aregister and posting dates ---------------------------------- aregister always shows one line (and date and amount) per transaction. But sometimes transactions have postings with different dates. Also, not all of a transaction's postings may be within the report period. To resolve this, aregister shows the earliest of the transaction's date and posting dates that is in-period, and the sum of the in-period postings. In other words it will show a combined line item with just the earliest date, and the running balance will (temporarily, until the transaction's last posting) be inaccurate. Use 'register -H' if you need to see the individual postings. There is also a '--txn-dates' flag, which filters strictly by transaction date, ignoring posting dates. This too can cause an inaccurate running balance.  File: hledger.info, Node: balance, Next: balancesheet, Prev: aregister, Up: PART 4 COMMANDS 24.6 balance ============ (bal) Show accounts and their balances. 'balance' is one of hledger's oldest and most versatile commands, for listing account balances, balance changes, values, value changes and more, during one time period or many. Generally it shows a table, with rows representing accounts, and columns representing periods. Note there are some higher-level variants of the 'balance' command with convenient defaults, which can be simpler to use: 'balancesheet', 'balancesheetequity', 'cashflow' and 'incomestatement'. When you need more control, then use 'balance'. * Menu: * balance features:: * Simple balance report:: * Balance report line format:: * Filtered balance report:: * List or tree mode:: * Depth limiting:: * Dropping top-level accounts:: * Showing declared accounts:: * Sorting by amount:: * Percentages:: * Multi-period balance report:: * Balance change end balance:: * Balance report types:: * Budget report:: * Balance report layout:: * Useful balance reports::  File: hledger.info, Node: balance features, Next: Simple balance report, Up: balance 24.6.1 balance features ----------------------- Here's a quick overview of the 'balance' command's features, followed by more detailed descriptions and examples. Many of these work with the higher-level commands as well. 'balance' can show.. * accounts as a list ('-l') or a tree ('-t') * optionally depth-limited ('-[1-9]') * sorted by declaration order and name, or by amount ..and their.. * balance changes (the default) * or actual and planned balance changes ('--budget') * or value of balance changes ('-V') * or change of balance values ('--valuechange') * or unrealised capital gain/loss ('--gain') * or postings count ('--count') ..in.. * one time period (the whole journal period by default) * or multiple periods ('-D', '-W', '-M', '-Q', '-Y', '-p INTERVAL') ..either.. * per period (the default) * or accumulated since report start date ('--cumulative') * or accumulated since account creation ('--historical/-H') ..possibly converted to.. * cost ('--value=cost[,COMM]'/'--cost'/'-B') * or market value, as of transaction dates ('--value=then[,COMM]') * or at period ends ('--value=end[,COMM]') * or now ('--value=now') * or at some other date ('--value=YYYY-MM-DD') ..with.. * totals ('-T'), averages ('-A'), percentages ('-%'), inverted sign ('--invert') * rows and columns swapped ('--transpose') * another field used as account name ('--pivot') * custom-formatted line items (single-period reports only) ('--format') * commodities displayed on the same line or multiple lines ('--layout') This command supports the output destination and output format options, with output formats 'txt', 'csv', 'tsv', 'json', and (multi-period reports only:) 'html'. In 'txt' output in a colour-supporting terminal, negative amounts are shown in red. The '--related'/'-r' flag shows the balance of the _other_ postings in the transactions of the postings which would normally be shown.  File: hledger.info, Node: Simple balance report, Next: Balance report line format, Prev: balance features, Up: balance 24.6.2 Simple balance report ---------------------------- With no arguments, 'balance' shows a list of all accounts and their change of balance - ie, the sum of posting amounts, both inflows and outflows - during the entire period of the journal. ("Simple" here means just one column of numbers, covering a single period. You can also have multi-period reports, described later.) For real-world accounts, these numbers will normally be their end balance at the end of the journal period; more on this below. Accounts are sorted by declaration order if any, and then alphabetically by account name. For instance (using examples/sample.journal): $ hledger -f examples/sample.journal bal $1 assets:bank:saving $-2 assets:cash $1 expenses:food $1 expenses:supplies $-1 income:gifts $-1 income:salary $1 liabilities:debts -------------------- 0 Accounts with a zero balance (and no non-zero subaccounts, in tree mode - see below) are hidden by default. Use '-E/--empty' to show them (revealing 'assets:bank:checking' here): $ hledger -f examples/sample.journal bal -E 0 assets:bank:checking $1 assets:bank:saving $-2 assets:cash $1 expenses:food $1 expenses:supplies $-1 income:gifts $-1 income:salary $1 liabilities:debts -------------------- 0 The total of the amounts displayed is shown as the last line, unless '-N'/'--no-total' is used.  File: hledger.info, Node: Balance report line format, Next: Filtered balance report, Prev: Simple balance report, Up: balance 24.6.3 Balance report line format --------------------------------- For single-period balance reports displayed in the terminal (only), you can use '--format FMT' to customise the format and content of each line. Eg: $ hledger -f examples/sample.journal balance --format "%20(account) %12(total)" assets $-1 bank:saving $1 cash $-2 expenses $2 food $1 supplies $1 income $-2 gifts $-1 salary $-1 liabilities:debts $1 --------------------------------- 0 The FMT format string specifies the formatting applied to each account/balance pair. It may contain any suitable text, with data fields interpolated like so: '%[MIN][.MAX](FIELDNAME)' * MIN pads with spaces to at least this width (optional) * MAX truncates at this width (optional) * FIELDNAME must be enclosed in parentheses, and can be one of: * 'depth_spacer' - a number of spaces equal to the account's depth, or if MIN is specified, MIN * depth spaces. * 'account' - the account's name * 'total' - the account's balance/posted total, right justified Also, FMT can begin with an optional prefix to control how multi-commodity amounts are rendered: * '%_' - render on multiple lines, bottom-aligned (the default) * '%^' - render on multiple lines, top-aligned * '%,' - render on one line, comma-separated There are some quirks. Eg in one-line mode, '%(depth_spacer)' has no effect, instead '%(account)' has indentation built in. Experimentation may be needed to get pleasing results. Some example formats: * '%(total)' - the account's total * '%-20.20(account)' - the account's name, left justified, padded to 20 characters and clipped at 20 characters * '%,%-50(account) %25(total)' - account name padded to 50 characters, total padded to 20 characters, with multiple commodities rendered on one line * '%20(total) %2(depth_spacer)%-(account)' - the default format for the single-column balance report  File: hledger.info, Node: Filtered balance report, Next: List or tree mode, Prev: Balance report line format, Up: balance 24.6.4 Filtered balance report ------------------------------ You can show fewer accounts, a different time period, totals from cleared transactions only, etc. by using query arguments or options to limit the postings being matched. Eg: $ hledger -f examples/sample.journal bal --cleared assets date:200806 $-2 assets:cash -------------------- $-2  File: hledger.info, Node: List or tree mode, Next: Depth limiting, Prev: Filtered balance report, Up: balance 24.6.5 List or tree mode ------------------------ By default, or with '-l/--flat', accounts are shown as a flat list with their full names visible, as in the examples above. With '-t/--tree', the account hierarchy is shown, with subaccounts' "leaf" names indented below their parent: $ hledger -f examples/sample.journal balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 Notes: * "Boring" accounts are combined with their subaccount for more compact output, unless '--no-elide' is used. Boring accounts have no balance of their own and just one subaccount (eg 'assets:bank' and 'liabilities' above). * All balances shown are "inclusive", ie including the balances from all subaccounts. Note this means some repetition in the output, which requires explanation when sharing reports with non-plaintextaccounting-users. A tree mode report's final total is the sum of the top-level balances shown, not of all the balances shown. * Each group of sibling accounts (ie, under a common parent) is sorted separately.  File: hledger.info, Node: Depth limiting, Next: Dropping top-level accounts, Prev: List or tree mode, Up: balance 24.6.6 Depth limiting --------------------- With a 'depth:NUM' query, or '--depth NUM' option, or just '-NUM' (eg: '-3') balance reports will show accounts only to the specified depth, hiding the deeper subaccounts. This can be useful for getting an overview without too much detail. Account balances at the depth limit always include the balances from any deeper subaccounts (even in list mode). Eg, limiting to depth 1: $ hledger -f examples/sample.journal balance -1 $-1 assets $2 expenses $-2 income $1 liabilities -------------------- 0  File: hledger.info, Node: Dropping top-level accounts, Next: Showing declared accounts, Prev: Depth limiting, Up: balance 24.6.7 Dropping top-level accounts ---------------------------------- You can also hide one or more top-level account name parts, using '--drop NUM'. This can be useful for hiding repetitive top-level account names: $ hledger -f examples/sample.journal bal expenses --drop 1 $1 food $1 supplies -------------------- $2  File: hledger.info, Node: Showing declared accounts, Next: Sorting by amount, Prev: Dropping top-level accounts, Up: balance 24.6.8 Showing declared accounts -------------------------------- With '--declared', accounts which have been declared with an account directive will be included in the balance report, even if they have no transactions. (Since they will have a zero balance, you will also need '-E/--empty' to see them.) More precisely, _leaf_ declared accounts (with no subaccounts) will be included, since those are usually the more useful in reports. The idea of this is to be able to see a useful "complete" balance report, even when you don't have transactions in all of your declared accounts yet.  File: hledger.info, Node: Sorting by amount, Next: Percentages, Prev: Showing declared accounts, Up: balance 24.6.9 Sorting by amount ------------------------ With '-S/--sort-amount', accounts with the largest (most positive) balances are shown first. Eg: 'hledger bal expenses -MAS' shows your biggest averaged monthly expenses first. When more than one commodity is present, they will be sorted by the alphabetically earliest commodity first, and then by subsequent commodities (if an amount is missing a commodity, it is treated as 0). Revenues and liability balances are typically negative, however, so '-S' shows these in reverse order. To work around this, you can add '--invert' to flip the signs. (Or, use one of the higher-level reports, which flip the sign automatically. Eg: 'hledger incomestatement -MAS').  File: hledger.info, Node: Percentages, Next: Multi-period balance report, Prev: Sorting by amount, Up: balance 24.6.10 Percentages ------------------- With '-%/--percent', balance reports show each account's value expressed as a percentage of the (column) total. Note it is not useful to calculate percentages if the amounts in a column have mixed signs. In this case, make a separate report for each sign, eg: $ hledger bal -% amt:`>0` $ hledger bal -% amt:`<0` Similarly, if the amounts in a column have mixed commodities, convert them to one commodity with '-B', '-V', '-X' or '--value', or make a separate report for each commodity: $ hledger bal -% cur:\\$ $ hledger bal -% cur:€  File: hledger.info, Node: Multi-period balance report, Next: Balance change end balance, Prev: Percentages, Up: balance 24.6.11 Multi-period balance report ----------------------------------- With a report interval (set by the '-D/--daily', '-W/--weekly', '-M/--monthly', '-Q/--quarterly', '-Y/--yearly', or '-p/--period' flag), 'balance' shows a tabular report, with columns representing successive time periods (and a title): $ hledger -f examples/sample.journal bal --quarterly income expenses -E Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 ===================++================================= expenses:food || 0 $1 0 0 expenses:supplies || 0 $1 0 0 income:gifts || 0 $-1 0 0 income:salary || $-1 0 0 0 -------------------++--------------------------------- || $-1 $1 0 0 Notes: * The report's start/end dates will be expanded, if necessary, to fully encompass the displayed subperiods (so that the first and last subperiods have the same duration as the others). * Leading and trailing periods (columns) containing all zeroes are not shown, unless '-E/--empty' is used. * Accounts (rows) containing all zeroes are not shown, unless '-E/--empty' is used. * Amounts with many commodities are shown in abbreviated form, unless '--no-elide' is used. _(experimental)_ * Average and/or total columns can be added with the '-A/--average' and '-T/--row-total' flags. * The '--transpose' flag can be used to exchange rows and columns. * The '--pivot FIELD' option causes a different transaction field to be used as "account name". See PIVOTING. Multi-period reports with many periods can be too wide for easy viewing in the terminal. Here are some ways to handle that: * Hide the totals row with '-N/--no-total' * Convert to a single currency with '-V' * Maximize the terminal window * Reduce the terminal's font size * View with a pager like less, eg: 'hledger bal -D --color=yes | less -RS' * Output as CSV and use a CSV viewer like visidata ('hledger bal -D -O csv | vd -f csv'), Emacs' csv-mode ('M-x csv-mode, C-c C-a'), or a spreadsheet ('hledger bal -D -o a.csv && open a.csv') * Output as HTML and view with a browser: 'hledger bal -D -o a.html && open a.html'  File: hledger.info, Node: Balance change end balance, Next: Balance report types, Prev: Multi-period balance report, Up: balance 24.6.12 Balance change, end balance ----------------------------------- It's important to be clear on the meaning of the numbers shown in balance reports. Here is some terminology we use: A *_balance change_* is the net amount added to, or removed from, an account during some period. An *_end balance_* is the amount accumulated in an account as of some date (and some time, but hledger doesn't store that; assume end of day in your timezone). It is the sum of previous balance changes. We call it a *_historical end balance_* if it includes all balance changes since the account was created. For a real world account, this means it will match the "historical record", eg the balances reported in your bank statements or bank web UI. (If they are correct!) In general, balance changes are what you want to see when reviewing revenues and expenses, and historical end balances are what you want to see when reviewing or reconciling asset, liability and equity accounts. 'balance' shows balance changes by default. To see accurate historical end balances: 1. Initialise account starting balances with an "opening balances" transaction (a transfer from equity to the account), unless the journal covers the account's full lifetime. 2. Include all of of the account's prior postings in the report, by not specifying a report start date, or by using the '-H/--historical' flag. ('-H' causes report start date to be ignored when summing postings.)  File: hledger.info, Node: Balance report types, Next: Budget report, Prev: Balance change end balance, Up: balance 24.6.13 Balance report types ---------------------------- The balance command is quite flexible; here is the full detail on how to control what it reports. If the following seems complicated, don't worry - this is for advanced reporting, and it does take time and experimentation to get familiar with all the report modes. There are three important option groups: 'hledger balance [CALCULATIONTYPE] [ACCUMULATIONTYPE] [VALUATIONTYPE] ...' * Menu: * Calculation type:: * Accumulation type:: * Valuation type:: * Combining balance report types::  File: hledger.info, Node: Calculation type, Next: Accumulation type, Up: Balance report types 24.6.13.1 Calculation type .......................... The basic calculation to perform for each table cell. It is one of: * '--sum' : sum the posting amounts (*default*) * '--budget' : sum the amounts, but also show the budget goal amount (for each account/period) * '--valuechange' : show the change in period-end historical balance values (caused by deposits, withdrawals, and/or market price fluctuations) * '--gain' : show the unrealised capital gain/loss, (the current valued balance minus each amount's original cost) * '--count' : show the count of postings  File: hledger.info, Node: Accumulation type, Next: Valuation type, Prev: Calculation type, Up: Balance report types 24.6.13.2 Accumulation type ........................... How amounts should accumulate across report periods. Another way to say it: which time period's postings should contribute to each cell's calculation. It is one of: * '--change' : calculate with postings from column start to column end, ie "just this column". Typically used to see revenues/expenses. (*default for balance, incomestatement*) * '--cumulative' : calculate with postings from report start to column end, ie "previous columns plus this column". Typically used to show changes accumulated since the report's start date. Not often used. * '--historical/-H' : calculate with postings from journal start to column end, ie "all postings from before report start date until this column's end". Typically used to see historical end balances of assets/liabilities/equity. (*default for balancesheet, balancesheetequity, cashflow*)  File: hledger.info, Node: Valuation type, Next: Combining balance report types, Prev: Accumulation type, Up: Balance report types 24.6.13.3 Valuation type ........................ Which kind of value or cost conversion should be applied, if any, before displaying the report. It is one of: * no valuation type : don't convert to cost or value (*default*) * '--value=cost[,COMM]' : convert amounts to cost (then optionally to some other commodity) * '--value=then[,COMM]' : convert amounts to market value on transaction dates * '--value=end[,COMM]' : convert amounts to market value on period end date(s) (*default with '--valuechange', '--gain'*) * '--value=now[,COMM]' : convert amounts to market value on today's date * '--value=YYYY-MM-DD[,COMM]' : convert amounts to market value on another date or one of the equivalent simpler flags: * '-B/--cost' : like -value=cost (though, note -cost and -value are independent options which can both be used at once) * '-V/--market' : like -value=end * '-X COMM/--exchange COMM' : like -value=end,COMM See Cost reporting and Value reporting for more about these.  File: hledger.info, Node: Combining balance report types, Prev: Valuation type, Up: Balance report types 24.6.13.4 Combining balance report types ........................................ Most combinations of these options should produce reasonable reports, but if you find any that seem wrong or misleading, let us know. The following restrictions are applied: * '--valuechange' implies '--value=end' * '--valuechange' makes '--change' the default when used with the 'balancesheet'/'balancesheetequity' commands * '--cumulative' or '--historical' disables '--row-total/-T' For reference, here is what the combinations of accumulation and valuation show: Valuation:>no valuation '--value= then' '--value= end' '--value= Accumulation:v YYYY-MM-DD /now' ----------------------------------------------------------------------------- '--change'change in sum of period-end DATE-value period posting-date value of of change in market values change in period in period period '--cumulative'change from sum of period-end DATE-value report start to posting-date value of of change period end market values change from from report from report report start start to start to period to period end period end end '--historicalchange from sum of period-end DATE-value /-H' journal start posting-date value of of change to period end market values change from from journal (historical end from journal journal start start to balance) start to period to period end period end end  File: hledger.info, Node: Budget report, Next: Balance report layout, Prev: Balance report types, Up: balance 24.6.14 Budget report --------------------- The '--budget' report type is like a regular balance report, but with two main differences: * Budget goals and performance percentages are also shown, in brackets * Accounts which don't have budget goals are hidden by default. This is useful for comparing planned and actual income, expenses, time usage, etc. Periodic transaction rules are used to define budget goals. For example, here's a periodic rule defining monthly goals for bus travel and food expenses: ;; Budget ~ monthly (expenses:bus) $30 (expenses:food) $400 After recording some actual expenses, ;; Two months worth of expenses 2017-11-01 income $-1950 expenses:bus $35 expenses:food:groceries $310 expenses:food:dining $42 expenses:movies $38 assets:bank:checking 2017-12-01 income $-2100 expenses:bus $53 expenses:food:groceries $380 expenses:food:dining $32 expenses:gifts $100 assets:bank:checking we can see a budget report like this: $ hledger bal -M --budget Budget performance in 2017-11-01..2017-12-31: || Nov Dec ===============++============================================ || $-425 $-565 expenses || $425 [ 99% of $430] $565 [131% of $430] expenses:bus || $35 [117% of $30] $53 [177% of $30] expenses:food || $352 [ 88% of $400] $412 [103% of $400] ---------------++-------------------------------------------- || 0 [ 0% of $430] 0 [ 0% of $430] This is "goal-based budgeting"; you define goals for accounts and periods, often recurring, and hledger shows performance relative to the goals. This contrasts with "envelope budgeting", which is more detailed and strict - useful when cash is tight, but also quite a bit more work. https://plaintextaccounting.org/Budgeting has more on this topic. * Menu: * Using the budget report:: * Budget date surprises:: * Selecting budget goals:: * Budgeting vs forecasting::  File: hledger.info, Node: Using the budget report, Next: Budget date surprises, Up: Budget report 24.6.14.1 Using the budget report ................................. Historically this report has been confusing and fragile. hledger's version should be relatively robust and intuitive, but you may still find surprises. Here are more notes to help with learning and troubleshooting. * In the above example, 'expenses:bus' and 'expenses:food' are shown because they have budget goals during the report period. * Their parent 'expenses' is also shown, with budget goals aggregated from the children. * The subaccounts 'expenses:food:groceries' and 'expenses:food:dining' are not shown since they have no budget goal of their own, but they contribute to 'expenses:food''s actual amount. * Unbudgeted accounts 'expenses:movies' and 'expenses:gifts' are also not shown, but they contribute to 'expenses''s actual amount. * The other unbudgeted accounts 'income' and 'assets:bank:checking' are grouped as ''. * '--depth' or 'depth:' can be used to limit report depth in the usual way (but will not reveal unbudgeted subaccounts). * Amounts are always inclusive of subaccounts (even in '-l/--list' mode). * Numbers displayed in a -budget report will not always agree with the totals, because of hidden unbudgeted accounts; this is normal. '-E/--empty' can be used to reveal the hidden accounts. * In the periodic rules used for setting budget goals, unbalanced postings are convenient. * You can filter budget reports with the usual queries, eg to focus on particular accounts. It's common to restrict them to just expenses. (The '' account is occasionally hard to exclude; this is because of date surprises, discussed below.) * When you have multiple currencies, you may want to convert them to one ('-X COMM --infer-market-prices') and/or show just one at a time ('cur:COMM'). If you do need to show multiple currencies at once, '--layout bare' can be helpful. * You can "roll over" amounts (actual and budgeted) to the next period with '--cumulative'. See also: https://hledger.org/budgeting.html.  File: hledger.info, Node: Budget date surprises, Next: Selecting budget goals, Prev: Using the budget report, Up: Budget report 24.6.14.2 Budget date surprises ............................... With small data, or when starting out, some of the generated budget goal transaction dates might fall outside the report periods. Eg with the following journal and report, the first period appears to have no 'expenses:food' budget. (Also the '' account should be excluded by the 'expenses' query, but isn't.): ~ monthly in 2020 (expenses:food) $500 2020-01-15 expenses:food $400 assets:checking $ hledger bal --budget expenses Budget performance in 2020-01-15: || 2020-01-15 ===============++==================== || $400 expenses:food || 0 [ 0% of $500] ---------------++-------------------- || $400 [80% of $500] In this case, the budget goal transactions are generated on first days of of month (this can be seen with 'hledger print --forecast tag:generated expenses'). Whereas the report period defaults to just the 15th day of january (this can be seen from the report table's column headings). To fix this kind of thing, be more explicit about the report period (and/or the periodic rules' dates). In this case, adding '-b 2020' does the trick.  File: hledger.info, Node: Selecting budget goals, Next: Budgeting vs forecasting, Prev: Budget date surprises, Up: Budget report 24.6.14.3 Selecting budget goals ................................ By default, the budget report uses all available periodic transaction rules to generate goals. This includes rules with a different report interval from your report. Eg if you have daily, weekly and monthly periodic rules, all of these will contribute to the goals in a monthly budget report. You can select a subset of periodic rules by providing an argument to the '--budget' flag. '--budget=DESCPAT' will match all periodic rules whose description contains DESCPAT, a case-insensitive substring (not a regular expression or query). This means you can give your periodic rules descriptions (remember that two spaces are needed between period expression and description), and then select from multiple budgets defined in your journal.  File: hledger.info, Node: Budgeting vs forecasting, Prev: Selecting budget goals, Up: Budget report 24.6.14.4 Budgeting vs forecasting .................................. '--budget' and '--forecast' both use the periodic transaction rules in the journal to generate temporary transactions for reporting purposes. However they are separate features - though you can use both at the same time if you want. Here are some differences between them: 1. '--budget' is a command-specific option; it selects the *budget report*. '--forecast' is a general option; *forecasting works with all reports*. 2. '--budget' uses *all periodic rules*; '--budget=DESCPAT' uses *just the rules matched* by DESCPAT. '--forecast' uses *all periodic rules*. 3. '--budget''s budget goal transactions are invisible, except that they produce *goal amounts*. '--forecast''s forecast transactions are visible, and *appear in reports*. 4. '--budget' generates budget goal transactions *throughout the report period*, optionally restricted by periods specified in the periodic transaction rules. '--forecast' generates forecast transactions from *after the last regular transaction*, to the end of the report period; while '--forecast=PERIODEXPR' generates them *throughout the specified period*; both optionally restricted by periods specified in the periodic transaction rules.  File: hledger.info, Node: Balance report layout, Next: Useful balance reports, Prev: Budget report, Up: balance 24.6.15 Balance report layout ----------------------------- The '--layout' option affects how balance reports show multi-commodity amounts and commodity symbols, which can improve readability. It can also normalise the data for easy consumption by other programs. It has four possible values: * '--layout=wide[,WIDTH]': commodities are shown on a single line, optionally elided to WIDTH * '--layout=tall': each commodity is shown on a separate line * '--layout=bare': commodity symbols are in their own column, amounts are bare numbers * '--layout=tidy': data is normalised to easily-consumed "tidy" form, with one row per data value Here are the '--layout' modes supported by each output format; note only CSV output supports all of them: - txt csv html json sql --------------------------------------- wide Y Y Y tall Y Y Y bare Y Y Y tidy Y Examples: * Wide layout. With many commodities, reports can be very wide: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=wide Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++==================================================================================================================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, -98.12 USD, 10.00 VEA, 18.00 VHT -11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT ------------------++-------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------- || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, -98.12 USD, 10.00 VEA, 18.00 VHT -11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT * Limited wide layout. A width limit reduces the width, but some commodities will be hidden: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=wide,32 Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++=========================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. -11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. ------------------++--------------------------------------------------------------------------------------------------------------------------- || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. -11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. * Tall layout. Each commodity gets a new line (may be different in each column), and account names are repeated: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=tall Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++================================================== Assets:US:ETrade || 10.00 ITOT 70.00 GLD -11.00 ITOT 70.00 GLD Assets:US:ETrade || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT Assets:US:ETrade || 12.00 VEA -98.12 USD 14.00 VEA 5120.50 USD Assets:US:ETrade || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA Assets:US:ETrade || 18.00 VHT 294.00 VHT ------------------++-------------------------------------------------- || 10.00 ITOT 70.00 GLD -11.00 ITOT 70.00 GLD || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT || 12.00 VEA -98.12 USD 14.00 VEA 5120.50 USD || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA || 18.00 VHT 294.00 VHT * Bare layout. Commodity symbols are kept in one column, each commodity gets its own report row, account names are repeated: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=bare Balance changes in 2012-01-01..2014-12-31: || Commodity 2012 2013 2014 Total ==================++============================================= Assets:US:ETrade || GLD 0 70.00 0 70.00 Assets:US:ETrade || ITOT 10.00 18.00 -11.00 17.00 Assets:US:ETrade || USD 337.18 -98.12 4881.44 5120.50 Assets:US:ETrade || VEA 12.00 10.00 14.00 36.00 Assets:US:ETrade || VHT 106.00 18.00 170.00 294.00 ------------------++--------------------------------------------- || GLD 0 70.00 0 70.00 || ITOT 10.00 18.00 -11.00 17.00 || USD 337.18 -98.12 4881.44 5120.50 || VEA 12.00 10.00 14.00 36.00 || VHT 106.00 18.00 170.00 294.00 * Bare layout also affects CSV output, which is useful for producing data that is easier to consume, eg for making charts: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -O csv --layout=bare "account","commodity","balance" "Assets:US:ETrade","GLD","70.00" "Assets:US:ETrade","ITOT","17.00" "Assets:US:ETrade","USD","5120.50" "Assets:US:ETrade","VEA","36.00" "Assets:US:ETrade","VHT","294.00" "total","GLD","70.00" "total","ITOT","17.00" "total","USD","5120.50" "total","VEA","36.00" "total","VHT","294.00" * Note: bare layout will sometimes display an extra row for the no-symbol commodity, because of zero amounts (hledger treats zeroes as commodity-less, usually). This can break 'hledger-bar' confusingly (workaround: add a 'cur:' query to exclude the no-symbol row). * Tidy layout produces normalised "tidy data", where every variable has its own column and each row represents a single data point. See https://cran.r-project.org/web/packages/tidyr/vignettes/tidy-data.html for more. This is the easiest kind of data for other software to consume. Here's how it looks: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -Y -O csv --layout=tidy "account","period","start_date","end_date","commodity","value" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","GLD","0" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","ITOT","10.00" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","USD","337.18" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","VEA","12.00" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","VHT","106.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","GLD","70.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","ITOT","18.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","USD","-98.12" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","VEA","10.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","VHT","18.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","GLD","0" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","ITOT","-11.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","USD","4881.44" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","VEA","14.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","VHT","170.00"  File: hledger.info, Node: Useful balance reports, Prev: Balance report layout, Up: balance 24.6.16 Useful balance reports ------------------------------ Some frequently used 'balance' options/reports are: * 'bal -M revenues expenses' Show revenues/expenses in each month. Also available as the 'incomestatement' command. * 'bal -M -H assets liabilities' Show historical asset/liability balances at each month end. Also available as the 'balancesheet' command. * 'bal -M -H assets liabilities equity' Show historical asset/liability/equity balances at each month end. Also available as the 'balancesheetequity' command. * 'bal -M assets not:receivable' Show changes to liquid assets in each month. Also available as the 'cashflow' command. Also: * 'bal -M expenses -2 -SA' Show monthly expenses summarised to depth 2 and sorted by average amount. * 'bal -M --budget expenses' Show monthly expenses and budget goals. * 'bal -M --valuechange investments' Show monthly change in market value of investment assets. * 'bal investments --valuechange -D date:lastweek amt:'>1000' -STA [--invert]' Show top gainers [or losers] last week  File: hledger.info, Node: balancesheet, Next: balancesheetequity, Prev: balance, Up: PART 4 COMMANDS 24.7 balancesheet ================= (bs) This command displays a balance sheet, showing historical ending balances of asset and liability accounts. (To see equity as well, use the balancesheetequity command.) Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the 'Asset', 'Cash' or 'Liability' type (see account types). Or if no such accounts are declared, it shows top-level accounts named 'asset' or 'liability' (case insensitive, plurals allowed) and their subaccounts. Example: $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 This command is a higher-level variant of the 'balance' command, and supports many of that command's features, such as multi-period reports. It is similar to 'hledger balance -H assets liabilities', but with smarter account detection, and liabilities displayed with their sign flipped. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'tsv', 'html', and (experimental) 'json'.  File: hledger.info, Node: balancesheetequity, Next: cashflow, Prev: balancesheet, Up: PART 4 COMMANDS 24.8 balancesheetequity ======================= (bse) This command displays a balance sheet, showing historical ending balances of asset, liability and equity accounts. Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the 'Asset', 'Cash', 'Liability' or 'Equity' type (see account types). Or if no such accounts are declared, it shows top-level accounts named 'asset', 'liability' or 'equity' (case insensitive, plurals allowed) and their subaccounts. Example: $ hledger balancesheetequity Balance Sheet With Equity Assets: $-2 assets $1 bank:saving $-3 cash -------------------- $-2 Liabilities: $1 liabilities:debts -------------------- $1 Equity: $1 equity:owner -------------------- $1 Total: -------------------- 0 This command is a higher-level variant of the 'balance' command, and supports many of that command's features, such as multi-period reports. It is similar to 'hledger balance -H assets liabilities equity', but with smarter account detection, and liabilities/equity displayed with their sign flipped. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'tsv', 'html', and (experimental) 'json'.  File: hledger.info, Node: cashflow, Next: check, Prev: balancesheetequity, Up: PART 4 COMMANDS 24.9 cashflow ============= (cf) This command displays a cashflow statement, showing the inflows and outflows affecting "cash" (ie, liquid, easily convertible) assets. Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the 'Cash' type (see account types). Or if no such accounts are declared, it shows accounts * under a top-level account named 'asset' (case insensitive, plural allowed) * whose name contains some variation of 'cash', 'bank', 'checking' or 'saving'. More precisely: all accounts matching this case insensitive regular expression: '^assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|currentcash)(:|$)' and their subaccounts. An example cashflow report: $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 This command is a higher-level variant of the 'balance' command, and supports many of that command's features, such as multi-period reports. It is similar to 'hledger balance assets not:fixed not:investment not:receivable', but with smarter account detection. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'tsv', 'html', and (experimental) 'json'.  File: hledger.info, Node: check, Next: close, Prev: cashflow, Up: PART 4 COMMANDS 24.10 check =========== Check for various kinds of errors in your data. hledger provides a number of built-in error checks to help prevent problems in your data. Some of these are run automatically; or, you can use this 'check' command to run them on demand, with no output and a zero exit code if all is well. Specify their names (or a prefix) as argument(s). Some examples: hledger check # basic checks hledger check -s # basic + strict checks hledger check ordereddates payees # basic + two other checks If you are an Emacs user, you can also configure flycheck-hledger to run these checks, providing instant feedback as you edit the journal. Here are the checks currently available: * Menu: * Default checks:: * Strict checks:: * Other checks:: * Custom checks:: * More about specific checks::  File: hledger.info, Node: Default checks, Next: Strict checks, Up: check 24.10.1 Default checks ---------------------- These checks are run automatically by (almost) all hledger commands: * *parseable* - data files are in a supported format, with no syntax errors and no invalid include directives. * *autobalanced* - all transactions are balanced, after converting to cost. Missing amounts and missing costs are inferred automatically where possible. * *assertions* - all balance assertions in the journal are passing. (This check can be disabled with '-I'/'--ignore-assertions'.)  File: hledger.info, Node: Strict checks, Next: Other checks, Prev: Default checks, Up: check 24.10.2 Strict checks --------------------- These additional checks are run when the '-s'/'--strict' (strict mode) flag is used. Or, they can be run by giving their names as arguments to 'check': * *balanced* - all transactions are balanced after converting to cost, without inferring missing costs. If conversion costs are required, they must be explicit. * *accounts* - all account names used by transactions have been declared * *commodities* - all commodity symbols used have been declared  File: hledger.info, Node: Other checks, Next: Custom checks, Prev: Strict checks, Up: check 24.10.3 Other checks -------------------- These checks can be run only by giving their names as arguments to 'check'. They are more specialised and not desirable for everyone: * *ordereddates* - transactions are ordered by date within each file * *payees* - all payees used by transactions have been declared * *recentassertions* - all accounts with balance assertions have a balance assertion within 7 days of their latest posting * *tags* - all tags used by transactions have been declared * *uniqueleafnames* - all account leaf names are unique  File: hledger.info, Node: Custom checks, Next: More about specific checks, Prev: Other checks, Up: check 24.10.4 Custom checks --------------------- A few more checks are are available as separate add-on commands, in https://github.com/simonmichael/hledger/tree/master/bin: * *hledger-check-tagfiles* - all tag values containing / (a forward slash) exist as file paths * *hledger-check-fancyassertions* - more complex balance assertions are passing You could make similar scripts to perform your own custom checks. See: Cookbook -> Scripting.  File: hledger.info, Node: More about specific checks, Prev: Custom checks, Up: check 24.10.5 More about specific checks ---------------------------------- 'hledger check recentassertions' will complain if any balance-asserted account has postings more than 7 days after its latest balance assertion. This aims to prevent the situation where you are regularly updating your journal, but forgetting to check your balances against the real world, then one day must dig back through months of data to find an error. It assumes that adding a balance assertion requires/reminds you to check the real-world balance. (That may not be true if you auto-generate balance assertions from bank data; in that case, I recommend to import transactions uncleared, and when you manually review and clear them, also check the latest assertion against the real-world balance.)  File: hledger.info, Node: close, Next: codes, Prev: check, Up: PART 4 COMMANDS 24.11 close =========== (equity) Generate transactions which transfer account balances to and/or from another account (typically equity). This can be useful for migrating balances to a new journal file, or for merging earnings into equity at end of accounting period. By default, it prints a transaction that zeroes out ALE accounts (asset, liability, equity accounts; this requires account types to be configured); or if ACCTQUERY is provided, the accounts matched by that. _(experimental)_ This command has four main modes, corresponding to the most common use cases: 1. With '--close' (default), it prints a "closing balances" transaction that zeroes out ALE (asset, liability, equity) accounts by default (this requires account types to be inferred or declared); or, the accounts matched by the provided ACCTQUERY arguments. 2. With '--open', it prints an opposite "opening balances" transaction that restores those balances from zero. This is similar to Ledger's equity command. 3. With '--migrate', it prints both the closing and opening transactions. This is the preferred way to migrate balances to a new file: run 'hledger close --migrate', add the closing transaction at the end of the old file, and add the opening transaction at the start of the new file. The matching closing/opening transactions cancel each other out, preserving correct balances during multi-file reporting. 4. With '--retain', it prints a "retain earnings" transaction that transfers RX (revenue and expense) balances to 'equity:retained earnings'. Businesses traditionally do this at the end of each accounting period; it is less necessary with computer-based accounting, but it could still be useful if you want to see the accounting equation (A=L+E) satisfied. In all modes, the defaults can be overridden: * the transaction descriptions can be changed with '--close-desc=DESC' and '--open-desc=DESC' * the account to transfer to/from can be changed with '--close-acct=ACCT' and '--open-acct=ACCT' * the accounts to be closed/opened can be changed with 'ACCTQUERY' (account query arguments). * the closing/opening dates can be changed with '-e DATE' (a report end date) By default just one destination/source posting will be used, with its amount left implicit. With '--x/--explicit', the amount will be shown explicitly, and if it involves multiple commodities, a separate posting will be generated for each of them (similar to 'print -x'). With '--show-costs', any amount costs are shown, with separate postings for each cost. This is currently the best way to view investment lots. If you have many currency conversion or investment transactions, it can generate very large journal entries. With '--interleaved', each individual transfer is shown with source and destination postings next to each other. This could be useful for troubleshooting. The default closing date is yesterday, or the journal's end date, whichever is later. You can change this by specifying a report end date with '-e'. The last day of the report period will be the closing date, eg '-e 2024' means "close on 2023-12-31". The opening date is always the day after the closing date. * Menu: * close and balance assertions:: * Example retain earnings:: * Example migrate balances to a new file:: * Example excluding closing/opening transactions::  File: hledger.info, Node: close and balance assertions, Next: Example retain earnings, Up: close 24.11.1 close and balance assertions ------------------------------------ Balance assertions will be generated, verifying that the accounts have been reset to zero (and then restored to their previous balances, if there is an opening transaction). These provide useful error checking, but you can ignore them temporarily with '-I', or remove them if you prefer. You probably should avoid filtering transactions by status or realness ('-C', '-R', 'status:'), or generating postings ('--auto'), with this command, since the balance assertions would depend on these. Note custom posting dates spanning the file boundary will disrupt the balance assertions: 2023-12-30 a purchase made in december, cleared in january expenses:food 5 assets:bank:checking -5 ; date: 2023-01-02 To solve that you can transfer the money to and from a temporary account, in effect splitting the multi-day transaction into two single-day transactions: ; in 2022.journal: 2022-12-30 a purchase made in december, cleared in january expenses:food 5 equity:pending -5 ; in 2023.journal: 2023-01-02 last year's transaction cleared equity:pending 5 = 0 assets:bank:checking -5  File: hledger.info, Node: Example retain earnings, Next: Example migrate balances to a new file, Prev: close and balance assertions, Up: close 24.11.2 Example: retain earnings -------------------------------- Record 2022's revenues/expenses as retained earnings on 2022-12-31, appending the generated transaction to the journal: $ hledger close --retain -f 2022.journal -p 2022 >> 2022.journal Note 2022's income statement will now show only zeroes, because revenues and expenses have been moved entirely to equity. To see them again, you could exclude the retain transaction: $ hledger -f 2022.journal is not:desc:'retain earnings'  File: hledger.info, Node: Example migrate balances to a new file, Next: Example excluding closing/opening transactions, Prev: Example retain earnings, Up: close 24.11.3 Example: migrate balances to a new file ----------------------------------------------- Close assets/liabilities/equity on 2022-12-31 and re-open them on 2023-01-01: $ hledger close --migrate -f 2022.journal -p 2022 # copy/paste the closing transaction to the end of 2022.journal # copy/paste the opening transaction to the start of 2023.journal Now 2022's balance sheet will show only zeroes, indicating a balanced accounting equation. (Unless you are using @/@@ notation - in that case, try adding -infer-equity.) To see the end-of-year balances again, you could exclude the closing transaction: $ hledger -f 2022.journal bs not:desc:'closing balances'  File: hledger.info, Node: Example excluding closing/opening transactions, Prev: Example migrate balances to a new file, Up: close 24.11.4 Example: excluding closing/opening transactions ------------------------------------------------------- When combining many files for multi-year reports, the closing/opening transactions cause some noise in transaction-oriented reports like 'print' and 'register'. You can exclude them as shown above, but 'not:desc:...' is not ideal as it depends on consistent descriptions; also you will want to avoid excluding the very first opening transaction, which could be awkward. Here is one alternative, using tags: Add 'clopen:' tags to all opening/closing balances transactions except the first, like this: ; 2021.journal 2021-06-01 first opening balances ... 2021-12-31 closing balances ; clopen:2022 ... ; 2022.journal 2022-01-01 opening balances ; clopen:2022 ... 2022-12-31 closing balances ; clopen:2023 ... ; 2023.journal 2023-01-01 opening balances ; clopen:2023 ... Now, assuming a combined journal like: ; all.journal include 2021.journal include 2022.journal include 2023.journal The 'clopen:' tag can exclude all but the first opening transaction. To show a clean multi-year checking register: $ hledger -f all.journal areg checking not:tag:clopen And the year values allow more precision. To show 2022's year-end balance sheet: $ hledger -f all.journal bs -e2023 not:tag:clopen=2023  File: hledger.info, Node: codes, Next: commodities, Prev: close, Up: PART 4 COMMANDS 24.12 codes =========== List the codes seen in transactions, in the order parsed. This command prints the value of each transaction's code field, in the order transactions were parsed. The transaction code is an optional value written in parentheses between the date and description, often used to store a cheque number, order number or similar. Transactions aren't required to have a code, and missing or empty codes will not be shown by default. With the '-E'/'--empty' flag, they will be printed as blank lines. You can add a query to select a subset of transactions. Examples: 2022/1/1 (123) Supermarket Food $5.00 Checking 2022/1/2 (124) Post Office Postage $8.32 Checking 2022/1/3 Supermarket Food $11.23 Checking 2022/1/4 (126) Post Office Postage $3.21 Checking $ hledger codes 123 124 126 $ hledger codes -E 123 124 126  File: hledger.info, Node: commodities, Next: demo, Prev: codes, Up: PART 4 COMMANDS 24.13 commodities ================= List all commodity/currency symbols used or declared in the journal.  File: hledger.info, Node: demo, Next: descriptions, Prev: commodities, Up: PART 4 COMMANDS 24.14 demo ========== Play demos of hledger usage in the terminal, if asciinema is installed. Run this command with no argument to list the demos. To play a demo, write its number or a prefix or substring of its title. Tips: Make your terminal window large enough to see the demo clearly. Use the -s/-speed SPEED option to set your preferred playback speed, eg '-s4' to play at 4x original speed or '-s.5' to play at half speed. The default speed is 2x. Other asciinema options can be added following a double dash, eg '-- -i.1' to limit pauses or '-- -h' to list asciinema's other options. During playback, several keys are available: SPACE to pause/unpause, . to step forward (while paused), CTRL-c quit. Examples: $ hledger demo # list available demos $ hledger demo 1 # play the first demo at default speed (2x) $ hledger demo install -s4 # play the "install" demo at 4x speed  File: hledger.info, Node: descriptions, Next: diff, Prev: demo, Up: PART 4 COMMANDS 24.15 descriptions ================== List the unique descriptions that appear in transactions. This command lists the unique descriptions that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. Example: $ hledger descriptions Store Name Gas Station | Petrol Person A  File: hledger.info, Node: diff, Next: files, Prev: descriptions, Up: PART 4 COMMANDS 24.16 diff ========== Compares a particular account's transactions in two input files. It shows any transactions to this account which are in one file but not in the other. More precisely, for each posting affecting this account in either file, it looks for a corresponding posting in the other file which posts the same amount to the same account (ignoring date, description, etc.) Since postings not transactions are compared, this also works when multiple bank transactions have been combined into a single journal entry. This is useful eg if you have downloaded an account's transactions from your bank (eg as CSV data). When hledger and your bank disagree about the account balance, you can compare the bank data with your journal to find out the cause. Examples: $ hledger diff -f $LEDGER_FILE -f bank.csv assets:bank:giro These transactions are in the first file only: 2014/01/01 Opening Balances assets:bank:giro EUR ... ... equity:opening balances EUR -... These transactions are in the second file only:  File: hledger.info, Node: files, Next: help, Prev: diff, Up: PART 4 COMMANDS 24.17 files =========== List all files included in the journal. With a REGEX argument, only file names matching the regular expression (case sensitive) are shown.  File: hledger.info, Node: help, Next: import, Prev: files, Up: PART 4 COMMANDS 24.18 help ========== Show the hledger user manual in the terminal, with 'info', 'man', or a pager. With a TOPIC argument, open it at that topic if possible. TOPIC can be any heading in the manual, or a heading prefix, case insensitive. Eg: 'commands', 'print', 'forecast', 'journal', 'amount', '"auto postings"'. This command shows the hledger manual built in to your hledger version. It can be useful when offline, or when you prefer the terminal to a web browser, or when the appropriate hledger manual or viewing tools are not installed on your system. By default it chooses the best viewer found in $PATH, trying (in this order): 'info', 'man', '$PAGER', 'less', 'more'. You can force the use of info, man, or a pager with the '-i', '-m', or '-p' flags, If no viewer can be found, or the command is run non-interactively, it just prints the manual to stdout. If using 'info', note that version 6 or greater is needed for TOPIC lookup. If you are on mac you will likely have info 4.8, and should consider installing a newer version, eg with 'brew install texinfo' (#1770). Examples $ hledger help --help # show how the help command works $ hledger help # show the hledger manual with info, man or $PAGER $ hledger help journal # show the journal topic in the hledger manual $ hledger help -m journal # show it with man, even if info is installed  File: hledger.info, Node: import, Next: incomestatement, Prev: help, Up: PART 4 COMMANDS 24.19 import ============ Read new transactions added to each FILE provided as arguments since last run, and add them to the journal. Or with -dry-run, just print the transactions that would be added. Or with -catchup, just mark all of the FILEs' current transactions as imported, without importing them. This command may append new transactions to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also 'add'). Unlike other hledger commands, with 'import' the journal file is an output file, and will be modified, though only by appending (existing data will not be changed). The input files are specified as arguments, so to import one or more CSV files to your main journal, you will run 'hledger import bank.csv' or perhaps 'hledger import *.csv'. Note you can import from any file format, though CSV files are the most common import source, and these docs focus on that case. * Menu: * Deduplication:: * Import testing:: * Importing balance assignments:: * Commodity display styles::  File: hledger.info, Node: Deduplication, Next: Import testing, Up: import 24.19.1 Deduplication --------------------- 'import' does _time-based deduplication_, to detect only the new transactions since the last successful import. (This does not mean "ignore transactions that look the same", but rather "ignore transactions that have been seen before".) This is intended for when you are periodically importing downloaded data, which may overlap with previous downloads. Eg if every week (or every day) you download a bank's last three months of CSV data, you can safely run 'hledger import thebank.csv' each time and only new transactions will be imported. Since the items being read (CSV records, eg) often do not come with unique identifiers, hledger detects new transactions by date, assuming that: 1. new items always have the newest dates 2. item dates do not change across reads 3. and items with the same date remain in the same relative order across reads. These are often true of CSV files representing transactions, or true enough so that it works pretty well in practice. 1 is important, but violations of 2 and 3 amongst the old transactions won't matter (and if you import often, the new transactions will be few, so less likely to be the ones affected). hledger remembers the latest date processed in each input file by saving a hidden ".latest.FILE" file in FILE's directory (after a succesful import). Eg when reading 'finance/bank.csv', it will look for and update the 'finance/.latest.bank.csv' state file. The format is simple: one or more lines containing the same ISO-format date (YYYY-MM-DD), meaning "I have processed transactions up to this date, and this many of them on that date." Normally you won't see or manipulate these state files yourself. But if needed, you can delete them to reset the state (making all transactions "new"), or you can construct them to "catch up" to a certain date. Note deduplication (and updating of state files) can also be done by 'print --new', but this is less often used. Related: CSV > Working with CSV > Deduplicating, importing.  File: hledger.info, Node: Import testing, Next: Importing balance assignments, Prev: Deduplication, Up: import 24.19.2 Import testing ---------------------- With '--dry-run', the transactions that will be imported are printed to the terminal, without updating your journal or state files. The output is valid journal format, like the print command, so you can re-parse it. Eg, to see any importable transactions which CSV rules have not categorised: $ hledger import --dry bank.csv | hledger -f- -I print unknown or (live updating): $ ls bank.csv* | entr bash -c 'echo ====; hledger import --dry bank.csv | hledger -f- -I print unknown' Note: when importing from multiple files at once, it's currently possible for some .latest files to be updated successfully, while the actual import fails because of a problem in one of the files, leaving them out of sync (and causing some transactions to be missed). To prevent this, do a -dry-run first and fix any problems before the real import.  File: hledger.info, Node: Importing balance assignments, Next: Commodity display styles, Prev: Import testing, Up: import 24.19.3 Importing balance assignments ------------------------------------- Entries added by import will have their posting amounts made explicit (like 'hledger print -x'). This means that any balance assignments in imported files must be evaluated; but, imported files don't get to see the main file's account balances. As a result, importing entries with balance assignments (eg from an institution that provides only balances and not posting amounts) will probably generate incorrect posting amounts. To avoid this problem, use print instead of import: $ hledger print IMPORTFILE [--new] >> $LEDGER_FILE (If you think import should leave amounts implicit like print does, please test it and send a pull request.)  File: hledger.info, Node: Commodity display styles, Prev: Importing balance assignments, Up: import 24.19.4 Commodity display styles -------------------------------- Imported amounts will be formatted according to the canonical commodity styles (declared or inferred) in the main journal file.  File: hledger.info, Node: incomestatement, Next: notes, Prev: import, Up: PART 4 COMMANDS 24.20 incomestatement ===================== (is) This command displays an income statement, showing revenues and expenses during one or more periods. Amounts are shown with normal positive sign, as in conventional financial statements. This report shows accounts declared with the 'Revenue' or 'Expense' type (see account types). Or if no such accounts are declared, it shows top-level accounts named 'revenue' or 'income' or 'expense' (case insensitive, plurals allowed) and their subaccounts. Example: $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 This command is a higher-level variant of the 'balance' command, and supports many of that command's features, such as multi-period reports. It is similar to 'hledger balance '(revenues|income)' expenses', but with smarter account detection, and revenues/income displayed with their sign flipped. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'tsv', 'html', and (experimental) 'json'.  File: hledger.info, Node: notes, Next: payees, Prev: incomestatement, Up: PART 4 COMMANDS 24.21 notes =========== List the unique notes that appear in transactions. This command lists the unique notes that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. The note is the part of the transaction description after a | character (or if there is no |, the whole description). Example: $ hledger notes Petrol Snacks  File: hledger.info, Node: payees, Next: prices, Prev: notes, Up: PART 4 COMMANDS 24.22 payees ============ List the unique payee/payer names that appear in transactions. This command lists unique payee/payer names which have been declared with payee directives (-declared), used in transaction descriptions (-used), or both (the default). The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). You can add query arguments to select a subset of transactions. This implies -used. Example: $ hledger payees Store Name Gas Station Person A  File: hledger.info, Node: prices, Next: print, Prev: payees, Up: PART 4 COMMANDS 24.23 prices ============ Print the market prices declared with P directives. With -infer-market-prices, also show any additional prices inferred from costs. With -show-reverse, also show additional prices inferred by reversing known prices. Price amounts are always displayed with their full precision, except for reverse prices which are limited to 8 decimal digits. Prices can be filtered by a date:, cur: or amt: query. Generally if you run this command with -infer-market-prices -show-reverse, it will show the same prices used internally to calculate value reports. But if in doubt, you can inspect those directly by running the value report with -debug=2.  File: hledger.info, Node: print, Next: register, Prev: prices, Up: PART 4 COMMANDS 24.24 print =========== Show transaction journal entries, sorted by date. The print command displays full journal entries (transactions) from the journal file, sorted by date (or with '--date2', by secondary date). Directives and inter-transaction comments are not shown, currently. This means the print command is somewhat lossy, and if you are using it to reformat/regenerate your journal you should take care to also copy over the directives and inter-transaction comments. Eg: $ hledger print -f examples/sample.journal date:200806 2008/06/01 gift assets:bank:checking $1 income:gifts $-1 2008/06/02 save assets:bank:saving $1 assets:bank:checking $-1 2008/06/03 * eat & shop expenses:food $1 expenses:supplies $1 assets:cash $-2 * Menu: * print explicitness:: * print amount style:: * print parseability:: * print other features:: * print output format::  File: hledger.info, Node: print explicitness, Next: print amount style, Up: print 24.24.1 print explicitness -------------------------- Normally, whether posting amounts are implicit or explicit is preserved. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, if a conversion cost is implied but not written, it will not appear in the output. You can use the '-x'/'--explicit' flag to force explicit display of all amounts and costs. This can be useful for troubleshooting or for making your journal more readable and robust against data entry errors. '-x' is also implied by using any of '-B','-V','-X','--value'. The '-x'/'--explicit' flag will cause any postings with a multi-commodity amount (which can arise when a multi-commodity transaction has an implicit amount) to be split into multiple single-commodity postings, keeping the output parseable.  File: hledger.info, Node: print amount style, Next: print parseability, Prev: print explicitness, Up: print 24.24.2 print amount style -------------------------- Amounts are shown right-aligned within each transaction (but not aligned across all transactions; you can do that with ledger-mode in Emacs). Amounts will be (mostly) normalised to their commodity display style: their symbol placement, decimal mark, and digit group marks will be made consistent. By default, decimal digits are shown as they are written in the journal. With the '--round' option, 'print' will try increasingly hard to display decimal digits according to the commodity display styles: * '--round=none' show amounts with original precisions (default) * '--round=soft' add/remove decimal zeros in amounts (except costs) * '--round=hard' round amounts (except costs), possibly hiding significant digits * '--round=all' round all amounts and costs 'soft' is good for non-lossy cleanup, formatting amounts more consistently where it's safe to do so. 'hard' and 'all' can cause 'print' to show invalid unbalanced journal entries; they may be useful eg for stronger cleanup, with manual fixups when needed.  File: hledger.info, Node: print parseability, Next: print other features, Prev: print amount style, Up: print 24.24.3 print parseability -------------------------- print's output is usually a valid hledger journal, and you can process it again with a second hledger command. This can be useful for certain kinds of search (though the same can be achieved with 'expr:' queries now): # Show running total of food expenses paid from cash. # -f- reads from stdin. -I/--ignore-assertions is sometimes needed. $ hledger print assets:cash | hledger -f- -I reg expenses:food There are some situations where print's output can become unparseable: * Value reporting affects posting amounts but not balance assertion or balance assignment amounts, potentially causing those to fail. * Auto postings can generate postings with too many missing amounts. * Account aliases can generate bad account names.  File: hledger.info, Node: print other features, Next: print output format, Prev: print parseability, Up: print 24.24.4 print, other features ----------------------------- With '-B'/'--cost', amounts with costs are shown converted to cost. With '--new', print shows only transactions it has not seen on a previous run. This uses the same deduplication system as the 'import' command. (See import's docs for details.) With '-m DESC'/'--match=DESC', print shows one recent transaction whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar-enough match, no transaction will be shown and the program exit code will be non-zero.  File: hledger.info, Node: print output format, Prev: print other features, Up: print 24.24.5 print output format --------------------------- This command also supports the output destination and output format options The output formats supported are 'txt', 'beancount', 'csv', 'tsv', 'json' and 'sql'. _Experimental:_ The 'beancount' format tries to produce Beancount-compatible output, as follows: * Transaction and postings with unmarked status are converted to cleared ('*') status. * Transactions' payee and note are backslash-escaped and double-quote-escaped and wrapped in double quotes. * Transaction tags are copied to Beancount #tag format. * Commodity symbols are converted to upper case, and a small number of currency symbols like '$' are converted to the corresponding currency names. * Account name parts are capitalised and unsupported characters are replaced with '-'. If an account name part does not begin with a letter, or if the first part is not Assets, Liabilities, Equity, Income, or Expenses, an error is raised. (Use '--alias' options to bring your accounts into compliance.) * An 'open' directive is generated for each account used, on the earliest transaction date. Some limitations: * Balance assertions are removed. * Balance assignments become missing amounts. * Virtual and balanced virtual postings become regular postings. * Directives are not converted. Here's an example of print's CSV output: $ hledger print -Ocsv "txnidx","date","date2","status","code","description","comment","account","amount","commodity","credit","debit","posting-status","posting-comment" "1","2008/01/01","","","","income","","assets:bank:checking","1","$","","1","","" "1","2008/01/01","","","","income","","income:salary","-1","$","1","","","" "2","2008/06/01","","","","gift","","assets:bank:checking","1","$","","1","","" "2","2008/06/01","","","","gift","","income:gifts","-1","$","1","","","" "3","2008/06/02","","","","save","","assets:bank:saving","1","$","","1","","" "3","2008/06/02","","","","save","","assets:bank:checking","-1","$","1","","","" "4","2008/06/03","","*","","eat & shop","","expenses:food","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","expenses:supplies","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","assets:cash","-2","$","2","","","" "5","2008/12/31","","*","","pay off","","liabilities:debts","1","$","","1","","" "5","2008/12/31","","*","","pay off","","assets:bank:checking","-1","$","1","","","" * There is one CSV record per posting, with the parent transaction's fields repeated. * The "txnidx" (transaction index) field shows which postings belong to the same transaction. (This number might change if transactions are reordered within the file, files are parsed/included in a different order, etc.) * The amount is separated into "commodity" (the symbol) and "amount" (numeric quantity) fields. * The numeric amount is repeated in either the "credit" or "debit" column, for convenience. (Those names are not accurate in the accounting sense; it just puts negative amounts under credit and zero or greater amounts under debit.)  File: hledger.info, Node: register, Next: rewrite, Prev: print, Up: PART 4 COMMANDS 24.25 register ============== (reg) Show postings and their running total. The register command displays matched postings, across all accounts, in date order, with their running total or running historical balance. (See also the 'aregister' command, which shows matched transactions in a specific account.) register normally shows line per posting, but note that multi-commodity amounts will occupy multiple lines (one line per commodity). It is typically used with a query selecting a particular account, to see that account's activity: $ hledger register checking 2008/01/01 income assets:bank:checking $1 $1 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $-1 $1 2008/12/31 pay off assets:bank:checking $-1 0 With '--date2', it shows and sorts by secondary date instead. For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the '--align-all' flag. The '--historical'/'-H' flag adds the balance from any undisplayed prior postings to the running total. This is useful when you want to see only recent activity, with a historically accurate running balance: $ hledger register checking -b 2008/6 --historical 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $-1 $1 2008/12/31 pay off assets:bank:checking $-1 0 The '--depth' option limits the amount of sub-account detail displayed. The '--average'/'-A' flag shows the running average posting amount instead of the running total (so, the final number displayed is the average for the whole report period). This flag implies '--empty' (see below). It is affected by '--historical'. It works best when showing just one account and one commodity. The '--related'/'-r' flag shows the _other_ postings in the transactions of the postings which would normally be shown. The '--invert' flag negates all amounts. For example, it can be used on an income account where amounts are normally displayed as negative numbers. It's also useful to show postings on the checking account together with the related account: $ hledger register --related --invert assets:checking With a reporting interval, register shows summary postings, one per interval, aggregating the postings to each account: $ hledger register --monthly income 2008/01 income:salary $-1 $-1 2008/06 income:gifts $-1 $-2 Periods with no activity, and summary postings with a zero amount, are not shown by default; use the '--empty'/'-E' flag to see them: $ hledger register --monthly income -E 2008/01 income:salary $-1 $-1 2008/02 0 $-1 2008/03 0 $-1 2008/04 0 $-1 2008/05 0 $-1 2008/06 income:gifts $-1 $-2 2008/07 0 $-2 2008/08 0 $-2 2008/09 0 $-2 2008/10 0 $-2 2008/11 0 $-2 2008/12 0 $-2 Often, you'll want to see just one line per interval. The '--depth' option helps with this, causing subaccounts to be aggregated: $ hledger register --monthly assets --depth 1h 2008/01 assets $1 $1 2008/06 assets $-1 0 2008/12 assets $-1 $-1 Note when using report intervals, if you specify start/end dates these will be adjusted outward if necessary to contain a whole number of intervals. This ensures that the first and last intervals are full length and comparable to the others in the report. With '-m DESC'/'--match=DESC', register does a fuzzy search for one recent posting whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar-enough match, no posting will be shown and the program exit code will be non-zero. * Menu: * Custom register output::  File: hledger.info, Node: Custom register output, Up: register 24.25.1 Custom register output ------------------------------ register uses the full terminal width by default, except on windows. You can override this by setting the 'COLUMNS' environment variable (not a bash shell variable) or by using the '--width'/'-w' option. The description and account columns normally share the space equally (about half of (width - 40) each). You can adjust this by adding a description width as part of -width's argument, comma-separated: '--width W,D' . Here's a diagram (won't display correctly in -help): <--------------------------------- width (W) ----------------------------------> date (10) description (D) account (W-41-D) amount (12) balance (12) DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA and some examples: $ hledger reg # use terminal width (or 80 on windows) $ hledger reg -w 100 # use width 100 $ COLUMNS=100 hledger reg # set with one-time environment variable $ export COLUMNS=100; hledger reg # set till session end (or window resize) $ hledger reg -w 100,40 # set overall width 100, description width 40 $ hledger reg -w $COLUMNS,40 # use terminal width, & description width 40 This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'tsv', and (experimental) 'json'.  File: hledger.info, Node: rewrite, Next: roi, Prev: register, Up: PART 4 COMMANDS 24.26 rewrite ============= Print all transactions, rewriting the postings of matched transactions. For now the only rewrite available is adding new postings, like print -auto. This is a start at a generic rewriter of transaction entries. It reads the default journal and prints the transactions, like print, but adds one or more specified postings to any transactions matching QUERY. The posting amounts can be fixed, or a multiplier of the existing transaction's first posting amount. Examples: $ hledger-rewrite.hs ^income --add-posting '(liabilities:tax) *.33 ; income tax' --add-posting '(reserve:gifts) $100' $ hledger-rewrite.hs expenses:gifts --add-posting '(reserve:gifts) *-1"' $ hledger-rewrite.hs -f rewrites.hledger rewrites.hledger may consist of entries like: = ^income amt:<0 date:2017 (liabilities:tax) *0.33 ; tax on income (reserve:grocery) *0.25 ; reserve 25% for grocery (reserve:) *0.25 ; reserve 25% for grocery Note the single quotes to protect the dollar sign from bash, and the two spaces between account and amount. More: $ hledger rewrite -- [QUERY] --add-posting "ACCT AMTEXPR" ... $ hledger rewrite -- ^income --add-posting '(liabilities:tax) *.33' $ hledger rewrite -- expenses:gifts --add-posting '(budget:gifts) *-1"' $ hledger rewrite -- ^income --add-posting '(budget:foreign currency) *0.25 JPY; diversify' Argument for '--add-posting' option is a usual posting of transaction with an exception for amount specification. More precisely, you can use ''*'' (star symbol) before the amount to indicate that that this is a factor for an amount of original matched posting. If the amount includes a commodity name, the new posting amount will be in the new commodity; otherwise, it will be in the matched posting amount's commodity. * Menu: * Re-write rules in a file:: * Diff output format:: * rewrite vs print --auto::  File: hledger.info, Node: Re-write rules in a file, Next: Diff output format, Up: rewrite 24.26.1 Re-write rules in a file -------------------------------- During the run this tool will execute so called "Automated Transactions" found in any journal it process. I.e instead of specifying this operations in command line you can put them in a journal file. $ rewrite-rules.journal Make contents look like this: = ^income (liabilities:tax) *.33 = expenses:gifts budget:gifts *-1 assets:budget *1 Note that ''='' (equality symbol) that is used instead of date in transactions you usually write. It indicates the query by which you want to match the posting to add new ones. $ hledger rewrite -- -f input.journal -f rewrite-rules.journal > rewritten-tidy-output.journal This is something similar to the commands pipeline: $ hledger rewrite -- -f input.journal '^income' --add-posting '(liabilities:tax) *.33' \ | hledger rewrite -- -f - expenses:gifts --add-posting 'budget:gifts *-1' \ --add-posting 'assets:budget *1' \ > rewritten-tidy-output.journal It is important to understand that relative order of such entries in journal is important. You can re-use result of previously added postings.  File: hledger.info, Node: Diff output format, Next: rewrite vs print --auto, Prev: Re-write rules in a file, Up: rewrite 24.26.2 Diff output format -------------------------- To use this tool for batch modification of your journal files you may find useful output in form of unified diff. $ hledger rewrite -- --diff -f examples/sample.journal '^income' --add-posting '(liabilities:tax) *.33' Output might look like: --- /tmp/examples/sample.journal +++ /tmp/examples/sample.journal @@ -18,3 +18,4 @@ 2008/01/01 income - assets:bank:checking $1 + assets:bank:checking $1 income:salary + (liabilities:tax) 0 @@ -22,3 +23,4 @@ 2008/06/01 gift - assets:bank:checking $1 + assets:bank:checking $1 income:gifts + (liabilities:tax) 0 If you'll pass this through 'patch' tool you'll get transactions containing the posting that matches your query be updated. Note that multiple files might be update according to list of input files specified via '--file' options and 'include' directives inside of these files. Be careful. Whole transaction being re-formatted in a style of output from 'hledger print'. See also: https://github.com/simonmichael/hledger/issues/99  File: hledger.info, Node: rewrite vs print --auto, Prev: Diff output format, Up: rewrite 24.26.3 rewrite vs. print -auto ------------------------------- This command predates print -auto, and currently does much the same thing, but with these differences: * with multiple files, rewrite lets rules in any file affect all other files. print -auto uses standard directive scoping; rules affect only child files. * rewrite's query limits which transactions can be rewritten; all are printed. print -auto's query limits which transactions are printed. * rewrite applies rules specified on command line or in the journal. print -auto applies rules specified in the journal.  File: hledger.info, Node: roi, Next: stats, Prev: rewrite, Up: PART 4 COMMANDS 24.27 roi ========= Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. At a minimum, you need to supply a query (which could be just an account name) to select your investment(s) with '--inv', and another query to identify your profit and loss transactions with '--pnl'. If you do not record changes in the value of your investment manually, or do not require computation of time-weighted return (TWR), '--pnl' could be an empty query ('--pnl ""' or '--pnl STR' where 'STR' does not match any of your accounts). This command will compute and display the internalized rate of return (IRR, also known as money-weighted rate of return) and time-weighted rate of return (TWR) for your investments for the time period requested. IRR is always annualized due to the way it is computed, but TWR is reported both as a rate over the chosen reporting period and as an annual rate. Price directives will be taken into account if you supply appropriate '--cost' or '--value' flags (see VALUATION). Note, in some cases this report can fail, for these reasons: * Error (NotBracketed): No solution for Internal Rate of Return (IRR). Possible causes: IRR is huge (>1000000%), balance of investment becomes negative at some point in time. * Error (SearchFailed): Failed to find solution for Internal Rate of Return (IRR). Either search does not converge to a solution, or converges too slowly. Examples: * Using roi to compute total return of investment in stocks: https://github.com/simonmichael/hledger/blob/master/examples/investing/roi-unrealised.ledger * Cookbook > Return on Investment: https://hledger.org/roi.html * Menu: * Spaces and special characters in --inv and --pnl:: * Semantics of --inv and --pnl:: * IRR and TWR explained::  File: hledger.info, Node: Spaces and special characters in --inv and --pnl, Next: Semantics of --inv and --pnl, Up: roi 24.27.1 Spaces and special characters in '--inv' and ---------------------------------------------------- '--pnl' Note that '--inv' and '--pnl''s argument is a query, and queries could have several space-separated terms (see QUERIES). To indicate that all search terms form single command-line argument, you will need to put them in quotes (see Special characters): $ hledger roi --inv 'term1 term2 term3 ...' If any query terms contain spaces themselves, you will need an extra level of nested quoting, eg: $ hledger roi --inv="'Assets:Test 1'" --pnl="'Equity:Unrealized Profit and Loss'"  File: hledger.info, Node: Semantics of --inv and --pnl, Next: IRR and TWR explained, Prev: Spaces and special characters in --inv and --pnl, Up: roi 24.27.2 Semantics of '--inv' and '--pnl' ---------------------------------------- Query supplied to '--inv' has to match all transactions that are related to your investment. Transactions not matching '--inv' will be ignored. In these transactions, ROI will conside postings that match '--inv' to be "investment postings" and other postings (not matching '--inv') will be sorted into two categories: "cash flow" and "profit and loss", as ROI needs to know which part of the investment value is your contributions and which is due to the return on investment. * "Cash flow" is depositing or withdrawing money, buying or selling assets, or otherwise converting between your investment commodity and any other commodity. Example: 2019-01-01 Investing in Snake Oil assets:cash -$100 investment:snake oil 2020-01-01 Selling my Snake Oil assets:cash $10 investment:snake oil = 0 * "Profit and loss" is change in the value of your investment: 2019-06-01 Snake Oil falls in value investment:snake oil = $57 equity:unrealized profit or loss All non-investment postings are assumed to be "cash flow", unless they match '--pnl' query. Changes in value of your investment due to "profit and loss" postings will be considered as part of your investment return. Example: if you use '--inv snake --pnl equity:unrealized', then postings in the example below would be classifed as: 2019-01-01 Snake Oil #1 assets:cash -$100 ; cash flow posting investment:snake oil ; investment posting 2019-03-01 Snake Oil #2 equity:unrealized pnl -$100 ; profit and loss posting snake oil ; investment posting 2019-07-01 Snake Oil #3 equity:unrealized pnl ; profit and loss posting cash -$100 ; cash flow posting snake oil $50 ; investment posting  File: hledger.info, Node: IRR and TWR explained, Prev: Semantics of --inv and --pnl, Up: roi 24.27.3 IRR and TWR explained ----------------------------- "ROI" stands for "return on investment". Traditionally this was computed as a difference between current value of investment and its initial value, expressed in percentage of the initial value. However, this approach is only practical in simple cases, where investments receives no in-flows or out-flows of money, and where rate of growth is fixed over time. For more complex scenarios you need different ways to compute rate of return, and this command implements two of them: IRR and TWR. Internal rate of return, or "IRR" (also called "money-weighted rate of return") takes into account effects of in-flows and out-flows, and the time between them. Investment at a particular fixed interest rate is going to give you more interest than the same amount invested at the same interest rate, but made later in time. If you are withdrawing from your investment, your future gains would be smaller (in absolute numbers), and will be a smaller percentage of your initial investment, so your IRR will be smaller. And if you are adding to your investment, you will receive bigger absolute gains, which will be a bigger percentage of your initial investment, so your IRR will be larger. As mentioned before, in-flows and out-flows would be any cash that you personally put in or withdraw, and for the "roi" command, these are the postings that match the query in the'--inv' argument and NOT match the query in the'--pnl' argument. If you manually record changes in the value of your investment as transactions that balance them against "profit and loss" (or "unrealized gains") account or use price directives, then in order for IRR to compute the precise effect of your in-flows and out-flows on the rate of return, you will need to record the value of your investement on or close to the days when in- or out-flows occur. In technical terms, IRR uses the same approach as computation of net present value, and tries to find a discount rate that makes net present value of all the cash flows of your investment to add up to zero. This could be hard to wrap your head around, especially if you haven't done discounted cash flow analysis before. Implementation of IRR in hledger should produce results that match the '=XIRR' formula in Excel. Second way to compute rate of return that 'roi' command implements is called "time-weighted rate of return" or "TWR". Like IRR, it will account for the effect of your in-flows and out-flows, but unlike IRR it will try to compute the true rate of return of the underlying asset, compensating for the effect that deposits and withdrawas have on the apparent rate of growth of your investment. TWR represents your investment as an imaginary "unit fund" where in-flows/ out-flows lead to buying or selling "units" of your investment and changes in its value change the value of "investment unit". Change in "unit price" over the reporting period gives you rate of return of your investment, and make TWR less sensitive than IRR to the effects of cash in-flows and out-flows. References: * Explanation of rate of return * Explanation of IRR * Explanation of TWR * IRR vs TWR * Examples of computing IRR and TWR and discussion of the limitations of both metrics  File: hledger.info, Node: stats, Next: tags, Prev: roi, Up: PART 4 COMMANDS 24.28 stats =========== Show journal and performance statistics. The stats command displays summary information for the whole journal, or a matched part of it. With a reporting interval, it shows a report for each report period. At the end, it shows (in the terminal) the overall run time and number of transactions processed per second. Note these are approximate and will vary based on machine, current load, data size, hledger version, haskell lib versions, GHC version.. but they may be of interest. The 'stats' command's run time is similar to that of a single-column balance report. Example: $ hledger stats -f examples/1000x1000x10.journal Main file : /Users/simon/src/hledger/examples/1000x1000x10.journal Included files : Transactions span : 2000-01-01 to 2002-09-27 (1000 days) Last transaction : 2002-09-26 (6995 days ago) Transactions : 1000 (1.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 1000 Accounts : 1000 (depth 10) Commodities : 26 (A, B, C, D, E, F, G, H, I, J, K, L, M, N, O, P, Q, R, S, T, U, V, W, X, Y, Z) Market prices : 1000 (A) Run time : 0.12 s Throughput : 8342 txns/s This command supports the -o/-output-file option (but not -O/-output-format selection).  File: hledger.info, Node: tags, Next: test, Prev: stats, Up: PART 4 COMMANDS 24.29 tags ========== List the tags used in the journal, or their values. This command lists the tag names used in the journal, whether on transactions, postings, or account declarations. With a TAGREGEX argument, only tag names matching this regular expression (case insensitive, infix matched) are shown. With QUERY arguments, only transactions and accounts matching this query are considered. If the query involves transaction fields (date:, desc:, amt:, ...), the search is restricted to the matched transactions and their accounts. With the -values flag, the tags' unique non-empty values are listed instead. With -E/-empty, blank/empty values are also shown. With -parsed, tags or values are shown in the order they were parsed, with duplicates included. (Except, tags from account declarations are always shown first.) Tip: remember, accounts also acquire tags from their parents, postings also acquire tags from their account and transaction, transactions also acquire tags from their postings.  File: hledger.info, Node: test, Prev: tags, Up: PART 4 COMMANDS 24.30 test ========== Run built-in unit tests. This command runs the unit tests built in to hledger and hledger-lib, printing the results on stdout. If any test fails, the exit code will be non-zero. This is mainly used by hledger developers, but you can also use it to sanity-check the installed hledger executable on your platform. All tests are expected to pass - if you ever see a failure, please report as a bug! This command also accepts tasty test runner options, written after a - (double hyphen). Eg to run only the tests in Hledger.Data.Amount, with ANSI colour codes disabled: $ hledger test -- -pData.Amount --color=never For help on these, see https://github.com/feuerbach/tasty#options ('-- --help' currently doesn't show them).  File: hledger.info, Node: PART 5 COMMON TASKS, Next: BUGS, Prev: PART 4 COMMANDS, Up: Top 25 PART 5: COMMON TASKS *********************** Here are some quick examples of how to do some basic tasks with hledger. * Menu: * Getting help:: * Constructing command lines:: * Starting a journal file:: * Setting LEDGER_FILE:: * Setting opening balances:: * Recording transactions:: * Reconciling:: * Reporting:: * Migrating to a new file::  File: hledger.info, Node: Getting help, Next: Constructing command lines, Up: PART 5 COMMON TASKS 25.1 Getting help ================= Here's how to list commands and view options and command docs: $ hledger # show available commands $ hledger --help # show common options $ hledger CMD --help # show CMD's options, common options and CMD's documentation You can also view your hledger version's manual in several formats by using the help command. Eg: $ hledger help # show the hledger manual with info, man or $PAGER (best available) $ hledger help journal # show the journal topic in the hledger manual $ hledger help --help # find out more about the help command To view manuals and introductory docs on the web, visit https://hledger.org. Chat and mail list support and discussion archives can be found at https://hledger.org/support.  File: hledger.info, Node: Constructing command lines, Next: Starting a journal file, Prev: Getting help, Up: PART 5 COMMON TASKS 25.2 Constructing command lines =============================== hledger has a flexible command line interface. We strive to keep it simple and ergonomic, but if you run into one of the sharp edges described in OPTIONS, here are some tips that might help: * command-specific options must go after the command (it's fine to put common options there too: 'hledger CMD OPTS ARGS') * running add-on executables directly simplifies command line parsing ('hledger-ui OPTS ARGS') * enclose "problematic" args in single quotes * if needed, also add a backslash to hide regular expression metacharacters from the shell * to see how a misbehaving command line is being parsed, add '--debug=2'.  File: hledger.info, Node: Starting a journal file, Next: Setting LEDGER_FILE, Prev: Constructing command lines, Up: PART 5 COMMON TASKS 25.3 Starting a journal file ============================ hledger looks for your accounting data in a journal file, '$HOME/.hledger.journal' by default: $ hledger stats The hledger journal file "/Users/simon/.hledger.journal" was not found. Please create it first, eg with "hledger add" or a text editor. Or, specify an existing journal file with -f or LEDGER_FILE. You can override this by setting the 'LEDGER_FILE' environment variable (see below). It's a good practice to keep this important file under version control, and to start a new file each year. So you could do something like this: $ mkdir ~/finance $ cd ~/finance $ git init Initialized empty Git repository in /Users/simon/finance/.git/ $ touch 2023.journal $ echo "export LEDGER_FILE=$HOME/finance/2023.journal" >> ~/.profile $ source ~/.profile $ hledger stats Main file : /Users/simon/finance/2023.journal Included files : Transactions span : to (0 days) Last transaction : none Transactions : 0 (0.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 0 Accounts : 0 (depth 0) Commodities : 0 () Market prices : 0 ()  File: hledger.info, Node: Setting LEDGER_FILE, Next: Setting opening balances, Prev: Starting a journal file, Up: PART 5 COMMON TASKS 25.4 Setting LEDGER_FILE ======================== How to set 'LEDGER_FILE' permanently depends on your setup: On unix and mac, running these commands in the terminal will work for many people; adapt as needed: $ echo 'export LEDGER_FILE=~/finance/2023.journal' >> ~/.profile $ source ~/.profile When correctly configured, in a new terminal window 'env | grep LEDGER_FILE' will show your file, and so will 'hledger files'. On mac, this additional step might be helpful for GUI applications (like Emacs started from the dock): add an entry to '~/.MacOSX/environment.plist' like { "LEDGER_FILE" : "~/finance/2023.journal" } and then run 'killall Dock' in a terminal window (or restart the machine). On Windows, see https://www.java.com/en/download/help/path.html, or try running these commands in a powershell window (let us know if it persists across a reboot, and if you need to be an Administrator): > CD > MKDIR finance > SETX LEDGER_FILE "C:\Users\USERNAME\finance\2023.journal"  File: hledger.info, Node: Setting opening balances, Next: Recording transactions, Prev: Setting LEDGER_FILE, Up: PART 5 COMMON TASKS 25.5 Setting opening balances ============================= Pick a starting date for which you can look up the balances of some real-world assets (bank accounts, wallet..) and liabilities (credit cards..). To avoid a lot of data entry, you may want to start with just one or two accounts, like your checking account or cash wallet; and pick a recent starting date, like today or the start of the week. You can always come back later and add more accounts and older transactions, eg going back to january 1st. Add an opening balances transaction to the journal, declaring the balances on this date. Here are two ways to do it: * The first way: open the journal in any text editor and save an entry like this: 2023-01-01 * opening balances assets:bank:checking $1000 = $1000 assets:bank:savings $2000 = $2000 assets:cash $100 = $100 liabilities:creditcard $-50 = $-50 equity:opening/closing balances These are start-of-day balances, ie whatever was in the account at the end of the previous day. The * after the date is an optional status flag. Here it means "cleared & confirmed". The currency symbols are optional, but usually a good idea as you'll be dealing with multiple currencies sooner or later. The = amounts are optional balance assertions, providing extra error checking. * The second way: run 'hledger add' and follow the prompts to record a similar transaction: $ hledger add Adding transactions to journal file /Users/simon/finance/2023.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control-d or control-c. Date [2023-02-07]: 2023-01-01 Description: * opening balances Account 1: assets:bank:checking Amount 1: $1000 Account 2: assets:bank:savings Amount 2 [$-1000]: $2000 Account 3: assets:cash Amount 3 [$-3000]: $100 Account 4: liabilities:creditcard Amount 4 [$-3100]: $-50 Account 5: equity:opening/closing balances Amount 5 [$-3050]: Account 6 (or . or enter to finish this transaction): . 2023-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl-D/ctrl-C to quit) Date [2023-01-01]: . If you're using version control, this could be a good time to commit the journal. Eg: $ git commit -m 'initial balances' 2023.journal  File: hledger.info, Node: Recording transactions, Next: Reconciling, Prev: Setting opening balances, Up: PART 5 COMMON TASKS 25.6 Recording transactions =========================== As you spend or receive money, you can record these transactions using one of the methods above (text editor, hledger add) or by using the hledger-iadd or hledger-web add-ons, or by using the import command to convert CSV data downloaded from your bank. Here are some simple transactions, see the hledger_journal(5) manual and hledger.org for more ideas: 2023/1/10 * gift received assets:cash $20 income:gifts 2023.1.12 * farmers market expenses:food $13 assets:cash 2023-01-15 paycheck income:salary assets:bank:checking $1000  File: hledger.info, Node: Reconciling, Next: Reporting, Prev: Recording transactions, Up: PART 5 COMMON TASKS 25.7 Reconciling ================ Periodically you should reconcile - compare your hledger-reported balances against external sources of truth, like bank statements or your bank's website - to be sure that your ledger accurately represents the real-world balances (and, that the real-world institutions have not made a mistake!). This gets easy and fast with (1) practice and (2) frequency. If you do it daily, it can take 2-10 minutes. If you let it pile up, expect it to take longer as you hunt down errors and discrepancies. A typical workflow: 1. Reconcile cash. Count what's in your wallet. Compare with what hledger reports ('hledger bal cash'). If they are different, try to remember the missing transaction, or look for the error in the already-recorded transactions. A register report can be helpful ('hledger reg cash'). If you can't find the error, add an adjustment transaction. Eg if you have $105 after the above, and can't explain the missing $2, it could be: 2023-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc 2. Reconcile checking. Log in to your bank's website. Compare today's (cleared) balance with hledger's cleared balance ('hledger bal checking -C'). If they are different, track down the error or record the missing transaction(s) or add an adjustment transaction, similar to the above. Unlike the cash case, you can usually compare the transaction history and running balance from your bank with the one reported by 'hledger reg checking -C'. This will be easier if you generally record transaction dates quite similar to your bank's clearing dates. 3. Repeat for other asset/liability accounts. Tip: instead of the register command, use hledger-ui to see a live-updating register while you edit the journal: 'hledger-ui --watch --register checking -C' After reconciling, it could be a good time to mark the reconciled transactions' status as "cleared and confirmed", if you want to track that, by adding the '*' marker. Eg in the paycheck transaction above, insert '*' between '2023-01-15' and 'paycheck' If you're using version control, this can be another good time to commit: $ git commit -m 'txns' 2023.journal  File: hledger.info, Node: Reporting, Next: Migrating to a new file, Prev: Reconciling, Up: PART 5 COMMON TASKS 25.8 Reporting ============== Here are some basic reports. Show all transactions: $ hledger print 2023-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 2023-01-10 * gift received assets:cash $20 income:gifts 2023-01-12 * farmers market expenses:food $13 assets:cash 2023-01-15 * paycheck income:salary assets:bank:checking $1000 2023-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc Show account names, and their hierarchy: $ hledger accounts --tree assets bank checking savings cash equity opening/closing balances expenses food misc income gifts salary liabilities creditcard Show all account totals: $ hledger balance $4105 assets $4000 bank $2000 checking $2000 savings $105 cash $-3050 equity:opening/closing balances $15 expenses $13 food $2 misc $-1020 income $-20 gifts $-1000 salary $-50 liabilities:creditcard -------------------- 0 Show only asset and liability balances, as a flat list, limited to depth 2: $ hledger bal assets liabilities -2 $4000 assets:bank $105 assets:cash $-50 liabilities:creditcard -------------------- $4055 Show the same thing without negative numbers, formatted as a simple balance sheet: $ hledger bs -2 Balance Sheet 2023-01-16 || 2023-01-16 ========================++============ Assets || ------------------------++------------ assets:bank || $4000 assets:cash || $105 ------------------------++------------ || $4105 ========================++============ Liabilities || ------------------------++------------ liabilities:creditcard || $50 ------------------------++------------ || $50 ========================++============ Net: || $4055 The final total is your "net worth" on the end date. (Or use 'bse' for a full balance sheet with equity.) Show income and expense totals, formatted as an income statement: hledger is Income Statement 2023-01-01-2023-01-16 || 2023-01-01-2023-01-16 ===============++======================= Revenues || ---------------++----------------------- income:gifts || $20 income:salary || $1000 ---------------++----------------------- || $1020 ===============++======================= Expenses || ---------------++----------------------- expenses:food || $13 expenses:misc || $2 ---------------++----------------------- || $15 ===============++======================= Net: || $1005 The final total is your net income during this period. Show transactions affecting your wallet, with running total: $ hledger register cash 2023-01-01 opening balances assets:cash $100 $100 2023-01-10 gift received assets:cash $20 $120 2023-01-12 farmers market assets:cash $-13 $107 2023-01-16 adjust cash assets:cash $-2 $105 Show weekly posting counts as a bar chart: $ hledger activity -W 2019-12-30 ***** 2023-01-06 **** 2023-01-13 ****  File: hledger.info, Node: Migrating to a new file, Prev: Reporting, Up: PART 5 COMMON TASKS 25.9 Migrating to a new file ============================ At the end of the year, you may want to continue your journal in a new file, so that old transactions don't slow down or clutter your reports, and to help ensure the integrity of your accounting history. See the close command. If using version control, don't forget to 'git add' the new file.  File: hledger.info, Node: BUGS, Prev: PART 5 COMMON TASKS, Up: Top 26 BUGS ******* We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). Some known issues and limitations: The need to precede add-on command options with '--' when invoked from hledger is awkward. (See Command options, Constructing command lines.) A UTF-8-aware system locale must be configured to work with non-ascii data. (See Unicode characters, Troubleshooting.) On Microsoft Windows, depending whether you are running in a CMD window or a Cygwin/MSYS/Mintty window and how you installed hledger, non-ascii characters and colours may not be supported, and the tab key may not be supported by 'hledger add'. (Running in a WSL window should resolve these.) When processing large data files, hledger uses more memory than Ledger. * Menu: * Troubleshooting::  File: hledger.info, Node: Troubleshooting, Up: BUGS 26.1 Troubleshooting ==================== Here are some common issues you might encounter when you run hledger, and how to resolve them (and remember also you can usually get quick Support): *PATH issues: I get an error like "No command 'hledger' found"* Depending how you installed hledger, the executables may not be in your shell's PATH. Eg on unix systems, stack installs hledger in '~/.local/bin' and cabal installs it in '~/.cabal/bin'. You may need to add one of these directories to your shell's PATH, and/or open a new terminal window. *LEDGER_FILE issues: I configured LEDGER_FILE but hledger is not using it* * 'LEDGER_FILE' should be a real environment variable, not just a shell variable. Eg on unix, the command 'env | grep LEDGER_FILE' should show it. You may need to use 'export' (see https://stackoverflow.com/a/7411509). * You may need to force your shell to see the new configuration. A simple way is to close your terminal window and open a new one. *LANG issues: I get errors like "Illegal byte sequence" or "Invalid or incomplete multibyte or wide character" or "commitAndReleaseBuffer: invalid argument (invalid character)"* Programs compiled with GHC (hledger, haskell build tools, etc.) need the system locale to be UTF-8-aware, or they will fail when they encounter non-ascii characters. To fix it, set the LANG environment variable to a locale which supports UTF-8 and which is installed on your system. On unix, 'locale -a' lists the installed locales. Look for one which mentions 'utf8', 'UTF-8' or similar. Some examples: 'C.UTF-8', 'en_US.utf-8', 'fr_FR.utf8'. If necessary, use your system package manager to install one. Then select it by setting the 'LANG' environment variable. Note, exact spelling and capitalisation of the locale name may be important: Here's one common way to configure this permanently for your shell: $ echo "export LANG=en_US.utf8" >>~/.profile # close and re-open terminal window If you are using Nix (not NixOS) for GHC and Hledger, you might need to set the 'LOCALE_ARCHIVE' variable: $ echo "export LOCALE_ARCHIVE=${glibcLocales}/lib/locale/locale-archive" >>~/.profile # close and re-open terminal window *COMPATIBILITY ISSUES: hledger gives an error with my Ledger file* Not all of Ledger's journal file syntax or feature set is supported. See hledger and Ledger for full details.  Tag Table: Node: Top208 Node: PART 1 USER INTERFACE3820 Ref: #part-1-user-interface3959 Node: Input3959 Ref: #input4069 Node: Data formats5018 Ref: #data-formats5131 Node: Standard input6493 Ref: #standard-input6633 Node: Multiple files6860 Ref: #multiple-files6999 Node: Strict mode7597 Ref: #strict-mode7707 Node: Commands8431 Ref: #commands8533 Node: Add-on commands9600 Ref: #add-on-commands9702 Node: Options10818 Ref: #options10930 Node: General help options11258 Ref: #general-help-options11404 Node: General input options11686 Ref: #general-input-options11868 Node: General reporting options12525 Ref: #general-reporting-options12686 Node: Command line tips16076 Ref: #command-line-tips16206 Node: Option repetition16465 Ref: #option-repetition16609 Node: Special characters16713 Ref: #special-characters16886 Node: Single escaping shell metacharacters17049 Ref: #single-escaping-shell-metacharacters17290 Node: Double escaping regular expression metacharacters17893 Ref: #double-escaping-regular-expression-metacharacters18204 Node: Triple escaping for add-on commands18730 Ref: #triple-escaping-for-add-on-commands18990 Node: Less escaping19634 Ref: #less-escaping19788 Node: Unicode characters20112 Ref: #unicode-characters20287 Node: Regular expressions21699 Ref: #regular-expressions21872 Node: hledger's regular expressions24968 Ref: #hledgers-regular-expressions25127 Node: Argument files26513 Ref: #argument-files26649 Node: Output27146 Ref: #output27258 Node: Output destination27385 Ref: #output-destination27516 Node: Output format27941 Ref: #output-format28087 Node: CSV output29684 Ref: #csv-output29800 Node: HTML output29903 Ref: #html-output30041 Node: JSON output30135 Ref: #json-output30273 Node: SQL output31195 Ref: #sql-output31311 Node: Commodity styles32046 Ref: #commodity-styles32186 Node: Colour32785 Ref: #colour32903 Node: Box-drawing33307 Ref: #box-drawing33425 Node: Paging33715 Ref: #paging33829 Node: Debug output34782 Ref: #debug-output34888 Node: Environment35551 Ref: #environment35675 Node: PART 2 DATA FORMATS36219 Ref: #part-2-data-formats36362 Node: Journal36362 Ref: #journal36471 Node: Journal cheatsheet37128 Ref: #journal-cheatsheet37267 Node: About journal format41252 Ref: #about-journal-format41412 Node: Comments43028 Ref: #comments43158 Node: Transactions43974 Ref: #transactions44097 Node: Dates45111 Ref: #dates45218 Node: Simple dates45263 Ref: #simple-dates45379 Node: Posting dates45879 Ref: #posting-dates45997 Node: Status46966 Ref: #status47067 Node: Code48775 Ref: #code48878 Node: Description49110 Ref: #description49241 Node: Payee and note49561 Ref: #payee-and-note49667 Node: Transaction comments50002 Ref: #transaction-comments50155 Node: Postings50518 Ref: #postings50651 Node: Account names51646 Ref: #account-names51776 Node: Amounts53450 Ref: #amounts53565 Node: Decimal marks digit group marks54550 Ref: #decimal-marks-digit-group-marks54725 Node: Commodity55584 Ref: #commodity55771 Node: Directives influencing number parsing and display56723 Ref: #directives-influencing-number-parsing-and-display56982 Node: Commodity display style57434 Ref: #commodity-display-style57640 Node: Rounding59050 Ref: #rounding59168 Node: Costs59618 Ref: #costs59734 Node: Other cost/lot notations61930 Ref: #other-costlot-notations62062 Node: Balance assertions64651 Ref: #balance-assertions64802 Node: Assertions and ordering65884 Ref: #assertions-and-ordering66073 Node: Assertions and multiple included files66773 Ref: #assertions-and-multiple-included-files67033 Node: Assertions and multiple -f files67533 Ref: #assertions-and-multiple--f-files67784 Node: Assertions and commodities68181 Ref: #assertions-and-commodities68402 Node: Assertions and costs69582 Ref: #assertions-and-costs69785 Node: Assertions and subaccounts70226 Ref: #assertions-and-subaccounts70446 Node: Assertions and virtual postings70770 Ref: #assertions-and-virtual-postings71008 Node: Assertions and auto postings71140 Ref: #assertions-and-auto-postings71370 Node: Assertions and precision72015 Ref: #assertions-and-precision72197 Node: Posting comments72464 Ref: #posting-comments72610 Node: Tags72987 Ref: #tags73101 Node: Tag values74294 Ref: #tag-values74383 Node: Directives75142 Ref: #directives75269 Node: Directives and multiple files76599 Ref: #directives-and-multiple-files76777 Node: Directive effects77544 Ref: #directive-effects77698 Node: account directive80711 Ref: #account-directive80867 Node: Account comments82265 Ref: #account-comments82415 Node: Account subdirectives82923 Ref: #account-subdirectives83114 Node: Account error checking83256 Ref: #account-error-checking83454 Node: Account display order84643 Ref: #account-display-order84831 Node: Account types85932 Ref: #account-types86073 Node: alias directive89700 Ref: #alias-directive89861 Node: Basic aliases90911 Ref: #basic-aliases91042 Node: Regex aliases91786 Ref: #regex-aliases91943 Node: Combining aliases92833 Ref: #combining-aliases93011 Node: Aliases and multiple files94287 Ref: #aliases-and-multiple-files94491 Node: end aliases directive95070 Ref: #end-aliases-directive95289 Node: Aliases can generate bad account names95438 Ref: #aliases-can-generate-bad-account-names95686 Node: Aliases and account types96271 Ref: #aliases-and-account-types96463 Node: commodity directive97159 Ref: #commodity-directive97333 Node: Commodity directive syntax98518 Ref: #commodity-directive-syntax98703 Node: Commodity error checking100154 Ref: #commodity-error-checking100335 Node: decimal-mark directive100629 Ref: #decimal-mark-directive100811 Node: include directive101208 Ref: #include-directive101372 Node: P directive102284 Ref: #p-directive102429 Node: payee directive103318 Ref: #payee-directive103467 Node: tag directive103940 Ref: #tag-directive104095 Node: Periodic transactions104563 Ref: #periodic-transactions104728 Node: Periodic rule syntax106717 Ref: #periodic-rule-syntax106895 Node: Periodic rules and relative dates107540 Ref: #periodic-rules-and-relative-dates107806 Node: Two spaces between period expression and description!108317 Ref: #two-spaces-between-period-expression-and-description108594 Node: Auto postings109278 Ref: #auto-postings109426 Node: Auto postings and multiple files112471 Ref: #auto-postings-and-multiple-files112635 Node: Auto postings and dates113036 Ref: #auto-postings-and-dates113284 Node: Auto postings and transaction balancing / inferred amounts / balance assertions113459 Ref: #auto-postings-and-transaction-balancing-inferred-amounts-balance-assertions113815 Node: Auto posting tags114318 Ref: #auto-posting-tags114600 Node: Auto postings on forecast transactions only115236 Ref: #auto-postings-on-forecast-transactions-only115482 Node: Other syntax115729 Ref: #other-syntax115845 Node: Balance assignments116472 Ref: #balance-assignments116628 Node: Balance assignments and prices118001 Ref: #balance-assignments-and-prices118216 Node: Balance assignments and multiple files118427 Ref: #balance-assignments-and-multiple-files118658 Node: Bracketed posting dates118851 Ref: #bracketed-posting-dates119035 Node: D directive119549 Ref: #d-directive119717 Node: apply account directive121317 Ref: #apply-account-directive121497 Node: Y directive122184 Ref: #y-directive122344 Node: Secondary dates123172 Ref: #secondary-dates123326 Node: Star comments124140 Ref: #star-comments124300 Node: Valuation expressions124832 Ref: #valuation-expressions125009 Node: Virtual postings125131 Ref: #virtual-postings125308 Node: Other Ledger directives126745 Ref: #other-ledger-directives126908 Node: CSV127474 Ref: #csv127567 Node: CSV rules cheatsheet129647 Ref: #csv-rules-cheatsheet129776 Node: source131574 Ref: #source131697 Node: separator132577 Ref: #separator132690 Node: skip133230 Ref: #skip133338 Node: date-format133882 Ref: #date-format134003 Node: timezone134727 Ref: #timezone134850 Node: newest-first135855 Ref: #newest-first135993 Node: intra-day-reversed136570 Ref: #intra-day-reversed136724 Node: decimal-mark137172 Ref: #decimal-mark137313 Node: fields list137652 Ref: #fields-list137791 Node: Field assignment139462 Ref: #field-assignment139606 Node: Field names140683 Ref: #field-names140814 Node: date field142017 Ref: #date-field142135 Node: date2 field142183 Ref: #date2-field142324 Node: status field142380 Ref: #status-field142523 Node: code field142572 Ref: #code-field142717 Node: description field142762 Ref: #description-field142922 Node: comment field142981 Ref: #comment-field143136 Node: account field143429 Ref: #account-field143579 Node: amount field144149 Ref: #amount-field144298 Node: currency field146990 Ref: #currency-field147143 Node: balance field147400 Ref: #balance-field147532 Node: if block147904 Ref: #if-block148025 Node: Matchers149433 Ref: #matchers149547 Node: What matchers match150344 Ref: #what-matchers-match150493 Node: Combining matchers150933 Ref: #combining-matchers151101 Node: Match groups151587 Ref: #match-groups151715 Node: if table152462 Ref: #if-table152584 Node: balance-type154146 Ref: #balance-type154275 Node: include154975 Ref: #include155102 Node: Working with CSV155546 Ref: #working-with-csv155693 Node: Rapid feedback156100 Ref: #rapid-feedback156233 Node: Valid CSV156685 Ref: #valid-csv156831 Node: File Extension157563 Ref: #file-extension157736 Node: Reading CSV from standard input158300 Ref: #reading-csv-from-standard-input158524 Node: Reading multiple CSV files158688 Ref: #reading-multiple-csv-files158919 Node: Reading files specified by rule159160 Ref: #reading-files-specified-by-rule159388 Node: Valid transactions160559 Ref: #valid-transactions160758 Node: Deduplicating importing161386 Ref: #deduplicating-importing161581 Node: Setting amounts162617 Ref: #setting-amounts162788 Node: Amount signs165146 Ref: #amount-signs165316 Node: Setting currency/commodity166213 Ref: #setting-currencycommodity166417 Node: Amount decimal places167591 Ref: #amount-decimal-places167797 Node: Referencing other fields168109 Ref: #referencing-other-fields168322 Node: How CSV rules are evaluated169219 Ref: #how-csv-rules-are-evaluated169436 Node: Well factored rules170889 Ref: #well-factored-rules171057 Node: CSV rules examples171381 Ref: #csv-rules-examples171516 Node: Bank of Ireland171581 Ref: #bank-of-ireland171718 Node: Coinbase173180 Ref: #coinbase173318 Node: Amazon174365 Ref: #amazon174490 Node: Paypal176209 Ref: #paypal176317 Node: Timeclock183961 Ref: #timeclock184066 Node: Timedot186244 Ref: #timedot186367 Node: Timedot examples189472 Ref: #timedot-examples189578 Node: PART 3 REPORTING CONCEPTS191749 Ref: #part-3-reporting-concepts191931 Node: Amount formatting parseability191931 Ref: #amount-formatting-parseability192128 Node: Time periods194333 Ref: #time-periods194472 Node: Report start & end date194590 Ref: #report-start-end-date194742 Node: Smart dates196401 Ref: #smart-dates196554 Node: Report intervals198422 Ref: #report-intervals198577 Node: Date adjustment198995 Ref: #date-adjustment199155 Node: Period expressions200006 Ref: #period-expressions200147 Node: Period expressions with a report interval201911 Ref: #period-expressions-with-a-report-interval202145 Node: More complex report intervals202359 Ref: #more-complex-report-intervals202604 Node: Multiple weekday intervals204405 Ref: #multiple-weekday-intervals204594 Node: Depth205416 Ref: #depth205518 Node: Queries205814 Ref: #queries205916 Node: Query types207546 Ref: #query-types207667 Node: Combining query terms210901 Ref: #combining-query-terms211078 Node: Queries and command options212346 Ref: #queries-and-command-options212545 Node: Queries and valuation212794 Ref: #queries-and-valuation212989 Node: Querying with account aliases213218 Ref: #querying-with-account-aliases213429 Node: Querying with cost or value213559 Ref: #querying-with-cost-or-value213736 Node: Pivoting214037 Ref: #pivoting214151 Node: Generating data215928 Ref: #generating-data216060 Node: Forecasting217643 Ref: #forecasting217768 Node: --forecast218299 Ref: #forecast218430 Node: Inspecting forecast transactions219400 Ref: #inspecting-forecast-transactions219602 Node: Forecast reports220732 Ref: #forecast-reports220905 Node: Forecast tags221841 Ref: #forecast-tags222001 Node: Forecast period in detail222461 Ref: #forecast-period-in-detail222655 Node: Forecast troubleshooting223549 Ref: #forecast-troubleshooting223717 Node: Budgeting224620 Ref: #budgeting224740 Node: Cost reporting225177 Ref: #cost-reporting225311 Node: Recording costs225972 Ref: #recording-costs226108 Node: Reporting at cost227699 Ref: #reporting-at-cost227874 Node: Equity conversion postings228464 Ref: #equity-conversion-postings228678 Node: Inferring equity conversion postings231109 Ref: #inferring-equity-conversion-postings231372 Node: Combining costs and equity conversion postings232124 Ref: #combining-costs-and-equity-conversion-postings232434 Node: Requirements for detecting equity conversion postings233422 Ref: #requirements-for-detecting-equity-conversion-postings233744 Node: Infer cost and equity by default ?234944 Ref: #infer-cost-and-equity-by-default235173 Node: Value reporting235381 Ref: #value-reporting235523 Node: -V Value236297 Ref: #v-value236429 Node: -X Value in specified commodity236624 Ref: #x-value-in-specified-commodity236825 Node: Valuation date236974 Ref: #valuation-date237151 Node: Finding market price237934 Ref: #finding-market-price238145 Node: --infer-market-prices market prices from transactions239314 Ref: #infer-market-prices-market-prices-from-transactions239596 Node: Valuation commodity242358 Ref: #valuation-commodity242577 Node: Simple valuation examples243790 Ref: #simple-valuation-examples243994 Node: --value Flexible valuation244653 Ref: #value-flexible-valuation244863 Node: More valuation examples246507 Ref: #more-valuation-examples246722 Node: Interaction of valuation and queries247992 Ref: #interaction-of-valuation-and-queries248239 Node: Effect of valuation on reports248711 Ref: #effect-of-valuation-on-reports248914 Node: PART 4 COMMANDS256611 Ref: #part-4-commands256760 Node: Commands overview257139 Ref: #commands-overview257273 Node: DATA ENTRY257452 Ref: #data-entry257576 Node: DATA CREATION257775 Ref: #data-creation257929 Node: DATA MANAGEMENT258047 Ref: #data-management258212 Node: REPORTS FINANCIAL258333 Ref: #reports-financial258508 Node: REPORTS VERSATILE258813 Ref: #reports-versatile258986 Node: REPORTS BASIC259239 Ref: #reports-basic259391 Node: HELP259900 Ref: #help260022 Node: ADD-ONS260132 Ref: #add-ons260238 Node: accounts260817 Ref: #accounts260950 Node: activity262837 Ref: #activity262956 Node: add263330 Ref: #add263440 Node: aregister266251 Ref: #aregister266372 Node: aregister and posting dates269260 Ref: #aregister-and-posting-dates269405 Node: balance270161 Ref: #balance270287 Node: balance features271272 Ref: #balance-features271412 Node: Simple balance report273378 Ref: #simple-balance-report273563 Node: Balance report line format275188 Ref: #balance-report-line-format275390 Node: Filtered balance report277548 Ref: #filtered-balance-report277740 Node: List or tree mode278067 Ref: #list-or-tree-mode278235 Node: Depth limiting279580 Ref: #depth-limiting279746 Node: Dropping top-level accounts280347 Ref: #dropping-top-level-accounts280547 Node: Showing declared accounts280857 Ref: #showing-declared-accounts281056 Node: Sorting by amount281587 Ref: #sorting-by-amount281754 Node: Percentages282424 Ref: #percentages282583 Node: Multi-period balance report283131 Ref: #multi-period-balance-report283331 Node: Balance change end balance285606 Ref: #balance-change-end-balance285815 Node: Balance report types287243 Ref: #balance-report-types287424 Node: Calculation type287922 Ref: #calculation-type288077 Node: Accumulation type288626 Ref: #accumulation-type288806 Node: Valuation type289708 Ref: #valuation-type289896 Node: Combining balance report types290897 Ref: #combining-balance-report-types291091 Node: Budget report292929 Ref: #budget-report293091 Node: Using the budget report295234 Ref: #using-the-budget-report295407 Node: Budget date surprises297510 Ref: #budget-date-surprises297710 Node: Selecting budget goals298874 Ref: #selecting-budget-goals299077 Node: Budgeting vs forecasting299822 Ref: #budgeting-vs-forecasting299999 Node: Balance report layout301270 Ref: #balance-report-layout301450 Node: Useful balance reports309635 Ref: #useful-balance-reports309795 Node: balancesheet310880 Ref: #balancesheet311025 Node: balancesheetequity312352 Ref: #balancesheetequity312510 Node: cashflow313906 Ref: #cashflow314037 Node: check315472 Ref: #check315586 Node: Default checks316390 Ref: #default-checks316516 Node: Strict checks317013 Ref: #strict-checks317158 Node: Other checks317638 Ref: #other-checks317780 Node: Custom checks318313 Ref: #custom-checks318470 Node: More about specific checks318887 Ref: #more-about-specific-checks319049 Node: close319755 Ref: #close319866 Node: close and balance assertions323331 Ref: #close-and-balance-assertions323509 Node: Example retain earnings324660 Ref: #example-retain-earnings324877 Node: Example migrate balances to a new file325309 Ref: #example-migrate-balances-to-a-new-file325574 Node: Example excluding closing/opening transactions326150 Ref: #example-excluding-closingopening-transactions326399 Node: codes327617 Ref: #codes327734 Node: commodities328598 Ref: #commodities328726 Node: demo328796 Ref: #demo328917 Node: descriptions329833 Ref: #descriptions329963 Node: diff330254 Ref: #diff330369 Node: files331411 Ref: #files331520 Node: help331661 Ref: #help-1331770 Node: import333143 Ref: #import333266 Node: Deduplication334374 Ref: #deduplication334499 Node: Import testing336518 Ref: #import-testing336683 Node: Importing balance assignments337526 Ref: #importing-balance-assignments337732 Node: Commodity display styles338381 Ref: #commodity-display-styles338554 Node: incomestatement338683 Ref: #incomestatement338825 Node: notes340153 Ref: #notes340275 Node: payees340637 Ref: #payees340752 Node: prices341271 Ref: #prices341386 Node: print342039 Ref: #print342154 Node: print explicitness343130 Ref: #print-explicitness343273 Node: print amount style344052 Ref: #print-amount-style344222 Node: print parseability345274 Ref: #print-parseability345446 Node: print other features346195 Ref: #print-other-features346374 Node: print output format346895 Ref: #print-output-format347043 Node: register350162 Ref: #register350284 Node: Custom register output355315 Ref: #custom-register-output355446 Node: rewrite356790 Ref: #rewrite356908 Node: Re-write rules in a file358806 Ref: #re-write-rules-in-a-file358969 Node: Diff output format360118 Ref: #diff-output-format360301 Node: rewrite vs print --auto361393 Ref: #rewrite-vs.-print---auto361553 Node: roi362109 Ref: #roi362216 Node: Spaces and special characters in --inv and --pnl364028 Ref: #spaces-and-special-characters-in---inv-and---pnl364268 Node: Semantics of --inv and --pnl364756 Ref: #semantics-of---inv-and---pnl364995 Node: IRR and TWR explained366845 Ref: #irr-and-twr-explained367005 Node: stats370258 Ref: #stats370366 Node: tags371753 Ref: #tags-1371860 Node: test372869 Ref: #test372962 Node: PART 5 COMMON TASKS373704 Ref: #part-5-common-tasks373850 Node: Getting help374148 Ref: #getting-help374289 Node: Constructing command lines375049 Ref: #constructing-command-lines375250 Node: Starting a journal file375907 Ref: #starting-a-journal-file376109 Node: Setting LEDGER_FILE377311 Ref: #setting-ledger_file377503 Node: Setting opening balances378460 Ref: #setting-opening-balances378661 Node: Recording transactions381802 Ref: #recording-transactions381991 Node: Reconciling382547 Ref: #reconciling382699 Node: Reporting384956 Ref: #reporting385105 Node: Migrating to a new file389090 Ref: #migrating-to-a-new-file389247 Node: BUGS389546 Ref: #bugs389636 Node: Troubleshooting390515 Ref: #troubleshooting390615  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.32.3/embeddedfiles/hledger-ui.10000644000000000000000000005220114555433336016276 0ustar0000000000000000 .TH "HLEDGER\-UI" "1" "January 2024" "hledger-ui-1.32.3 " "hledger User Manuals" .SH NAME hledger\-ui \- robust, friendly plain text accounting (TUI version) .SH SYNOPSIS \f[CR]hledger\-ui [OPTS] [QUERYARGS]\f[R] .PD 0 .P .PD \f[CR]hledger ui \-\- [OPTS] [QUERYARGS]\f[R] .SH DESCRIPTION This manual is for hledger\[aq]s terminal interface, version 1.32.3. See also the hledger manual for common concepts and file formats. .PP hledger is a robust, user\-friendly, cross\-platform set of programs for tracking money, time, or any other commodity, using double\-entry accounting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). .PP hledger\-ui is hledger\[aq]s terminal interface, providing an efficient full\-window text UI for viewing accounts and transactions, and some limited data entry capability. It is easier than hledger\[aq]s command\-line interface, and sometimes quicker and more convenient than the web interface. .PP Like hledger, it reads from (and appends to) a journal file specified by the \f[CR]LEDGER_FILE\f[R] environment variable (defaulting to \f[CR]$HOME/.hledger.journal\f[R]); or you can specify files with \f[CR]\-f\f[R] options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. (See hledger(1) \-> Input for details.) .PP Unlike hledger, hledger\-ui hides all future\-dated transactions by default. They can be revealed, along with any rule\-generated periodic transactions, by pressing the F key (or starting with \-\-forecast) to enable \[dq]forecast mode\[dq]. .SH OPTIONS Any QUERYARGS are interpreted as a hledger search query which filters the data. .PP hledger\-ui provides the following options: .TP \f[CR]\-w \-\-watch\f[R] watch for data and date changes and reload automatically .TP \f[CR]\-\-theme=default|terminal|greenterm\f[R] use this custom display theme .TP \f[CR]\-\-menu\f[R] start in the menu screen .TP \f[CR]\-\-cash\f[R] start in the cash accounts screen .TP \f[CR]\-\-bs\f[R] start in the balance sheet accounts screen .TP \f[CR]\-\-is\f[R] start in the income statement accounts screen .TP \f[CR]\-\-all\f[R] start in the all accounts screen .TP \f[CR]\-\-register=ACCTREGEX\f[R] start in the (first) matched account\[aq]s register screen .TP \f[CR]\-\-change\f[R] show period balances (changes) at startup instead of historical balances .TP \f[CR]\-l \-\-flat\f[R] show accounts as a flat list (default) .TP \f[CR]\-t \-\-tree\f[R] show accounts as a tree .PP hledger\-ui also supports many of hledger\[aq]s general options (and the hledger manual\[aq]s command line tips also apply here): .SS General help options .TP \f[CR]\-h \-\-help\f[R] show general or COMMAND help .TP \f[CR]\-\-man\f[R] show general or COMMAND user manual with man .TP \f[CR]\-\-info\f[R] show general or COMMAND user manual with info .TP \f[CR]\-\-version\f[R] show general or ADDONCMD version .TP \f[CR]\-\-debug[=N]\f[R] show debug output (levels 1\-9, default: 1) .SS General input options .TP \f[CR]\-f FILE \-\-file=FILE\f[R] use a different input file. For stdin, use \- (default: \f[CR]$LEDGER_FILE\f[R] or \f[CR]$HOME/.hledger.journal\f[R]) .TP \f[CR]\-\-rules\-file=RULESFILE\f[R] Conversion rules file to use when reading CSV (default: FILE.rules) .TP \f[CR]\-\-separator=CHAR\f[R] Field separator to expect when reading CSV (default: \[aq],\[aq]) .TP \f[CR]\-\-alias=OLD=NEW\f[R] rename accounts named OLD to NEW .TP \f[CR]\-\-pivot FIELDNAME\f[R] use some other field or tag for the account name .TP \f[CR]\-I \-\-ignore\-assertions\f[R] disable balance assertion checks (note: does not disable balance assignments) .TP \f[CR]\-s \-\-strict\f[R] do extra error checking (check that all posted accounts are declared) .SS General reporting options .TP \f[CR]\-b \-\-begin=DATE\f[R] include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) .TP \f[CR]\-e \-\-end=DATE\f[R] include postings/txns before this date (will be adjusted to following subperiod end when using a report interval) .TP \f[CR]\-D \-\-daily\f[R] multiperiod/multicolumn report by day .TP \f[CR]\-W \-\-weekly\f[R] multiperiod/multicolumn report by week .TP \f[CR]\-M \-\-monthly\f[R] multiperiod/multicolumn report by month .TP \f[CR]\-Q \-\-quarterly\f[R] multiperiod/multicolumn report by quarter .TP \f[CR]\-Y \-\-yearly\f[R] multiperiod/multicolumn report by year .TP \f[CR]\-p \-\-period=PERIODEXP\f[R] set start date, end date, and/or reporting interval all at once using period expressions syntax .TP \f[CR]\-\-date2\f[R] match the secondary date instead (see command help for other effects) .TP \f[CR]\-\-today=DATE\f[R] override today\[aq]s date (affects relative smart dates, for tests/examples) .TP \f[CR]\-U \-\-unmarked\f[R] include only unmarked postings/txns (can combine with \-P or \-C) .TP \f[CR]\-P \-\-pending\f[R] include only pending postings/txns .TP \f[CR]\-C \-\-cleared\f[R] include only cleared postings/txns .TP \f[CR]\-R \-\-real\f[R] include only non\-virtual postings .TP \f[CR]\-NUM \-\-depth=NUM\f[R] hide/aggregate accounts or postings more than NUM levels deep .TP \f[CR]\-E \-\-empty\f[R] show items with zero amount, normally hidden (and vice\-versa in hledger\-ui/hledger\-web) .TP \f[CR]\-B \-\-cost\f[R] convert amounts to their cost/selling amount at transaction time .TP \f[CR]\-V \-\-market\f[R] convert amounts to their market value in default valuation commodities .TP \f[CR]\-X \-\-exchange=COMM\f[R] convert amounts to their market value in commodity COMM .TP \f[CR]\-\-value\f[R] convert amounts to cost or market value, more flexibly than \-B/\-V/\-X .TP \f[CR]\-\-infer\-equity\f[R] infer conversion equity postings from costs .TP \f[CR]\-\-infer\-costs\f[R] infer costs from conversion equity postings .TP \f[CR]\-\-infer\-market\-prices\f[R] use costs as additional market prices, as if they were P directives .TP \f[CR]\-\-forecast\f[R] generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger\-ui make future\-dated transactions visible. .TP \f[CR]\-\-auto\f[R] generate extra postings by applying auto posting rules to all txns (not just forecast txns) .TP \f[CR]\-\-verbose\-tags\f[R] add visible tags indicating transactions or postings which have been generated/modified .TP \f[CR]\-\-commodity\-style\f[R] Override the commodity style in the output for the specified commodity. For example \[aq]EUR1.000,00\[aq]. .TP \f[CR]\-\-color=WHEN (or \-\-colour=WHEN)\f[R] Should color\-supporting commands use ANSI color codes in text output. \[aq]auto\[aq] (default): whenever stdout seems to be a color\-supporting terminal. \[aq]always\[aq] or \[aq]yes\[aq]: always, useful eg when piping output into \[aq]less \-R\[aq]. \[aq]never\[aq] or \[aq]no\[aq]: never. A NO_COLOR environment variable overrides this. .TP \f[CR]\-\-pretty[=WHEN]\f[R] Show prettier output, e.g. using unicode box\-drawing characters. Accepts \[aq]yes\[aq] (the default) or \[aq]no\[aq] (\[aq]y\[aq], \[aq]n\[aq], \[aq]always\[aq], \[aq]never\[aq] also work). If you provide an argument you must use \[aq]=\[aq], e.g. \[aq]\-\-pretty=yes\[aq]. .PP When a reporting option appears more than once in the command line, the last one takes precedence. .PP Some reporting options can also be written as query arguments. .SH MOUSE In most modern terminals, you can navigate through the screens with a mouse or touchpad: .IP \[bu] 2 Use mouse wheel or trackpad to scroll up and down .IP \[bu] 2 Click on list items to go deeper .IP \[bu] 2 Click on the left margin (column 0) to go back. .SH KEYS Keyboard gives more control. .PP \f[CR]?\f[R] shows a help dialog listing all keys. (Some of these also appear in the quick help at the bottom of each screen.) Press \f[CR]?\f[R] again (or \f[CR]ESCAPE\f[R], or \f[CR]LEFT\f[R], or \f[CR]q\f[R]) to close it. The following keys work on most screens: .PP The cursor keys navigate: \f[CR]RIGHT\f[R] or \f[CR]ENTER\f[R] goes deeper, \f[CR]LEFT\f[R] returns to the previous screen, \f[CR]UP\f[R]/\f[CR]DOWN\f[R]/\f[CR]PGUP\f[R]/\f[CR]PGDN\f[R]/\f[CR]HOME\f[R]/\f[CR]END\f[R] move up and down through lists. Emacs\-style (\f[CR]CTRL\-p\f[R]/\f[CR]CTRL\-n\f[R]/\f[CR]CTRL\-f\f[R]/\f[CR]CTRL\-b\f[R]) and VI\-style (\f[CR]k\f[R],\f[CR]j\f[R],\f[CR]l\f[R],\f[CR]h\f[R]) movement keys are also supported. A tip: movement speed is limited by your keyboard repeat rate, to move faster you may want to adjust it. (If you\[aq]re on a mac, the karabiner app is one way to do that.) .PP With shift pressed, the cursor keys adjust the report period, limiting the transactions to be shown (by default, all are shown). \f[CR]SHIFT\-DOWN/UP\f[R] steps downward and upward through these standard report period durations: year, quarter, month, week, day. Then, \f[CR]SHIFT\-LEFT/RIGHT\f[R] moves to the previous/next period. \f[CR]T\f[R] sets the report period to today. With the \f[CR]\-w/\-\-watch\f[R] option, when viewing a \[dq]current\[dq] period (the current day, week, month, quarter, or year), the period will move automatically to track the current date. To set a non\-standard period, you can use \f[CR]/\f[R] and a \f[CR]date:\f[R] query. .PP (Mac users: SHIFT\-DOWN/UP keys do not work by default in Terminal, as of MacOS Monterey. You can configure them as follows: open Terminal, press CMD\-comma to open preferences, click Profiles, select your current terminal profile on the left, click Keyboard on the right, click + and add this for Shift\-Down: \f[CR]\[rs]033[1;2B\f[R], click + and add this for Shift\-Up: \f[CR]\[rs]033[1;2A\f[R]. Press the Escape key to enter the \f[CR]\[rs]033\f[R] part, you can\[aq]t type it directly.) .PP \f[CR]/\f[R] lets you set a general filter query limiting the data shown, using the same query terms as in hledger and hledger\-web. While editing the query, you can use CTRL\-a/e/d/k, BS, cursor keys; press \f[CR]ENTER\f[R] to set it, or \f[CR]ESCAPE\f[R]to cancel. There are also keys for quickly adjusting some common filters like account depth and transaction status (see below). \f[CR]BACKSPACE\f[R] or \f[CR]DELETE\f[R] removes all filters, showing all transactions. .PP As mentioned above, by default hledger\-ui hides future transactions \- both ordinary transactions recorded in the journal, and periodic transactions generated by rule. \f[CR]F\f[R] toggles forecast mode, in which future/forecasted transactions are shown. .PP \f[CR]ESCAPE\f[R] resets the UI state and jumps back to the top screen, restoring the app\[aq]s initial state at startup. Or, it cancels minibuffer data entry or the help dialog. .PP \f[CR]CTRL\-l\f[R] redraws the screen and centers the selection if possible (selections near the top won\[aq]t be centered, since we don\[aq]t scroll above the top). .PP \f[CR]g\f[R] reloads from the data file(s) and updates the current screen and any previous screens. (With large files, this could cause a noticeable pause.) .PP \f[CR]I\f[R] toggles balance assertion checking. Disabling balance assertions temporarily can be useful for troubleshooting. .PP \f[CR]a\f[R] runs command\-line hledger\[aq]s add command, and reloads the updated file. This allows some basic data entry. .PP \f[CR]A\f[R] is like \f[CR]a\f[R], but runs the hledger\-iadd tool, which provides a terminal interface. This key will be available if \f[CR]hledger\-iadd\f[R] is installed in $path. .PP \f[CR]E\f[R] runs $HLEDGER_UI_EDITOR, or $EDITOR, or a default (\f[CR]emacsclient \-a \[dq]\[dq] \-nw\f[R]) on the journal file. With some editors (emacs, vi), the cursor will be positioned at the current transaction when invoked from the register and transaction screens, and at the error location (if possible) when invoked from the error screen. .PP \f[CR]B\f[R] toggles cost mode, showing amounts converted to their cost\[aq]s commodity (see hledger manual > Cost reporting. .PP \f[CR]V\f[R] toggles value mode, showing amounts converted to their market value (see hledger manual > Valuation flag). More specifically, .IP "1." 3 By default, the \f[CR]V\f[R] key toggles showing end value (\f[CR]\-\-value=end\f[R]) on or off. The valuation date will be the report end date if specified, otherwise today. .IP "2." 3 If you started hledger\-ui with some other valuation (such as \f[CR]\-\-value=then,EUR\f[R]), the \f[CR]V\f[R] key toggles that off or on. .PP Cost/value tips: \- When showing end value, you can change the report end date without restarting, by pressing \f[CR]/\f[R] and adding a query like \f[CR]date:..YYYY\-MM\-DD\f[R]. \- Either cost mode, or value mode, can be active, but not both at once. Cost mode takes precedence. \- There\[aq]s not yet any visual indicator that cost or value mode is active, other than the amount values. .PP \f[CR]q\f[R] quits the application. .PP Additional screen\-specific keys are described below. .SH SCREENS At startup, hledger\-ui shows a menu screen by default. From here you can navigate to other screens using the cursor keys: \f[CR]UP\f[R]/\f[CR]DOWN\f[R] to select, \f[CR]RIGHT\f[R] to move to the selected screen, \f[CR]LEFT\f[R] to return to the previous screen. Or you can use \f[CR]ESC\f[R] to return directly to the top menu screen. .PP You can also use a command line flag to specific a different startup screen (\f[CR]\-\-cs\f[R], \f[CR]\-\-bs\f[R], \f[CR]\-\-is\f[R], \f[CR]\-\-all\f[R], or \f[CR]\-\-register=ACCT\f[R]). .SS Menu This is the top\-most screen. From here you can navigate to several screens listing accounts of various types. Note some of these may not show anything until you have configured account types. .SS Cash accounts This screen shows \[dq]cash\[dq] (ie, liquid asset) accounts (like \f[CR]hledger balancesheet type:c\f[R]). It always shows balances (historical ending balances on the date shown in the title line). .SS Balance sheet accounts This screen shows asset, liability and equity accounts (like \f[CR]hledger balancesheetequity\f[R]). It always shows balances. .SS Income statement accounts This screen shows revenue and expense accounts (like \f[CR]hledger incomestatement\f[R]). It always shows changes (balance changes in the period shown in the title line). .SS All accounts This screen shows all accounts in your journal (unless filtered by a query; like \f[CR]hledger balance\f[R]). It shows balances by default; you can toggle showing changes with the \f[CR]H\f[R] key. .SS Register This screen shows the transactions affecting a particular account. Each line represents one transaction, and shows: .IP \[bu] 2 the other account(s) involved, in abbreviated form. (If there are both real and virtual postings, it shows only the accounts affected by real postings.) .IP \[bu] 2 the overall change to the current account\[aq]s balance; positive for an inflow to this account, negative for an outflow. .IP \[bu] 2 the running total after the transaction. With the \f[CR]H\f[R] key you can toggle between .RS 2 .IP \[bu] 2 the period total, which is from just the transactions displayed .IP \[bu] 2 or the historical total, which includes any undisplayed transactions before the start of the report period (and matching the filter query if any). This will be the running historical balance (what you would see on a bank\[aq]s website, eg) if not disturbed by a query. .RE .PP Note, this screen combines each transaction\[aq]s in\-period postings to a single line item, dated with the earliest in\-period transaction or posting date (like hledger\[aq]s \f[CR]aregister\f[R]). So custom posting dates can cause the running balance to be temporarily inaccurate. (See hledger manual > aregister and posting dates.) .PP Transactions affecting this account\[aq]s subaccounts will be included in the register if the accounts screen is in tree mode, or if it\[aq]s in list mode but this account has subaccounts which are not shown due to a depth limit. In other words, the register always shows the transactions contributing to the balance shown on the accounts screen. Tree mode/list mode can be toggled with \f[CR]t\f[R] here also. .PP \f[CR]U\f[R] toggles filtering by unmarked status, showing or hiding unmarked transactions. Similarly, \f[CR]P\f[R] toggles pending transactions, and \f[CR]C\f[R] toggles cleared transactions. (By default, transactions with all statuses are shown; if you activate one or two status filters, only those transactions are shown; and if you activate all three, the filter is removed.) .PP \f[CR]R\f[R] toggles real mode, in which virtual postings are ignored. .PP \f[CR]z\f[R] toggles nonzero mode, in which only transactions posting a nonzero change are shown (hledger\-ui shows zero items by default, unlike command\-line hledger). .PP Press \f[CR]RIGHT\f[R] to view the selected transaction in detail. .SS Transaction This screen shows a single transaction, as a general journal entry, similar to hledger\[aq]s print command and journal format (hledger_journal(5)). .PP The transaction\[aq]s date(s) and any cleared flag, transaction code, description, comments, along with all of its account postings are shown. Simple transactions have two postings, but there can be more (or in certain cases, fewer). .PP \f[CR]UP\f[R] and \f[CR]DOWN\f[R] will step through all transactions listed in the previous account register screen. In the title bar, the numbers in parentheses show your position within that account register. They will vary depending on which account register you came from (remember most transactions appear in multiple account registers). The #N number preceding them is the transaction\[aq]s position within the complete unfiltered journal, which is a more stable id (at least until the next reload). .PP On this screen (and the register screen), the \f[CR]E\f[R] key will open your text editor with the cursor positioned at the current transaction if possible. .PP This screen has a limitation with showing file updates: it will not show them until you exit and re\-enter it. So eg to see the effect of using the \f[CR]E\f[R] key, currently you must: \- press \f[CR]E\f[R], edit and save the file, then exit the editor, returning to hledger\-ui \- press \f[CR]g\f[R] to reload the file (or use \f[CR]\-w/\-\-watch\f[R] mode) \- press \f[CR]LEFT\f[R] then \f[CR]RIGHT\f[R] to exit and re\-enter the transaction screen. .SS Error This screen will appear if there is a problem, such as a parse error, when you press g to reload. Once you have fixed the problem, press g again to reload and resume normal operation. (Or, you can press escape to cancel the reload attempt.) .SH TIPS .SS Watch mode One of hledger\-ui\[aq]s best features is the auto\-reloading \f[CR]\-w/\-\-watch\f[R] mode. With this flag, it will update the display automatically whenever changes are saved to the data files. .PP This is very useful when reconciling. A good workflow is to have your bank\[aq]s online register open in a browser window, for reference; the journal file open in an editor window; and hledger\-ui in watch mode in a terminal window, eg: .IP .EX $ hledger\-ui \-\-watch \-\-register checking \-C .EE .PP As you mark things cleared in the editor, you can see the effect immediately without having to context switch. This leaves more mental bandwidth for your accounting. Of course you can still interact with hledger\-ui when needed, eg to toggle cleared mode, or to explore the history. .PP There are currently some limitations with \f[CR]\-\-watch\f[R]: .PP It may not work correctly for you, depending on platform or system configuration. (Eg #836.) .PP At least on mac, there can be a slow build\-up of CPU usage over time, until the program is restarted (or, suspending and restarting with \f[CR]CTRL\-z\f[R] \f[CR]fg\f[R] may be enough). .PP It will not detect file changes made by certain editors, such as Jetbrains IDEs or \f[CR]gedit\f[R], or on certain less common filesystems. (To work around, press \f[CR]g\f[R] to reload manually, or try #1617\[aq]s \f[CR]fs.inotify.max_user_watches\f[R] workaround and let us know.) .PP If you are viewing files mounted from another machine, the system clocks on both machines should be roughly in agreement. .SS Debug output You can add \f[CR]\-\-debug[=N]\f[R] to the command line to log debug output. This will be logged to the file \f[CR]hledger\-ui.log\f[R] in the current directory. N ranges from 1 (least output, the default) to 9 (maximum output). .SH ENVIRONMENT \f[B]COLUMNS\f[R] The screen width to use. Default: the full terminal width. .PP \f[B]LEDGER_FILE\f[R] The main journal file to use when not specified with \f[CR]\-f/\-\-file\f[R]. Default: \f[CR]$HOME/.hledger.journal\f[R]. .SH BUGS We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). .PP Some known issues: .PP \f[CR]\-f\-\f[R] doesn\[aq]t work (hledger\-ui can\[aq]t read from stdin). .PP If you press \f[CR]g\f[R] with large files, there could be a noticeable pause. .PP The Transaction screen does not update from file changes until you exit and re\-endter it (see SCREENS > Transaction above). .PP \f[CR]\-\-watch\f[R] is not yet fully robust on all platforms (see Watch mode above). .SH AUTHORS Simon Michael and contributors. .br See http://hledger.org/CREDITS.html .SH COPYRIGHT Copyright 2007-2023 Simon Michael and contributors. .SH LICENSE Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), ledger(1) hledger-1.32.3/embeddedfiles/hledger-ui.txt0000644000000000000000000005417314555433336016767 0ustar0000000000000000 HLEDGER-UI(1) hledger User Manuals HLEDGER-UI(1) NAME hledger-ui - robust, friendly plain text accounting (TUI version) SYNOPSIS hledger-ui [OPTS] [QUERYARGS] hledger ui -- [OPTS] [QUERYARGS] DESCRIPTION This manual is for hledger's terminal interface, version 1.32.3. See also the hledger manual for common concepts and file formats. hledger is a robust, user-friendly, cross-platform set of programs for tracking money, time, or any other commodity, using double-entry ac- counting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). hledger-ui is hledger's terminal interface, providing an efficient full-window text UI for viewing accounts and transactions, and some limited data entry capability. It is easier than hledger's com- mand-line interface, and sometimes quicker and more convenient than the web interface. Like hledger, it reads from (and appends to) a journal file specified by the LEDGER_FILE environment variable (defaulting to $HOME/.hledger.journal); or you can specify files with -f options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. (See hledger(1) -> Input for details.) Unlike hledger, hledger-ui hides all future-dated transactions by de- fault. They can be revealed, along with any rule-generated periodic transactions, by pressing the F key (or starting with --forecast) to enable "forecast mode". OPTIONS Any QUERYARGS are interpreted as a hledger search query which filters the data. hledger-ui provides the following options: -w --watch watch for data and date changes and reload automatically --theme=default|terminal|greenterm use this custom display theme --menu start in the menu screen --cash start in the cash accounts screen --bs start in the balance sheet accounts screen --is start in the income statement accounts screen --all start in the all accounts screen --register=ACCTREGEX start in the (first) matched account's register screen --change show period balances (changes) at startup instead of historical balances -l --flat show accounts as a flat list (default) -t --tree show accounts as a tree hledger-ui also supports many of hledger's general options (and the hledger manual's command line tips also apply here): General help options -h --help show general or COMMAND help --man show general or COMMAND user manual with man --info show general or COMMAND user manual with info --version show general or ADDONCMD version --debug[=N] show debug output (levels 1-9, default: 1) General input options -f FILE --file=FILE use a different input file. For stdin, use - (default: $LEDGER_FILE or $HOME/.hledger.journal) --rules-file=RULESFILE Conversion rules file to use when reading CSV (default: FILE.rules) --separator=CHAR Field separator to expect when reading CSV (default: ',') --alias=OLD=NEW rename accounts named OLD to NEW --pivot FIELDNAME use some other field or tag for the account name -I --ignore-assertions disable balance assertion checks (note: does not disable balance assignments) -s --strict do extra error checking (check that all posted accounts are de- clared) General reporting options -b --begin=DATE include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) -e --end=DATE include postings/txns before this date (will be adjusted to fol- lowing subperiod end when using a report interval) -D --daily multiperiod/multicolumn report by day -W --weekly multiperiod/multicolumn report by week -M --monthly multiperiod/multicolumn report by month -Q --quarterly multiperiod/multicolumn report by quarter -Y --yearly multiperiod/multicolumn report by year -p --period=PERIODEXP set start date, end date, and/or reporting interval all at once using period expressions syntax --date2 match the secondary date instead (see command help for other ef- fects) --today=DATE override today's date (affects relative smart dates, for tests/examples) -U --unmarked include only unmarked postings/txns (can combine with -P or -C) -P --pending include only pending postings/txns -C --cleared include only cleared postings/txns -R --real include only non-virtual postings -NUM --depth=NUM hide/aggregate accounts or postings more than NUM levels deep -E --empty show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) -B --cost convert amounts to their cost/selling amount at transaction time -V --market convert amounts to their market value in default valuation com- modities -X --exchange=COMM convert amounts to their market value in commodity COMM --value convert amounts to cost or market value, more flexibly than -B/-V/-X --infer-equity infer conversion equity postings from costs --infer-costs infer costs from conversion equity postings --infer-market-prices use costs as additional market prices, as if they were P direc- tives --forecast generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger-ui make fu- ture-dated transactions visible. --auto generate extra postings by applying auto posting rules to all txns (not just forecast txns) --verbose-tags add visible tags indicating transactions or postings which have been generated/modified --commodity-style Override the commodity style in the output for the specified commodity. For example 'EUR1.000,00'. --color=WHEN (or --colour=WHEN) Should color-supporting commands use ANSI color codes in text output. 'auto' (default): whenever stdout seems to be a color-supporting terminal. 'always' or 'yes': always, useful eg when piping output into 'less -R'. 'never' or 'no': never. A NO_COLOR environment variable overrides this. --pretty[=WHEN] Show prettier output, e.g. using unicode box-drawing charac- ters. Accepts 'yes' (the default) or 'no' ('y', 'n', 'always', 'never' also work). If you provide an argument you must use '=', e.g. '--pretty=yes'. When a reporting option appears more than once in the command line, the last one takes precedence. Some reporting options can also be written as query arguments. MOUSE In most modern terminals, you can navigate through the screens with a mouse or touchpad: o Use mouse wheel or trackpad to scroll up and down o Click on list items to go deeper o Click on the left margin (column 0) to go back. KEYS Keyboard gives more control. ? shows a help dialog listing all keys. (Some of these also appear in the quick help at the bottom of each screen.) Press ? again (or ES- CAPE, or LEFT, or q) to close it. The following keys work on most screens: The cursor keys navigate: RIGHT or ENTER goes deeper, LEFT returns to the previous screen, UP/DOWN/PGUP/PGDN/HOME/END move up and down through lists. Emacs-style (CTRL-p/CTRL-n/CTRL-f/CTRL-b) and VI-style (k,j,l,h) movement keys are also supported. A tip: movement speed is limited by your keyboard repeat rate, to move faster you may want to adjust it. (If you're on a mac, the karabiner app is one way to do that.) With shift pressed, the cursor keys adjust the report period, limiting the transactions to be shown (by default, all are shown). SHIFT-DOWN/UP steps downward and upward through these standard report period durations: year, quarter, month, week, day. Then, SHIFT-LEFT/RIGHT moves to the previous/next period. T sets the report period to today. With the -w/--watch option, when viewing a "current" period (the current day, week, month, quarter, or year), the period will move automatically to track the current date. To set a non-stan- dard period, you can use / and a date: query. (Mac users: SHIFT-DOWN/UP keys do not work by default in Terminal, as of MacOS Monterey. You can configure them as follows: open Terminal, press CMD-comma to open preferences, click Profiles, select your cur- rent terminal profile on the left, click Keyboard on the right, click + and add this for Shift-Down: \033[1;2B, click + and add this for Shift-Up: \033[1;2A. Press the Escape key to enter the \033 part, you can't type it directly.) / lets you set a general filter query limiting the data shown, using the same query terms as in hledger and hledger-web. While editing the query, you can use CTRL-a/e/d/k, BS, cursor keys; press ENTER to set it, or ESCAPEto cancel. There are also keys for quickly adjusting some common filters like account depth and transaction status (see below). BACKSPACE or DELETE removes all filters, showing all transactions. As mentioned above, by default hledger-ui hides future transactions - both ordinary transactions recorded in the journal, and periodic trans- actions generated by rule. F toggles forecast mode, in which fu- ture/forecasted transactions are shown. ESCAPE resets the UI state and jumps back to the top screen, restoring the app's initial state at startup. Or, it cancels minibuffer data en- try or the help dialog. CTRL-l redraws the screen and centers the selection if possible (selec- tions near the top won't be centered, since we don't scroll above the top). g reloads from the data file(s) and updates the current screen and any previous screens. (With large files, this could cause a noticeable pause.) I toggles balance assertion checking. Disabling balance assertions temporarily can be useful for troubleshooting. a runs command-line hledger's add command, and reloads the updated file. This allows some basic data entry. A is like a, but runs the hledger-iadd tool, which provides a terminal interface. This key will be available if hledger-iadd is installed in $path. E runs $HLEDGER_UI_EDITOR, or $EDITOR, or a default (emacsclient -a "" -nw) on the journal file. With some editors (emacs, vi), the cursor will be positioned at the current transaction when invoked from the register and transaction screens, and at the error location (if possi- ble) when invoked from the error screen. B toggles cost mode, showing amounts converted to their cost's commod- ity (see hledger manual > Cost reporting. V toggles value mode, showing amounts converted to their market value (see hledger manual > Valuation flag). More specifically, 1. By default, the V key toggles showing end value (--value=end) on or off. The valuation date will be the report end date if specified, otherwise today. 2. If you started hledger-ui with some other valuation (such as --value=then,EUR), the V key toggles that off or on. Cost/value tips: - When showing end value, you can change the report end date without restarting, by pressing / and adding a query like date:..YYYY-MM-DD. - Either cost mode, or value mode, can be active, but not both at once. Cost mode takes precedence. - There's not yet any visual indicator that cost or value mode is active, other than the amount values. q quits the application. Additional screen-specific keys are described below. SCREENS At startup, hledger-ui shows a menu screen by default. From here you can navigate to other screens using the cursor keys: UP/DOWN to select, RIGHT to move to the selected screen, LEFT to return to the previous screen. Or you can use ESC to return directly to the top menu screen. You can also use a command line flag to specific a different startup screen (--cs, --bs, --is, --all, or --register=ACCT). Menu This is the top-most screen. From here you can navigate to several screens listing accounts of various types. Note some of these may not show anything until you have configured account types. Cash accounts This screen shows "cash" (ie, liquid asset) accounts (like hledger bal- ancesheet type:c). It always shows balances (historical ending bal- ances on the date shown in the title line). Balance sheet accounts This screen shows asset, liability and equity accounts (like hledger balancesheetequity). It always shows balances. Income statement accounts This screen shows revenue and expense accounts (like hledger incomes- tatement). It always shows changes (balance changes in the period shown in the title line). All accounts This screen shows all accounts in your journal (unless filtered by a query; like hledger balance). It shows balances by default; you can toggle showing changes with the H key. Register This screen shows the transactions affecting a particular account. Each line represents one transaction, and shows: o the other account(s) involved, in abbreviated form. (If there are both real and virtual postings, it shows only the accounts affected by real postings.) o the overall change to the current account's balance; positive for an inflow to this account, negative for an outflow. o the running total after the transaction. With the H key you can tog- gle between o the period total, which is from just the transactions displayed o or the historical total, which includes any undisplayed transac- tions before the start of the report period (and matching the fil- ter query if any). This will be the running historical balance (what you would see on a bank's website, eg) if not disturbed by a query. Note, this screen combines each transaction's in-period postings to a single line item, dated with the earliest in-period transaction or posting date (like hledger's aregister). So custom posting dates can cause the running balance to be temporarily inaccurate. (See hledger manual > aregister and posting dates.) Transactions affecting this account's subaccounts will be included in the register if the accounts screen is in tree mode, or if it's in list mode but this account has subaccounts which are not shown due to a depth limit. In other words, the register always shows the transac- tions contributing to the balance shown on the accounts screen. Tree mode/list mode can be toggled with t here also. U toggles filtering by unmarked status, showing or hiding unmarked transactions. Similarly, P toggles pending transactions, and C toggles cleared transactions. (By default, transactions with all statuses are shown; if you activate one or two status filters, only those transac- tions are shown; and if you activate all three, the filter is removed.) R toggles real mode, in which virtual postings are ignored. z toggles nonzero mode, in which only transactions posting a nonzero change are shown (hledger-ui shows zero items by default, unlike com- mand-line hledger). Press RIGHT to view the selected transaction in detail. Transaction This screen shows a single transaction, as a general journal entry, similar to hledger's print command and journal format (hledger_jour- nal(5)). The transaction's date(s) and any cleared flag, transaction code, de- scription, comments, along with all of its account postings are shown. Simple transactions have two postings, but there can be more (or in certain cases, fewer). UP and DOWN will step through all transactions listed in the previous account register screen. In the title bar, the numbers in parentheses show your position within that account register. They will vary de- pending on which account register you came from (remember most transac- tions appear in multiple account registers). The #N number preceding them is the transaction's position within the complete unfiltered jour- nal, which is a more stable id (at least until the next reload). On this screen (and the register screen), the E key will open your text editor with the cursor positioned at the current transaction if possi- ble. This screen has a limitation with showing file updates: it will not show them until you exit and re-enter it. So eg to see the effect of using the E key, currently you must: - press E, edit and save the file, then exit the editor, returning to hledger-ui - press g to reload the file (or use -w/--watch mode) - press LEFT then RIGHT to exit and re-enter the transaction screen. Error This screen will appear if there is a problem, such as a parse error, when you press g to reload. Once you have fixed the problem, press g again to reload and resume normal operation. (Or, you can press escape to cancel the reload attempt.) TIPS Watch mode One of hledger-ui's best features is the auto-reloading -w/--watch mode. With this flag, it will update the display automatically when- ever changes are saved to the data files. This is very useful when reconciling. A good workflow is to have your bank's online register open in a browser window, for reference; the journal file open in an editor window; and hledger-ui in watch mode in a terminal window, eg: $ hledger-ui --watch --register checking -C As you mark things cleared in the editor, you can see the effect imme- diately without having to context switch. This leaves more mental bandwidth for your accounting. Of course you can still interact with hledger-ui when needed, eg to toggle cleared mode, or to explore the history. There are currently some limitations with --watch: It may not work correctly for you, depending on platform or system con- figuration. (Eg #836.) At least on mac, there can be a slow build-up of CPU usage over time, until the program is restarted (or, suspending and restarting with CTRL-z fg may be enough). It will not detect file changes made by certain editors, such as Jet- brains IDEs or gedit, or on certain less common filesystems. (To work around, press g to reload manually, or try #1617's fs.ino- tify.max_user_watches workaround and let us know.) If you are viewing files mounted from another machine, the system clocks on both machines should be roughly in agreement. Debug output You can add --debug[=N] to the command line to log debug output. This will be logged to the file hledger-ui.log in the current directory. N ranges from 1 (least output, the default) to 9 (maximum output). ENVIRONMENT COLUMNS The screen width to use. Default: the full terminal width. LEDGER_FILE The main journal file to use when not specified with -f/--file. Default: $HOME/.hledger.journal. BUGS We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). Some known issues: -f- doesn't work (hledger-ui can't read from stdin). If you press g with large files, there could be a noticeable pause. The Transaction screen does not update from file changes until you exit and re-endter it (see SCREENS > Transaction above). --watch is not yet fully robust on all platforms (see Watch mode above). AUTHORS Simon Michael and contributors. See http://hledger.org/CREDITS.html COPYRIGHT Copyright 2007-2023 Simon Michael and contributors. LICENSE Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), ledger(1) hledger-ui-1.32.3 January 2024 HLEDGER-UI(1) hledger-1.32.3/embeddedfiles/hledger-ui.info0000644000000000000000000005556014555433336017104 0ustar0000000000000000This is hledger-ui.info, produced by makeinfo version 7.1 from stdin. INFO-DIR-SECTION User Applications START-INFO-DIR-ENTRY * hledger-ui: (hledger-ui). Terminal UI for the hledger accounting tool. END-INFO-DIR-ENTRY  File: hledger-ui.info, Node: Top, Next: OPTIONS, Up: (dir) hledger-ui(1) ************* hledger-ui - robust, friendly plain text accounting (TUI version) 'hledger-ui [OPTS] [QUERYARGS]' 'hledger ui -- [OPTS] [QUERYARGS]' This manual is for hledger's terminal interface, version 1.32.3. See also the hledger manual for common concepts and file formats. hledger is a robust, user-friendly, cross-platform set of programs for tracking money, time, or any other commodity, using double-entry accounting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). hledger-ui is hledger's terminal interface, providing an efficient full-window text UI for viewing accounts and transactions, and some limited data entry capability. It is easier than hledger's command-line interface, and sometimes quicker and more convenient than the web interface. Like hledger, it reads from (and appends to) a journal file specified by the 'LEDGER_FILE' environment variable (defaulting to '$HOME/.hledger.journal'); or you can specify files with '-f' options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. (See hledger(1) -> Input for details.) Unlike hledger, hledger-ui hides all future-dated transactions by default. They can be revealed, along with any rule-generated periodic transactions, by pressing the F key (or starting with -forecast) to enable "forecast mode". * Menu: * OPTIONS:: * MOUSE:: * KEYS:: * SCREENS:: * TIPS:: * ENVIRONMENT:: * BUGS::  File: hledger-ui.info, Node: OPTIONS, Next: MOUSE, Prev: Top, Up: Top 1 OPTIONS ********* Any QUERYARGS are interpreted as a hledger search query which filters the data. hledger-ui provides the following options: '-w --watch' watch for data and date changes and reload automatically '--theme=default|terminal|greenterm' use this custom display theme '--menu' start in the menu screen '--cash' start in the cash accounts screen '--bs' start in the balance sheet accounts screen '--is' start in the income statement accounts screen '--all' start in the all accounts screen '--register=ACCTREGEX' start in the (first) matched account's register screen '--change' show period balances (changes) at startup instead of historical balances '-l --flat' show accounts as a flat list (default) '-t --tree' show accounts as a tree hledger-ui also supports many of hledger's general options (and the hledger manual's command line tips also apply here): * Menu: * General help options:: * General input options:: * General reporting options::  File: hledger-ui.info, Node: General help options, Next: General input options, Up: OPTIONS 1.1 General help options ======================== '-h --help' show general or COMMAND help '--man' show general or COMMAND user manual with man '--info' show general or COMMAND user manual with info '--version' show general or ADDONCMD version '--debug[=N]' show debug output (levels 1-9, default: 1)  File: hledger-ui.info, Node: General input options, Next: General reporting options, Prev: General help options, Up: OPTIONS 1.2 General input options ========================= '-f FILE --file=FILE' use a different input file. For stdin, use - (default: '$LEDGER_FILE' or '$HOME/.hledger.journal') '--rules-file=RULESFILE' Conversion rules file to use when reading CSV (default: FILE.rules) '--separator=CHAR' Field separator to expect when reading CSV (default: ',') '--alias=OLD=NEW' rename accounts named OLD to NEW '--pivot FIELDNAME' use some other field or tag for the account name '-I --ignore-assertions' disable balance assertion checks (note: does not disable balance assignments) '-s --strict' do extra error checking (check that all posted accounts are declared)  File: hledger-ui.info, Node: General reporting options, Prev: General input options, Up: OPTIONS 1.3 General reporting options ============================= '-b --begin=DATE' include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) '-e --end=DATE' include postings/txns before this date (will be adjusted to following subperiod end when using a report interval) '-D --daily' multiperiod/multicolumn report by day '-W --weekly' multiperiod/multicolumn report by week '-M --monthly' multiperiod/multicolumn report by month '-Q --quarterly' multiperiod/multicolumn report by quarter '-Y --yearly' multiperiod/multicolumn report by year '-p --period=PERIODEXP' set start date, end date, and/or reporting interval all at once using period expressions syntax '--date2' match the secondary date instead (see command help for other effects) '--today=DATE' override today's date (affects relative smart dates, for tests/examples) '-U --unmarked' include only unmarked postings/txns (can combine with -P or -C) '-P --pending' include only pending postings/txns '-C --cleared' include only cleared postings/txns '-R --real' include only non-virtual postings '-NUM --depth=NUM' hide/aggregate accounts or postings more than NUM levels deep '-E --empty' show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) '-B --cost' convert amounts to their cost/selling amount at transaction time '-V --market' convert amounts to their market value in default valuation commodities '-X --exchange=COMM' convert amounts to their market value in commodity COMM '--value' convert amounts to cost or market value, more flexibly than -B/-V/-X '--infer-equity' infer conversion equity postings from costs '--infer-costs' infer costs from conversion equity postings '--infer-market-prices' use costs as additional market prices, as if they were P directives '--forecast' generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger-ui make future-dated transactions visible. '--auto' generate extra postings by applying auto posting rules to all txns (not just forecast txns) '--verbose-tags' add visible tags indicating transactions or postings which have been generated/modified '--commodity-style' Override the commodity style in the output for the specified commodity. For example 'EUR1.000,00'. '--color=WHEN (or --colour=WHEN)' Should color-supporting commands use ANSI color codes in text output. 'auto' (default): whenever stdout seems to be a color-supporting terminal. 'always' or 'yes': always, useful eg when piping output into 'less -R'. 'never' or 'no': never. A NO_COLOR environment variable overrides this. '--pretty[=WHEN]' Show prettier output, e.g. using unicode box-drawing characters. Accepts 'yes' (the default) or 'no' ('y', 'n', 'always', 'never' also work). If you provide an argument you must use '=', e.g. '-pretty=yes'. When a reporting option appears more than once in the command line, the last one takes precedence. Some reporting options can also be written as query arguments.  File: hledger-ui.info, Node: MOUSE, Next: KEYS, Prev: OPTIONS, Up: Top 2 MOUSE ******* In most modern terminals, you can navigate through the screens with a mouse or touchpad: * Use mouse wheel or trackpad to scroll up and down * Click on list items to go deeper * Click on the left margin (column 0) to go back.  File: hledger-ui.info, Node: KEYS, Next: SCREENS, Prev: MOUSE, Up: Top 3 KEYS ****** Keyboard gives more control. '?' shows a help dialog listing all keys. (Some of these also appear in the quick help at the bottom of each screen.) Press '?' again (or 'ESCAPE', or 'LEFT', or 'q') to close it. The following keys work on most screens: The cursor keys navigate: 'RIGHT' or 'ENTER' goes deeper, 'LEFT' returns to the previous screen, 'UP'/'DOWN'/'PGUP'/'PGDN'/'HOME'/'END' move up and down through lists. Emacs-style ('CTRL-p'/'CTRL-n'/'CTRL-f'/'CTRL-b') and VI-style ('k','j','l','h') movement keys are also supported. A tip: movement speed is limited by your keyboard repeat rate, to move faster you may want to adjust it. (If you're on a mac, the karabiner app is one way to do that.) With shift pressed, the cursor keys adjust the report period, limiting the transactions to be shown (by default, all are shown). 'SHIFT-DOWN/UP' steps downward and upward through these standard report period durations: year, quarter, month, week, day. Then, 'SHIFT-LEFT/RIGHT' moves to the previous/next period. 'T' sets the report period to today. With the '-w/--watch' option, when viewing a "current" period (the current day, week, month, quarter, or year), the period will move automatically to track the current date. To set a non-standard period, you can use '/' and a 'date:' query. (Mac users: SHIFT-DOWN/UP keys do not work by default in Terminal, as of MacOS Monterey. You can configure them as follows: open Terminal, press CMD-comma to open preferences, click Profiles, select your current terminal profile on the left, click Keyboard on the right, click + and add this for Shift-Down: '\033[1;2B', click + and add this for Shift-Up: '\033[1;2A'. Press the Escape key to enter the '\033' part, you can't type it directly.) '/' lets you set a general filter query limiting the data shown, using the same query terms as in hledger and hledger-web. While editing the query, you can use CTRL-a/e/d/k, BS, cursor keys; press 'ENTER' to set it, or 'ESCAPE'to cancel. There are also keys for quickly adjusting some common filters like account depth and transaction status (see below). 'BACKSPACE' or 'DELETE' removes all filters, showing all transactions. As mentioned above, by default hledger-ui hides future transactions - both ordinary transactions recorded in the journal, and periodic transactions generated by rule. 'F' toggles forecast mode, in which future/forecasted transactions are shown. 'ESCAPE' resets the UI state and jumps back to the top screen, restoring the app's initial state at startup. Or, it cancels minibuffer data entry or the help dialog. 'CTRL-l' redraws the screen and centers the selection if possible (selections near the top won't be centered, since we don't scroll above the top). 'g' reloads from the data file(s) and updates the current screen and any previous screens. (With large files, this could cause a noticeable pause.) 'I' toggles balance assertion checking. Disabling balance assertions temporarily can be useful for troubleshooting. 'a' runs command-line hledger's add command, and reloads the updated file. This allows some basic data entry. 'A' is like 'a', but runs the hledger-iadd tool, which provides a terminal interface. This key will be available if 'hledger-iadd' is installed in $path. 'E' runs $HLEDGER_UI_EDITOR, or $EDITOR, or a default ('emacsclient -a "" -nw') on the journal file. With some editors (emacs, vi), the cursor will be positioned at the current transaction when invoked from the register and transaction screens, and at the error location (if possible) when invoked from the error screen. 'B' toggles cost mode, showing amounts converted to their cost's commodity (see hledger manual > Cost reporting. 'V' toggles value mode, showing amounts converted to their market value (see hledger manual > Valuation flag). More specifically, 1. By default, the 'V' key toggles showing end value ('--value=end') on or off. The valuation date will be the report end date if specified, otherwise today. 2. If you started hledger-ui with some other valuation (such as '--value=then,EUR'), the 'V' key toggles that off or on. Cost/value tips: - When showing end value, you can change the report end date without restarting, by pressing '/' and adding a query like 'date:..YYYY-MM-DD'. - Either cost mode, or value mode, can be active, but not both at once. Cost mode takes precedence. - There's not yet any visual indicator that cost or value mode is active, other than the amount values. 'q' quits the application. Additional screen-specific keys are described below.  File: hledger-ui.info, Node: SCREENS, Next: TIPS, Prev: KEYS, Up: Top 4 SCREENS ********* At startup, hledger-ui shows a menu screen by default. From here you can navigate to other screens using the cursor keys: 'UP'/'DOWN' to select, 'RIGHT' to move to the selected screen, 'LEFT' to return to the previous screen. Or you can use 'ESC' to return directly to the top menu screen. You can also use a command line flag to specific a different startup screen ('--cs', '--bs', '--is', '--all', or '--register=ACCT'). * Menu: * Menu:: * Cash accounts:: * Balance sheet accounts:: * Income statement accounts:: * All accounts:: * Register:: * Transaction:: * Error::  File: hledger-ui.info, Node: Menu, Next: Cash accounts, Up: SCREENS 4.1 Menu ======== This is the top-most screen. From here you can navigate to several screens listing accounts of various types. Note some of these may not show anything until you have configured account types.  File: hledger-ui.info, Node: Cash accounts, Next: Balance sheet accounts, Prev: Menu, Up: SCREENS 4.2 Cash accounts ================= This screen shows "cash" (ie, liquid asset) accounts (like 'hledger balancesheet type:c'). It always shows balances (historical ending balances on the date shown in the title line).  File: hledger-ui.info, Node: Balance sheet accounts, Next: Income statement accounts, Prev: Cash accounts, Up: SCREENS 4.3 Balance sheet accounts ========================== This screen shows asset, liability and equity accounts (like 'hledger balancesheetequity'). It always shows balances.  File: hledger-ui.info, Node: Income statement accounts, Next: All accounts, Prev: Balance sheet accounts, Up: SCREENS 4.4 Income statement accounts ============================= This screen shows revenue and expense accounts (like 'hledger incomestatement'). It always shows changes (balance changes in the period shown in the title line).  File: hledger-ui.info, Node: All accounts, Next: Register, Prev: Income statement accounts, Up: SCREENS 4.5 All accounts ================ This screen shows all accounts in your journal (unless filtered by a query; like 'hledger balance'). It shows balances by default; you can toggle showing changes with the 'H' key.  File: hledger-ui.info, Node: Register, Next: Transaction, Prev: All accounts, Up: SCREENS 4.6 Register ============ This screen shows the transactions affecting a particular account. Each line represents one transaction, and shows: * the other account(s) involved, in abbreviated form. (If there are both real and virtual postings, it shows only the accounts affected by real postings.) * the overall change to the current account's balance; positive for an inflow to this account, negative for an outflow. * the running total after the transaction. With the 'H' key you can toggle between * the period total, which is from just the transactions displayed * or the historical total, which includes any undisplayed transactions before the start of the report period (and matching the filter query if any). This will be the running historical balance (what you would see on a bank's website, eg) if not disturbed by a query. Note, this screen combines each transaction's in-period postings to a single line item, dated with the earliest in-period transaction or posting date (like hledger's 'aregister'). So custom posting dates can cause the running balance to be temporarily inaccurate. (See hledger manual > aregister and posting dates.) Transactions affecting this account's subaccounts will be included in the register if the accounts screen is in tree mode, or if it's in list mode but this account has subaccounts which are not shown due to a depth limit. In other words, the register always shows the transactions contributing to the balance shown on the accounts screen. Tree mode/list mode can be toggled with 't' here also. 'U' toggles filtering by unmarked status, showing or hiding unmarked transactions. Similarly, 'P' toggles pending transactions, and 'C' toggles cleared transactions. (By default, transactions with all statuses are shown; if you activate one or two status filters, only those transactions are shown; and if you activate all three, the filter is removed.) 'R' toggles real mode, in which virtual postings are ignored. 'z' toggles nonzero mode, in which only transactions posting a nonzero change are shown (hledger-ui shows zero items by default, unlike command-line hledger). Press 'RIGHT' to view the selected transaction in detail.  File: hledger-ui.info, Node: Transaction, Next: Error, Prev: Register, Up: SCREENS 4.7 Transaction =============== This screen shows a single transaction, as a general journal entry, similar to hledger's print command and journal format (hledger_journal(5)). The transaction's date(s) and any cleared flag, transaction code, description, comments, along with all of its account postings are shown. Simple transactions have two postings, but there can be more (or in certain cases, fewer). 'UP' and 'DOWN' will step through all transactions listed in the previous account register screen. In the title bar, the numbers in parentheses show your position within that account register. They will vary depending on which account register you came from (remember most transactions appear in multiple account registers). The #N number preceding them is the transaction's position within the complete unfiltered journal, which is a more stable id (at least until the next reload). On this screen (and the register screen), the 'E' key will open your text editor with the cursor positioned at the current transaction if possible. This screen has a limitation with showing file updates: it will not show them until you exit and re-enter it. So eg to see the effect of using the 'E' key, currently you must: - press 'E', edit and save the file, then exit the editor, returning to hledger-ui - press 'g' to reload the file (or use '-w/--watch' mode) - press 'LEFT' then 'RIGHT' to exit and re-enter the transaction screen.  File: hledger-ui.info, Node: Error, Prev: Transaction, Up: SCREENS 4.8 Error ========= This screen will appear if there is a problem, such as a parse error, when you press g to reload. Once you have fixed the problem, press g again to reload and resume normal operation. (Or, you can press escape to cancel the reload attempt.)  File: hledger-ui.info, Node: TIPS, Next: ENVIRONMENT, Prev: SCREENS, Up: Top 5 TIPS ****** * Menu: * Watch mode:: * Debug output::  File: hledger-ui.info, Node: Watch mode, Next: Debug output, Up: TIPS 5.1 Watch mode ============== One of hledger-ui's best features is the auto-reloading '-w/--watch' mode. With this flag, it will update the display automatically whenever changes are saved to the data files. This is very useful when reconciling. A good workflow is to have your bank's online register open in a browser window, for reference; the journal file open in an editor window; and hledger-ui in watch mode in a terminal window, eg: $ hledger-ui --watch --register checking -C As you mark things cleared in the editor, you can see the effect immediately without having to context switch. This leaves more mental bandwidth for your accounting. Of course you can still interact with hledger-ui when needed, eg to toggle cleared mode, or to explore the history. There are currently some limitations with '--watch': It may not work correctly for you, depending on platform or system configuration. (Eg #836.) At least on mac, there can be a slow build-up of CPU usage over time, until the program is restarted (or, suspending and restarting with 'CTRL-z' 'fg' may be enough). It will not detect file changes made by certain editors, such as Jetbrains IDEs or 'gedit', or on certain less common filesystems. (To work around, press 'g' to reload manually, or try #1617's 'fs.inotify.max_user_watches' workaround and let us know.) If you are viewing files mounted from another machine, the system clocks on both machines should be roughly in agreement.  File: hledger-ui.info, Node: Debug output, Prev: Watch mode, Up: TIPS 5.2 Debug output ================ You can add '--debug[=N]' to the command line to log debug output. This will be logged to the file 'hledger-ui.log' in the current directory. N ranges from 1 (least output, the default) to 9 (maximum output).  File: hledger-ui.info, Node: ENVIRONMENT, Next: BUGS, Prev: TIPS, Up: Top 6 ENVIRONMENT ************* *COLUMNS* The screen width to use. Default: the full terminal width. *LEDGER_FILE* The main journal file to use when not specified with '-f/--file'. Default: '$HOME/.hledger.journal'.  File: hledger-ui.info, Node: BUGS, Prev: ENVIRONMENT, Up: Top 7 BUGS ****** We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). Some known issues: '-f-' doesn't work (hledger-ui can't read from stdin). If you press 'g' with large files, there could be a noticeable pause. The Transaction screen does not update from file changes until you exit and re-endter it (see SCREENS > Transaction above). '--watch' is not yet fully robust on all platforms (see Watch mode above).  Tag Table: Node: Top221 Node: OPTIONS1830 Ref: #options1928 Node: General help options2951 Ref: #general-help-options3100 Node: General input options3382 Ref: #general-input-options3567 Node: General reporting options4224 Ref: #general-reporting-options4388 Node: MOUSE7778 Ref: #mouse7873 Node: KEYS8110 Ref: #keys8203 Node: SCREENS12858 Ref: #screens12956 Node: Menu13536 Ref: #menu13629 Node: Cash accounts13824 Ref: #cash-accounts13966 Node: Balance sheet accounts14150 Ref: #balance-sheet-accounts14331 Node: Income statement accounts14451 Ref: #income-statement-accounts14637 Node: All accounts14801 Ref: #all-accounts14947 Node: Register15129 Ref: #register15253 Node: Transaction17537 Ref: #transaction17660 Node: Error19077 Ref: #error19171 Node: TIPS19415 Ref: #tips19514 Node: Watch mode19556 Ref: #watch-mode19663 Node: Debug output21122 Ref: #debug-output21233 Node: ENVIRONMENT21445 Ref: #environment21555 Node: BUGS21746 Ref: #bugs21829  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.32.3/embeddedfiles/hledger-web.10000644000000000000000000004764714555433336016460 0ustar0000000000000000 .TH "HLEDGER\-WEB" "1" "January 2024" "hledger-web-1.32.3 " "hledger User Manuals" .SH NAME hledger\-web \- robust, friendly plain text accounting (Web version) .SH SYNOPSIS \f[CR]hledger\-web [\-\-serve|\-\-serve\-api] [OPTS] [ARGS]\f[R] .PD 0 .P .PD \f[CR]hledger web \-\- [\-\-serve|\-\-serve\-api] [OPTS] [ARGS]\f[R] .SH DESCRIPTION This manual is for hledger\[aq]s web interface, version 1.32.3. See also the hledger manual for common concepts and file formats. .PP hledger is a robust, user\-friendly, cross\-platform set of programs for tracking money, time, or any other commodity, using double\-entry accounting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). .PP hledger\-web is a simple web application for browsing and adding transactions. It provides a more user\-friendly UI than the hledger CLI or hledger\-ui TUI, showing more at once (accounts, the current account register, balance charts) and allowing history\-aware data entry, interactive searching, and bookmarking. .PP hledger\-web also lets you share a journal with multiple users, or even the public web. There is no access control, so if you need that you should put it behind a suitable web proxy. As a small protection against data loss when running an unprotected instance, it writes a numbered backup of the main journal file (only) on every edit. .PP Like hledger, it reads from (and appends to) a journal file specified by the \f[CR]LEDGER_FILE\f[R] environment variable (defaulting to \f[CR]$HOME/.hledger.journal\f[R]); or you can specify files with \f[CR]\-f\f[R] options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. (See hledger(1) \-> Input for details.) .PP hledger\-web can be run in three modes: .IP \[bu] 2 Transient mode (the default): your default web browser will be opened to show the app if possible, and the app exits automatically after two minutes of inactivity (no requests received and no open browser windows viewing it). .IP \[bu] 2 With \f[CR]\-\-serve\f[R]: the app runs without stopping, and without opening a browser. .IP \[bu] 2 With \f[CR]\-\-serve\-api\f[R]: only the JSON API is served. .PP In all cases hledger\-web runs as a foreground process, logging requests to stdout. .SH OPTIONS hledger\-web provides the following options: .TP \f[CR]\-\-serve\f[R] serve and log requests, don\[aq]t browse or auto\-exit after timeout .TP \f[CR]\-\-serve\-api\f[R] like \-\-serve, but serve only the JSON web API, not the web UI .TP \f[CR]\-\-allow=view|add|edit\f[R] set the user\[aq]s access level for changing data (default: \f[CR]add\f[R]). It also accepts \f[CR]sandstorm\f[R] for use on that platform (reads permissions from the \f[CR]X\-Sandstorm\-Permissions\f[R] request header). .TP \f[CR]\-\-cors=ORIGIN\f[R] allow cross\-origin requests from the specified origin; setting ORIGIN to \[dq]*\[dq] allows requests from any origin .TP \f[CR]\-\-host=IPADDR\f[R] listen on this IP address (default: 127.0.0.1) .PP By default the server listens on IP address \f[CR]127.0.0.1\f[R], which is accessible only to requests from the local machine.. You can use \f[CR]\-\-host\f[R] to listen on a different address configured on the machine, eg to allow access from other machines. The special address \f[CR]0.0.0.0\f[R] causes it to listen on all addresses configured on the machine. .TP \f[CR]\-\-port=PORT\f[R] listen on this TCP port (default: 5000) .PP Similarly, you can use \f[CR]\-\-port\f[R] to listen on a TCP port other than 5000. This is useful if you want to run multiple hledger\-web instances on a machine. .TP \f[CR]\-\-socket=SOCKETFILE\f[R] listen on the given unix socket instead of an IP address and port (unix only; implies \-\-serve) .PP When \f[CR]\-\-socket\f[R] is used, hledger\-web creates and communicates via a socket file instead of a TCP port. This can be more secure, respects unix file permissions, and makes certain use cases easier, such as running per\-user instances behind an nginx reverse proxy. (Eg: \f[CR]proxy_pass http://unix:/tmp/hledger/${remote_user}.socket;\f[R].) .TP \f[CR]\-\-base\-url=URL\f[R] set the base url (default: http://IPADDR:PORT). .PP You can use \f[CR]\-\-base\-url\f[R] to change the protocol, hostname, port and path that appear in hledger\-web\[aq]s hyperlinks. This is useful eg when integrating hledger\-web within a larger website. The default is \f[CR]http://HOST:PORT/\f[R] using the server\[aq]s configured host address and TCP port (or \f[CR]http://HOST\f[R] if PORT is 80). Note this affects url generation but not route parsing. .TP \f[CR]\-\-test\f[R] run hledger\-web\[aq]s tests and exit. hspec test runner args may follow a \-\-, eg: hledger\-web \-\-test \-\- \-\-help .PP hledger\-web also supports many of hledger\[aq]s general options. Query options and arguments may be used to set an initial filter, which although not shown in the UI, will restrict the data shown, in addition to any search query entered in the UI. .SS General help options .TP \f[CR]\-h \-\-help\f[R] show general or COMMAND help .TP \f[CR]\-\-man\f[R] show general or COMMAND user manual with man .TP \f[CR]\-\-info\f[R] show general or COMMAND user manual with info .TP \f[CR]\-\-version\f[R] show general or ADDONCMD version .TP \f[CR]\-\-debug[=N]\f[R] show debug output (levels 1\-9, default: 1) .SS General input options .TP \f[CR]\-f FILE \-\-file=FILE\f[R] use a different input file. For stdin, use \- (default: \f[CR]$LEDGER_FILE\f[R] or \f[CR]$HOME/.hledger.journal\f[R]) .TP \f[CR]\-\-rules\-file=RULESFILE\f[R] Conversion rules file to use when reading CSV (default: FILE.rules) .TP \f[CR]\-\-separator=CHAR\f[R] Field separator to expect when reading CSV (default: \[aq],\[aq]) .TP \f[CR]\-\-alias=OLD=NEW\f[R] rename accounts named OLD to NEW .TP \f[CR]\-\-pivot FIELDNAME\f[R] use some other field or tag for the account name .TP \f[CR]\-I \-\-ignore\-assertions\f[R] disable balance assertion checks (note: does not disable balance assignments) .TP \f[CR]\-s \-\-strict\f[R] do extra error checking (check that all posted accounts are declared) .SS General reporting options .TP \f[CR]\-b \-\-begin=DATE\f[R] include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) .TP \f[CR]\-e \-\-end=DATE\f[R] include postings/txns before this date (will be adjusted to following subperiod end when using a report interval) .TP \f[CR]\-D \-\-daily\f[R] multiperiod/multicolumn report by day .TP \f[CR]\-W \-\-weekly\f[R] multiperiod/multicolumn report by week .TP \f[CR]\-M \-\-monthly\f[R] multiperiod/multicolumn report by month .TP \f[CR]\-Q \-\-quarterly\f[R] multiperiod/multicolumn report by quarter .TP \f[CR]\-Y \-\-yearly\f[R] multiperiod/multicolumn report by year .TP \f[CR]\-p \-\-period=PERIODEXP\f[R] set start date, end date, and/or reporting interval all at once using period expressions syntax .TP \f[CR]\-\-date2\f[R] match the secondary date instead (see command help for other effects) .TP \f[CR]\-\-today=DATE\f[R] override today\[aq]s date (affects relative smart dates, for tests/examples) .TP \f[CR]\-U \-\-unmarked\f[R] include only unmarked postings/txns (can combine with \-P or \-C) .TP \f[CR]\-P \-\-pending\f[R] include only pending postings/txns .TP \f[CR]\-C \-\-cleared\f[R] include only cleared postings/txns .TP \f[CR]\-R \-\-real\f[R] include only non\-virtual postings .TP \f[CR]\-NUM \-\-depth=NUM\f[R] hide/aggregate accounts or postings more than NUM levels deep .TP \f[CR]\-E \-\-empty\f[R] show items with zero amount, normally hidden (and vice\-versa in hledger\-ui/hledger\-web) .TP \f[CR]\-B \-\-cost\f[R] convert amounts to their cost/selling amount at transaction time .TP \f[CR]\-V \-\-market\f[R] convert amounts to their market value in default valuation commodities .TP \f[CR]\-X \-\-exchange=COMM\f[R] convert amounts to their market value in commodity COMM .TP \f[CR]\-\-value\f[R] convert amounts to cost or market value, more flexibly than \-B/\-V/\-X .TP \f[CR]\-\-infer\-equity\f[R] infer conversion equity postings from costs .TP \f[CR]\-\-infer\-costs\f[R] infer costs from conversion equity postings .TP \f[CR]\-\-infer\-market\-prices\f[R] use costs as additional market prices, as if they were P directives .TP \f[CR]\-\-forecast\f[R] generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger\-ui make future\-dated transactions visible. .TP \f[CR]\-\-auto\f[R] generate extra postings by applying auto posting rules to all txns (not just forecast txns) .TP \f[CR]\-\-verbose\-tags\f[R] add visible tags indicating transactions or postings which have been generated/modified .TP \f[CR]\-\-commodity\-style\f[R] Override the commodity style in the output for the specified commodity. For example \[aq]EUR1.000,00\[aq]. .TP \f[CR]\-\-color=WHEN (or \-\-colour=WHEN)\f[R] Should color\-supporting commands use ANSI color codes in text output. \[aq]auto\[aq] (default): whenever stdout seems to be a color\-supporting terminal. \[aq]always\[aq] or \[aq]yes\[aq]: always, useful eg when piping output into \[aq]less \-R\[aq]. \[aq]never\[aq] or \[aq]no\[aq]: never. A NO_COLOR environment variable overrides this. .TP \f[CR]\-\-pretty[=WHEN]\f[R] Show prettier output, e.g. using unicode box\-drawing characters. Accepts \[aq]yes\[aq] (the default) or \[aq]no\[aq] (\[aq]y\[aq], \[aq]n\[aq], \[aq]always\[aq], \[aq]never\[aq] also work). If you provide an argument you must use \[aq]=\[aq], e.g. \[aq]\-\-pretty=yes\[aq]. .PP When a reporting option appears more than once in the command line, the last one takes precedence. .PP Some reporting options can also be written as query arguments. .SH PERMISSIONS By default, hledger\-web allows anyone who can reach it to view the journal and to add new transactions, but not to change existing data. .PP You can restrict who can reach it by .IP \[bu] 2 setting the IP address it listens on (see \f[CR]\-\-host\f[R] above). By default it listens on 127.0.0.1, accessible to all users on the local machine. .IP \[bu] 2 putting it behind an authenticating proxy, using eg apache or nginx .IP \[bu] 2 custom firewall rules .PP You can restrict what the users who reach it can do, by .IP \[bu] 2 using the \f[CR]\-\-capabilities=CAP[,CAP..]\f[R] flag when you start it, enabling one or more of the following capabilities. The default value is \f[CR]view,add\f[R]: .RS 2 .IP \[bu] 2 \f[CR]view\f[R] \- allows viewing the journal file and all included files .IP \[bu] 2 \f[CR]add\f[R] \- allows adding new transactions to the main journal file .IP \[bu] 2 \f[CR]manage\f[R] \- allows editing, uploading or downloading the main or included files .RE .IP \[bu] 2 using the \f[CR]\-\-capabilities\-header=HTTPHEADER\f[R] flag to specify a HTTP header from which it will read capabilities to enable. hledger\-web on Sandstorm uses the X\-Sandstorm\-Permissions header to integrate with Sandstorm\[aq]s permissions. This is disabled by default. .SH EDITING, UPLOADING, DOWNLOADING If you enable the \f[CR]manage\f[R] capability mentioned above, you\[aq]ll see a new \[dq]spanner\[dq] button to the right of the search form. Clicking this will let you edit, upload, or download the journal file or any files it includes. .PP Note, unlike any other hledger command, in this mode you (or any visitor) can alter or wipe the data files. .PP Normally whenever a file is changed in this way, hledger\-web saves a numbered backup (assuming file permissions allow it, the disk is not full, etc.) hledger\-web is not aware of version control systems, currently; if you use one, you\[aq]ll have to arrange to commit the changes yourself (eg with a cron job or a file watcher like entr). .PP Changes which would leave the journal file(s) unparseable or non\-valid (eg with failing balance assertions) are prevented. (Probably. This needs re\-testing.) .SH RELOADING hledger\-web detects changes made to the files by other means (eg if you edit it directly, outside of hledger\-web), and it will show the new data when you reload the page or navigate to a new page. If a change makes a file unparseable, hledger\-web will display an error message until the file has been fixed. .PP (Note: if you are viewing files mounted from another machine, make sure that both machine clocks are roughly in step.) .SH JSON API In addition to the web UI, hledger\-web also serves a JSON API that can be used to get data or add new transactions. If you want the JSON API only, you can use the \f[CR]\-\-serve\-api\f[R] flag. Eg: .IP .EX $ hledger\-web \-f examples/sample.journal \-\-serve\-api \&... .EE .PP You can get JSON data from these routes: .IP .EX /version /accountnames /transactions /prices /commodities /accounts /accounttransactions/ACCOUNTNAME .EE .PP Eg, all account names in the journal (similar to the accounts command). (hledger\-web\[aq]s JSON does not include newlines, here we use python to prettify it): .IP .EX $ curl \-s http://127.0.0.1:5000/accountnames | python \-m json.tool [ \[dq]assets\[dq], \[dq]assets:bank\[dq], \[dq]assets:bank:checking\[dq], \[dq]assets:bank:saving\[dq], \[dq]assets:cash\[dq], \[dq]expenses\[dq], \[dq]expenses:food\[dq], \[dq]expenses:supplies\[dq], \[dq]income\[dq], \[dq]income:gifts\[dq], \[dq]income:salary\[dq], \[dq]liabilities\[dq], \[dq]liabilities:debts\[dq] ] .EE .PP Or all transactions: .IP .EX $ curl \-s http://127.0.0.1:5000/transactions | python \-m json.tool [ { \[dq]tcode\[dq]: \[dq]\[dq], \[dq]tcomment\[dq]: \[dq]\[dq], \[dq]tdate\[dq]: \[dq]2008\-01\-01\[dq], \[dq]tdate2\[dq]: null, \[dq]tdescription\[dq]: \[dq]income\[dq], \[dq]tindex\[dq]: 1, \[dq]tpostings\[dq]: [ { \[dq]paccount\[dq]: \[dq]assets:bank:checking\[dq], \[dq]pamount\[dq]: [ { \[dq]acommodity\[dq]: \[dq]$\[dq], \[dq]aismultiplier\[dq]: false, \[dq]aprice\[dq]: null, \&... .EE .PP Most of the JSON corresponds to hledger\[aq]s data types; for details of what the fields mean, see the Hledger.Data.Json haddock docs and click on the various data types, eg Transaction. And for a higher level understanding, see the journal docs. .PP In some cases there is outer JSON corresponding to a \[dq]Report\[dq] type. To understand that, go to the Hledger.Web.Handler.MiscR haddock and look at the source for the appropriate handler to see what it returns. Eg for \f[CR]/accounttransactions\f[R] it\[aq]s getAccounttransactionsR, returning a \[dq]\f[CR]accountTransactionsReport ...\f[R]\[dq]. Looking up the haddock for that we can see that /accounttransactions returns an AccountTransactionsReport, which consists of a report title and a list of AccountTransactionsReportItem (etc). .PP You can add a new transaction to the journal with a PUT request to \f[CR]/add\f[R], if hledger\-web was started with the \f[CR]add\f[R] capability (enabled by default). The payload must be the full, exact JSON representation of a hledger transaction (partial data won\[aq]t do). You can get sample JSON from hledger\-web\[aq]s \f[CR]/transactions\f[R] or \f[CR]/accounttransactions\f[R], or you can export it with hledger\-lib, eg like so: .IP .EX \&.../hledger$ stack ghci hledger\-lib >>> writeJsonFile \[dq]txn.json\[dq] (head $ jtxns samplejournal) >>> :q .EE .PP Here\[aq]s how it looks as of hledger\-1.17 (remember, this JSON corresponds to hledger\[aq]s Transaction and related data types): .IP .EX { \[dq]tcomment\[dq]: \[dq]\[dq], \[dq]tpostings\[dq]: [ { \[dq]pbalanceassertion\[dq]: null, \[dq]pstatus\[dq]: \[dq]Unmarked\[dq], \[dq]pamount\[dq]: [ { \[dq]aprice\[dq]: null, \[dq]acommodity\[dq]: \[dq]$\[dq], \[dq]aquantity\[dq]: { \[dq]floatingPoint\[dq]: 1, \[dq]decimalPlaces\[dq]: 10, \[dq]decimalMantissa\[dq]: 10000000000 }, \[dq]aismultiplier\[dq]: false, \[dq]astyle\[dq]: { \[dq]ascommodityside\[dq]: \[dq]L\[dq], \[dq]asdigitgroups\[dq]: null, \[dq]ascommodityspaced\[dq]: false, \[dq]asprecision\[dq]: 2, \[dq]asdecimalpoint\[dq]: \[dq].\[dq] } } ], \[dq]ptransaction_\[dq]: \[dq]1\[dq], \[dq]paccount\[dq]: \[dq]assets:bank:checking\[dq], \[dq]pdate\[dq]: null, \[dq]ptype\[dq]: \[dq]RegularPosting\[dq], \[dq]pcomment\[dq]: \[dq]\[dq], \[dq]pdate2\[dq]: null, \[dq]ptags\[dq]: [], \[dq]poriginal\[dq]: null }, { \[dq]pbalanceassertion\[dq]: null, \[dq]pstatus\[dq]: \[dq]Unmarked\[dq], \[dq]pamount\[dq]: [ { \[dq]aprice\[dq]: null, \[dq]acommodity\[dq]: \[dq]$\[dq], \[dq]aquantity\[dq]: { \[dq]floatingPoint\[dq]: \-1, \[dq]decimalPlaces\[dq]: 10, \[dq]decimalMantissa\[dq]: \-10000000000 }, \[dq]aismultiplier\[dq]: false, \[dq]astyle\[dq]: { \[dq]ascommodityside\[dq]: \[dq]L\[dq], \[dq]asdigitgroups\[dq]: null, \[dq]ascommodityspaced\[dq]: false, \[dq]asprecision\[dq]: 2, \[dq]asdecimalpoint\[dq]: \[dq].\[dq] } } ], \[dq]ptransaction_\[dq]: \[dq]1\[dq], \[dq]paccount\[dq]: \[dq]income:salary\[dq], \[dq]pdate\[dq]: null, \[dq]ptype\[dq]: \[dq]RegularPosting\[dq], \[dq]pcomment\[dq]: \[dq]\[dq], \[dq]pdate2\[dq]: null, \[dq]ptags\[dq]: [], \[dq]poriginal\[dq]: null } ], \[dq]ttags\[dq]: [], \[dq]tsourcepos\[dq]: { \[dq]tag\[dq]: \[dq]JournalSourcePos\[dq], \[dq]contents\[dq]: [ \[dq]\[dq], [ 1, 1 ] ] }, \[dq]tdate\[dq]: \[dq]2008\-01\-01\[dq], \[dq]tcode\[dq]: \[dq]\[dq], \[dq]tindex\[dq]: 1, \[dq]tprecedingcomment\[dq]: \[dq]\[dq], \[dq]tdate2\[dq]: null, \[dq]tdescription\[dq]: \[dq]income\[dq], \[dq]tstatus\[dq]: \[dq]Unmarked\[dq] } .EE .PP And here\[aq]s how to test adding it with curl. This should add a new entry to your journal: .IP .EX $ curl http://127.0.0.1:5000/add \-X PUT \-H \[aq]Content\-Type: application/json\[aq] \-\-data\-binary \[at]txn.json .EE .SH DEBUG OUTPUT .SS Debug output You can add \f[CR]\-\-debug[=N]\f[R] to the command line to log debug output. N ranges from 1 (least output, the default) to 9 (maximum output). Typically you would start with 1 and increase until you are seeing enough. Debug output goes to stderr, interleaved with the requests logged on stdout. To capture debug output in a log file instead, you can usually redirect stderr, eg: .PD 0 .P .PD \f[CR]hledger\-web \-\-debug=3 2>hledger\-web.log\f[R]. .SH ENVIRONMENT \f[B]LEDGER_FILE\f[R] The main journal file to use when not specified with \f[CR]\-f/\-\-file\f[R]. Default: \f[CR]$HOME/.hledger.journal\f[R]. .SH BUGS We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). .PP Some known issues: .PP Does not work well on small screens, or in text\-mode browsers. .SH AUTHORS Simon Michael and contributors. .br See http://hledger.org/CREDITS.html .SH COPYRIGHT Copyright 2007-2023 Simon Michael and contributors. .SH LICENSE Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), ledger(1) hledger-1.32.3/embeddedfiles/hledger-web.txt0000644000000000000000000005342514555433336017126 0ustar0000000000000000 HLEDGER-WEB(1) hledger User Manuals HLEDGER-WEB(1) NAME hledger-web - robust, friendly plain text accounting (Web version) SYNOPSIS hledger-web [--serve|--serve-api] [OPTS] [ARGS] hledger web -- [--serve|--serve-api] [OPTS] [ARGS] DESCRIPTION This manual is for hledger's web interface, version 1.32.3. See also the hledger manual for common concepts and file formats. hledger is a robust, user-friendly, cross-platform set of programs for tracking money, time, or any other commodity, using double-entry ac- counting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). hledger-web is a simple web application for browsing and adding trans- actions. It provides a more user-friendly UI than the hledger CLI or hledger-ui TUI, showing more at once (accounts, the current account register, balance charts) and allowing history-aware data entry, inter- active searching, and bookmarking. hledger-web also lets you share a journal with multiple users, or even the public web. There is no access control, so if you need that you should put it behind a suitable web proxy. As a small protection against data loss when running an unprotected instance, it writes a numbered backup of the main journal file (only) on every edit. Like hledger, it reads from (and appends to) a journal file specified by the LEDGER_FILE environment variable (defaulting to $HOME/.hledger.journal); or you can specify files with -f options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. (See hledger(1) -> Input for details.) hledger-web can be run in three modes: o Transient mode (the default): your default web browser will be opened to show the app if possible, and the app exits automatically after two minutes of inactivity (no requests received and no open browser windows viewing it). o With --serve: the app runs without stopping, and without opening a browser. o With --serve-api: only the JSON API is served. In all cases hledger-web runs as a foreground process, logging requests to stdout. OPTIONS hledger-web provides the following options: --serve serve and log requests, don't browse or auto-exit after timeout --serve-api like --serve, but serve only the JSON web API, not the web UI --allow=view|add|edit set the user's access level for changing data (default: add). It also accepts sandstorm for use on that platform (reads per- missions from the X-Sandstorm-Permissions request header). --cors=ORIGIN allow cross-origin requests from the specified origin; setting ORIGIN to "*" allows requests from any origin --host=IPADDR listen on this IP address (default: 127.0.0.1) By default the server listens on IP address 127.0.0.1, which is acces- sible only to requests from the local machine.. You can use --host to listen on a different address configured on the machine, eg to allow access from other machines. The special address 0.0.0.0 causes it to listen on all addresses configured on the machine. --port=PORT listen on this TCP port (default: 5000) Similarly, you can use --port to listen on a TCP port other than 5000. This is useful if you want to run multiple hledger-web instances on a machine. --socket=SOCKETFILE listen on the given unix socket instead of an IP address and port (unix only; implies --serve) When --socket is used, hledger-web creates and communicates via a socket file instead of a TCP port. This can be more secure, respects unix file permissions, and makes certain use cases easier, such as run- ning per-user instances behind an nginx reverse proxy. (Eg: proxy_pass http://unix:/tmp/hledger/${remote_user}.socket;.) --base-url=URL set the base url (default: http://IPADDR:PORT). You can use --base-url to change the protocol, hostname, port and path that appear in hledger-web's hyperlinks. This is useful eg when inte- grating hledger-web within a larger website. The default is http://HOST:PORT/ using the server's configured host address and TCP port (or http://HOST if PORT is 80). Note this affects url generation but not route parsing. --test run hledger-web's tests and exit. hspec test runner args may follow a --, eg: hledger-web --test -- --help hledger-web also supports many of hledger's general options. Query op- tions and arguments may be used to set an initial filter, which al- though not shown in the UI, will restrict the data shown, in addition to any search query entered in the UI. General help options -h --help show general or COMMAND help --man show general or COMMAND user manual with man --info show general or COMMAND user manual with info --version show general or ADDONCMD version --debug[=N] show debug output (levels 1-9, default: 1) General input options -f FILE --file=FILE use a different input file. For stdin, use - (default: $LEDGER_FILE or $HOME/.hledger.journal) --rules-file=RULESFILE Conversion rules file to use when reading CSV (default: FILE.rules) --separator=CHAR Field separator to expect when reading CSV (default: ',') --alias=OLD=NEW rename accounts named OLD to NEW --pivot FIELDNAME use some other field or tag for the account name -I --ignore-assertions disable balance assertion checks (note: does not disable balance assignments) -s --strict do extra error checking (check that all posted accounts are de- clared) General reporting options -b --begin=DATE include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) -e --end=DATE include postings/txns before this date (will be adjusted to fol- lowing subperiod end when using a report interval) -D --daily multiperiod/multicolumn report by day -W --weekly multiperiod/multicolumn report by week -M --monthly multiperiod/multicolumn report by month -Q --quarterly multiperiod/multicolumn report by quarter -Y --yearly multiperiod/multicolumn report by year -p --period=PERIODEXP set start date, end date, and/or reporting interval all at once using period expressions syntax --date2 match the secondary date instead (see command help for other ef- fects) --today=DATE override today's date (affects relative smart dates, for tests/examples) -U --unmarked include only unmarked postings/txns (can combine with -P or -C) -P --pending include only pending postings/txns -C --cleared include only cleared postings/txns -R --real include only non-virtual postings -NUM --depth=NUM hide/aggregate accounts or postings more than NUM levels deep -E --empty show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) -B --cost convert amounts to their cost/selling amount at transaction time -V --market convert amounts to their market value in default valuation com- modities -X --exchange=COMM convert amounts to their market value in commodity COMM --value convert amounts to cost or market value, more flexibly than -B/-V/-X --infer-equity infer conversion equity postings from costs --infer-costs infer costs from conversion equity postings --infer-market-prices use costs as additional market prices, as if they were P direc- tives --forecast generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger-ui make fu- ture-dated transactions visible. --auto generate extra postings by applying auto posting rules to all txns (not just forecast txns) --verbose-tags add visible tags indicating transactions or postings which have been generated/modified --commodity-style Override the commodity style in the output for the specified commodity. For example 'EUR1.000,00'. --color=WHEN (or --colour=WHEN) Should color-supporting commands use ANSI color codes in text output. 'auto' (default): whenever stdout seems to be a color-supporting terminal. 'always' or 'yes': always, useful eg when piping output into 'less -R'. 'never' or 'no': never. A NO_COLOR environment variable overrides this. --pretty[=WHEN] Show prettier output, e.g. using unicode box-drawing charac- ters. Accepts 'yes' (the default) or 'no' ('y', 'n', 'always', 'never' also work). If you provide an argument you must use '=', e.g. '--pretty=yes'. When a reporting option appears more than once in the command line, the last one takes precedence. Some reporting options can also be written as query arguments. PERMISSIONS By default, hledger-web allows anyone who can reach it to view the journal and to add new transactions, but not to change existing data. You can restrict who can reach it by o setting the IP address it listens on (see --host above). By default it listens on 127.0.0.1, accessible to all users on the local ma- chine. o putting it behind an authenticating proxy, using eg apache or nginx o custom firewall rules You can restrict what the users who reach it can do, by o using the --capabilities=CAP[,CAP..] flag when you start it, enabling one or more of the following capabilities. The default value is view,add: o view - allows viewing the journal file and all included files o add - allows adding new transactions to the main journal file o manage - allows editing, uploading or downloading the main or in- cluded files o using the --capabilities-header=HTTPHEADER flag to specify a HTTP header from which it will read capabilities to enable. hledger-web on Sandstorm uses the X-Sandstorm-Permissions header to integrate with Sandstorm's permissions. This is disabled by default. EDITING, UPLOADING, DOWNLOADING If you enable the manage capability mentioned above, you'll see a new "spanner" button to the right of the search form. Clicking this will let you edit, upload, or download the journal file or any files it in- cludes. Note, unlike any other hledger command, in this mode you (or any visi- tor) can alter or wipe the data files. Normally whenever a file is changed in this way, hledger-web saves a numbered backup (assuming file permissions allow it, the disk is not full, etc.) hledger-web is not aware of version control systems, cur- rently; if you use one, you'll have to arrange to commit the changes yourself (eg with a cron job or a file watcher like entr). Changes which would leave the journal file(s) unparseable or non-valid (eg with failing balance assertions) are prevented. (Probably. This needs re-testing.) RELOADING hledger-web detects changes made to the files by other means (eg if you edit it directly, outside of hledger-web), and it will show the new data when you reload the page or navigate to a new page. If a change makes a file unparseable, hledger-web will display an error message un- til the file has been fixed. (Note: if you are viewing files mounted from another machine, make sure that both machine clocks are roughly in step.) JSON API In addition to the web UI, hledger-web also serves a JSON API that can be used to get data or add new transactions. If you want the JSON API only, you can use the --serve-api flag. Eg: $ hledger-web -f examples/sample.journal --serve-api ... You can get JSON data from these routes: /version /accountnames /transactions /prices /commodities /accounts /accounttransactions/ACCOUNTNAME Eg, all account names in the journal (similar to the accounts command). (hledger-web's JSON does not include newlines, here we use python to prettify it): $ curl -s http://127.0.0.1:5000/accountnames | python -m json.tool [ "assets", "assets:bank", "assets:bank:checking", "assets:bank:saving", "assets:cash", "expenses", "expenses:food", "expenses:supplies", "income", "income:gifts", "income:salary", "liabilities", "liabilities:debts" ] Or all transactions: $ curl -s http://127.0.0.1:5000/transactions | python -m json.tool [ { "tcode": "", "tcomment": "", "tdate": "2008-01-01", "tdate2": null, "tdescription": "income", "tindex": 1, "tpostings": [ { "paccount": "assets:bank:checking", "pamount": [ { "acommodity": "$", "aismultiplier": false, "aprice": null, ... Most of the JSON corresponds to hledger's data types; for details of what the fields mean, see the Hledger.Data.Json haddock docs and click on the various data types, eg Transaction. And for a higher level un- derstanding, see the journal docs. In some cases there is outer JSON corresponding to a "Report" type. To understand that, go to the Hledger.Web.Handler.MiscR haddock and look at the source for the appropriate handler to see what it returns. Eg for /accounttransactions it's getAccounttransactionsR, returning a "ac- countTransactionsReport ...". Looking up the haddock for that we can see that /accounttransactions returns an AccountTransactionsReport, which consists of a report title and a list of AccountTransactionsRe- portItem (etc). You can add a new transaction to the journal with a PUT request to /add, if hledger-web was started with the add capability (enabled by default). The payload must be the full, exact JSON representation of a hledger transaction (partial data won't do). You can get sample JSON from hledger-web's /transactions or /accounttransactions, or you can export it with hledger-lib, eg like so: .../hledger$ stack ghci hledger-lib >>> writeJsonFile "txn.json" (head $ jtxns samplejournal) >>> :q Here's how it looks as of hledger-1.17 (remember, this JSON corresponds to hledger's Transaction and related data types): { "tcomment": "", "tpostings": [ { "pbalanceassertion": null, "pstatus": "Unmarked", "pamount": [ { "aprice": null, "acommodity": "$", "aquantity": { "floatingPoint": 1, "decimalPlaces": 10, "decimalMantissa": 10000000000 }, "aismultiplier": false, "astyle": { "ascommodityside": "L", "asdigitgroups": null, "ascommodityspaced": false, "asprecision": 2, "asdecimalpoint": "." } } ], "ptransaction_": "1", "paccount": "assets:bank:checking", "pdate": null, "ptype": "RegularPosting", "pcomment": "", "pdate2": null, "ptags": [], "poriginal": null }, { "pbalanceassertion": null, "pstatus": "Unmarked", "pamount": [ { "aprice": null, "acommodity": "$", "aquantity": { "floatingPoint": -1, "decimalPlaces": 10, "decimalMantissa": -10000000000 }, "aismultiplier": false, "astyle": { "ascommodityside": "L", "asdigitgroups": null, "ascommodityspaced": false, "asprecision": 2, "asdecimalpoint": "." } } ], "ptransaction_": "1", "paccount": "income:salary", "pdate": null, "ptype": "RegularPosting", "pcomment": "", "pdate2": null, "ptags": [], "poriginal": null } ], "ttags": [], "tsourcepos": { "tag": "JournalSourcePos", "contents": [ "", [ 1, 1 ] ] }, "tdate": "2008-01-01", "tcode": "", "tindex": 1, "tprecedingcomment": "", "tdate2": null, "tdescription": "income", "tstatus": "Unmarked" } And here's how to test adding it with curl. This should add a new en- try to your journal: $ curl http://127.0.0.1:5000/add -X PUT -H 'Content-Type: application/json' --data-binary @txn.json DEBUG OUTPUT Debug output You can add --debug[=N] to the command line to log debug output. N ranges from 1 (least output, the default) to 9 (maximum output). Typi- cally you would start with 1 and increase until you are seeing enough. Debug output goes to stderr, interleaved with the requests logged on stdout. To capture debug output in a log file instead, you can usually redirect stderr, eg: hledger-web --debug=3 2>hledger-web.log. ENVIRONMENT LEDGER_FILE The main journal file to use when not specified with -f/--file. Default: $HOME/.hledger.journal. BUGS We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). Some known issues: Does not work well on small screens, or in text-mode browsers. AUTHORS Simon Michael and contributors. See http://hledger.org/CREDITS.html COPYRIGHT Copyright 2007-2023 Simon Michael and contributors. LICENSE Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), ledger(1) hledger-web-1.32.3 January 2024 HLEDGER-WEB(1) hledger-1.32.3/embeddedfiles/hledger-web.info0000644000000000000000000005016214555433336017235 0ustar0000000000000000This is hledger-web.info, produced by makeinfo version 7.1 from stdin. INFO-DIR-SECTION User Applications START-INFO-DIR-ENTRY * hledger-web: (hledger-web). Web UI/API for the hledger accounting tool. END-INFO-DIR-ENTRY  File: hledger-web.info, Node: Top, Next: OPTIONS, Up: (dir) hledger-web(1) ************** hledger-web - robust, friendly plain text accounting (Web version) 'hledger-web [--serve|--serve-api] [OPTS] [ARGS]' 'hledger web -- [--serve|--serve-api] [OPTS] [ARGS]' This manual is for hledger's web interface, version 1.32.3. See also the hledger manual for common concepts and file formats. hledger is a robust, user-friendly, cross-platform set of programs for tracking money, time, or any other commodity, using double-entry accounting and a simple, editable file format. hledger is inspired by and largely compatible with ledger(1), and largely interconvertible with beancount(1). hledger-web is a simple web application for browsing and adding transactions. It provides a more user-friendly UI than the hledger CLI or hledger-ui TUI, showing more at once (accounts, the current account register, balance charts) and allowing history-aware data entry, interactive searching, and bookmarking. hledger-web also lets you share a journal with multiple users, or even the public web. There is no access control, so if you need that you should put it behind a suitable web proxy. As a small protection against data loss when running an unprotected instance, it writes a numbered backup of the main journal file (only) on every edit. Like hledger, it reads from (and appends to) a journal file specified by the 'LEDGER_FILE' environment variable (defaulting to '$HOME/.hledger.journal'); or you can specify files with '-f' options. It can also read timeclock files, timedot files, or any CSV/SSV/TSV file with a date field. (See hledger(1) -> Input for details.) hledger-web can be run in three modes: * Transient mode (the default): your default web browser will be opened to show the app if possible, and the app exits automatically after two minutes of inactivity (no requests received and no open browser windows viewing it). * With '--serve': the app runs without stopping, and without opening a browser. * With '--serve-api': only the JSON API is served. In all cases hledger-web runs as a foreground process, logging requests to stdout. * Menu: * OPTIONS:: * PERMISSIONS:: * EDITING UPLOADING DOWNLOADING:: * RELOADING:: * JSON API:: * DEBUG OUTPUT:: * ENVIRONMENT:: * BUGS::  File: hledger-web.info, Node: OPTIONS, Next: PERMISSIONS, Prev: Top, Up: Top 1 OPTIONS ********* hledger-web provides the following options: '--serve' serve and log requests, don't browse or auto-exit after timeout '--serve-api' like -serve, but serve only the JSON web API, not the web UI '--allow=view|add|edit' set the user's access level for changing data (default: 'add'). It also accepts 'sandstorm' for use on that platform (reads permissions from the 'X-Sandstorm-Permissions' request header). '--cors=ORIGIN' allow cross-origin requests from the specified origin; setting ORIGIN to "*" allows requests from any origin '--host=IPADDR' listen on this IP address (default: 127.0.0.1) By default the server listens on IP address '127.0.0.1', which is accessible only to requests from the local machine.. You can use '--host' to listen on a different address configured on the machine, eg to allow access from other machines. The special address '0.0.0.0' causes it to listen on all addresses configured on the machine. '--port=PORT' listen on this TCP port (default: 5000) Similarly, you can use '--port' to listen on a TCP port other than 5000. This is useful if you want to run multiple hledger-web instances on a machine. '--socket=SOCKETFILE' listen on the given unix socket instead of an IP address and port (unix only; implies -serve) When '--socket' is used, hledger-web creates and communicates via a socket file instead of a TCP port. This can be more secure, respects unix file permissions, and makes certain use cases easier, such as running per-user instances behind an nginx reverse proxy. (Eg: 'proxy_pass http://unix:/tmp/hledger/${remote_user}.socket;'.) '--base-url=URL' set the base url (default: http://IPADDR:PORT). You can use '--base-url' to change the protocol, hostname, port and path that appear in hledger-web's hyperlinks. This is useful eg when integrating hledger-web within a larger website. The default is 'http://HOST:PORT/' using the server's configured host address and TCP port (or 'http://HOST' if PORT is 80). Note this affects url generation but not route parsing. '--test' run hledger-web's tests and exit. hspec test runner args may follow a -, eg: hledger-web -test - -help hledger-web also supports many of hledger's general options. Query options and arguments may be used to set an initial filter, which although not shown in the UI, will restrict the data shown, in addition to any search query entered in the UI. * Menu: * General help options:: * General input options:: * General reporting options::  File: hledger-web.info, Node: General help options, Next: General input options, Up: OPTIONS 1.1 General help options ======================== '-h --help' show general or COMMAND help '--man' show general or COMMAND user manual with man '--info' show general or COMMAND user manual with info '--version' show general or ADDONCMD version '--debug[=N]' show debug output (levels 1-9, default: 1)  File: hledger-web.info, Node: General input options, Next: General reporting options, Prev: General help options, Up: OPTIONS 1.2 General input options ========================= '-f FILE --file=FILE' use a different input file. For stdin, use - (default: '$LEDGER_FILE' or '$HOME/.hledger.journal') '--rules-file=RULESFILE' Conversion rules file to use when reading CSV (default: FILE.rules) '--separator=CHAR' Field separator to expect when reading CSV (default: ',') '--alias=OLD=NEW' rename accounts named OLD to NEW '--pivot FIELDNAME' use some other field or tag for the account name '-I --ignore-assertions' disable balance assertion checks (note: does not disable balance assignments) '-s --strict' do extra error checking (check that all posted accounts are declared)  File: hledger-web.info, Node: General reporting options, Prev: General input options, Up: OPTIONS 1.3 General reporting options ============================= '-b --begin=DATE' include postings/txns on or after this date (will be adjusted to preceding subperiod start when using a report interval) '-e --end=DATE' include postings/txns before this date (will be adjusted to following subperiod end when using a report interval) '-D --daily' multiperiod/multicolumn report by day '-W --weekly' multiperiod/multicolumn report by week '-M --monthly' multiperiod/multicolumn report by month '-Q --quarterly' multiperiod/multicolumn report by quarter '-Y --yearly' multiperiod/multicolumn report by year '-p --period=PERIODEXP' set start date, end date, and/or reporting interval all at once using period expressions syntax '--date2' match the secondary date instead (see command help for other effects) '--today=DATE' override today's date (affects relative smart dates, for tests/examples) '-U --unmarked' include only unmarked postings/txns (can combine with -P or -C) '-P --pending' include only pending postings/txns '-C --cleared' include only cleared postings/txns '-R --real' include only non-virtual postings '-NUM --depth=NUM' hide/aggregate accounts or postings more than NUM levels deep '-E --empty' show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) '-B --cost' convert amounts to their cost/selling amount at transaction time '-V --market' convert amounts to their market value in default valuation commodities '-X --exchange=COMM' convert amounts to their market value in commodity COMM '--value' convert amounts to cost or market value, more flexibly than -B/-V/-X '--infer-equity' infer conversion equity postings from costs '--infer-costs' infer costs from conversion equity postings '--infer-market-prices' use costs as additional market prices, as if they were P directives '--forecast' generate transactions from periodic rules, between the latest recorded txn and 6 months from today, or during the specified PERIOD (= is required). Auto posting rules will be applied to these transactions as well. Also, in hledger-ui make future-dated transactions visible. '--auto' generate extra postings by applying auto posting rules to all txns (not just forecast txns) '--verbose-tags' add visible tags indicating transactions or postings which have been generated/modified '--commodity-style' Override the commodity style in the output for the specified commodity. For example 'EUR1.000,00'. '--color=WHEN (or --colour=WHEN)' Should color-supporting commands use ANSI color codes in text output. 'auto' (default): whenever stdout seems to be a color-supporting terminal. 'always' or 'yes': always, useful eg when piping output into 'less -R'. 'never' or 'no': never. A NO_COLOR environment variable overrides this. '--pretty[=WHEN]' Show prettier output, e.g. using unicode box-drawing characters. Accepts 'yes' (the default) or 'no' ('y', 'n', 'always', 'never' also work). If you provide an argument you must use '=', e.g. '-pretty=yes'. When a reporting option appears more than once in the command line, the last one takes precedence. Some reporting options can also be written as query arguments.  File: hledger-web.info, Node: PERMISSIONS, Next: EDITING UPLOADING DOWNLOADING, Prev: OPTIONS, Up: Top 2 PERMISSIONS ************* By default, hledger-web allows anyone who can reach it to view the journal and to add new transactions, but not to change existing data. You can restrict who can reach it by * setting the IP address it listens on (see '--host' above). By default it listens on 127.0.0.1, accessible to all users on the local machine. * putting it behind an authenticating proxy, using eg apache or nginx * custom firewall rules You can restrict what the users who reach it can do, by * using the '--capabilities=CAP[,CAP..]' flag when you start it, enabling one or more of the following capabilities. The default value is 'view,add': * 'view' - allows viewing the journal file and all included files * 'add' - allows adding new transactions to the main journal file * 'manage' - allows editing, uploading or downloading the main or included files * using the '--capabilities-header=HTTPHEADER' flag to specify a HTTP header from which it will read capabilities to enable. hledger-web on Sandstorm uses the X-Sandstorm-Permissions header to integrate with Sandstorm's permissions. This is disabled by default.  File: hledger-web.info, Node: EDITING UPLOADING DOWNLOADING, Next: RELOADING, Prev: PERMISSIONS, Up: Top 3 EDITING, UPLOADING, DOWNLOADING ********************************* If you enable the 'manage' capability mentioned above, you'll see a new "spanner" button to the right of the search form. Clicking this will let you edit, upload, or download the journal file or any files it includes. Note, unlike any other hledger command, in this mode you (or any visitor) can alter or wipe the data files. Normally whenever a file is changed in this way, hledger-web saves a numbered backup (assuming file permissions allow it, the disk is not full, etc.) hledger-web is not aware of version control systems, currently; if you use one, you'll have to arrange to commit the changes yourself (eg with a cron job or a file watcher like entr). Changes which would leave the journal file(s) unparseable or non-valid (eg with failing balance assertions) are prevented. (Probably. This needs re-testing.)  File: hledger-web.info, Node: RELOADING, Next: JSON API, Prev: EDITING UPLOADING DOWNLOADING, Up: Top 4 RELOADING *********** hledger-web detects changes made to the files by other means (eg if you edit it directly, outside of hledger-web), and it will show the new data when you reload the page or navigate to a new page. If a change makes a file unparseable, hledger-web will display an error message until the file has been fixed. (Note: if you are viewing files mounted from another machine, make sure that both machine clocks are roughly in step.)  File: hledger-web.info, Node: JSON API, Next: DEBUG OUTPUT, Prev: RELOADING, Up: Top 5 JSON API ********** In addition to the web UI, hledger-web also serves a JSON API that can be used to get data or add new transactions. If you want the JSON API only, you can use the '--serve-api' flag. Eg: $ hledger-web -f examples/sample.journal --serve-api ... You can get JSON data from these routes: /version /accountnames /transactions /prices /commodities /accounts /accounttransactions/ACCOUNTNAME Eg, all account names in the journal (similar to the accounts command). (hledger-web's JSON does not include newlines, here we use python to prettify it): $ curl -s http://127.0.0.1:5000/accountnames | python -m json.tool [ "assets", "assets:bank", "assets:bank:checking", "assets:bank:saving", "assets:cash", "expenses", "expenses:food", "expenses:supplies", "income", "income:gifts", "income:salary", "liabilities", "liabilities:debts" ] Or all transactions: $ curl -s http://127.0.0.1:5000/transactions | python -m json.tool [ { "tcode": "", "tcomment": "", "tdate": "2008-01-01", "tdate2": null, "tdescription": "income", "tindex": 1, "tpostings": [ { "paccount": "assets:bank:checking", "pamount": [ { "acommodity": "$", "aismultiplier": false, "aprice": null, ... Most of the JSON corresponds to hledger's data types; for details of what the fields mean, see the Hledger.Data.Json haddock docs and click on the various data types, eg Transaction. And for a higher level understanding, see the journal docs. In some cases there is outer JSON corresponding to a "Report" type. To understand that, go to the Hledger.Web.Handler.MiscR haddock and look at the source for the appropriate handler to see what it returns. Eg for '/accounttransactions' it's getAccounttransactionsR, returning a "'accountTransactionsReport ...'". Looking up the haddock for that we can see that /accounttransactions returns an AccountTransactionsReport, which consists of a report title and a list of AccountTransactionsReportItem (etc). You can add a new transaction to the journal with a PUT request to '/add', if hledger-web was started with the 'add' capability (enabled by default). The payload must be the full, exact JSON representation of a hledger transaction (partial data won't do). You can get sample JSON from hledger-web's '/transactions' or '/accounttransactions', or you can export it with hledger-lib, eg like so: .../hledger$ stack ghci hledger-lib >>> writeJsonFile "txn.json" (head $ jtxns samplejournal) >>> :q Here's how it looks as of hledger-1.17 (remember, this JSON corresponds to hledger's Transaction and related data types): { "tcomment": "", "tpostings": [ { "pbalanceassertion": null, "pstatus": "Unmarked", "pamount": [ { "aprice": null, "acommodity": "$", "aquantity": { "floatingPoint": 1, "decimalPlaces": 10, "decimalMantissa": 10000000000 }, "aismultiplier": false, "astyle": { "ascommodityside": "L", "asdigitgroups": null, "ascommodityspaced": false, "asprecision": 2, "asdecimalpoint": "." } } ], "ptransaction_": "1", "paccount": "assets:bank:checking", "pdate": null, "ptype": "RegularPosting", "pcomment": "", "pdate2": null, "ptags": [], "poriginal": null }, { "pbalanceassertion": null, "pstatus": "Unmarked", "pamount": [ { "aprice": null, "acommodity": "$", "aquantity": { "floatingPoint": -1, "decimalPlaces": 10, "decimalMantissa": -10000000000 }, "aismultiplier": false, "astyle": { "ascommodityside": "L", "asdigitgroups": null, "ascommodityspaced": false, "asprecision": 2, "asdecimalpoint": "." } } ], "ptransaction_": "1", "paccount": "income:salary", "pdate": null, "ptype": "RegularPosting", "pcomment": "", "pdate2": null, "ptags": [], "poriginal": null } ], "ttags": [], "tsourcepos": { "tag": "JournalSourcePos", "contents": [ "", [ 1, 1 ] ] }, "tdate": "2008-01-01", "tcode": "", "tindex": 1, "tprecedingcomment": "", "tdate2": null, "tdescription": "income", "tstatus": "Unmarked" } And here's how to test adding it with curl. This should add a new entry to your journal: $ curl http://127.0.0.1:5000/add -X PUT -H 'Content-Type: application/json' --data-binary @txn.json  File: hledger-web.info, Node: DEBUG OUTPUT, Next: ENVIRONMENT, Prev: JSON API, Up: Top 6 DEBUG OUTPUT ************** * Menu: * Debug output::  File: hledger-web.info, Node: Debug output, Up: DEBUG OUTPUT 6.1 Debug output ================ You can add '--debug[=N]' to the command line to log debug output. N ranges from 1 (least output, the default) to 9 (maximum output). Typically you would start with 1 and increase until you are seeing enough. Debug output goes to stderr, interleaved with the requests logged on stdout. To capture debug output in a log file instead, you can usually redirect stderr, eg: 'hledger-web --debug=3 2>hledger-web.log'.  File: hledger-web.info, Node: ENVIRONMENT, Next: BUGS, Prev: DEBUG OUTPUT, Up: Top 7 ENVIRONMENT ************* *LEDGER_FILE* The main journal file to use when not specified with '-f/--file'. Default: '$HOME/.hledger.journal'.  File: hledger-web.info, Node: BUGS, Prev: ENVIRONMENT, Up: Top 8 BUGS ****** We welcome bug reports in the hledger issue tracker (shortcut: http://bugs.hledger.org), or on the #hledger chat or hledger mail list (https://hledger.org/support). Some known issues: Does not work well on small screens, or in text-mode browsers.  Tag Table: Node: Top223 Node: OPTIONS2577 Ref: #options2682 Node: General help options5256 Ref: #general-help-options5406 Node: General input options5688 Ref: #general-input-options5874 Node: General reporting options6531 Ref: #general-reporting-options6696 Node: PERMISSIONS10086 Ref: #permissions10225 Node: EDITING UPLOADING DOWNLOADING11437 Ref: #editing-uploading-downloading11618 Node: RELOADING12452 Ref: #reloading12586 Node: JSON API13019 Ref: #json-api13134 Node: DEBUG OUTPUT18622 Ref: #debug-output18747 Node: Debug output18774 Ref: #debug-output-118875 Node: ENVIRONMENT19292 Ref: #environment19411 Node: BUGS19528 Ref: #bugs19612  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.32.3/shell-completion/hledger-completion.bash0000644000000000000000000010162514513751565021317 0ustar0000000000000000# -*- mode: sh; sh-basic-offset: 4; indent-tabs-mode: nil -*- # ex: ft=sh ts=4 sw=4 et # shellcheck disable=2034,2154 # Completion script for hledger. # Created using a Makefile and real hledger. # This script is sourced by an interactive shell, so do NOT do things like # 'set -o pipefail' or mangle the global environment in any other way! # That said, we *do* remove colon (:) from COMP_WORDBREAKS which impacts # the rest of the session and completion for other programs. # INSTALLATION: # To install you can simply source this file from your shell's startup files. # # Alternatively, copy/symlink it into `${BASH_COMPLETION_USER_DIR}/completions` # or `${XDG_DATA_HOME:-$HOME/.local/share}/bash-completion/completions`, rename # it to either `hledger`, `_hledger` or `hledger.bash`, and it will be loaded # dynamically the first time you use the `hledger` command. Optionally, create # symlinks to this file for any extensions used e.g.: # # mkdir -p "${BASH_COMPLETION_USER_DIR:-${XDG_DATA_HOME:-$HOME/.local/share}/bash-completion}/completions" && # cd "${BASH_COMPLETION_USER_DIR:-${XDG_DATA_HOME:-$HOME/.local/share}/bash-completion}/completions" && # cp /path/to/hledger-completion.bash hledger && # ln -s hledger hledger-ui && # ln -s hledger hledger-web && # : done. _hledger_completion() { local cur prev words cword _init_completion -n : || return 0 # Current treatment for special characters: # - exclude colon (:) from COMP_WORDBREAKS # - option processing assumes that `=` is in COMP_WORDBREAKS # - use compopt -o filenames selectively to escape the rest COMP_WORDBREAKS=${COMP_WORDBREAKS//:} case $COMP_WORDBREAKS in *=*) : ;; *) COMP_WORDBREAKS=$COMP_WORDBREAKS= ;; esac local subcommand local subcommandOptions local i for ((i=1; i<${#words[@]}; i++)); do subcommand=${words[i]} if ! grep -Fxqe "$subcommand" <<< "$_hledger_complist_commands"; then subcommand= continue fi # There could be other commands begining with $subcommand, e.g.: # $subcommand == reg --> register, register-match, # $subcommand == bal --> balance, balancesheet, balancesheetequity, etc. # Do not ignore them! if ((i == cword)); then _hledger_compreply "$( _hledger_compgen "$_hledger_complist_commands" )" return 0 fi # Replace dashes with underscores and use indirect expansion subcommandOptions=_hledger_complist_options_${subcommand//-/_} if [[ $cur == -* ]]; then _hledger_compreply "$(_hledger_compgen "${!subcommandOptions}")" # Suspend space on completion of long options requiring an argument [[ ${COMPREPLY[0]} == --*= ]] && compopt -o nospace return 0 fi break done # Option argument completion _hledger_compreply_optarg && return if [[ -z $subcommand ]]; then if [[ $cur == -* ]]; then _hledger_compreply "$( _hledger_compgen "$_hledger_complist_generic_options" )" # Suspend space on completion of long options requiring an argument [[ ${COMPREPLY[0]} == --*= ]] && compopt -o nospace else _hledger_compreply "$( _hledger_compgen "$_hledger_complist_commands" )" fi return 0 fi # Set this from here on because queries tend to have lots of special chars # TODO: better handling of special characters compopt -o filenames # Query completion _hledger_compreply_query && return # Subcommand specific case $subcommand in # These do not expect or support any query arguments commodities|check|files|help|import|print-unique|test) return 0 ;; esac # Offer query filters and accounts for the rest _hledger_compreply "$(_hledger_compgen "$_hledger_complist_query_filters")" if [[ -z $cur ]]; then _hledger_compreply_append "$( _hledger_compgen "$(_hledger accounts --flat --depth 1)" )" else _hledger_compreply_append "$( _hledger_compgen "$(_hledger accounts --flat)" )" fi # Suspend space on completion of query prefix # Do not sort, keep accounts and query filters grouped separately [[ ${COMPREPLY[0]} == *: ]] && compopt -o nospace compopt -o nosort return 0 } _hledger_extension_completion() { local cmd=${1##*/} local ext=${cmd#hledger-} # Pretend that hledger is called with the given extension # as the first argument and call main completion function COMP_WORDS=("hledger" "$ext" "${COMP_WORDS[@]:1}") COMP_CWORD=$((COMP_CWORD + 1)) _hledger_completion "hledger" "${@:1}" } # Register completion function for hledger: complete -F _hledger_completion hledger # Register completion functions for hledger extensions: complete -F _hledger_extension_completion hledger-ui hledger-web # Helpers # Comment out when done _hledger_debug() { ((HLEDGER_DEBUG)) || return 0 local var vars=(words) (($#)) && vars=("$@") for var in "${vars[@]}"; do printf '\ndebug: %s\n' "$(declare -p "$var")" >&2 done } # Stolen from bash-completion # This function quotes the argument in a way so that readline dequoting # results in the original argument. This is necessary for at least # `compgen' which requires its arguments quoted/escaped: _hledger_quote_by_ref() { printf -v "$2" %q "$1" # If result becomes quoted like this: $'string', re-evaluate in order to # drop the additional quoting. See also: http://www.mail-archive.com/ # bash-completion-devel@lists.alioth.debian.org/msg01942.html [[ ${!2} == \$* ]] && eval "$2=${!2}" } # Set the value of COMPREPLY from newline delimited completion candidates _hledger_compreply() { local IFS=$'\n' # shellcheck disable=2206 COMPREPLY=($1) } # Append the value of COMPREPLY from newline delimited completion candidates _hledger_compreply_append() { local IFS=$'\n' # shellcheck disable=2206 COMPREPLY+=($1) } # Generate input suitable for _hledger_compreply() from newline delimited # completion candidates. It doesn't seem there is a way to feed a literal # word list to compgen -- it will eat your quotes, drink your booze and... # Completion candidates are quoted accordingly first and then we leave it to # compgen to deal with readline. # # Arguments: # $1: a newline separated list with completion cadidates # $2: (optional) a prefix string to add to generated completions # $3: (optional) a word to match instead of $cur, the default. # If $match is null and $prefix is defined the match is done against $cur # stripped of $prefix. If both $prefix and $match are null we match against # $cur and no prefix is added to completions. _hledger_compgen() { local complist=$1 local prefix=$2 local match=$3 local quoted=() local word local i=0 while IFS= read -r word; do _hledger_quote_by_ref "$word" word quoted[i++]=$word done <<< "$complist" if (($# < 3)); then match=${cur:${#prefix}} fi local IFS=$'\n' compgen -P "$prefix" -W "${quoted[*]}" -- "$match" } # Try required option argument completion. Set COMPREPLY and return 0 on # success, 1 if option doesn't require an argument or out of context _hledger_compreply_optarg() { local option=${words[cword - 1]} local match=$cur local wordlist # Match the empty string on --file=, not the equal sign itself if [[ $cur == = ]]; then match="" # Once input is present, cword is incremented so we compensate elif [[ $prev == = ]]; then option=${words[cword - 2]} fi [[ $option == -* ]] || return case $option in --alias) compopt -o nospace -o filenames _hledger_compreply "$( _hledger_compgen "$(_hledger accounts --flat)" "" "$match" )" ;; -f|--file|--rules-file|-o|--output-file) compopt -o filenames _hledger_compreply "$(compgen -f -- "$match")" ;; --pivot) compopt -o nosort wordlist="code description note payee" _hledger_compreply "$(compgen -W "$wordlist" -- "$match")" _hledger_compreply_append "$( _hledger_compgen "$(_hledger tags)" "" "$match" )" ;; --value) wordlist="cost then end now" _hledger_compreply "$(compgen -W "$wordlist" -- "$match")" ;; -X|--exchange) _hledger_compreply "$( _hledger_compgen "$(_hledger commodities)" "" "$match" )" ;; --color|--colour) compopt -o nosort wordlist="auto always yes never no" _hledger_compreply "$(compgen -W "$wordlist" -- "$match")" ;; -O|--output-format) wordlist="txt csv json sql" _hledger_compreply "$(compgen -W "$wordlist" -- "$match")" ;; --close-acct|--open-acct) compopt -o filenames _hledger_compreply "$( _hledger_compgen "$(_hledger accounts --flat)" "" "$match" )" ;; --debug) wordlist="{1..9}" _hledger_compreply "$(compgen -W "$wordlist" -- "$match")" ;; # Argument required, but no handler (yet) -b|-e|-p) _hledger_compreply "" ;; # Check if an unhandled long option requires an argument *) local optionList argRequired if [[ -n $subcommandOptions ]]; then optionList=${!subcommandOptions} else optionList=$_hledger_complist_generic_options fi while IFS= read -r argRequired; do if [[ $argRequired == "$option=" ]]; then _hledger_compreply "" return 0 fi done <<< "$optionList" return 1 ;; esac return 0 } # Query filter completion through introspection _hledger_compreply_query() { [[ $cur =~ .: ]] || return local query=${cur%%:*}: local match=${cur#*:} grep -Fxqe "$query" <<< "$_hledger_complist_query_filters" || return local hledgerArgs=() case $query in acct:) if (( ${#match} )); then hledgerArgs=(accounts --flat) else hledgerArgs=(accounts --flat --depth 1) fi ;; code:) hledgerArgs=(codes) ;; cur:) hledgerArgs=(commodities) ;; desc:) hledgerArgs=(descriptions) ;; note:) hledgerArgs=(notes) ;; payee:) hledgerArgs=(payees) ;; tag:) hledgerArgs=(tags) ;; *) local wordlist case $query in amt:) wordlist="< <= > >=" ;; real:) wordlist="\ 0" ;; status:) wordlist="\ * !" ;; *) return 1 ;; esac _hledger_compreply "$( compgen -P "$query" -W "$wordlist" -- "$match" )" return 0 ;; esac _hledger_compreply "$( _hledger_compgen "$(_hledger "${hledgerArgs[@]}")" "$query" )" return 0 } # Parse the command line so far and fill the array $optarg with the arguments to # given options. $optarg should be declared by the caller _hledger_optarg() { local options=("$@") local i j offset optarg=() # hledger balance --file ~/ledger _ # 0 1 2 3 4 for ((i=1; i < ${#words[@]} - 2; i++)); do offset=0 for j in "${!options[@]}"; do if [[ ${words[i]} == "${options[j]}" ]]; then if [[ ${words[i+1]} == '=' ]]; then offset=2 else offset=1 fi # Pass it through compgen to unescape it optarg+=("$(compgen -W "${words[i + offset]}")") fi done ((i += offset)) done } # Get ledger file from -f --file arguments from COMP_WORDS and pass it to the # 'hledger' call. Note that --rules-file - if present - must also be passed! # Multiple files are allowed so pass them all in the order of appearance. _hledger() { local hledgerArgs=("$@") local file local -a optarg _hledger_optarg -f --file for file in "${optarg[@]}"; do [[ -f $file ]] && hledgerArgs+=(--file "$file") done _hledger_optarg --rules-file for file in "${optarg[@]}"; do [[ -f $file ]] && hledgerArgs+=(--rules-file "$file") done # Discard errors. Is there a way to validate files before using them? hledger "${hledgerArgs[@]}" 2>/dev/null } # Include lists of commands and options generated by the Makefile using the # m4 macro processor. # Included files must have exactly one newline at EOF to prevent weired errors. read -r -d "" _hledger_complist_commands <<"__TEXT__" accounts activity add areg aregister bal balance balancesheet balancesheetequity bs bse cashflow cf check close codes commodities descriptions diff files help import incomestatement is notes payees prices print print-unique reg register register-match rewrite roi stats tags test ui web __TEXT__ read -r -d "" _hledger_complist_query_filters <<"__TEXT__" acct: amt: code: cur: date: date2: depth: desc: inacct: not: note: payee: real: status: tag: __TEXT__ read -r -d "" _hledger_complist_generic_options <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ # Dashes are replaced by m4 with underscores to form valid identifiers # Referenced by indirect expansion of $subcommandOptions read -r -d "" _hledger_complist_options_accounts <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --declared --depth= --drop= --empty --end= --exchange= --file= --flat --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --tree --types --unmarked --used --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_activity <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_add <<"__TEXT__" --alias= --anon --debug= --file= --help --ignore-assertions --info --man --no-new-accounts --pivot= --rules-file= --strict --version __TEXT__ read -r -d "" _hledger_complist_options_areg <<"__TEXT__" --alias= --align-all --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --no-elide --output-file= --output-format= --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --txn-dates --unmarked --value= --version --weekly --width= --yearly __TEXT__ read -r -d "" _hledger_complist_options_aregister <<"__TEXT__" --alias= --align-all --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --no-elide --output-file= --output-format= --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --txn-dates --unmarked --value= --version --weekly --width= --yearly __TEXT__ read -r -d "" _hledger_complist_options_bal <<"__TEXT__" --alias= --anon --auto --average --begin= --budget --change --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --declared --depth= --drop= --empty --end= --exchange= --file= --flat --forecast --format= --gain --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --invert --layout= --man --market --monthly --no-elide --no-total --output-file= --output-format= --pending --percent --period= --pivot= --pretty --quarterly --real --related --row-total --rules-file= --sort-amount --strict --sum --today= --transpose --tree --unmarked --value= --valuechange --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_balance <<"__TEXT__" --alias= --anon --auto --average --begin= --budget --change --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --declared --depth= --drop= --empty --end= --exchange= --file= --flat --forecast --format= --gain --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --invert --layout= --man --market --monthly --no-elide --no-total --output-file= --output-format= --pending --percent --period= --pivot= --pretty --quarterly --real --related --row-total --rules-file= --sort-amount --strict --sum --today= --transpose --tree --unmarked --value= --valuechange --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_balancesheet <<"__TEXT__" --alias= --anon --auto --average --begin= --budget --change --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --declared --depth= --drop= --empty --end= --exchange= --file= --flat --forecast --format= --gain --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --layout= --man --market --monthly --no-elide --no-total --output-file= --output-format= --pending --percent --period= --pivot= --pretty --quarterly --real --row-total --rules-file= --sort-amount --strict --sum --today= --tree --unmarked --value= --valuechange --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_balancesheetequity <<"__TEXT__" --alias= --anon --auto --average --begin= --budget --change --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --declared --depth= --drop= --empty --end= --exchange= --file= --flat --forecast --format= --gain --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --layout= --man --market --monthly --no-elide --no-total --output-file= --output-format= --pending --percent --period= --pivot= --pretty --quarterly --real --row-total --rules-file= --sort-amount --strict --sum --today= --tree --unmarked --value= --valuechange --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_bs <<"__TEXT__" --alias= --anon --auto --average --begin= --budget --change --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --declared --depth= --drop= --empty --end= --exchange= --file= --flat --forecast --format= --gain --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --layout= --man --market --monthly --no-elide --no-total --output-file= --output-format= --pending --percent --period= --pivot= --pretty --quarterly --real --row-total --rules-file= --sort-amount --strict --sum --today= --tree --unmarked --value= --valuechange --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_bse <<"__TEXT__" --alias= --anon --auto --average --begin= --budget --change --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --declared --depth= --drop= --empty --end= --exchange= --file= --flat --forecast --format= --gain --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --layout= --man --market --monthly --no-elide --no-total --output-file= --output-format= --pending --percent --period= --pivot= --pretty --quarterly --real --row-total --rules-file= --sort-amount --strict --sum --today= --tree --unmarked --value= --valuechange --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_cashflow <<"__TEXT__" --alias= --anon --auto --average --begin= --budget --change --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --declared --depth= --drop= --empty --end= --exchange= --file= --flat --forecast --format= --gain --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --layout= --man --market --monthly --no-elide --no-total --output-file= --output-format= --pending --percent --period= --pivot= --pretty --quarterly --real --row-total --rules-file= --sort-amount --strict --sum --today= --tree --unmarked --value= --valuechange --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_cf <<"__TEXT__" --alias= --anon --auto --average --begin= --budget --change --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --declared --depth= --drop= --empty --end= --exchange= --file= --flat --forecast --format= --gain --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --layout= --man --market --monthly --no-elide --no-total --output-file= --output-format= --pending --percent --period= --pivot= --pretty --quarterly --real --row-total --rules-file= --sort-amount --strict --sum --today= --tree --unmarked --value= --valuechange --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_check <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_close <<"__TEXT__" --alias= --anon --auto --begin= --cleared --close --close-acct= --close-desc= --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --explicit --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --interleaved --man --market --monthly --open --open-acct= --open-desc= --pending --period= --pivot= --pretty --quarterly --real --rules-file= --show-costs --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_codes <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_commodities <<"__TEXT__" --alias= --anon --debug= --file= --help --ignore-assertions --info --man --pivot= --rules-file= --strict --version __TEXT__ read -r -d "" _hledger_complist_options_descriptions <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_diff <<"__TEXT__" --alias= --anon --debug= --file= --help --ignore-assertions --info --man --pivot= --rules-file= --strict --version __TEXT__ read -r -d "" _hledger_complist_options_files <<"__TEXT__" --alias= --anon --debug= --file= --help --ignore-assertions --info --man --pivot= --rules-file= --strict --version __TEXT__ read -r -d "" _hledger_complist_options_help <<"__TEXT__" --help __TEXT__ read -r -d "" _hledger_complist_options_import <<"__TEXT__" --alias= --anon --auto --begin= --catchup --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --dry-run --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_incomestatement <<"__TEXT__" --alias= --anon --auto --average --begin= --budget --change --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --declared --depth= --drop= --empty --end= --exchange= --file= --flat --forecast --format= --gain --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --layout= --man --market --monthly --no-elide --no-total --output-file= --output-format= --pending --percent --period= --pivot= --pretty --quarterly --real --row-total --rules-file= --sort-amount --strict --sum --today= --tree --unmarked --value= --valuechange --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_is <<"__TEXT__" --alias= --anon --auto --average --begin= --budget --change --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --declared --depth= --drop= --empty --end= --exchange= --file= --flat --forecast --format= --gain --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --layout= --man --market --monthly --no-elide --no-total --output-file= --output-format= --pending --percent --period= --pivot= --pretty --quarterly --real --row-total --rules-file= --sort-amount --strict --sum --today= --tree --unmarked --value= --valuechange --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_notes <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_payees <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --declared --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --used --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_prices <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --infer-reverse-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_print <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --explicit --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --match= --monthly --new --output-file= --output-format= --pending --period= --pivot= --pretty --quarterly --real --rules-file= --show-costs --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_print_unique <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_reg <<"__TEXT__" --alias= --align-all --anon --auto --average --begin= --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --invert --man --market --monthly --output-file= --output-format= --pending --period= --pivot= --pretty --quarterly --real --related --rules-file= --strict --today= --unmarked --value= --version --weekly --width= --yearly __TEXT__ read -r -d "" _hledger_complist_options_register <<"__TEXT__" --alias= --align-all --anon --auto --average --begin= --cleared --color= --commodity-style= --cost --cumulative --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --historical --ignore-assertions --infer-equity --infer-market-prices --info --invert --man --market --monthly --output-file= --output-format= --pending --period= --pivot= --pretty --quarterly --real --related --rules-file= --strict --today= --unmarked --value= --version --weekly --width= --yearly __TEXT__ read -r -d "" _hledger_complist_options_register_match <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_rewrite <<"__TEXT__" --add-posting= --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --diff --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_roi <<"__TEXT__" --alias= --anon --auto --begin= --cashflow --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --investment= --man --market --monthly --pending --period= --pivot= --pretty --profit-loss= --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_stats <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --output-file= --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_tags <<"__TEXT__" --alias= --anon --auto --begin= --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --parsed --pending --period= --pivot= --pretty --quarterly --real --rules-file= --strict --today= --unmarked --value= --values --version --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_test <<"__TEXT__" --debug= --help --info --man --version __TEXT__ read -r -d "" _hledger_complist_options_ui <<"__TEXT__" --alias= --anon --auto --begin= --change --cleared --color= --commodity-style= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file= --flat --forecast --help --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --pretty --quarterly --real --register= --rules-file= --strict --theme= --today= --tree --unmarked --value= --version --watch --weekly --yearly __TEXT__ read -r -d "" _hledger_complist_options_web <<"__TEXT__" --alias= --anon --auto --base-url= --begin= --capabilities-header= --capabilities= --cleared --color= --commodity-style= --cors= --cost --daily --date2 --debug= --depth= --empty --end= --exchange= --file-url= --file= --forecast --help --host= --ignore-assertions --infer-equity --infer-market-prices --info --man --market --monthly --pending --period= --pivot= --port= --pretty --quarterly --real --rules-file= --serve --serve-api --socket= --strict --test --today= --unmarked --value= --version --weekly --yearly __TEXT__ return 0 hledger-1.32.3/Hledger/Cli/Commands/Accounts.txt0000644000000000000000000000344714555141606017561 0ustar0000000000000000accounts Show account names. _FLAGS This command lists account names. By default it shows all known accounts, either used in transactions or declared with account directives. With query arguments, only matched account names and account names referenced by matched postings are shown. Or it can show just the used accounts (--used/-u), the declared accounts (--declared/-d), the accounts declared but not used (--unused), the accounts used but not declared (--undeclared), or the first account matched by an account name pattern, if any (--find). It shows a flat list by default. With --tree, it uses indentation to show the account hierarchy. In flat mode you can add --drop N to omit the first few account name components. Account names can be depth-clipped with depth:N or --depth N or -N. With --types, it also shows each account's type, if it's known. (See Declaring accounts > Account types.) With --positions, it also shows the file and line number of each account's declaration, if any, and the account's overall declaration order; these may be useful when troubleshooting account display order. With --directives, it adds the account keyword, showing valid account directives which can be pasted into a journal file. This is useful together with --undeclared when updating your account declarations to satisfy hledger check accounts. The --find flag can be used to look up a single account name, in the same way that the aregister command does. It returns the alphanumerically-first matched account name, or if none can be found, it fails with a non-zero exit code. Examples: $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts $ hledger accounts --undeclared --directives >> $LEDGER_FILE $ hledger check accounts hledger-1.32.3/Hledger/Cli/Commands/Activity.txt0000644000000000000000000000060014555141606017562 0ustar0000000000000000activity Show an ascii barchart of posting counts per interval. _FLAGS The activity command displays an ascii histogram showing transaction counts by day, week, month or other reporting interval (by day is the default). With query arguments, it counts only matched transactions. Examples: $ hledger activity --quarterly 2008-01-01 ** 2008-04-01 ******* 2008-07-01 2008-10-01 ** hledger-1.32.3/Hledger/Cli/Commands/Add.txt0000644000000000000000000000532314555431531016464 0ustar0000000000000000add Prompt for transactions and add them to the journal. Any arguments will be used as default inputs for the first N prompts. _FLAGS Many hledger users edit their journals directly with a text editor, or generate them from CSV. For more interactive data entry, there is the add command, which prompts interactively on the console for new transactions, and appends them to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also import). To use it, just run hledger add and follow the prompts. You can add as many transactions as you like; when you are finished, enter . or press control-d or control-c to exit. Features: - add tries to provide useful defaults, using the most similar (by description) recent transaction (filtered by the query, if any) as a template. - You can also set the initial defaults with command line arguments. - Readline-style edit keys can be used during data entry. - The tab key will auto-complete whenever possible - accounts, payees/descriptions, dates (yesterday, today, tomorrow). If the input area is empty, it will insert the default value. - If the journal defines a default commodity, it will be added to any bare numbers entered. - A parenthesised transaction code may be entered following a date. - Comments and tags may be entered following a description or amount. - If you make a mistake, enter < at any prompt to go one step backward. - Input prompts are displayed in a different colour when the terminal supports it. Example (see https://hledger.org/add.html for a detailed tutorial): $ hledger add Adding transactions to journal file /src/hledger/examples/sample.journal Any command line arguments will be used as defaults. Use tab key to complete, readline keys to edit, enter to accept defaults. An optional (CODE) may follow transaction dates. An optional ; COMMENT may follow descriptions or amounts. If you make a mistake, enter < at any prompt to go one step backward. To end a transaction, enter . when prompted. To quit, enter . at a date prompt or press control-d or control-c. Date [2015/05/22]: Description: supermarket Account 1: expenses:food Amount 1: $10 Account 2: assets:checking Amount 2 [$-10.0]: Account 3 (or . or enter to finish this transaction): . 2015/05/22 supermarket expenses:food $10 assets:checking $-10.0 Save this transaction to the journal ? [y]: Saved. Starting the next transaction (. or ctrl-D/ctrl-C to quit) Date [2015/05/22]: $ On Microsoft Windows, the add command makes sure that no part of the file path ends with a period, as that would cause problems (#1056). hledger-1.32.3/Hledger/Cli/Commands/Aregister.txt0000644000000000000000000000673714555431531017733 0ustar0000000000000000aregister (areg) Show the transactions and running historical balance of a single account, with each transaction displayed as one line. _FLAGS aregister shows the overall transactions affecting a particular account (and any subaccounts). Each report line represents one transaction in this account. Transactions before the report start date are always included in the running balance (--historical mode is always on). This is a more "real world", bank-like view than the register command (which shows individual postings, possibly from multiple accounts, not necessarily in historical mode). As a quick rule of thumb: - use aregister for reviewing and reconciling real-world asset/liability accounts - use register for reviewing detailed revenues/expenses. aregister requires one argument: the account to report on. You can write either the full account name, or a case-insensitive regular expression which will select the alphabetically first matched account. When there are multiple matches, the alphabetically-first choice can be surprising; eg if you have assets:per:checking 1 and assets:biz:checking 2 accounts, hledger areg checking would select assets:biz:checking 2. It's just a convenience to save typing, so if in doubt, write the full account name, or a distinctive substring that matches uniquely. Transactions involving subaccounts of this account will also be shown. aregister ignores depth limits, so its final total will always match a balance report with similar arguments. Any additional arguments form a query which will filter the transactions shown. Note some queries will disturb the running balance, causing it to be different from the account's real-world running balance. An example: this shows the transactions and historical running balance during july, in the first account whose name contains "checking": $ hledger areg checking date:jul Each aregister line item shows: - the transaction's date (or the relevant posting's date if different, see below) - the names of all the other account(s) involved in this transaction (probably abbreviated) - the total change to this account's balance from this transaction - the account's historical running balance after this transaction. Transactions making a net change of zero are not shown by default; add the -E/--empty flag to show them. For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the --align-all flag. This command also supports the output destination and output format options. The output formats supported are txt, csv, tsv, and json. aregister and posting dates aregister always shows one line (and date and amount) per transaction. But sometimes transactions have postings with different dates. Also, not all of a transaction's postings may be within the report period. To resolve this, aregister shows the earliest of the transaction's date and posting dates that is in-period, and the sum of the in-period postings. In other words it will show a combined line item with just the earliest date, and the running balance will (temporarily, until the transaction's last posting) be inaccurate. Use register -H if you need to see the individual postings. There is also a --txn-dates flag, which filters strictly by transaction date, ignoring posting dates. This too can cause an inaccurate running balance. hledger-1.32.3/Hledger/Cli/Commands/Balance.txt0000644000000000000000000010532214555431531017321 0ustar0000000000000000balance (bal) Show accounts and their balances. _FLAGS balance is one of hledger's oldest and most versatile commands, for listing account balances, balance changes, values, value changes and more, during one time period or many. Generally it shows a table, with rows representing accounts, and columns representing periods. Note there are some higher-level variants of the balance command with convenient defaults, which can be simpler to use: balancesheet, balancesheetequity, cashflow and incomestatement. When you need more control, then use balance. balance features Here's a quick overview of the balance command's features, followed by more detailed descriptions and examples. Many of these work with the higher-level commands as well. balance can show.. - accounts as a list (-l) or a tree (-t) - optionally depth-limited (-[1-9]) - sorted by declaration order and name, or by amount ..and their.. - balance changes (the default) - or actual and planned balance changes (--budget) - or value of balance changes (-V) - or change of balance values (--valuechange) - or unrealised capital gain/loss (--gain) - or postings count (--count) ..in.. - one time period (the whole journal period by default) - or multiple periods (-D, -W, -M, -Q, -Y, -p INTERVAL) ..either.. - per period (the default) - or accumulated since report start date (--cumulative) - or accumulated since account creation (--historical/-H) ..possibly converted to.. - cost (--value=cost[,COMM]/--cost/-B) - or market value, as of transaction dates (--value=then[,COMM]) - or at period ends (--value=end[,COMM]) - or now (--value=now) - or at some other date (--value=YYYY-MM-DD) ..with.. - totals (-T), averages (-A), percentages (-%), inverted sign (--invert) - rows and columns swapped (--transpose) - another field used as account name (--pivot) - custom-formatted line items (single-period reports only) (--format) - commodities displayed on the same line or multiple lines (--layout) This command supports the output destination and output format options, with output formats txt, csv, tsv, json, and (multi-period reports only:) html. In txt output in a colour-supporting terminal, negative amounts are shown in red. The --related/-r flag shows the balance of the other postings in the transactions of the postings which would normally be shown. Simple balance report With no arguments, balance shows a list of all accounts and their change of balance - ie, the sum of posting amounts, both inflows and outflows - during the entire period of the journal. ("Simple" here means just one column of numbers, covering a single period. You can also have multi-period reports, described later.) For real-world accounts, these numbers will normally be their end balance at the end of the journal period; more on this below. Accounts are sorted by declaration order if any, and then alphabetically by account name. For instance (using examples/sample.journal): $ hledger -f examples/sample.journal bal $1 assets:bank:saving $-2 assets:cash $1 expenses:food $1 expenses:supplies $-1 income:gifts $-1 income:salary $1 liabilities:debts -------------------- 0 Accounts with a zero balance (and no non-zero subaccounts, in tree mode - see below) are hidden by default. Use -E/--empty to show them (revealing assets:bank:checking here): $ hledger -f examples/sample.journal bal -E 0 assets:bank:checking $1 assets:bank:saving $-2 assets:cash $1 expenses:food $1 expenses:supplies $-1 income:gifts $-1 income:salary $1 liabilities:debts -------------------- 0 The total of the amounts displayed is shown as the last line, unless -N/--no-total is used. Balance report line format For single-period balance reports displayed in the terminal (only), you can use --format FMT to customise the format and content of each line. Eg: $ hledger -f examples/sample.journal balance --format "%20(account) %12(total)" assets $-1 bank:saving $1 cash $-2 expenses $2 food $1 supplies $1 income $-2 gifts $-1 salary $-1 liabilities:debts $1 --------------------------------- 0 The FMT format string specifies the formatting applied to each account/balance pair. It may contain any suitable text, with data fields interpolated like so: %[MIN][.MAX](FIELDNAME) - MIN pads with spaces to at least this width (optional) - MAX truncates at this width (optional) - FIELDNAME must be enclosed in parentheses, and can be one of: - depth_spacer - a number of spaces equal to the account's depth, or if MIN is specified, MIN * depth spaces. - account - the account's name - total - the account's balance/posted total, right justified Also, FMT can begin with an optional prefix to control how multi-commodity amounts are rendered: - %_ - render on multiple lines, bottom-aligned (the default) - %^ - render on multiple lines, top-aligned - %, - render on one line, comma-separated There are some quirks. Eg in one-line mode, %(depth_spacer) has no effect, instead %(account) has indentation built in. Experimentation may be needed to get pleasing results. Some example formats: - %(total) - the account's total - %-20.20(account) - the account's name, left justified, padded to 20 characters and clipped at 20 characters - %,%-50(account) %25(total) - account name padded to 50 characters, total padded to 20 characters, with multiple commodities rendered on one line - %20(total) %2(depth_spacer)%-(account) - the default format for the single-column balance report Filtered balance report You can show fewer accounts, a different time period, totals from cleared transactions only, etc. by using query arguments or options to limit the postings being matched. Eg: $ hledger -f examples/sample.journal bal --cleared assets date:200806 $-2 assets:cash -------------------- $-2 List or tree mode By default, or with -l/--flat, accounts are shown as a flat list with their full names visible, as in the examples above. With -t/--tree, the account hierarchy is shown, with subaccounts' "leaf" names indented below their parent: $ hledger -f examples/sample.journal balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 Notes: - "Boring" accounts are combined with their subaccount for more compact output, unless --no-elide is used. Boring accounts have no balance of their own and just one subaccount (eg assets:bank and liabilities above). - All balances shown are "inclusive", ie including the balances from all subaccounts. Note this means some repetition in the output, which requires explanation when sharing reports with non-plaintextaccounting-users. A tree mode report's final total is the sum of the top-level balances shown, not of all the balances shown. - Each group of sibling accounts (ie, under a common parent) is sorted separately. Depth limiting With a depth:NUM query, or --depth NUM option, or just -NUM (eg: -3) balance reports will show accounts only to the specified depth, hiding the deeper subaccounts. This can be useful for getting an overview without too much detail. Account balances at the depth limit always include the balances from any deeper subaccounts (even in list mode). Eg, limiting to depth 1: $ hledger -f examples/sample.journal balance -1 $-1 assets $2 expenses $-2 income $1 liabilities -------------------- 0 Dropping top-level accounts You can also hide one or more top-level account name parts, using --drop NUM. This can be useful for hiding repetitive top-level account names: $ hledger -f examples/sample.journal bal expenses --drop 1 $1 food $1 supplies -------------------- $2 Showing declared accounts With --declared, accounts which have been declared with an account directive will be included in the balance report, even if they have no transactions. (Since they will have a zero balance, you will also need -E/--empty to see them.) More precisely, leaf declared accounts (with no subaccounts) will be included, since those are usually the more useful in reports. The idea of this is to be able to see a useful "complete" balance report, even when you don't have transactions in all of your declared accounts yet. Sorting by amount With -S/--sort-amount, accounts with the largest (most positive) balances are shown first. Eg: hledger bal expenses -MAS shows your biggest averaged monthly expenses first. When more than one commodity is present, they will be sorted by the alphabetically earliest commodity first, and then by subsequent commodities (if an amount is missing a commodity, it is treated as 0). Revenues and liability balances are typically negative, however, so -S shows these in reverse order. To work around this, you can add --invert to flip the signs. (Or, use one of the higher-level reports, which flip the sign automatically. Eg: hledger incomestatement -MAS). Percentages With -%/--percent, balance reports show each account's value expressed as a percentage of the (column) total. Note it is not useful to calculate percentages if the amounts in a column have mixed signs. In this case, make a separate report for each sign, eg: $ hledger bal -% amt:`>0` $ hledger bal -% amt:`<0` Similarly, if the amounts in a column have mixed commodities, convert them to one commodity with -B, -V, -X or --value, or make a separate report for each commodity: $ hledger bal -% cur:\\$ $ hledger bal -% cur:€ Multi-period balance report With a report interval (set by the -D/--daily, -W/--weekly, -M/--monthly, -Q/--quarterly, -Y/--yearly, or -p/--period flag), balance shows a tabular report, with columns representing successive time periods (and a title): $ hledger -f examples/sample.journal bal --quarterly income expenses -E Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 ===================++================================= expenses:food || 0 $1 0 0 expenses:supplies || 0 $1 0 0 income:gifts || 0 $-1 0 0 income:salary || $-1 0 0 0 -------------------++--------------------------------- || $-1 $1 0 0 Notes: - The report's start/end dates will be expanded, if necessary, to fully encompass the displayed subperiods (so that the first and last subperiods have the same duration as the others). - Leading and trailing periods (columns) containing all zeroes are not shown, unless -E/--empty is used. - Accounts (rows) containing all zeroes are not shown, unless -E/--empty is used. - Amounts with many commodities are shown in abbreviated form, unless --no-elide is used. (experimental) - Average and/or total columns can be added with the -A/--average and -T/--row-total flags. - The --transpose flag can be used to exchange rows and columns. - The --pivot FIELD option causes a different transaction field to be used as "account name". See PIVOTING. Multi-period reports with many periods can be too wide for easy viewing in the terminal. Here are some ways to handle that: - Hide the totals row with -N/--no-total - Convert to a single currency with -V - Maximize the terminal window - Reduce the terminal's font size - View with a pager like less, eg: hledger bal -D --color=yes | less -RS - Output as CSV and use a CSV viewer like visidata (hledger bal -D -O csv | vd -f csv), Emacs' csv-mode (M-x csv-mode, C-c C-a), or a spreadsheet (hledger bal -D -o a.csv && open a.csv) - Output as HTML and view with a browser: hledger bal -D -o a.html && open a.html Balance change, end balance It's important to be clear on the meaning of the numbers shown in balance reports. Here is some terminology we use: A balance change is the net amount added to, or removed from, an account during some period. An end balance is the amount accumulated in an account as of some date (and some time, but hledger doesn't store that; assume end of day in your timezone). It is the sum of previous balance changes. We call it a historical end balance if it includes all balance changes since the account was created. For a real world account, this means it will match the "historical record", eg the balances reported in your bank statements or bank web UI. (If they are correct!) In general, balance changes are what you want to see when reviewing revenues and expenses, and historical end balances are what you want to see when reviewing or reconciling asset, liability and equity accounts. balance shows balance changes by default. To see accurate historical end balances: 1. Initialise account starting balances with an "opening balances" transaction (a transfer from equity to the account), unless the journal covers the account's full lifetime. 2. Include all of of the account's prior postings in the report, by not specifying a report start date, or by using the -H/--historical flag. (-H causes report start date to be ignored when summing postings.) Balance report types The balance command is quite flexible; here is the full detail on how to control what it reports. If the following seems complicated, don't worry - this is for advanced reporting, and it does take time and experimentation to get familiar with all the report modes. There are three important option groups: hledger balance [CALCULATIONTYPE] [ACCUMULATIONTYPE] [VALUATIONTYPE] ... Calculation type The basic calculation to perform for each table cell. It is one of: - --sum : sum the posting amounts (default) - --budget : sum the amounts, but also show the budget goal amount (for each account/period) - --valuechange : show the change in period-end historical balance values (caused by deposits, withdrawals, and/or market price fluctuations) - --gain : show the unrealised capital gain/loss, (the current valued balance minus each amount's original cost) - --count : show the count of postings Accumulation type How amounts should accumulate across report periods. Another way to say it: which time period's postings should contribute to each cell's calculation. It is one of: - --change : calculate with postings from column start to column end, ie "just this column". Typically used to see revenues/expenses. (default for balance, incomestatement) - --cumulative : calculate with postings from report start to column end, ie "previous columns plus this column". Typically used to show changes accumulated since the report's start date. Not often used. - --historical/-H : calculate with postings from journal start to column end, ie "all postings from before report start date until this column's end". Typically used to see historical end balances of assets/liabilities/equity. (default for balancesheet, balancesheetequity, cashflow) Valuation type Which kind of value or cost conversion should be applied, if any, before displaying the report. It is one of: - no valuation type : don't convert to cost or value (default) - --value=cost[,COMM] : convert amounts to cost (then optionally to some other commodity) - --value=then[,COMM] : convert amounts to market value on transaction dates - --value=end[,COMM] : convert amounts to market value on period end date(s) (default with --valuechange, --gain) - --value=now[,COMM] : convert amounts to market value on today's date - --value=YYYY-MM-DD[,COMM] : convert amounts to market value on another date or one of the equivalent simpler flags: - -B/--cost : like --value=cost (though, note --cost and --value are independent options which can both be used at once) - -V/--market : like --value=end - -X COMM/--exchange COMM : like --value=end,COMM See Cost reporting and Value reporting for more about these. Combining balance report types Most combinations of these options should produce reasonable reports, but if you find any that seem wrong or misleading, let us know. The following restrictions are applied: - --valuechange implies --value=end - --valuechange makes --change the default when used with the balancesheet/balancesheetequity commands - --cumulative or --historical disables --row-total/-T For reference, here is what the combinations of accumulation and valuation show: ------------------------------------------------------------------------------------------------ Valuation:> no valuation --value= then --value= end --value= YYYY-MM-DD /now Accumulation:v ------------------ ---------------- ----------------- --------------- -------------------------- --change change in period sum of period-end DATE-value of change in posting-date value of change period market values in in period period --cumulative change from sum of period-end DATE-value of change from report start to posting-date value of change report start to period end period end market values from report from report start start to period to period end end --historical /-H change from sum of period-end DATE-value of change from journal start to posting-date value of change journal start to period period end market values from journal end (historical end from journal start to period balance) start to period end end ------------------------------------------------------------------------------------------------ Budget report The --budget report type is like a regular balance report, but with two main differences: - Budget goals and performance percentages are also shown, in brackets - Accounts which don't have budget goals are hidden by default. This is useful for comparing planned and actual income, expenses, time usage, etc. Periodic transaction rules are used to define budget goals. For example, here's a periodic rule defining monthly goals for bus travel and food expenses: ;; Budget ~ monthly (expenses:bus) $30 (expenses:food) $400 After recording some actual expenses, ;; Two months worth of expenses 2017-11-01 income $-1950 expenses:bus $35 expenses:food:groceries $310 expenses:food:dining $42 expenses:movies $38 assets:bank:checking 2017-12-01 income $-2100 expenses:bus $53 expenses:food:groceries $380 expenses:food:dining $32 expenses:gifts $100 assets:bank:checking we can see a budget report like this: $ hledger bal -M --budget Budget performance in 2017-11-01..2017-12-31: || Nov Dec ===============++============================================ || $-425 $-565 expenses || $425 [ 99% of $430] $565 [131% of $430] expenses:bus || $35 [117% of $30] $53 [177% of $30] expenses:food || $352 [ 88% of $400] $412 [103% of $400] ---------------++-------------------------------------------- || 0 [ 0% of $430] 0 [ 0% of $430] This is "goal-based budgeting"; you define goals for accounts and periods, often recurring, and hledger shows performance relative to the goals. This contrasts with "envelope budgeting", which is more detailed and strict - useful when cash is tight, but also quite a bit more work. https://plaintextaccounting.org/Budgeting has more on this topic. Using the budget report Historically this report has been confusing and fragile. hledger's version should be relatively robust and intuitive, but you may still find surprises. Here are more notes to help with learning and troubleshooting. - In the above example, expenses:bus and expenses:food are shown because they have budget goals during the report period. - Their parent expenses is also shown, with budget goals aggregated from the children. - The subaccounts expenses:food:groceries and expenses:food:dining are not shown since they have no budget goal of their own, but they contribute to expenses:food's actual amount. - Unbudgeted accounts expenses:movies and expenses:gifts are also not shown, but they contribute to expenses's actual amount. - The other unbudgeted accounts income and assets:bank:checking are grouped as . - --depth or depth: can be used to limit report depth in the usual way (but will not reveal unbudgeted subaccounts). - Amounts are always inclusive of subaccounts (even in -l/--list mode). - Numbers displayed in a --budget report will not always agree with the totals, because of hidden unbudgeted accounts; this is normal. -E/--empty can be used to reveal the hidden accounts. - In the periodic rules used for setting budget goals, unbalanced postings are convenient. - You can filter budget reports with the usual queries, eg to focus on particular accounts. It's common to restrict them to just expenses. (The account is occasionally hard to exclude; this is because of date surprises, discussed below.) - When you have multiple currencies, you may want to convert them to one (-X COMM --infer-market-prices) and/or show just one at a time (cur:COMM). If you do need to show multiple currencies at once, --layout bare can be helpful. - You can "roll over" amounts (actual and budgeted) to the next period with --cumulative. See also: https://hledger.org/budgeting.html. Budget date surprises With small data, or when starting out, some of the generated budget goal transaction dates might fall outside the report periods. Eg with the following journal and report, the first period appears to have no expenses:food budget. (Also the account should be excluded by the expenses query, but isn't.): ~ monthly in 2020 (expenses:food) $500 2020-01-15 expenses:food $400 assets:checking $ hledger bal --budget expenses Budget performance in 2020-01-15: || 2020-01-15 ===============++==================== || $400 expenses:food || 0 [ 0% of $500] ---------------++-------------------- || $400 [80% of $500] In this case, the budget goal transactions are generated on first days of of month (this can be seen with hledger print --forecast tag:generated expenses). Whereas the report period defaults to just the 15th day of january (this can be seen from the report table's column headings). To fix this kind of thing, be more explicit about the report period (and/or the periodic rules' dates). In this case, adding -b 2020 does the trick. Selecting budget goals By default, the budget report uses all available periodic transaction rules to generate goals. This includes rules with a different report interval from your report. Eg if you have daily, weekly and monthly periodic rules, all of these will contribute to the goals in a monthly budget report. You can select a subset of periodic rules by providing an argument to the --budget flag. --budget=DESCPAT will match all periodic rules whose description contains DESCPAT, a case-insensitive substring (not a regular expression or query). This means you can give your periodic rules descriptions (remember that two spaces are needed between period expression and description), and then select from multiple budgets defined in your journal. Budgeting vs forecasting --budget and --forecast both use the periodic transaction rules in the journal to generate temporary transactions for reporting purposes. However they are separate features - though you can use both at the same time if you want. Here are some differences between them: 1. --budget is a command-specific option; it selects the budget report. --forecast is a general option; forecasting works with all reports. 2. --budget uses all periodic rules; --budget=DESCPAT uses just the rules matched by DESCPAT. --forecast uses all periodic rules. 3. --budget's budget goal transactions are invisible, except that they produce goal amounts. --forecast's forecast transactions are visible, and appear in reports. 4. --budget generates budget goal transactions throughout the report period, optionally restricted by periods specified in the periodic transaction rules. --forecast generates forecast transactions from after the last regular transaction, to the end of the report period; while --forecast=PERIODEXPR generates them throughout the specified period; both optionally restricted by periods specified in the periodic transaction rules. Balance report layout The --layout option affects how balance reports show multi-commodity amounts and commodity symbols, which can improve readability. It can also normalise the data for easy consumption by other programs. It has four possible values: - --layout=wide[,WIDTH]: commodities are shown on a single line, optionally elided to WIDTH - --layout=tall: each commodity is shown on a separate line - --layout=bare: commodity symbols are in their own column, amounts are bare numbers - --layout=tidy: data is normalised to easily-consumed "tidy" form, with one row per data value Here are the --layout modes supported by each output format; note only CSV output supports all of them: - txt csv html json sql ------ ----- ----- ------ ------ ----- wide Y Y Y tall Y Y Y bare Y Y Y tidy Y Examples: - Wide layout. With many commodities, reports can be very wide: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=wide Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++==================================================================================================================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, -98.12 USD, 10.00 VEA, 18.00 VHT -11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT ------------------++-------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------------- || 10.00 ITOT, 337.18 USD, 12.00 VEA, 106.00 VHT 70.00 GLD, 18.00 ITOT, -98.12 USD, 10.00 VEA, 18.00 VHT -11.00 ITOT, 4881.44 USD, 14.00 VEA, 170.00 VHT 70.00 GLD, 17.00 ITOT, 5120.50 USD, 36.00 VEA, 294.00 VHT - Limited wide layout. A width limit reduces the width, but some commodities will be hidden: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=wide,32 Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++=========================================================================================================================== Assets:US:ETrade || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. -11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. ------------------++--------------------------------------------------------------------------------------------------------------------------- || 10.00 ITOT, 337.18 USD, 2 more.. 70.00 GLD, 18.00 ITOT, 3 more.. -11.00 ITOT, 3 more.. 70.00 GLD, 17.00 ITOT, 3 more.. - Tall layout. Each commodity gets a new line (may be different in each column), and account names are repeated: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=tall Balance changes in 2012-01-01..2014-12-31: || 2012 2013 2014 Total ==================++================================================== Assets:US:ETrade || 10.00 ITOT 70.00 GLD -11.00 ITOT 70.00 GLD Assets:US:ETrade || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT Assets:US:ETrade || 12.00 VEA -98.12 USD 14.00 VEA 5120.50 USD Assets:US:ETrade || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA Assets:US:ETrade || 18.00 VHT 294.00 VHT ------------------++-------------------------------------------------- || 10.00 ITOT 70.00 GLD -11.00 ITOT 70.00 GLD || 337.18 USD 18.00 ITOT 4881.44 USD 17.00 ITOT || 12.00 VEA -98.12 USD 14.00 VEA 5120.50 USD || 106.00 VHT 10.00 VEA 170.00 VHT 36.00 VEA || 18.00 VHT 294.00 VHT - Bare layout. Commodity symbols are kept in one column, each commodity gets its own report row, account names are repeated: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -T -Y --layout=bare Balance changes in 2012-01-01..2014-12-31: || Commodity 2012 2013 2014 Total ==================++============================================= Assets:US:ETrade || GLD 0 70.00 0 70.00 Assets:US:ETrade || ITOT 10.00 18.00 -11.00 17.00 Assets:US:ETrade || USD 337.18 -98.12 4881.44 5120.50 Assets:US:ETrade || VEA 12.00 10.00 14.00 36.00 Assets:US:ETrade || VHT 106.00 18.00 170.00 294.00 ------------------++--------------------------------------------- || GLD 0 70.00 0 70.00 || ITOT 10.00 18.00 -11.00 17.00 || USD 337.18 -98.12 4881.44 5120.50 || VEA 12.00 10.00 14.00 36.00 || VHT 106.00 18.00 170.00 294.00 - Bare layout also affects CSV output, which is useful for producing data that is easier to consume, eg for making charts: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -O csv --layout=bare "account","commodity","balance" "Assets:US:ETrade","GLD","70.00" "Assets:US:ETrade","ITOT","17.00" "Assets:US:ETrade","USD","5120.50" "Assets:US:ETrade","VEA","36.00" "Assets:US:ETrade","VHT","294.00" "total","GLD","70.00" "total","ITOT","17.00" "total","USD","5120.50" "total","VEA","36.00" "total","VHT","294.00" - Note: bare layout will sometimes display an extra row for the no-symbol commodity, because of zero amounts (hledger treats zeroes as commodity-less, usually). This can break hledger-bar confusingly (workaround: add a cur: query to exclude the no-symbol row). - Tidy layout produces normalised "tidy data", where every variable has its own column and each row represents a single data point. See https://cran.r-project.org/web/packages/tidyr/vignettes/tidy-data.html for more. This is the easiest kind of data for other software to consume. Here's how it looks: $ hledger -f examples/bcexample.hledger bal assets:us:etrade -3 -Y -O csv --layout=tidy "account","period","start_date","end_date","commodity","value" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","GLD","0" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","ITOT","10.00" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","USD","337.18" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","VEA","12.00" "Assets:US:ETrade","2012","2012-01-01","2012-12-31","VHT","106.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","GLD","70.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","ITOT","18.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","USD","-98.12" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","VEA","10.00" "Assets:US:ETrade","2013","2013-01-01","2013-12-31","VHT","18.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","GLD","0" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","ITOT","-11.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","USD","4881.44" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","VEA","14.00" "Assets:US:ETrade","2014","2014-01-01","2014-12-31","VHT","170.00" Useful balance reports Some frequently used balance options/reports are: - bal -M revenues expenses Show revenues/expenses in each month. Also available as the incomestatement command. - bal -M -H assets liabilities Show historical asset/liability balances at each month end. Also available as the balancesheet command. - bal -M -H assets liabilities equity Show historical asset/liability/equity balances at each month end. Also available as the balancesheetequity command. - bal -M assets not:receivable Show changes to liquid assets in each month. Also available as the cashflow command. Also: - bal -M expenses -2 -SA Show monthly expenses summarised to depth 2 and sorted by average amount. - bal -M --budget expenses Show monthly expenses and budget goals. - bal -M --valuechange investments Show monthly change in market value of investment assets. - bal investments --valuechange -D date:lastweek amt:'>1000' -STA [--invert] Show top gainers [or losers] last week hledger-1.32.3/Hledger/Cli/Commands/Balancesheet.txt0000644000000000000000000000243214555431531020350 0ustar0000000000000000balancesheet (bs) This command displays a balance sheet, showing historical ending balances of asset and liability accounts. (To see equity as well, use the balancesheetequity command.) Amounts are shown with normal positive sign, as in conventional financial statements. _FLAGS This report shows accounts declared with the Asset, Cash or Liability type (see account types). Or if no such accounts are declared, it shows top-level accounts named asset or liability (case insensitive, plurals allowed) and their subaccounts. Example: $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 This command is a higher-level variant of the balance command, and supports many of that command's features, such as multi-period reports. It is similar to hledger balance -H assets liabilities, but with smarter account detection, and liabilities displayed with their sign flipped. This command also supports the output destination and output format options The output formats supported are txt, csv, tsv, html, and (experimental) json. hledger-1.32.3/Hledger/Cli/Commands/Balancesheetequity.txt0000644000000000000000000000254214555431531021613 0ustar0000000000000000balancesheetequity (bse) This command displays a balance sheet, showing historical ending balances of asset, liability and equity accounts. Amounts are shown with normal positive sign, as in conventional financial statements. _FLAGS This report shows accounts declared with the Asset, Cash, Liability or Equity type (see account types). Or if no such accounts are declared, it shows top-level accounts named asset, liability or equity (case insensitive, plurals allowed) and their subaccounts. Example: $ hledger balancesheetequity Balance Sheet With Equity Assets: $-2 assets $1 bank:saving $-3 cash -------------------- $-2 Liabilities: $1 liabilities:debts -------------------- $1 Equity: $1 equity:owner -------------------- $1 Total: -------------------- 0 This command is a higher-level variant of the balance command, and supports many of that command's features, such as multi-period reports. It is similar to hledger balance -H assets liabilities equity, but with smarter account detection, and liabilities/equity displayed with their sign flipped. This command also supports the output destination and output format options The output formats supported are txt, csv, tsv, html, and (experimental) json. hledger-1.32.3/Hledger/Cli/Commands/Cashflow.txt0000644000000000000000000000256314555431531017545 0ustar0000000000000000cashflow (cf) This command displays a cashflow statement, showing the inflows and outflows affecting "cash" (ie, liquid, easily convertible) assets. Amounts are shown with normal positive sign, as in conventional financial statements. _FLAGS This report shows accounts declared with the Cash type (see account types). Or if no such accounts are declared, it shows accounts - under a top-level account named asset (case insensitive, plural allowed) - whose name contains some variation of cash, bank, checking or saving. More precisely: all accounts matching this case insensitive regular expression: ^assets?(:.+)?:(cash|bank|che(ck|que?)(ing)?|savings?|currentcash)(:|$) and their subaccounts. An example cashflow report: $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 This command is a higher-level variant of the balance command, and supports many of that command's features, such as multi-period reports. It is similar to hledger balance assets not:fixed not:investment not:receivable, but with smarter account detection. This command also supports the output destination and output format options The output formats supported are txt, csv, tsv, html, and (experimental) json. hledger-1.32.3/Hledger/Cli/Commands/Check.txt0000644000000000000000000000640514555141606017014 0ustar0000000000000000check Check for various kinds of errors in your data. _FLAGS hledger provides a number of built-in error checks to help prevent problems in your data. Some of these are run automatically; or, you can use this check command to run them on demand, with no output and a zero exit code if all is well. Specify their names (or a prefix) as argument(s). Some examples: hledger check # basic checks hledger check -s # basic + strict checks hledger check ordereddates payees # basic + two other checks If you are an Emacs user, you can also configure flycheck-hledger to run these checks, providing instant feedback as you edit the journal. Here are the checks currently available: Default checks These checks are run automatically by (almost) all hledger commands: - parseable - data files are in a supported format, with no syntax errors and no invalid include directives. - autobalanced - all transactions are balanced, after converting to cost. Missing amounts and missing costs are inferred automatically where possible. - assertions - all balance assertions in the journal are passing. (This check can be disabled with -I/--ignore-assertions.) Strict checks These additional checks are run when the -s/--strict (strict mode) flag is used. Or, they can be run by giving their names as arguments to check: - balanced - all transactions are balanced after converting to cost, without inferring missing costs. If conversion costs are required, they must be explicit. - accounts - all account names used by transactions have been declared - commodities - all commodity symbols used have been declared Other checks These checks can be run only by giving their names as arguments to check. They are more specialised and not desirable for everyone: - ordereddates - transactions are ordered by date within each file - payees - all payees used by transactions have been declared - recentassertions - all accounts with balance assertions have a balance assertion within 7 days of their latest posting - tags - all tags used by transactions have been declared - uniqueleafnames - all account leaf names are unique Custom checks A few more checks are are available as separate add-on commands, in https://github.com/simonmichael/hledger/tree/master/bin: - hledger-check-tagfiles - all tag values containing / (a forward slash) exist as file paths - hledger-check-fancyassertions - more complex balance assertions are passing You could make similar scripts to perform your own custom checks. See: Cookbook -> Scripting. More about specific checks hledger check recentassertions will complain if any balance-asserted account has postings more than 7 days after its latest balance assertion. This aims to prevent the situation where you are regularly updating your journal, but forgetting to check your balances against the real world, then one day must dig back through months of data to find an error. It assumes that adding a balance assertion requires/reminds you to check the real-world balance. (That may not be true if you auto-generate balance assertions from bank data; in that case, I recommend to import transactions uncleared, and when you manually review and clear them, also check the latest assertion against the real-world balance.) hledger-1.32.3/Hledger/Cli/Commands/Close.txt0000644000000000000000000001501414555431531017037 0ustar0000000000000000close (equity) Generate transactions which transfer account balances to and/or from another account (typically equity). This can be useful for migrating balances to a new journal file, or for merging earnings into equity at end of accounting period. By default, it prints a transaction that zeroes out ALE accounts (asset, liability, equity accounts; this requires account types to be configured); or if ACCTQUERY is provided, the accounts matched by that. (experimental) _FLAGS This command has four main modes, corresponding to the most common use cases: 1. With --close (default), it prints a "closing balances" transaction that zeroes out ALE (asset, liability, equity) accounts by default (this requires account types to be inferred or declared); or, the accounts matched by the provided ACCTQUERY arguments. 2. With --open, it prints an opposite "opening balances" transaction that restores those balances from zero. This is similar to Ledger's equity command. 3. With --migrate, it prints both the closing and opening transactions. This is the preferred way to migrate balances to a new file: run hledger close --migrate, add the closing transaction at the end of the old file, and add the opening transaction at the start of the new file. The matching closing/opening transactions cancel each other out, preserving correct balances during multi-file reporting. 4. With --retain, it prints a "retain earnings" transaction that transfers RX (revenue and expense) balances to equity:retained earnings. Businesses traditionally do this at the end of each accounting period; it is less necessary with computer-based accounting, but it could still be useful if you want to see the accounting equation (A=L+E) satisfied. In all modes, the defaults can be overridden: - the transaction descriptions can be changed with --close-desc=DESC and --open-desc=DESC - the account to transfer to/from can be changed with --close-acct=ACCT and --open-acct=ACCT - the accounts to be closed/opened can be changed with ACCTQUERY (account query arguments). - the closing/opening dates can be changed with -e DATE (a report end date) By default just one destination/source posting will be used, with its amount left implicit. With --x/--explicit, the amount will be shown explicitly, and if it involves multiple commodities, a separate posting will be generated for each of them (similar to print -x). With --show-costs, any amount costs are shown, with separate postings for each cost. This is currently the best way to view investment lots. If you have many currency conversion or investment transactions, it can generate very large journal entries. With --interleaved, each individual transfer is shown with source and destination postings next to each other. This could be useful for troubleshooting. The default closing date is yesterday, or the journal's end date, whichever is later. You can change this by specifying a report end date with -e. The last day of the report period will be the closing date, eg -e 2024 means "close on 2023-12-31". The opening date is always the day after the closing date. close and balance assertions Balance assertions will be generated, verifying that the accounts have been reset to zero (and then restored to their previous balances, if there is an opening transaction). These provide useful error checking, but you can ignore them temporarily with -I, or remove them if you prefer. You probably should avoid filtering transactions by status or realness (-C, -R, status:), or generating postings (--auto), with this command, since the balance assertions would depend on these. Note custom posting dates spanning the file boundary will disrupt the balance assertions: 2023-12-30 a purchase made in december, cleared in january expenses:food 5 assets:bank:checking -5 ; date: 2023-01-02 To solve that you can transfer the money to and from a temporary account, in effect splitting the multi-day transaction into two single-day transactions: ; in 2022.journal: 2022-12-30 a purchase made in december, cleared in january expenses:food 5 equity:pending -5 ; in 2023.journal: 2023-01-02 last year's transaction cleared equity:pending 5 = 0 assets:bank:checking -5 Example: retain earnings Record 2022's revenues/expenses as retained earnings on 2022-12-31, appending the generated transaction to the journal: $ hledger close --retain -f 2022.journal -p 2022 >> 2022.journal Note 2022's income statement will now show only zeroes, because revenues and expenses have been moved entirely to equity. To see them again, you could exclude the retain transaction: $ hledger -f 2022.journal is not:desc:'retain earnings' Example: migrate balances to a new file Close assets/liabilities/equity on 2022-12-31 and re-open them on 2023-01-01: $ hledger close --migrate -f 2022.journal -p 2022 # copy/paste the closing transaction to the end of 2022.journal # copy/paste the opening transaction to the start of 2023.journal Now 2022's balance sheet will show only zeroes, indicating a balanced accounting equation. (Unless you are using @/@@ notation - in that case, try adding --infer-equity.) To see the end-of-year balances again, you could exclude the closing transaction: $ hledger -f 2022.journal bs not:desc:'closing balances' Example: excluding closing/opening transactions When combining many files for multi-year reports, the closing/opening transactions cause some noise in transaction-oriented reports like print and register. You can exclude them as shown above, but not:desc:... is not ideal as it depends on consistent descriptions; also you will want to avoid excluding the very first opening transaction, which could be awkward. Here is one alternative, using tags: Add clopen: tags to all opening/closing balances transactions except the first, like this: ; 2021.journal 2021-06-01 first opening balances ... 2021-12-31 closing balances ; clopen:2022 ... ; 2022.journal 2022-01-01 opening balances ; clopen:2022 ... 2022-12-31 closing balances ; clopen:2023 ... ; 2023.journal 2023-01-01 opening balances ; clopen:2023 ... Now, assuming a combined journal like: ; all.journal include 2021.journal include 2022.journal include 2023.journal The clopen: tag can exclude all but the first opening transaction. To show a clean multi-year checking register: $ hledger -f all.journal areg checking not:tag:clopen And the year values allow more precision. To show 2022's year-end balance sheet: $ hledger -f all.journal bs -e2023 not:tag:clopen=2023 hledger-1.32.3/Hledger/Cli/Commands/Codes.txt0000644000000000000000000000153414555141606017032 0ustar0000000000000000codes List the codes seen in transactions, in the order parsed. _FLAGS This command prints the value of each transaction's code field, in the order transactions were parsed. The transaction code is an optional value written in parentheses between the date and description, often used to store a cheque number, order number or similar. Transactions aren't required to have a code, and missing or empty codes will not be shown by default. With the -E/--empty flag, they will be printed as blank lines. You can add a query to select a subset of transactions. Examples: 2022/1/1 (123) Supermarket Food $5.00 Checking 2022/1/2 (124) Post Office Postage $8.32 Checking 2022/1/3 Supermarket Food $11.23 Checking 2022/1/4 (126) Post Office Postage $3.21 Checking $ hledger codes 123 124 126 $ hledger codes -E 123 124 126 hledger-1.32.3/Hledger/Cli/Commands/Commodities.txt0000644000000000000000000000013214555141607020243 0ustar0000000000000000commodities List all commodity/currency symbols used or declared in the journal. _FLAGS hledger-1.32.3/Hledger/Cli/Commands/Demo.txt0000644000000000000000000000160514555141606016660 0ustar0000000000000000demo Play demos of hledger usage in the terminal, if asciinema is installed. _FLAGS Run this command with no argument to list the demos. To play a demo, write its number or a prefix or substring of its title. Tips: Make your terminal window large enough to see the demo clearly. Use the -s/--speed SPEED option to set your preferred playback speed, eg -s4 to play at 4x original speed or -s.5 to play at half speed. The default speed is 2x. Other asciinema options can be added following a double dash, eg -- -i.1 to limit pauses or -- -h to list asciinema's other options. During playback, several keys are available: SPACE to pause/unpause, . to step forward (while paused), CTRL-c quit. Examples: $ hledger demo # list available demos $ hledger demo 1 # play the first demo at default speed (2x) $ hledger demo install -s4 # play the "install" demo at 4x speed hledger-1.32.3/Hledger/Cli/Commands/Descriptions.txt0000644000000000000000000000046114555141606020441 0ustar0000000000000000descriptions List the unique descriptions that appear in transactions. _FLAGS This command lists the unique descriptions that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. Example: $ hledger descriptions Store Name Gas Station | Petrol Person A hledger-1.32.3/Hledger/Cli/Commands/Diff.txt0000644000000000000000000000202414555141607016641 0ustar0000000000000000diff Compares a particular account's transactions in two input files. It shows any transactions to this account which are in one file but not in the other. More precisely, for each posting affecting this account in either file, it looks for a corresponding posting in the other file which posts the same amount to the same account (ignoring date, description, etc.) Since postings not transactions are compared, this also works when multiple bank transactions have been combined into a single journal entry. This is useful eg if you have downloaded an account's transactions from your bank (eg as CSV data). When hledger and your bank disagree about the account balance, you can compare the bank data with your journal to find out the cause. _FLAGS Examples: $ hledger diff -f $LEDGER_FILE -f bank.csv assets:bank:giro These transactions are in the first file only: 2014/01/01 Opening Balances assets:bank:giro EUR ... ... equity:opening balances EUR -... These transactions are in the second file only: hledger-1.32.3/Hledger/Cli/Commands/Files.txt0000644000000000000000000000023214555141606017031 0ustar0000000000000000files List all files included in the journal. With a REGEX argument, only file names matching the regular expression (case sensitive) are shown. _FLAGS hledger-1.32.3/Hledger/Cli/Commands/Help.txt0000644000000000000000000000246514555141606016671 0ustar0000000000000000help Show the hledger user manual in the terminal, with info, man, or a pager. With a TOPIC argument, open it at that topic if possible. TOPIC can be any heading in the manual, or a heading prefix, case insensitive. Eg: commands, print, forecast, journal, amount, "auto postings". _FLAGS This command shows the hledger manual built in to your hledger version. It can be useful when offline, or when you prefer the terminal to a web browser, or when the appropriate hledger manual or viewing tools are not installed on your system. By default it chooses the best viewer found in $PATH, trying (in this order): info, man, $PAGER, less, more. You can force the use of info, man, or a pager with the -i, -m, or -p flags, If no viewer can be found, or the command is run non-interactively, it just prints the manual to stdout. If using info, note that version 6 or greater is needed for TOPIC lookup. If you are on mac you will likely have info 4.8, and should consider installing a newer version, eg with brew install texinfo (#1770). Examples $ hledger help --help # show how the help command works $ hledger help # show the hledger manual with info, man or $PAGER $ hledger help journal # show the journal topic in the hledger manual $ hledger help -m journal # show it with man, even if info is installed hledger-1.32.3/Hledger/Cli/Commands/Import.txt0000644000000000000000000001106714555141606017251 0ustar0000000000000000import Read new transactions added to each FILE provided as arguments since last run, and add them to the journal. Or with --dry-run, just print the transactions that would be added. Or with --catchup, just mark all of the FILEs' current transactions as imported, without importing them. _FLAGS This command may append new transactions to the main journal file (which should be in journal format). Existing transactions are not changed. This is one of the few hledger commands that writes to the journal file (see also add). Unlike other hledger commands, with import the journal file is an output file, and will be modified, though only by appending (existing data will not be changed). The input files are specified as arguments, so to import one or more CSV files to your main journal, you will run hledger import bank.csv or perhaps hledger import *.csv. Note you can import from any file format, though CSV files are the most common import source, and these docs focus on that case. Deduplication import does time-based deduplication, to detect only the new transactions since the last successful import. (This does not mean "ignore transactions that look the same", but rather "ignore transactions that have been seen before".) This is intended for when you are periodically importing downloaded data, which may overlap with previous downloads. Eg if every week (or every day) you download a bank's last three months of CSV data, you can safely run hledger import thebank.csv each time and only new transactions will be imported. Since the items being read (CSV records, eg) often do not come with unique identifiers, hledger detects new transactions by date, assuming that: 1. new items always have the newest dates 2. item dates do not change across reads 3. and items with the same date remain in the same relative order across reads. These are often true of CSV files representing transactions, or true enough so that it works pretty well in practice. 1 is important, but violations of 2 and 3 amongst the old transactions won't matter (and if you import often, the new transactions will be few, so less likely to be the ones affected). hledger remembers the latest date processed in each input file by saving a hidden ".latest.FILE" file in FILE's directory (after a succesful import). Eg when reading finance/bank.csv, it will look for and update the finance/.latest.bank.csv state file. The format is simple: one or more lines containing the same ISO-format date (YYYY-MM-DD), meaning "I have processed transactions up to this date, and this many of them on that date." Normally you won't see or manipulate these state files yourself. But if needed, you can delete them to reset the state (making all transactions "new"), or you can construct them to "catch up" to a certain date. Note deduplication (and updating of state files) can also be done by print --new, but this is less often used. Related: CSV > Working with CSV > Deduplicating, importing. Import testing With --dry-run, the transactions that will be imported are printed to the terminal, without updating your journal or state files. The output is valid journal format, like the print command, so you can re-parse it. Eg, to see any importable transactions which CSV rules have not categorised: $ hledger import --dry bank.csv | hledger -f- -I print unknown or (live updating): $ ls bank.csv* | entr bash -c 'echo ====; hledger import --dry bank.csv | hledger -f- -I print unknown' Note: when importing from multiple files at once, it's currently possible for some .latest files to be updated successfully, while the actual import fails because of a problem in one of the files, leaving them out of sync (and causing some transactions to be missed). To prevent this, do a --dry-run first and fix any problems before the real import. Importing balance assignments Entries added by import will have their posting amounts made explicit (like hledger print -x). This means that any balance assignments in imported files must be evaluated; but, imported files don't get to see the main file's account balances. As a result, importing entries with balance assignments (eg from an institution that provides only balances and not posting amounts) will probably generate incorrect posting amounts. To avoid this problem, use print instead of import: $ hledger print IMPORTFILE [--new] >> $LEDGER_FILE (If you think import should leave amounts implicit like print does, please test it and send a pull request.) Commodity display styles Imported amounts will be formatted according to the canonical commodity styles (declared or inferred) in the main journal file. hledger-1.32.3/Hledger/Cli/Commands/Incomestatement.txt0000644000000000000000000000243714555431531021136 0ustar0000000000000000incomestatement (is) This command displays an income statement, showing revenues and expenses during one or more periods. Amounts are shown with normal positive sign, as in conventional financial statements. _FLAGS This report shows accounts declared with the Revenue or Expense type (see account types). Or if no such accounts are declared, it shows top-level accounts named revenue or income or expense (case insensitive, plurals allowed) and their subaccounts. Example: $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 This command is a higher-level variant of the balance command, and supports many of that command's features, such as multi-period reports. It is similar to hledger balance '(revenues|income)' expenses, but with smarter account detection, and revenues/income displayed with their sign flipped. This command also supports the output destination and output format options The output formats supported are txt, csv, tsv, html, and (experimental) json. hledger-1.32.3/Hledger/Cli/Commands/Notes.txt0000644000000000000000000000056014555141606017063 0ustar0000000000000000notes List the unique notes that appear in transactions. _FLAGS This command lists the unique notes that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. The note is the part of the transaction description after a | character (or if there is no |, the whole description). Example: $ hledger notes Petrol Snacks hledger-1.32.3/Hledger/Cli/Commands/Payees.txt0000644000000000000000000000101414555141606017214 0ustar0000000000000000payees List the unique payee/payer names that appear in transactions. _FLAGS This command lists unique payee/payer names which have been declared with payee directives (--declared), used in transaction descriptions (--used), or both (the default). The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). You can add query arguments to select a subset of transactions. This implies --used. Example: $ hledger payees Store Name Gas Station Person A hledger-1.32.3/Hledger/Cli/Commands/Prices.txt0000644000000000000000000000122514555141606017217 0ustar0000000000000000prices Print the market prices declared with P directives. With --infer-market-prices, also show any additional prices inferred from costs. With --show-reverse, also show additional prices inferred by reversing known prices. Price amounts are always displayed with their full precision, except for reverse prices which are limited to 8 decimal digits. Prices can be filtered by a date:, cur: or amt: query. Generally if you run this command with --infer-market-prices --show-reverse, it will show the same prices used internally to calculate value reports. But if in doubt, you can inspect those directly by running the value report with --debug=2. _FLAGS hledger-1.32.3/Hledger/Cli/Commands/Print.txt0000644000000000000000000001554214555431531017074 0ustar0000000000000000print Show transaction journal entries, sorted by date. _FLAGS The print command displays full journal entries (transactions) from the journal file, sorted by date (or with --date2, by secondary date). Directives and inter-transaction comments are not shown, currently. This means the print command is somewhat lossy, and if you are using it to reformat/regenerate your journal you should take care to also copy over the directives and inter-transaction comments. Eg: $ hledger print -f examples/sample.journal date:200806 2008/06/01 gift assets:bank:checking $1 income:gifts $-1 2008/06/02 save assets:bank:saving $1 assets:bank:checking $-1 2008/06/03 * eat & shop expenses:food $1 expenses:supplies $1 assets:cash $-2 print explicitness Normally, whether posting amounts are implicit or explicit is preserved. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, if a conversion cost is implied but not written, it will not appear in the output. You can use the -x/--explicit flag to force explicit display of all amounts and costs. This can be useful for troubleshooting or for making your journal more readable and robust against data entry errors. -x is also implied by using any of -B,-V,-X,--value. The -x/--explicit flag will cause any postings with a multi-commodity amount (which can arise when a multi-commodity transaction has an implicit amount) to be split into multiple single-commodity postings, keeping the output parseable. print amount style Amounts are shown right-aligned within each transaction (but not aligned across all transactions; you can do that with ledger-mode in Emacs). Amounts will be (mostly) normalised to their commodity display style: their symbol placement, decimal mark, and digit group marks will be made consistent. By default, decimal digits are shown as they are written in the journal. With the --round option, print will try increasingly hard to display decimal digits according to the commodity display styles: - --round=none show amounts with original precisions (default) - --round=soft add/remove decimal zeros in amounts (except costs) - --round=hard round amounts (except costs), possibly hiding significant digits - --round=all round all amounts and costs soft is good for non-lossy cleanup, formatting amounts more consistently where it's safe to do so. hard and all can cause print to show invalid unbalanced journal entries; they may be useful eg for stronger cleanup, with manual fixups when needed. print parseability print's output is usually a valid hledger journal, and you can process it again with a second hledger command. This can be useful for certain kinds of search (though the same can be achieved with expr: queries now): # Show running total of food expenses paid from cash. # -f- reads from stdin. -I/--ignore-assertions is sometimes needed. $ hledger print assets:cash | hledger -f- -I reg expenses:food There are some situations where print's output can become unparseable: - Value reporting affects posting amounts but not balance assertion or balance assignment amounts, potentially causing those to fail. - Auto postings can generate postings with too many missing amounts. - Account aliases can generate bad account names. print, other features With -B/--cost, amounts with costs are shown converted to cost. With --new, print shows only transactions it has not seen on a previous run. This uses the same deduplication system as the import command. (See import's docs for details.) With -m DESC/--match=DESC, print shows one recent transaction whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar-enough match, no transaction will be shown and the program exit code will be non-zero. print output format This command also supports the output destination and output format options The output formats supported are txt, beancount, csv, tsv, json and sql. Experimental: The beancount format tries to produce Beancount-compatible output, as follows: - Transaction and postings with unmarked status are converted to cleared (*) status. - Transactions' payee and note are backslash-escaped and double-quote-escaped and wrapped in double quotes. - Transaction tags are copied to Beancount #tag format. - Commodity symbols are converted to upper case, and a small number of currency symbols like $ are converted to the corresponding currency names. - Account name parts are capitalised and unsupported characters are replaced with -. If an account name part does not begin with a letter, or if the first part is not Assets, Liabilities, Equity, Income, or Expenses, an error is raised. (Use --alias options to bring your accounts into compliance.) - An open directive is generated for each account used, on the earliest transaction date. Some limitations: - Balance assertions are removed. - Balance assignments become missing amounts. - Virtual and balanced virtual postings become regular postings. - Directives are not converted. Here's an example of print's CSV output: $ hledger print -Ocsv "txnidx","date","date2","status","code","description","comment","account","amount","commodity","credit","debit","posting-status","posting-comment" "1","2008/01/01","","","","income","","assets:bank:checking","1","$","","1","","" "1","2008/01/01","","","","income","","income:salary","-1","$","1","","","" "2","2008/06/01","","","","gift","","assets:bank:checking","1","$","","1","","" "2","2008/06/01","","","","gift","","income:gifts","-1","$","1","","","" "3","2008/06/02","","","","save","","assets:bank:saving","1","$","","1","","" "3","2008/06/02","","","","save","","assets:bank:checking","-1","$","1","","","" "4","2008/06/03","","*","","eat & shop","","expenses:food","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","expenses:supplies","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","assets:cash","-2","$","2","","","" "5","2008/12/31","","*","","pay off","","liabilities:debts","1","$","","1","","" "5","2008/12/31","","*","","pay off","","assets:bank:checking","-1","$","1","","","" - There is one CSV record per posting, with the parent transaction's fields repeated. - The "txnidx" (transaction index) field shows which postings belong to the same transaction. (This number might change if transactions are reordered within the file, files are parsed/included in a different order, etc.) - The amount is separated into "commodity" (the symbol) and "amount" (numeric quantity) fields. - The numeric amount is repeated in either the "credit" or "debit" column, for convenience. (Those names are not accurate in the accounting sense; it just puts negative amounts under credit and zero or greater amounts under debit.) hledger-1.32.3/Hledger/Cli/Commands/Register.txt0000644000000000000000000001416214555431531017561 0ustar0000000000000000register (reg) Show postings and their running total. _FLAGS The register command displays matched postings, across all accounts, in date order, with their running total or running historical balance. (See also the aregister command, which shows matched transactions in a specific account.) register normally shows line per posting, but note that multi-commodity amounts will occupy multiple lines (one line per commodity). It is typically used with a query selecting a particular account, to see that account's activity: $ hledger register checking 2008/01/01 income assets:bank:checking $1 $1 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $-1 $1 2008/12/31 pay off assets:bank:checking $-1 0 With --date2, it shows and sorts by secondary date instead. For performance reasons, column widths are chosen based on the first 1000 lines; this means unusually wide values in later lines can cause visual discontinuities as column widths are adjusted. If you want to ensure perfect alignment, at the cost of more time and memory, use the --align-all flag. The --historical/-H flag adds the balance from any undisplayed prior postings to the running total. This is useful when you want to see only recent activity, with a historically accurate running balance: $ hledger register checking -b 2008/6 --historical 2008/06/01 gift assets:bank:checking $1 $2 2008/06/02 save assets:bank:checking $-1 $1 2008/12/31 pay off assets:bank:checking $-1 0 The --depth option limits the amount of sub-account detail displayed. The --average/-A flag shows the running average posting amount instead of the running total (so, the final number displayed is the average for the whole report period). This flag implies --empty (see below). It is affected by --historical. It works best when showing just one account and one commodity. The --related/-r flag shows the other postings in the transactions of the postings which would normally be shown. The --invert flag negates all amounts. For example, it can be used on an income account where amounts are normally displayed as negative numbers. It's also useful to show postings on the checking account together with the related account: $ hledger register --related --invert assets:checking With a reporting interval, register shows summary postings, one per interval, aggregating the postings to each account: $ hledger register --monthly income 2008/01 income:salary $-1 $-1 2008/06 income:gifts $-1 $-2 Periods with no activity, and summary postings with a zero amount, are not shown by default; use the --empty/-E flag to see them: $ hledger register --monthly income -E 2008/01 income:salary $-1 $-1 2008/02 0 $-1 2008/03 0 $-1 2008/04 0 $-1 2008/05 0 $-1 2008/06 income:gifts $-1 $-2 2008/07 0 $-2 2008/08 0 $-2 2008/09 0 $-2 2008/10 0 $-2 2008/11 0 $-2 2008/12 0 $-2 Often, you'll want to see just one line per interval. The --depth option helps with this, causing subaccounts to be aggregated: $ hledger register --monthly assets --depth 1h 2008/01 assets $1 $1 2008/06 assets $-1 0 2008/12 assets $-1 $-1 Note when using report intervals, if you specify start/end dates these will be adjusted outward if necessary to contain a whole number of intervals. This ensures that the first and last intervals are full length and comparable to the others in the report. With -m DESC/--match=DESC, register does a fuzzy search for one recent posting whose description is most similar to DESC. DESC should contain at least two characters. If there is no similar-enough match, no posting will be shown and the program exit code will be non-zero. Custom register output register uses the full terminal width by default, except on windows. You can override this by setting the COLUMNS environment variable (not a bash shell variable) or by using the --width/-w option. The description and account columns normally share the space equally (about half of (width - 40) each). You can adjust this by adding a description width as part of --width's argument, comma-separated: --width W,D . Here's a diagram (won't display correctly in --help): <--------------------------------- width (W) ----------------------------------> date (10) description (D) account (W-41-D) amount (12) balance (12) DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA and some examples: $ hledger reg # use terminal width (or 80 on windows) $ hledger reg -w 100 # use width 100 $ COLUMNS=100 hledger reg # set with one-time environment variable $ export COLUMNS=100; hledger reg # set till session end (or window resize) $ hledger reg -w 100,40 # set overall width 100, description width 40 $ hledger reg -w $COLUMNS,40 # use terminal width, & description width 40 This command also supports the output destination and output format options The output formats supported are txt, csv, tsv, and (experimental) json. hledger-1.32.3/Hledger/Cli/Commands/Rewrite.txt0000644000000000000000000001101114555141606017405 0ustar0000000000000000rewrite Print all transactions, rewriting the postings of matched transactions. For now the only rewrite available is adding new postings, like print --auto. _FLAGS This is a start at a generic rewriter of transaction entries. It reads the default journal and prints the transactions, like print, but adds one or more specified postings to any transactions matching QUERY. The posting amounts can be fixed, or a multiplier of the existing transaction's first posting amount. Examples: $ hledger-rewrite.hs ^income --add-posting '(liabilities:tax) *.33 ; income tax' --add-posting '(reserve:gifts) $100' $ hledger-rewrite.hs expenses:gifts --add-posting '(reserve:gifts) *-1"' $ hledger-rewrite.hs -f rewrites.hledger rewrites.hledger may consist of entries like: = ^income amt:<0 date:2017 (liabilities:tax) *0.33 ; tax on income (reserve:grocery) *0.25 ; reserve 25% for grocery (reserve:) *0.25 ; reserve 25% for grocery Note the single quotes to protect the dollar sign from bash, and the two spaces between account and amount. More: $ hledger rewrite -- [QUERY] --add-posting "ACCT AMTEXPR" ... $ hledger rewrite -- ^income --add-posting '(liabilities:tax) *.33' $ hledger rewrite -- expenses:gifts --add-posting '(budget:gifts) *-1"' $ hledger rewrite -- ^income --add-posting '(budget:foreign currency) *0.25 JPY; diversify' Argument for --add-posting option is a usual posting of transaction with an exception for amount specification. More precisely, you can use '*' (star symbol) before the amount to indicate that that this is a factor for an amount of original matched posting. If the amount includes a commodity name, the new posting amount will be in the new commodity; otherwise, it will be in the matched posting amount's commodity. Re-write rules in a file During the run this tool will execute so called "Automated Transactions" found in any journal it process. I.e instead of specifying this operations in command line you can put them in a journal file. $ rewrite-rules.journal Make contents look like this: = ^income (liabilities:tax) *.33 = expenses:gifts budget:gifts *-1 assets:budget *1 Note that '=' (equality symbol) that is used instead of date in transactions you usually write. It indicates the query by which you want to match the posting to add new ones. $ hledger rewrite -- -f input.journal -f rewrite-rules.journal > rewritten-tidy-output.journal This is something similar to the commands pipeline: $ hledger rewrite -- -f input.journal '^income' --add-posting '(liabilities:tax) *.33' \ | hledger rewrite -- -f - expenses:gifts --add-posting 'budget:gifts *-1' \ --add-posting 'assets:budget *1' \ > rewritten-tidy-output.journal It is important to understand that relative order of such entries in journal is important. You can re-use result of previously added postings. Diff output format To use this tool for batch modification of your journal files you may find useful output in form of unified diff. $ hledger rewrite -- --diff -f examples/sample.journal '^income' --add-posting '(liabilities:tax) *.33' Output might look like: --- /tmp/examples/sample.journal +++ /tmp/examples/sample.journal @@ -18,3 +18,4 @@ 2008/01/01 income - assets:bank:checking $1 + assets:bank:checking $1 income:salary + (liabilities:tax) 0 @@ -22,3 +23,4 @@ 2008/06/01 gift - assets:bank:checking $1 + assets:bank:checking $1 income:gifts + (liabilities:tax) 0 If you'll pass this through patch tool you'll get transactions containing the posting that matches your query be updated. Note that multiple files might be update according to list of input files specified via --file options and include directives inside of these files. Be careful. Whole transaction being re-formatted in a style of output from hledger print. See also: https://github.com/simonmichael/hledger/issues/99 rewrite vs. print --auto This command predates print --auto, and currently does much the same thing, but with these differences: - with multiple files, rewrite lets rules in any file affect all other files. print --auto uses standard directive scoping; rules affect only child files. - rewrite's query limits which transactions can be rewritten; all are printed. print --auto's query limits which transactions are printed. - rewrite applies rules specified on command line or in the journal. print --auto applies rules specified in the journal. hledger-1.32.3/Hledger/Cli/Commands/Roi.txt0000644000000000000000000001612614555141606016531 0ustar0000000000000000roi Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. _FLAGS At a minimum, you need to supply a query (which could be just an account name) to select your investment(s) with --inv, and another query to identify your profit and loss transactions with --pnl. If you do not record changes in the value of your investment manually, or do not require computation of time-weighted return (TWR), --pnl could be an empty query (--pnl "" or --pnl STR where STR does not match any of your accounts). This command will compute and display the internalized rate of return (IRR, also known as money-weighted rate of return) and time-weighted rate of return (TWR) for your investments for the time period requested. IRR is always annualized due to the way it is computed, but TWR is reported both as a rate over the chosen reporting period and as an annual rate. Price directives will be taken into account if you supply appropriate --cost or --value flags (see VALUATION). Note, in some cases this report can fail, for these reasons: - Error (NotBracketed): No solution for Internal Rate of Return (IRR). Possible causes: IRR is huge (>1000000%), balance of investment becomes negative at some point in time. - Error (SearchFailed): Failed to find solution for Internal Rate of Return (IRR). Either search does not converge to a solution, or converges too slowly. Examples: - Using roi to compute total return of investment in stocks: https://github.com/simonmichael/hledger/blob/master/examples/investing/roi-unrealised.ledger - Cookbook > Return on Investment: https://hledger.org/roi.html Spaces and special characters in --inv and --pnl Note that --inv and --pnl's argument is a query, and queries could have several space-separated terms (see QUERIES). To indicate that all search terms form single command-line argument, you will need to put them in quotes (see Special characters): $ hledger roi --inv 'term1 term2 term3 ...' If any query terms contain spaces themselves, you will need an extra level of nested quoting, eg: $ hledger roi --inv="'Assets:Test 1'" --pnl="'Equity:Unrealized Profit and Loss'" Semantics of --inv and --pnl Query supplied to --inv has to match all transactions that are related to your investment. Transactions not matching --inv will be ignored. In these transactions, ROI will conside postings that match --inv to be "investment postings" and other postings (not matching --inv) will be sorted into two categories: "cash flow" and "profit and loss", as ROI needs to know which part of the investment value is your contributions and which is due to the return on investment. - "Cash flow" is depositing or withdrawing money, buying or selling assets, or otherwise converting between your investment commodity and any other commodity. Example: 2019-01-01 Investing in Snake Oil assets:cash -$100 investment:snake oil 2020-01-01 Selling my Snake Oil assets:cash $10 investment:snake oil = 0 - "Profit and loss" is change in the value of your investment: 2019-06-01 Snake Oil falls in value investment:snake oil = $57 equity:unrealized profit or loss All non-investment postings are assumed to be "cash flow", unless they match --pnl query. Changes in value of your investment due to "profit and loss" postings will be considered as part of your investment return. Example: if you use --inv snake --pnl equity:unrealized, then postings in the example below would be classifed as: 2019-01-01 Snake Oil #1 assets:cash -$100 ; cash flow posting investment:snake oil ; investment posting 2019-03-01 Snake Oil #2 equity:unrealized pnl -$100 ; profit and loss posting snake oil ; investment posting 2019-07-01 Snake Oil #3 equity:unrealized pnl ; profit and loss posting cash -$100 ; cash flow posting snake oil $50 ; investment posting IRR and TWR explained "ROI" stands for "return on investment". Traditionally this was computed as a difference between current value of investment and its initial value, expressed in percentage of the initial value. However, this approach is only practical in simple cases, where investments receives no in-flows or out-flows of money, and where rate of growth is fixed over time. For more complex scenarios you need different ways to compute rate of return, and this command implements two of them: IRR and TWR. Internal rate of return, or "IRR" (also called "money-weighted rate of return") takes into account effects of in-flows and out-flows, and the time between them. Investment at a particular fixed interest rate is going to give you more interest than the same amount invested at the same interest rate, but made later in time. If you are withdrawing from your investment, your future gains would be smaller (in absolute numbers), and will be a smaller percentage of your initial investment, so your IRR will be smaller. And if you are adding to your investment, you will receive bigger absolute gains, which will be a bigger percentage of your initial investment, so your IRR will be larger. As mentioned before, in-flows and out-flows would be any cash that you personally put in or withdraw, and for the "roi" command, these are the postings that match the query in the--inv argument and NOT match the query in the--pnl argument. If you manually record changes in the value of your investment as transactions that balance them against "profit and loss" (or "unrealized gains") account or use price directives, then in order for IRR to compute the precise effect of your in-flows and out-flows on the rate of return, you will need to record the value of your investement on or close to the days when in- or out-flows occur. In technical terms, IRR uses the same approach as computation of net present value, and tries to find a discount rate that makes net present value of all the cash flows of your investment to add up to zero. This could be hard to wrap your head around, especially if you haven't done discounted cash flow analysis before. Implementation of IRR in hledger should produce results that match the =XIRR formula in Excel. Second way to compute rate of return that roi command implements is called "time-weighted rate of return" or "TWR". Like IRR, it will account for the effect of your in-flows and out-flows, but unlike IRR it will try to compute the true rate of return of the underlying asset, compensating for the effect that deposits and withdrawas have on the apparent rate of growth of your investment. TWR represents your investment as an imaginary "unit fund" where in-flows/ out-flows lead to buying or selling "units" of your investment and changes in its value change the value of "investment unit". Change in "unit price" over the reporting period gives you rate of return of your investment, and make TWR less sensitive than IRR to the effects of cash in-flows and out-flows. References: - Explanation of rate of return - Explanation of IRR - Explanation of TWR - IRR vs TWR - Examples of computing IRR and TWR and discussion of the limitations of both metrics hledger-1.32.3/Hledger/Cli/Commands/Stats.txt0000644000000000000000000000255114555141607017074 0ustar0000000000000000stats Show journal and performance statistics. _FLAGS The stats command displays summary information for the whole journal, or a matched part of it. With a reporting interval, it shows a report for each report period. At the end, it shows (in the terminal) the overall run time and number of transactions processed per second. Note these are approximate and will vary based on machine, current load, data size, hledger version, haskell lib versions, GHC version.. but they may be of interest. The stats command's run time is similar to that of a single-column balance report. Example: $ hledger stats -f examples/1000x1000x10.journal Main file : /Users/simon/src/hledger/examples/1000x1000x10.journal Included files : Transactions span : 2000-01-01 to 2002-09-27 (1000 days) Last transaction : 2002-09-26 (6995 days ago) Transactions : 1000 (1.0 per day) Transactions last 30 days: 0 (0.0 per day) Transactions last 7 days : 0 (0.0 per day) Payees/descriptions : 1000 Accounts : 1000 (depth 10) Commodities : 26 (A, B, C, D, E, F, G, H, I, J, K, L, M, N, O, P, Q, R, S, T, U, V, W, X, Y, Z) Market prices : 1000 (A) Run time : 0.12 s Throughput : 8342 txns/s This command supports the -o/--output-file option (but not -O/--output-format selection). hledger-1.32.3/Hledger/Cli/Commands/Tags.txt0000644000000000000000000000175414555141606016677 0ustar0000000000000000tags List the tags used in the journal, or their values. _FLAGS This command lists the tag names used in the journal, whether on transactions, postings, or account declarations. With a TAGREGEX argument, only tag names matching this regular expression (case insensitive, infix matched) are shown. With QUERY arguments, only transactions and accounts matching this query are considered. If the query involves transaction fields (date:, desc:, amt:, ...), the search is restricted to the matched transactions and their accounts. With the --values flag, the tags' unique non-empty values are listed instead. With -E/--empty, blank/empty values are also shown. With --parsed, tags or values are shown in the order they were parsed, with duplicates included. (Except, tags from account declarations are always shown first.) Tip: remember, accounts also acquire tags from their parents, postings also acquire tags from their account and transaction, transactions also acquire tags from their postings. hledger-1.32.3/Hledger/Cli/Commands/Test.txt0000644000000000000000000000134314555141606016712 0ustar0000000000000000test Run built-in unit tests. _FLAGS This command runs the unit tests built in to hledger and hledger-lib, printing the results on stdout. If any test fails, the exit code will be non-zero. This is mainly used by hledger developers, but you can also use it to sanity-check the installed hledger executable on your platform. All tests are expected to pass - if you ever see a failure, please report as a bug! This command also accepts tasty test runner options, written after a -- (double hyphen). Eg to run only the tests in Hledger.Data.Amount, with ANSI colour codes disabled: $ hledger test -- -pData.Amount --color=never For help on these, see https://github.com/feuerbach/tasty#options (-- --help currently doesn't show them). hledger-1.32.3/LICENSE0000644000000000000000000010451313302271456012414 0ustar0000000000000000 GNU GENERAL PUBLIC LICENSE Version 3, 29 June 2007 Copyright (C) 2007 Free Software Foundation, Inc. Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. Preamble The GNU General Public License is a free, copyleft license for software and other kinds of works. The licenses for most software and other practical works are designed to take away your freedom to share and change the works. By contrast, the GNU General Public License is intended to guarantee your freedom to share and change all versions of a program--to make sure it remains free software for all its users. We, the Free Software Foundation, use the GNU General Public License for most of our software; it applies also to any other work released this way by its authors. You can apply it to your programs, too. When we speak of free software, we are referring to freedom, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for them if you wish), that you receive source code or can get it if you want it, that you can change the software or use pieces of it in new free programs, and that you know you can do these things. To protect your rights, we need to prevent others from denying you these rights or asking you to surrender the rights. Therefore, you have certain responsibilities if you distribute copies of the software, or if you modify it: responsibilities to respect the freedom of others. For example, if you distribute copies of such a program, whether gratis or for a fee, you must pass on to the recipients the same freedoms that you received. You must make sure that they, too, receive or can get the source code. And you must show them these terms so they know their rights. Developers that use the GNU GPL protect your rights with two steps: (1) assert copyright on the software, and (2) offer you this License giving you legal permission to copy, distribute and/or modify it. For the developers' and authors' protection, the GPL clearly explains that there is no warranty for this free software. For both users' and authors' sake, the GPL requires that modified versions be marked as changed, so that their problems will not be attributed erroneously to authors of previous versions. Some devices are designed to deny users access to install or run modified versions of the software inside them, although the manufacturer can do so. This is fundamentally incompatible with the aim of protecting users' freedom to change the software. The systematic pattern of such abuse occurs in the area of products for individuals to use, which is precisely where it is most unacceptable. Therefore, we have designed this version of the GPL to prohibit the practice for those products. If such problems arise substantially in other domains, we stand ready to extend this provision to those domains in future versions of the GPL, as needed to protect the freedom of users. Finally, every program is threatened constantly by software patents. States should not allow patents to restrict development and use of software on general-purpose computers, but in those that do, we wish to avoid the special danger that patents applied to a free program could make it effectively proprietary. To prevent this, the GPL assures that patents cannot be used to render the program non-free. The precise terms and conditions for copying, distribution and modification follow. TERMS AND CONDITIONS 0. Definitions. "This License" refers to version 3 of the GNU General Public License. "Copyright" also means copyright-like laws that apply to other kinds of works, such as semiconductor masks. "The Program" refers to any copyrightable work licensed under this License. Each licensee is addressed as "you". "Licensees" and "recipients" may be individuals or organizations. To "modify" a work means to copy from or adapt all or part of the work in a fashion requiring copyright permission, other than the making of an exact copy. The resulting work is called a "modified version" of the earlier work or a work "based on" the earlier work. A "covered work" means either the unmodified Program or a work based on the Program. To "propagate" a work means to do anything with it that, without permission, would make you directly or secondarily liable for infringement under applicable copyright law, except executing it on a computer or modifying a private copy. Propagation includes copying, distribution (with or without modification), making available to the public, and in some countries other activities as well. To "convey" a work means any kind of propagation that enables other parties to make or receive copies. Mere interaction with a user through a computer network, with no transfer of a copy, is not conveying. An interactive user interface displays "Appropriate Legal Notices" to the extent that it includes a convenient and prominently visible feature that (1) displays an appropriate copyright notice, and (2) tells the user that there is no warranty for the work (except to the extent that warranties are provided), that licensees may convey the work under this License, and how to view a copy of this License. If the interface presents a list of user commands or options, such as a menu, a prominent item in the list meets this criterion. 1. Source Code. The "source code" for a work means the preferred form of the work for making modifications to it. "Object code" means any non-source form of a work. A "Standard Interface" means an interface that either is an official standard defined by a recognized standards body, or, in the case of interfaces specified for a particular programming language, one that is widely used among developers working in that language. The "System Libraries" of an executable work include anything, other than the work as a whole, that (a) is included in the normal form of packaging a Major Component, but which is not part of that Major Component, and (b) serves only to enable use of the work with that Major Component, or to implement a Standard Interface for which an implementation is available to the public in source code form. A "Major Component", in this context, means a major essential component (kernel, window system, and so on) of the specific operating system (if any) on which the executable work runs, or a compiler used to produce the work, or an object code interpreter used to run it. The "Corresponding Source" for a work in object code form means all the source code needed to generate, install, and (for an executable work) run the object code and to modify the work, including scripts to control those activities. However, it does not include the work's System Libraries, or general-purpose tools or generally available free programs which are used unmodified in performing those activities but which are not part of the work. For example, Corresponding Source includes interface definition files associated with source files for the work, and the source code for shared libraries and dynamically linked subprograms that the work is specifically designed to require, such as by intimate data communication or control flow between those subprograms and other parts of the work. The Corresponding Source need not include anything that users can regenerate automatically from other parts of the Corresponding Source. The Corresponding Source for a work in source code form is that same work. 2. Basic Permissions. All rights granted under this License are granted for the term of copyright on the Program, and are irrevocable provided the stated conditions are met. This License explicitly affirms your unlimited permission to run the unmodified Program. The output from running a covered work is covered by this License only if the output, given its content, constitutes a covered work. This License acknowledges your rights of fair use or other equivalent, as provided by copyright law. You may make, run and propagate covered works that you do not convey, without conditions so long as your license otherwise remains in force. You may convey covered works to others for the sole purpose of having them make modifications exclusively for you, or provide you with facilities for running those works, provided that you comply with the terms of this License in conveying all material for which you do not control copyright. Those thus making or running the covered works for you must do so exclusively on your behalf, under your direction and control, on terms that prohibit them from making any copies of your copyrighted material outside their relationship with you. Conveying under any other circumstances is permitted solely under the conditions stated below. Sublicensing is not allowed; section 10 makes it unnecessary. 3. Protecting Users' Legal Rights From Anti-Circumvention Law. No covered work shall be deemed part of an effective technological measure under any applicable law fulfilling obligations under article 11 of the WIPO copyright treaty adopted on 20 December 1996, or similar laws prohibiting or restricting circumvention of such measures. When you convey a covered work, you waive any legal power to forbid circumvention of technological measures to the extent such circumvention is effected by exercising rights under this License with respect to the covered work, and you disclaim any intention to limit operation or modification of the work as a means of enforcing, against the work's users, your or third parties' legal rights to forbid circumvention of technological measures. 4. Conveying Verbatim Copies. You may convey verbatim copies of the Program's source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice; keep intact all notices stating that this License and any non-permissive terms added in accord with section 7 apply to the code; keep intact all notices of the absence of any warranty; and give all recipients a copy of this License along with the Program. You may charge any price or no price for each copy that you convey, and you may offer support or warranty protection for a fee. 5. Conveying Modified Source Versions. You may convey a work based on the Program, or the modifications to produce it from the Program, in the form of source code under the terms of section 4, provided that you also meet all of these conditions: a) The work must carry prominent notices stating that you modified it, and giving a relevant date. b) The work must carry prominent notices stating that it is released under this License and any conditions added under section 7. This requirement modifies the requirement in section 4 to "keep intact all notices". c) You must license the entire work, as a whole, under this License to anyone who comes into possession of a copy. This License will therefore apply, along with any applicable section 7 additional terms, to the whole of the work, and all its parts, regardless of how they are packaged. This License gives no permission to license the work in any other way, but it does not invalidate such permission if you have separately received it. d) If the work has interactive user interfaces, each must display Appropriate Legal Notices; however, if the Program has interactive interfaces that do not display Appropriate Legal Notices, your work need not make them do so. A compilation of a covered work with other separate and independent works, which are not by their nature extensions of the covered work, and which are not combined with it such as to form a larger program, in or on a volume of a storage or distribution medium, is called an "aggregate" if the compilation and its resulting copyright are not used to limit the access or legal rights of the compilation's users beyond what the individual works permit. Inclusion of a covered work in an aggregate does not cause this License to apply to the other parts of the aggregate. 6. Conveying Non-Source Forms. You may convey a covered work in object code form under the terms of sections 4 and 5, provided that you also convey the machine-readable Corresponding Source under the terms of this License, in one of these ways: a) Convey the object code in, or embodied in, a physical product (including a physical distribution medium), accompanied by the Corresponding Source fixed on a durable physical medium customarily used for software interchange. b) Convey the object code in, or embodied in, a physical product (including a physical distribution medium), accompanied by a written offer, valid for at least three years and valid for as long as you offer spare parts or customer support for that product model, to give anyone who possesses the object code either (1) a copy of the Corresponding Source for all the software in the product that is covered by this License, on a durable physical medium customarily used for software interchange, for a price no more than your reasonable cost of physically performing this conveying of source, or (2) access to copy the Corresponding Source from a network server at no charge. c) Convey individual copies of the object code with a copy of the written offer to provide the Corresponding Source. This alternative is allowed only occasionally and noncommercially, and only if you received the object code with such an offer, in accord with subsection 6b. d) Convey the object code by offering access from a designated place (gratis or for a charge), and offer equivalent access to the Corresponding Source in the same way through the same place at no further charge. You need not require recipients to copy the Corresponding Source along with the object code. If the place to copy the object code is a network server, the Corresponding Source may be on a different server (operated by you or a third party) that supports equivalent copying facilities, provided you maintain clear directions next to the object code saying where to find the Corresponding Source. Regardless of what server hosts the Corresponding Source, you remain obligated to ensure that it is available for as long as needed to satisfy these requirements. e) Convey the object code using peer-to-peer transmission, provided you inform other peers where the object code and Corresponding Source of the work are being offered to the general public at no charge under subsection 6d. A separable portion of the object code, whose source code is excluded from the Corresponding Source as a System Library, need not be included in conveying the object code work. A "User Product" is either (1) a "consumer product", which means any tangible personal property which is normally used for personal, family, or household purposes, or (2) anything designed or sold for incorporation into a dwelling. In determining whether a product is a consumer product, doubtful cases shall be resolved in favor of coverage. For a particular product received by a particular user, "normally used" refers to a typical or common use of that class of product, regardless of the status of the particular user or of the way in which the particular user actually uses, or expects or is expected to use, the product. A product is a consumer product regardless of whether the product has substantial commercial, industrial or non-consumer uses, unless such uses represent the only significant mode of use of the product. "Installation Information" for a User Product means any methods, procedures, authorization keys, or other information required to install and execute modified versions of a covered work in that User Product from a modified version of its Corresponding Source. The information must suffice to ensure that the continued functioning of the modified object code is in no case prevented or interfered with solely because modification has been made. If you convey an object code work under this section in, or with, or specifically for use in, a User Product, and the conveying occurs as part of a transaction in which the right of possession and use of the User Product is transferred to the recipient in perpetuity or for a fixed term (regardless of how the transaction is characterized), the Corresponding Source conveyed under this section must be accompanied by the Installation Information. But this requirement does not apply if neither you nor any third party retains the ability to install modified object code on the User Product (for example, the work has been installed in ROM). The requirement to provide Installation Information does not include a requirement to continue to provide support service, warranty, or updates for a work that has been modified or installed by the recipient, or for the User Product in which it has been modified or installed. Access to a network may be denied when the modification itself materially and adversely affects the operation of the network or violates the rules and protocols for communication across the network. Corresponding Source conveyed, and Installation Information provided, in accord with this section must be in a format that is publicly documented (and with an implementation available to the public in source code form), and must require no special password or key for unpacking, reading or copying. 7. Additional Terms. "Additional permissions" are terms that supplement the terms of this License by making exceptions from one or more of its conditions. Additional permissions that are applicable to the entire Program shall be treated as though they were included in this License, to the extent that they are valid under applicable law. If additional permissions apply only to part of the Program, that part may be used separately under those permissions, but the entire Program remains governed by this License without regard to the additional permissions. When you convey a copy of a covered work, you may at your option remove any additional permissions from that copy, or from any part of it. (Additional permissions may be written to require their own removal in certain cases when you modify the work.) You may place additional permissions on material, added by you to a covered work, for which you have or can give appropriate copyright permission. Notwithstanding any other provision of this License, for material you add to a covered work, you may (if authorized by the copyright holders of that material) supplement the terms of this License with terms: a) Disclaiming warranty or limiting liability differently from the terms of sections 15 and 16 of this License; or b) Requiring preservation of specified reasonable legal notices or author attributions in that material or in the Appropriate Legal Notices displayed by works containing it; or c) Prohibiting misrepresentation of the origin of that material, or requiring that modified versions of such material be marked in reasonable ways as different from the original version; or d) Limiting the use for publicity purposes of names of licensors or authors of the material; or e) Declining to grant rights under trademark law for use of some trade names, trademarks, or service marks; or f) Requiring indemnification of licensors and authors of that material by anyone who conveys the material (or modified versions of it) with contractual assumptions of liability to the recipient, for any liability that these contractual assumptions directly impose on those licensors and authors. All other non-permissive additional terms are considered "further restrictions" within the meaning of section 10. If the Program as you received it, or any part of it, contains a notice stating that it is governed by this License along with a term that is a further restriction, you may remove that term. If a license document contains a further restriction but permits relicensing or conveying under this License, you may add to a covered work material governed by the terms of that license document, provided that the further restriction does not survive such relicensing or conveying. If you add terms to a covered work in accord with this section, you must place, in the relevant source files, a statement of the additional terms that apply to those files, or a notice indicating where to find the applicable terms. Additional terms, permissive or non-permissive, may be stated in the form of a separately written license, or stated as exceptions; the above requirements apply either way. 8. Termination. You may not propagate or modify a covered work except as expressly provided under this License. Any attempt otherwise to propagate or modify it is void, and will automatically terminate your rights under this License (including any patent licenses granted under the third paragraph of section 11). However, if you cease all violation of this License, then your license from a particular copyright holder is reinstated (a) provisionally, unless and until the copyright holder explicitly and finally terminates your license, and (b) permanently, if the copyright holder fails to notify you of the violation by some reasonable means prior to 60 days after the cessation. Moreover, your license from a particular copyright holder is reinstated permanently if the copyright holder notifies you of the violation by some reasonable means, this is the first time you have received notice of violation of this License (for any work) from that copyright holder, and you cure the violation prior to 30 days after your receipt of the notice. Termination of your rights under this section does not terminate the licenses of parties who have received copies or rights from you under this License. If your rights have been terminated and not permanently reinstated, you do not qualify to receive new licenses for the same material under section 10. 9. Acceptance Not Required for Having Copies. You are not required to accept this License in order to receive or run a copy of the Program. Ancillary propagation of a covered work occurring solely as a consequence of using peer-to-peer transmission to receive a copy likewise does not require acceptance. However, nothing other than this License grants you permission to propagate or modify any covered work. These actions infringe copyright if you do not accept this License. Therefore, by modifying or propagating a covered work, you indicate your acceptance of this License to do so. 10. Automatic Licensing of Downstream Recipients. Each time you convey a covered work, the recipient automatically receives a license from the original licensors, to run, modify and propagate that work, subject to this License. You are not responsible for enforcing compliance by third parties with this License. An "entity transaction" is a transaction transferring control of an organization, or substantially all assets of one, or subdividing an organization, or merging organizations. If propagation of a covered work results from an entity transaction, each party to that transaction who receives a copy of the work also receives whatever licenses to the work the party's predecessor in interest had or could give under the previous paragraph, plus a right to possession of the Corresponding Source of the work from the predecessor in interest, if the predecessor has it or can get it with reasonable efforts. You may not impose any further restrictions on the exercise of the rights granted or affirmed under this License. For example, you may not impose a license fee, royalty, or other charge for exercise of rights granted under this License, and you may not initiate litigation (including a cross-claim or counterclaim in a lawsuit) alleging that any patent claim is infringed by making, using, selling, offering for sale, or importing the Program or any portion of it. 11. Patents. A "contributor" is a copyright holder who authorizes use under this License of the Program or a work on which the Program is based. The work thus licensed is called the contributor's "contributor version". A contributor's "essential patent claims" are all patent claims owned or controlled by the contributor, whether already acquired or hereafter acquired, that would be infringed by some manner, permitted by this License, of making, using, or selling its contributor version, but do not include claims that would be infringed only as a consequence of further modification of the contributor version. For purposes of this definition, "control" includes the right to grant patent sublicenses in a manner consistent with the requirements of this License. Each contributor grants you a non-exclusive, worldwide, royalty-free patent license under the contributor's essential patent claims, to make, use, sell, offer for sale, import and otherwise run, modify and propagate the contents of its contributor version. In the following three paragraphs, a "patent license" is any express agreement or commitment, however denominated, not to enforce a patent (such as an express permission to practice a patent or covenant not to sue for patent infringement). To "grant" such a patent license to a party means to make such an agreement or commitment not to enforce a patent against the party. If you convey a covered work, knowingly relying on a patent license, and the Corresponding Source of the work is not available for anyone to copy, free of charge and under the terms of this License, through a publicly available network server or other readily accessible means, then you must either (1) cause the Corresponding Source to be so available, or (2) arrange to deprive yourself of the benefit of the patent license for this particular work, or (3) arrange, in a manner consistent with the requirements of this License, to extend the patent license to downstream recipients. "Knowingly relying" means you have actual knowledge that, but for the patent license, your conveying the covered work in a country, or your recipient's use of the covered work in a country, would infringe one or more identifiable patents in that country that you have reason to believe are valid. If, pursuant to or in connection with a single transaction or arrangement, you convey, or propagate by procuring conveyance of, a covered work, and grant a patent license to some of the parties receiving the covered work authorizing them to use, propagate, modify or convey a specific copy of the covered work, then the patent license you grant is automatically extended to all recipients of the covered work and works based on it. A patent license is "discriminatory" if it does not include within the scope of its coverage, prohibits the exercise of, or is conditioned on the non-exercise of one or more of the rights that are specifically granted under this License. You may not convey a covered work if you are a party to an arrangement with a third party that is in the business of distributing software, under which you make payment to the third party based on the extent of your activity of conveying the work, and under which the third party grants, to any of the parties who would receive the covered work from you, a discriminatory patent license (a) in connection with copies of the covered work conveyed by you (or copies made from those copies), or (b) primarily for and in connection with specific products or compilations that contain the covered work, unless you entered into that arrangement, or that patent license was granted, prior to 28 March 2007. Nothing in this License shall be construed as excluding or limiting any implied license or other defenses to infringement that may otherwise be available to you under applicable patent law. 12. No Surrender of Others' Freedom. If conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot convey a covered work so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not convey it at all. For example, if you agree to terms that obligate you to collect a royalty for further conveying from those to whom you convey the Program, the only way you could satisfy both those terms and this License would be to refrain entirely from conveying the Program. 13. Use with the GNU Affero General Public License. Notwithstanding any other provision of this License, you have permission to link or combine any covered work with a work licensed under version 3 of the GNU Affero General Public License into a single combined work, and to convey the resulting work. The terms of this License will continue to apply to the part which is the covered work, but the special requirements of the GNU Affero General Public License, section 13, concerning interaction through a network will apply to the combination as such. 14. Revised Versions of this License. The Free Software Foundation may publish revised and/or new versions of the GNU General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Program specifies that a certain numbered version of the GNU General Public License "or any later version" applies to it, you have the option of following the terms and conditions either of that numbered version or of any later version published by the Free Software Foundation. If the Program does not specify a version number of the GNU General Public License, you may choose any version ever published by the Free Software Foundation. If the Program specifies that a proxy can decide which future versions of the GNU General Public License can be used, that proxy's public statement of acceptance of a version permanently authorizes you to choose that version for the Program. Later license versions may give you additional or different permissions. However, no additional obligations are imposed on any author or copyright holder as a result of your choosing to follow a later version. 15. Disclaimer of Warranty. THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 16. Limitation of Liability. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MODIFIES AND/OR CONVEYS THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. 17. Interpretation of Sections 15 and 16. If the disclaimer of warranty and limitation of liability provided above cannot be given local legal effect according to their terms, reviewing courts shall apply local law that most closely approximates an absolute waiver of all civil liability in connection with the Program, unless a warranty or assumption of liability accompanies a copy of the Program in return for a fee. END OF TERMS AND CONDITIONS How to Apply These Terms to Your New Programs If you develop a new program, and you want it to be of the greatest possible use to the public, the best way to achieve this is to make it free software which everyone can redistribute and change under these terms. To do so, attach the following notices to the program. It is safest to attach them to the start of each source file to most effectively state the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found. Copyright (C) This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . Also add information on how to contact you by electronic and paper mail. If the program does terminal interaction, make it output a short notice like this when it starts in an interactive mode: Copyright (C) This program comes with ABSOLUTELY NO WARRANTY; for details type `show w'. This is free software, and you are welcome to redistribute it under certain conditions; type `show c' for details. The hypothetical commands `show w' and `show c' should show the appropriate parts of the General Public License. Of course, your program's commands might be different; for a GUI interface, you would use an "about box". You should also get your employer (if you work as a programmer) or school, if any, to sign a "copyright disclaimer" for the program, if necessary. For more information on this, and how to apply and follow the GNU GPL, see . The GNU General Public License does not permit incorporating your program into proprietary programs. If your program is a subroutine library, you may consider it more useful to permit linking proprietary applications with the library. If this is what you want to do, use the GNU Lesser General Public License instead of this License. But first, please read . hledger-1.32.3/Setup.hs0000644000000000000000000000005613302271456013040 0ustar0000000000000000import Distribution.Simple main = defaultMain hledger-1.32.3/hledger.cabal0000644000000000000000000002233314555425350014011 0ustar0000000000000000cabal-version: 1.12 -- This file has been generated from package.yaml by hpack version 0.36.0. -- -- see: https://github.com/sol/hpack name: hledger version: 1.32.3 synopsis: Command-line interface for the hledger accounting system description: The command-line interface for the hledger accounting system. Its basic function is to read a plain text file describing financial transactions and produce useful reports. . hledger is a robust, cross-platform set of tools for tracking money, time, or any other commodity, using double-entry accounting and a simple, editable file format, with command-line, terminal and web interfaces. It is a Haskell rewrite of Ledger, and one of the leading implementations of Plain Text Accounting. Read more at: category: Finance, Console stability: stable homepage: http://hledger.org bug-reports: http://bugs.hledger.org author: Simon Michael maintainer: Simon Michael license: GPL-3 license-file: LICENSE build-type: Simple tested-with: GHC==8.10.7, GHC==9.0.2, GHC==9.2.8, GHC==9.4.5, GHC==9.6.2 extra-source-files: CHANGES.md README.md test/unittest.hs bench/10000x1000x10.journal hledger.1 hledger.txt hledger.info embeddedfiles/add.cast embeddedfiles/balance.cast embeddedfiles/install.cast embeddedfiles/print.cast embeddedfiles/hledger.1 embeddedfiles/hledger.txt embeddedfiles/hledger.info embeddedfiles/hledger-ui.1 embeddedfiles/hledger-ui.txt embeddedfiles/hledger-ui.info embeddedfiles/hledger-web.1 embeddedfiles/hledger-web.txt embeddedfiles/hledger-web.info shell-completion/hledger-completion.bash Hledger/Cli/Commands/Accounts.txt Hledger/Cli/Commands/Activity.txt Hledger/Cli/Commands/Add.txt Hledger/Cli/Commands/Aregister.txt Hledger/Cli/Commands/Balance.txt Hledger/Cli/Commands/Balancesheet.txt Hledger/Cli/Commands/Balancesheetequity.txt Hledger/Cli/Commands/Cashflow.txt Hledger/Cli/Commands/Check.txt Hledger/Cli/Commands/Close.txt Hledger/Cli/Commands/Codes.txt Hledger/Cli/Commands/Commodities.txt Hledger/Cli/Commands/Demo.txt Hledger/Cli/Commands/Descriptions.txt Hledger/Cli/Commands/Diff.txt Hledger/Cli/Commands/Files.txt Hledger/Cli/Commands/Help.txt Hledger/Cli/Commands/Import.txt Hledger/Cli/Commands/Incomestatement.txt Hledger/Cli/Commands/Notes.txt Hledger/Cli/Commands/Payees.txt Hledger/Cli/Commands/Prices.txt Hledger/Cli/Commands/Print.txt Hledger/Cli/Commands/Register.txt Hledger/Cli/Commands/Rewrite.txt Hledger/Cli/Commands/Roi.txt Hledger/Cli/Commands/Stats.txt Hledger/Cli/Commands/Tags.txt Hledger/Cli/Commands/Test.txt source-repository head type: git location: https://github.com/simonmichael/hledger flag terminfo description: On POSIX systems, build with the terminfo lib for detecting terminal width. manual: False default: True flag threaded description: Build with support for multithreaded execution manual: False default: True library exposed-modules: Hledger.Cli Hledger.Cli.CliOptions Hledger.Cli.Commands Hledger.Cli.Commands.Accounts Hledger.Cli.Commands.Activity Hledger.Cli.Commands.Add Hledger.Cli.Commands.Aregister Hledger.Cli.Commands.Balance Hledger.Cli.Commands.Balancesheet Hledger.Cli.Commands.Balancesheetequity Hledger.Cli.Commands.Cashflow Hledger.Cli.Commands.Check Hledger.Cli.Commands.Close Hledger.Cli.Commands.Codes Hledger.Cli.Commands.Commodities Hledger.Cli.Commands.Demo Hledger.Cli.Commands.Descriptions Hledger.Cli.Commands.Diff Hledger.Cli.Commands.Help Hledger.Cli.Commands.Files Hledger.Cli.Commands.Import Hledger.Cli.Commands.Incomestatement Hledger.Cli.Commands.Notes Hledger.Cli.Commands.Payees Hledger.Cli.Commands.Prices Hledger.Cli.Commands.Print Hledger.Cli.Commands.Register Hledger.Cli.Commands.Rewrite Hledger.Cli.Commands.Roi Hledger.Cli.Commands.Stats Hledger.Cli.Commands.Tags Hledger.Cli.CompoundBalanceCommand Hledger.Cli.Anon Hledger.Cli.DocFiles Hledger.Cli.Script Hledger.Cli.Utils Hledger.Cli.Version other-modules: Paths_hledger ghc-options: -Wall -Wno-incomplete-uni-patterns -Wno-missing-signatures -Wno-orphans -Wno-type-defaults -Wno-unused-do-bind -optP-Wno-nonportable-include-path cpp-options: -DVERSION="1.32.3" build-depends: Decimal >=0.5.1 , Diff >=0.2 , aeson >=1 && <2.3 , ansi-terminal >=0.9 , base >=4.14 && <4.19 , bytestring , cmdargs >=0.10 , containers >=0.5.9 , data-default >=0.5 , directory , extra >=1.6.3 , filepath , githash >=0.1.6.2 , hashable >=1.2.4 , haskeline >=0.6 , hledger-lib >=1.32.3 && <1.33 , lucid , math-functions >=0.3.3.0 , megaparsec >=7.0.0 && <9.7 , microlens >=0.4 , mtl >=2.2.1 , process , regex-tdfa , safe >=0.3.19 , shakespeare >=2.0.2.2 , split >=0.1 , tabular >=0.2 , tasty >=1.2.3 , temporary , text >=1.2.4.1 , text-ansi >=0.2.1 , time >=1.5 , timeit , transformers , unordered-containers , utf8-string >=0.3.5 , utility-ht >=0.0.13 , wizards >=1.0 default-language: Haskell2010 if (!(os(windows))) && (flag(terminfo)) build-depends: terminfo executable hledger main-is: hledger-cli.hs other-modules: Paths_hledger hs-source-dirs: app ghc-options: -Wall -Wno-incomplete-uni-patterns -Wno-missing-signatures -Wno-orphans -Wno-type-defaults -Wno-unused-do-bind -optP-Wno-nonportable-include-path cpp-options: -DVERSION="1.32.3" build-depends: Decimal >=0.5.1 , aeson >=1 && <2.3 , ansi-terminal >=0.9 , base >=4.14 && <4.19 , bytestring , cmdargs >=0.10 , containers >=0.5.9 , data-default >=0.5 , directory , extra >=1.6.3 , filepath , githash >=0.1.6.2 , haskeline >=0.6 , hledger , hledger-lib >=1.32.3 && <1.33 , math-functions >=0.3.3.0 , megaparsec >=7.0.0 && <9.7 , microlens >=0.4 , mtl >=2.2.1 , process , regex-tdfa , safe >=0.3.19 , shakespeare >=2.0.2.2 , split >=0.1 , tabular >=0.2 , tasty >=1.2.3 , temporary , text >=1.2.4.1 , text-ansi >=0.2.1 , time >=1.5 , timeit , transformers , unordered-containers , utf8-string >=0.3.5 , utility-ht >=0.0.13 , wizards >=1.0 default-language: Haskell2010 if (!(os(windows))) && (flag(terminfo)) build-depends: terminfo if flag(threaded) ghc-options: -threaded test-suite unittest type: exitcode-stdio-1.0 main-is: unittest.hs hs-source-dirs: test ghc-options: -Wall -Wno-incomplete-uni-patterns -Wno-missing-signatures -Wno-orphans -Wno-type-defaults -Wno-unused-do-bind -optP-Wno-nonportable-include-path cpp-options: -DVERSION="1.32.3" build-depends: Decimal >=0.5.1 , aeson >=1 && <2.3 , ansi-terminal >=0.9 , base >=4.14 && <4.19 , bytestring , cmdargs >=0.10 , containers >=0.5.9 , data-default >=0.5 , directory , extra >=1.6.3 , filepath , githash >=0.1.6.2 , haskeline >=0.6 , hledger , hledger-lib >=1.32.3 && <1.33 , math-functions >=0.3.3.0 , megaparsec >=7.0.0 && <9.7 , microlens >=0.4 , mtl >=2.2.1 , process , regex-tdfa , safe >=0.3.19 , shakespeare >=2.0.2.2 , split >=0.1 , tabular >=0.2 , tasty >=1.2.3 , temporary , text >=1.2.4.1 , text-ansi >=0.2.1 , time >=1.5 , timeit , transformers , unordered-containers , utf8-string >=0.3.5 , utility-ht >=0.0.13 , wizards >=1.0 default-language: Haskell2010 if (!(os(windows))) && (flag(terminfo)) build-depends: terminfo benchmark bench type: exitcode-stdio-1.0 main-is: bench.hs hs-source-dirs: bench ghc-options: -Wall -Wno-incomplete-uni-patterns -Wno-missing-signatures -Wno-orphans -Wno-type-defaults -Wno-unused-do-bind -optP-Wno-nonportable-include-path build-depends: Decimal >=0.5.1 , aeson >=1 && <2.3 , ansi-terminal >=0.9 , base >=4.14 && <4.19 , bytestring , cmdargs >=0.10 , containers >=0.5.9 , criterion , data-default >=0.5 , directory , extra >=1.6.3 , filepath , githash >=0.1.6.2 , haskeline >=0.6 , hledger , hledger-lib >=1.32.3 && <1.33 , html , math-functions >=0.3.3.0 , megaparsec >=7.0.0 && <9.7 , microlens >=0.4 , mtl >=2.2.1 , process , regex-tdfa , safe >=0.3.19 , shakespeare >=2.0.2.2 , split >=0.1 , tabular >=0.2 , tasty >=1.2.3 , temporary , text >=1.2.4.1 , text-ansi >=0.2.1 , time >=1.5 , timeit , transformers , unordered-containers , utf8-string >=0.3.5 , utility-ht >=0.0.13 , wizards >=1.0 buildable: False default-language: Haskell2010 if (!(os(windows))) && (flag(terminfo)) build-depends: terminfo