hledger-1.19.1/Hledger/0000755000000000000000000000000013700101030012736 5ustar0000000000000000hledger-1.19.1/Hledger/Cli/0000755000000000000000000000000013723502755013475 5ustar0000000000000000hledger-1.19.1/Hledger/Cli/Commands/0000755000000000000000000000000013725504032015226 5ustar0000000000000000hledger-1.19.1/app/0000755000000000000000000000000013700077706012172 5ustar0000000000000000hledger-1.19.1/bench/0000755000000000000000000000000013722544246012473 5ustar0000000000000000hledger-1.19.1/embeddedfiles/0000755000000000000000000000000013722544246014170 5ustar0000000000000000hledger-1.19.1/test/0000755000000000000000000000000013722544246012373 5ustar0000000000000000hledger-1.19.1/Hledger/Cli.hs0000644000000000000000000000174413700101030014007 0ustar0000000000000000{-| Hledger.Cli re-exports the options, utilities and commands provided by the hledger command-line program. This module also aggregates the built-in unit tests defined throughout hledger and hledger-lib, and adds some more which are easier to define here. -} {-# LANGUAGE OverloadedStrings #-} module Hledger.Cli ( module Hledger.Cli.CliOptions, module Hledger.Cli.Commands, module Hledger.Cli.DocFiles, module Hledger.Cli.Utils, module Hledger.Cli.Version, module Hledger, module System.Console.CmdArgs.Explicit ) where 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 -- unit tests (tests_Hledger_Cli) are defined in Hledger.Cli.Commands hledger-1.19.1/Hledger/Cli/Main.hs0000644000000000000000000002665013723502755014726 0ustar0000000000000000{-| hledger - a ledger-compatible accounting tool. Copyright (c) 2007-2011 Simon Michael Released under GPL version 3 or later. hledger is a partial haskell clone of John Wiegley's "ledger". It generates ledger-compatible register & balance reports from a plain text journal, and demonstrates a functional implementation of ledger. For more information, see http:\/\/hledger.org . This module provides the main function for the hledger command-line executable. It is exposed here so that it can be imported by eg benchmark scripts. You can use the command line: > $ hledger --help or ghci: > $ ghci hledger > > j <- readJournalFile def "examples/sample.journal" > > register [] ["income","expenses"] j > 2008/01/01 income income:salary $-1 $-1 > 2008/06/01 gift income:gifts $-1 $-2 > 2008/06/03 eat & shop expenses:food $1 $-1 > expenses:supplies $1 0 > > balance [Depth "1"] [] l > $-1 assets > $2 expenses > $-2 income > $1 liabilities > > l <- myLedger See "Hledger.Data.Ledger" for more examples. -} {-# LANGUAGE QuasiQuotes #-} module Hledger.Cli.Main where import Data.Char (isDigit) 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 Hledger.Cli -- | 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 -- 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 -- 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`) hasDetailedVersion = ("--version+" `elem`) printUsage = putStr $ showModeUsage $ mainmode addons badCommandError = error' ("command "++rawcmd++" is not recognized, run with no command to see a list") >> exitFailure -- PARTIAL: hasHelpFlag args = any (`elem` args) ["-h","--help"] f `orShowHelp` mode | hasHelpFlag args = putStr $ showModeUsage mode | otherwise = f dbgIO "processed opts" opts dbgIO "command matched" cmd dbgIO "isNullCommand" isNullCommand dbgIO "isInternalCommand" isInternalCommand dbgIO "isExternalCommand" isExternalCommand dbgIO "isBadCommand" isBadCommand d <- getCurrentDay dbgIO "period from opts" (period_ $ reportopts_ opts) dbgIO "interval from opts" (interval_ $ reportopts_ opts) dbgIO "query from opts & args" (queryFromOpts d $ reportopts_ opts) let journallesserror = error "journal-less command tried to use the journal" runHledgerCommand -- high priority flags and situations. -h, then --help, then --info are highest priority. | hasHelpFlag argsbeforecmd = dbgIO "" "-h before command, showing general usage" >> printUsage | not (hasHelpFlag argsaftercmd) && (hasVersion argsbeforecmd || (hasVersion argsaftercmd && isInternalCommand)) = putStrLn prognameandversion | not (hasHelpFlag argsaftercmd) && (hasDetailedVersion argsbeforecmd || (hasDetailedVersion argsaftercmd && isInternalCommand)) = putStrLn prognameanddetailedversion -- \| (null externalcmd) && "binary-filename" `inRawOpts` 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 addons | isBadCommand = badCommandError -- builtin commands | Just (cmdmode, cmdaction) <- findCommand cmd = (case True of -- these commands should not require or read the journal _ | cmd `elem` ["test","help"] -> 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 (not.(=="--")) 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 this 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 -- - not confuse things further or cause misleading errors. moveFlagsAfterCommand :: [String] -> [String] moveFlagsAfterCommand args = moveArgs $ ensureDebugHasArg args where -- quickly! make sure --debug has a numeric argument, or this all goes to hell 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 moveArgs args = insertFlagsAfterCommand $ moveArgs' (args, []) where -- -h ..., --version ... moveArgs' ((f:a:as), flags) | isMovableNoArgFlag f = moveArgs' (a:as, flags ++ [f]) -- -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) | isMovableReqArgFlagAndValue fv = moveArgs' (a:as, flags ++ [fv]) -- -f(missing arg) moveArgs' ((f:a:as), flags) | isMovableReqArgFlag f, not (isValue a) = moveArgs' (a:as, flags ++ [f]) -- anything else moveArgs' (as, flags) = (as, flags) insertFlagsAfterCommand ([], flags) = flags insertFlagsAfterCommand (command:args, flags) = [command] ++ flags ++ args isMovableNoArgFlag a = "-" `isPrefixOf` a && dropWhile (=='-') a `elem` noargflagstomove isMovableReqArgFlag a = "-" `isPrefixOf` a && dropWhile (=='-') a `elem` reqargflagstomove isMovableReqArgFlagAndValue ('-':'-':a:as) = case break (== '=') (a:as) of (f:fs,_:_) -> (f:fs) `elem` reqargflagstomove _ -> False isMovableReqArgFlagAndValue ('-':shortflag:_:_) = [shortflag] `elem` reqargflagstomove isMovableReqArgFlagAndValue _ = 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 hledger-1.19.1/Hledger/Cli/CliOptions.hs0000644000000000000000000007634513723502755016133 0ustar0000000000000000{-| Common cmdargs modes and flags, a command-line options type, and related utilities used by hledger commands. -} {-# LANGUAGE CPP, ScopedTypeVariables, FlexibleContexts, TypeFamilies, OverloadedStrings, PackageImports #-} 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, -- * CLI options CliOpts(..), defcliopts, getHledgerCliOpts, getHledgerCliOpts', rawOptsToCliOpts, checkCliOpts, outputFormats, defaultOutputFormat, defaultBalanceLineFormat, 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, -- | For balance: lineFormatFromOpts, -- * Other utils hledgerAddons, topicForMode, -- -- * Convenience re-exports -- module Data.String.Here, -- module System.Console.CmdArgs.Explicit, ) where import Prelude () import "base-compat-batteries" Prelude.Compat import qualified Control.Exception as C import Control.Monad (when) import Data.Char import Data.Default import Data.Either (isRight) import Data.Functor.Identity (Identity) import "base-compat-batteries" Data.List.Compat import Data.List.Extra (nubSort) import Data.List.Split (splitOneOf) import Data.Ord import Data.Maybe --import Data.String.Here -- import Data.Text (Text) import qualified Data.Text as T import Data.Void (Void) import Safe 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 Text.Megaparsec import Text.Megaparsec.Char import Hledger import Hledger.Cli.DocFiles import Hledger.Cli.Version -- common cmdargs flags -- | Common help flags: --help, --debug, --version... helpflags :: [Flag RawOpts] helpflags = [ flagNone ["help","h"] (setboolopt "help") "show general usage (or after CMD, command usage)" -- ,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" ,flagNone ["anon"] (setboolopt "anon") "anonymize accounts and payees" ,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" ] -- | 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" ,flagReq ["end","e"] (\s opts -> Right $ setopt "end" s opts) "DATE" "include postings/txns before this date" ,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 -- 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 ,flagNone ["B","cost"] (setboolopt "B") "show amounts converted to their cost/selling amount, using the transaction price. Equivalent to --value=cost." ,flagNone ["V","market"] (setboolopt "V") (unwords ["show amounts converted to current market value (single period reports)" ,"or period-end market value (multiperiod reports) in their default valuation commodity." ,"Equivalent to --value=now / --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=now,COMM / --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:" ,"'cost': convert to cost using transaction prices, then optionally to COMM using period-end market prices" ,"'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-value"] (setboolopt "infer-value") "with -V/-X/--value, also infer market prices from transactions" -- generated postings/transactions ,flagNone ["auto"] (setboolopt "auto") "apply automated posting rules to modify transactions" ,flagOpt "" ["forecast"] (\s opts -> Right $ setopt "forecast" s opts) "PERIODEXP" (unlines [ "Generate periodic transactions (from periodic transaction rules). By default these begin after the latest recorded transaction, and end 6 months from today, or at the report end date." , "Also, in hledger-ui, make future transactions visible." , "Note that = (and not a space) is required before PERIODEXP if you wish to supply it." ]) -- general output-related ,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." ]) ] -- | 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" ] -- | 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 ++ ".") 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 desc = flagArg (\s opts -> Right $ setopt "args" s opts) desc 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 usage." -- ,flagNone ["help"] (setboolopt "help") "Show long help." ] ,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 name = (defCommandMode [name]) { 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 documentation, as follows: -- -- - First line: the command name then any aliases, as one or more space or comma-separated words -- -- - Second line to a line containing just _FLAGS, or the end: the short help -- -- - Any lines after _FLAGS: the long help (split into lines for cmdargs) -- -- The CLI help displays the short help, then the cmdargs-generated -- flags list, then the long help (which some day we might make -- optional again). The manual displays the short help followed by -- the long help, with no flags list. -- parseCommandDoc :: CommandDoc -> Maybe ([Name], String, [String]) parseCommandDoc t = case lines t of [] -> Nothing (l:ls) -> Just (names, shorthelp, longhelplines) where names = words $ map (\c -> if c `elem` [',','\\'] then ' ' else c) l (shorthelpls, longhelpls) = break (== "_FLAGS") ls shorthelp = unlines $ reverse $ dropWhile null $ reverse shorthelpls longhelplines = dropWhile null $ drop 1 longhelpls -- | Get a mode's usage message as a nicely wrapped string. showModeUsage :: Mode a -> String showModeUsage = (showText defaultWrap :: [Text] -> String) . (helpText [] HelpFormatDefault :: Mode a -> [Text]) -- | 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 ,reportopts_ :: ReportOpts ,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) } deriving (Show) instance Default CliOpts where def = defcliopts defcliopts :: CliOpts defcliopts = CliOpts def def def def def def def def def def defaultWidth -- | 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 = checkCliOpts <$> do let iopts = rawOptsToInputOpts rawopts ropts <- rawOptsToReportOpts rawopts mcolumns <- readMay <$> getEnvSafe "COLUMNS" mtermwidth <- #ifdef mingw32_HOST_OS return Nothing #else setupTermFromEnv >>= return . flip getCapability termColumns -- 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 ,reportopts_ = ropts ,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 } -- | Do final validation of processed opts, raising an error if there is trouble. checkCliOpts :: CliOpts -> CliOpts checkCliOpts opts = either usageError (const opts) $ do -- XXX move to checkReportOpts or move _format to CliOpts case lineFormatFromOpts $ reportopts_ opts of Left err -> Left $ "could not parse format option: "++err Right _ -> Right () -- XXX check registerWidthsFromOpts opts -- | 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' args' = do let rawopts = either usageError id $ process mode' args' opts <- rawOptsToCliOpts rawopts debugArgs args' opts when ("help" `inRawOpts` rawopts_ opts) $ putStr shorthelp >> exitSuccess -- when ("help" `inRawOpts` 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. 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) 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 from options, -- or the default (-, meaning stdout). outputFileFromOpts :: CliOpts -> IO FilePath outputFileFromOpts opts = do d <- getCurrentDirectory case output_file_ opts of Just p -> expandPath d p Nothing -> return "-" defaultOutputFormat = "txt" outputFormats = [defaultOutputFormat] ++ ["csv" ,"html" ] -- | 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: "++show 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: "++show 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) -- for balance, currently: -- | Parse the format option if provided, possibly returning an error, -- otherwise get the default value. lineFormatFromOpts :: ReportOpts -> Either String StringFormat lineFormatFromOpts = maybe (Right defaultBalanceLineFormat) parseStringFormat . format_ -- | Default line format for balance report: "%20(total) %2(depth_spacer)%-(account)" defaultBalanceLineFormat :: StringFormat defaultBalanceLineFormat = BottomAligned [ FormatField False (Just 20) Nothing TotalField , FormatLiteral " " , FormatField True (Just 2) Nothing DepthSpacerField , FormatField True Nothing Nothing AccountField ] -- 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 = sortBy (comparing takeBaseName) as2 -- ["check","check.hs","check.py","check-dates","check-dates.hs"] let as4 = groupBy (\a b -> takeBaseName a == takeBaseName b) as3 -- [["check","check.hs","check.py"],["check-dates","check-dates.hs"]] let as5 = concatMap dropRedundantSourceVersion as4 -- ["check","check.hs","check.py","check-dates"] return as5 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 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 <- splitOneOf "[:;]" `fmap` getEnvSafe "PATH" pathfiles <- concat `fmap` mapM getDirectoryContentsSafe pathdirs return $ nubSort pathfiles -- exclude directories and files without execute permission. -- These will do a stat for each hledger-*, probably ok. -- But they need paths, not just filenames -- exes' <- filterM doesFileExist exe' -- exes'' <- filterM isExecutable exes' -- return exes'' -- | 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 -- 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" ,"lhs" ,"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) hledger-1.19.1/Hledger/Cli/DocFiles.hs0000644000000000000000000000713113700101030015473 0ustar0000000000000000{-# LANGUAGE TemplateHaskell, OverloadedStrings, PackageImports #-} {-| Embedded documentation files in various formats, and helpers for viewing them. |-} module Hledger.Cli.DocFiles ( Topic ,docFiles ,docTopics ,lookupDocNroff ,lookupDocTxt ,lookupDocInfo ,printHelpForTopic ,runManForTopic ,runInfoForTopic ,runPagerForTopic ) where import Prelude () import "base-compat-batteries" Prelude.Compat import Data.ByteString (ByteString) import qualified Data.ByteString.Char8 as BC import Data.String import System.IO import System.IO.Temp import System.Process import Hledger.Utils (first3, second3, third3, embedFileRelative) type Topic = String -- | These are all the main hledger manuals, in man, txt, and info formats. -- Only files under the current package directory can be embedded, -- so most of these are symlinked here from the other package directories. docFiles :: [(Topic, (ByteString, ByteString, ByteString))] docFiles = [ ("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") )) ,("journal", ($(embedFileRelative "embeddedfiles/hledger_journal.5") ,$(embedFileRelative "embeddedfiles/hledger_journal.txt") ,$(embedFileRelative "embeddedfiles/hledger_journal.info") )) ,("csv", ($(embedFileRelative "embeddedfiles/hledger_csv.5") ,$(embedFileRelative "embeddedfiles/hledger_csv.txt") ,$(embedFileRelative "embeddedfiles/hledger_csv.info") )) ,("timeclock", ($(embedFileRelative "embeddedfiles/hledger_timeclock.5") ,$(embedFileRelative "embeddedfiles/hledger_timeclock.txt") ,$(embedFileRelative "embeddedfiles/hledger_timeclock.info") )) ,("timedot", ($(embedFileRelative "embeddedfiles/hledger_timedot.5") ,$(embedFileRelative "embeddedfiles/hledger_timedot.txt") ,$(embedFileRelative "embeddedfiles/hledger_timedot.info") )) ] docTopics :: [Topic] docTopics = map fst docFiles lookupDocTxt :: Topic -> ByteString lookupDocTxt name = maybe (fromString $ "No text manual found for topic: "++name) second3 $ lookup name docFiles lookupDocNroff :: Topic -> ByteString lookupDocNroff name = maybe (fromString $ "No man page found for topic: "++name) first3 $ lookup name docFiles lookupDocInfo :: Topic -> ByteString lookupDocInfo name = maybe (fromString $ "No info manual found for topic: "++name) third3 $ lookup name docFiles printHelpForTopic :: Topic -> IO () printHelpForTopic t = BC.putStr (lookupDocTxt t) runPagerForTopic :: FilePath -> Topic -> IO () runPagerForTopic exe t = do (Just inp, _, _, ph) <- createProcess (proc exe []){ std_in=CreatePipe } BC.hPutStrLn inp (lookupDocTxt t) _ <- waitForProcess ph return () runManForTopic :: Topic -> IO () runManForTopic t = withSystemTempFile ("hledger-"++t++".nroff") $ \f h -> do BC.hPutStrLn h $ lookupDocNroff t hClose h -- the temp file path will presumably have a slash in it, so man should read it callCommand $ "man " ++ f runInfoForTopic :: Topic -> IO () runInfoForTopic t = withSystemTempFile ("hledger-"++t++".info") $ \f h -> do BC.hPutStrLn h $ lookupDocInfo t hClose h callCommand $ "info " ++ f hledger-1.19.1/Hledger/Cli/Utils.hs0000644000000000000000000003134213723300774015131 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-| Utilities for top-level modules and ghci. See also Hledger.Read and Hledger.Utils. -} module Hledger.Cli.Utils ( unsupportedOutputFormatError, withJournalDo, writeOutput, journalTransform, journalAddForecast, journalReload, journalReloadIfChanged, journalFileIsNewer, journalSpecifiedFileIsNewer, fileModificationTime, openBrowserOn, writeFileWithBackup, writeFileWithBackupIfChanged, readFileStrictly, pivotByOpts, anonymiseByOpts, tests_Cli_Utils, ) where import Control.Exception as C import Control.Monad import Data.List import Data.Maybe import qualified Data.Text as T import qualified Data.Text.IO as T import Data.Time (Day, addDays) import Safe (readMay) import System.Console.CmdArgs import System.Directory (getModificationTime, getDirectoryContents, copyFile) import System.Exit import System.FilePath ((), splitFileName, takeDirectory) import System.Info (os) import System.Process (readProcessWithExitCode) import System.Time (ClockTime, getClockTime, diffClockTimes, TimeDiff(TimeDiff)) import Text.Printf import Text.Regex.TDFA ((=~)) import System.Time (ClockTime(TOD)) import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds) import Hledger.Cli.CliOptions import Hledger.Cli.Anon import Hledger.Data import Hledger.Read import Hledger.Reports import Hledger.Utils -- | 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 implemented for this report or report mode." -- | 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 readJournalFiles (inputopts_ opts) journalpaths >>= mapM (journalTransform opts) >>= either error' cmd -- PARTIAL: -- | Apply some extra post-parse transformations to the journal, if -- specified by options. These happen after journal validation, but -- before report calculation. They include: -- -- - adding forecast transactions (--forecast) -- - pivoting account names (--pivot) -- - anonymising (--anonymise). -- journalTransform :: CliOpts -> Journal -> IO Journal journalTransform opts@CliOpts{reportopts_=_ropts} = journalAddForecast opts -- - converting amounts to market value (--value) -- >=> journalApplyValue ropts >=> return . pivotByOpts opts >=> return . anonymiseByOpts opts -- | Apply the pivot transformation on a journal, if option is present. pivotByOpts :: CliOpts -> Journal -> Journal pivotByOpts opts = case maybestringopt "pivot" . rawopts_ $ opts of Just tag -> journalPivot $ T.pack tag Nothing -> id -- | Apply the anonymisation transformation on a journal, if option is present anonymiseByOpts :: CliOpts -> Journal -> Journal anonymiseByOpts opts = if anon_ . inputopts_ $ opts then anon else id -- | Generate periodic transactions from all periodic transaction rules in the journal. -- These transactions are added to the in-memory Journal (but not the on-disk file). -- -- When --auto is active, auto posting rules will be applied to the -- generated transactions. If the query in any auto posting rule fails -- to parse, this function will raise an error. -- -- The start & end date for generated periodic transactions are determined in -- a somewhat complicated way; see the hledger manual -> Periodic transactions. -- journalAddForecast :: CliOpts -> Journal -> IO Journal journalAddForecast CliOpts{inputopts_=iopts, reportopts_=ropts} j = do today <- getCurrentDay -- "They can start no earlier than: the day following the latest normal transaction in the journal (or today if there are none)." let mjournalend = dbg2 "journalEndDate" $ journalEndDate False j -- ignore secondary dates forecastbeginDefault = dbg2 "forecastbeginDefault" $ fromMaybe today mjournalend -- "They end on or before the specified report end date, or 180 days from today if unspecified." mspecifiedend <- snd . dbg2 "specifieddates" <$> specifiedStartEndDates ropts let forecastendDefault = dbg2 "forecastendDefault" $ fromMaybe (addDays 180 today) mspecifiedend let forecastspan = dbg2 "forecastspan" $ spanDefaultsFrom (fromMaybe nulldatespan $ dbg2 "forecastspan flag" $ forecast_ ropts) (DateSpan (Just forecastbeginDefault) (Just forecastendDefault)) forecasttxns = [ txnTieKnot t | pt <- jperiodictxns j , t <- runPeriodicTransaction pt forecastspan , spanContainsDate forecastspan (tdate t) ] -- With --auto enabled, transaction modifiers are also applied to forecast txns forecasttxns' = (if auto_ iopts then either error' id . modifyTransactions today (jtxnmodifiers j) else id) -- PARTIAL: forecasttxns return $ case forecast_ ropts of Just _ -> journalBalanceTransactions' iopts j{ jtxns = concat [jtxns j, forecasttxns'] } Nothing -> j where journalBalanceTransactions' iopts j = let assrt = not . ignore_assertions_ $ iopts in either error' id $ journalBalanceTransactions assrt j -- PARTIAL: -- | 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 (if f == "-" then putStr else 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 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 -> IO (Either String Journal) journalReload opts = do journalpaths <- journalFilePathFromOpts opts readJournalFiles (inputopts_ opts) journalpaths >>= mapM (journalTransform opts) -- | 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 -> IO (Either String Journal, Bool) journalReloadIfChanged opts _d j = do let maybeChangedFilename f = do newer <- journalSpecifiedFileIsNewer j f return $ if newer then Just f else Nothing changedfiles <- catMaybes `fmap` mapM maybeChangedFilename (journalFilePaths j) if not $ null changedfiles then do whenLoud $ printf "%s has changed, reloading\n" (head changedfiles) ej <- journalReload opts return (ej, True) else return (Right j, False) -- | Has the journal's main data file changed since the journal was last -- read ? journalFileIsNewer :: Journal -> IO Bool journalFileIsNewer j@Journal{jlastreadtime=tread} = do tmod <- fileModificationTime $ journalFilePath j return $ diffClockTimes tmod tread > (TimeDiff 0 0 0 0 0 0 0) -- | Has the specified file (presumably one of journal's data files) -- changed since journal was last read ? journalSpecifiedFileIsNewer :: Journal -> FilePath -> IO Bool journalSpecifiedFileIsNewer Journal{jlastreadtime=tread} f = do tmod <- fileModificationTime f return $ diffClockTimes tmod tread > (TimeDiff 0 0 0 0 0 0 0) -- | Get the last modified time of the specified file, or if it does not -- exist or there is some other error, the current time. fileModificationTime :: FilePath -> IO ClockTime fileModificationTime f | null f = getClockTime | otherwise = (do utc <- getModificationTime f let nom = utcTimeToPOSIXSeconds utc let clo = TOD (read $ takeWhile (`elem` ("0123456789"::String)) $ show nom) 0 -- XXX read return clo ) `C.catch` \(_::C.IOException) -> getClockTime -- | Attempt to open a web browser on the given url, all platforms. openBrowserOn :: String -> IO ExitCode openBrowserOn u = trybrowsers browsers u where trybrowsers (b:bs) u = do (e,_,_) <- readProcessWithExitCode b [u] "" case e of ExitSuccess -> return ExitSuccess ExitFailure _ -> trybrowsers bs u trybrowsers [] u = do putStrLn $ printf "Could not start a web browser (tried: %s)" $ intercalate ", " browsers putStrLn $ printf "Please open your browser and visit %s" u 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 readFileStrictly :: FilePath -> IO T.Text readFileStrictly f = readFilePortably f >>= \s -> C.evaluate (T.length s) >> return s -- | 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 = catMaybes $ map (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 tests_Cli_Utils = tests "Utils" [ -- tests "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. -- test "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.19.1/Hledger/Cli/Anon.hs0000644000000000000000000000331013700101030014671 0ustar0000000000000000{-| Instances for anonymizing sensitive data in various types. Note that there is no clear way to anonymize numbers. -} 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 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 } 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.19.1/Hledger/Cli/Version.hs0000644000000000000000000000477213722544246015470 0ustar0000000000000000{-# LANGUAGE CPP, TemplateHaskell #-} {- Version number-related utilities. See also the Makefile. -} module Hledger.Cli.Version ( progname, version, prognameandversion, prognameanddetailedversion, binaryfilename ) where import System.Info (os, arch) import Text.Printf import Hledger.Utils -- package name and version from the cabal file progname, version, prognameandversion, prognameanddetailedversion :: String progname = "hledger" #ifdef VERSION version = VERSION #else version = "dev build" #endif prognameandversion = progname ++ " " ++ version prognameanddetailedversion = printf "%s %s" progname version -- developer build version strings include PATCHLEVEL (number of -- patches since the last tag). If defined, it must be a number. patchlevel :: String #ifdef PATCHLEVEL patchlevel = "." ++ show (PATCHLEVEL :: Int) #else patchlevel = "" #endif -- the package version plus patchlevel if specified buildversion :: String buildversion = version ++ patchlevel -- | 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 = prettify $ splitAtElement '.' buildversion where prettify (major:minor:bugfix:patches:[]) = printf "%s-%s.%s%s%s-%s-%s%s" progname major minor bugfix' patches' os' arch suffix where bugfix' | bugfix `elem` ["0"{-,"98","99"-}] = "" | otherwise = '.' : bugfix patches' | patches/="0" = '+' : patches | otherwise = "" (os',suffix) | os == "darwin" = ("mac","" :: String) | os == "mingw32" = ("windows",".exe") | otherwise = (os,"") prettify (major:minor:bugfix:[]) = prettify [major,minor,bugfix,"0"] prettify (major:minor:[]) = prettify [major,minor,"0","0"] prettify (major:[]) = prettify [major,"0","0","0"] prettify [] = error' "VERSION is empty, please fix" -- PARTIAL: prettify _ = error' "VERSION has too many components, please fix" hledger-1.19.1/Hledger/Cli/Commands.hs0000644000000000000000000005521413723502755015601 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. -} {-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands ( findCommand ,testcmd ,builtinCommands ,builtinCommandNames ,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.Checkdates ,module Hledger.Cli.Commands.Checkdupes ,module Hledger.Cli.Commands.Close ,module Hledger.Cli.Commands.Codes ,module Hledger.Cli.Commands.Commodities ,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.Printunique ,module Hledger.Cli.Commands.Register ,module Hledger.Cli.Commands.Registermatch ,module Hledger.Cli.Commands.Rewrite ,module Hledger.Cli.Commands.Stats ,module Hledger.Cli.Commands.Tags ) where import Data.Char (isSpace) import Data.Default import Data.List #if !(MIN_VERSION_base(4,11,0)) import Data.Monoid ((<>)) #endif import Data.Text (Text) import qualified Data.Text as T import Data.Time.Calendar 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.Checkdates import Hledger.Cli.Commands.Checkdupes import Hledger.Cli.Commands.Close import Hledger.Cli.Commands.Codes import Hledger.Cli.Commands.Commodities 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.Printunique import Hledger.Cli.Commands.Register import Hledger.Cli.Commands.Registermatch 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) ,(checkdatesmode , checkdates) ,(checkdupesmode , checkdupes) ,(closemode , close) ,(codesmode , codes) ,(commoditiesmode , commodities) ,(descriptionsmode , descriptions) ,(diffmode , diff) ,(filesmode , files) ,(helpmode , help') ,(importmode , importcmd) ,(incomestatementmode , incomestatement) ,(notesmode , notes) ,(payeesmode , payees) ,(pricesmode , prices) ,(printmode , print') ,(printuniquemode , printunique) ,(registermatchmode , registermatch) ,(registermode , register) ,(rewritemode , rewrite) ,(roimode , roi) ,(statsmode , stats) ,(tagsmode , tags) ,(testmode , testcmd) ] -- | 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 = [ "-------------------------------------------------------------------------------" ,progversion ,"Usage: hledger COMMAND [OPTIONS] [-- ADDONCMDOPTIONS]" ,"Commands (+ addons found in $PATH):" ,"" ,"Data entry (these commands modify the journal file):" ," add add transactions using guided prompts" ,"+iadd add transactions using curses ui" ," import add any new transactions from other files (eg csv)" ,"" ,"Data management:" ,"+autosync download/deduplicate/convert OFX data" ,"+check check more powerful balance assertions" ," check-dates check transactions are ordered by date" ," check-dupes check for accounts with the same leaf name" ," close (equity) generate balance-resetting transactions" ," diff compare account transactions in two journal files" ,"+interest generate interest transactions" ," rewrite generate automated postings/diffs (old, use --auto)" ,"" ,"Financial reports:" ," 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" ,"+irr calculate internal rate of return (old, use roi)" ," roi show return on investments" ,"" ,"Low-level reports:" ," accounts (a) show account names" ," activity show postings-per-interval bar charts" ," balance (b, bal) show balance changes/end balances/budgets in accounts" ," codes show transaction codes" ," commodities show commodity/currency symbols" ," descriptions show unique transaction descriptions" ," files show input file paths" ," notes show unique note segments of transaction descriptions" ," payees show unique payee segments of transaction descriptions" ," prices show market price records" ," print (p, txns) show transactions (journal entries)" ," print-unique show only transactions with unique descriptions" ," register (r, reg) show postings in one or more accounts & running total" ," register-match show a recent posting that best matches a description" ," stats show journal statistics" ," tags show tag names" ," test run self tests" ,"" ,"Alternate user interfaces:" ,"+ui run curses ui" ,"+web run web ui" ,"+api run http api server" ,"" ,"Other:" ] ++ othercmds ++ ["Help:" ," (no arguments) show this commands list" ," -h show general flags" ," COMMAND -h show flags & docs for COMMAND" ," help [MANUAL] show hledger manuals in various formats" ,"" ] -- commands show brief commands list -- edit open a text editor on some part of the journal -- aregister (ar, areg) show transactions in a single account -- | All names and aliases of builtin commands. builtinCommandNames :: [String] builtinCommandNames = concatMap (modeNames . fst) builtinCommands -- | Look up a builtin command's mode and action by exact command name or alias. findCommand :: String -> Maybe (Mode RawOpts, CliOpts -> Journal -> IO ()) findCommand cmdname = find (elem cmdname . modeNames . fst) builtinCommands -- | Extract the command names from commandsList: the first word -- of lines beginning with a space or + sign. commandsFromCommandsList :: [String] -> [String] commandsFromCommandsList s = [w | c:l <- s, c `elem` [' ','+'], let w:_ = words l] knownCommands :: [String] knownCommands = sort . commandsFromCommandsList $ commandsList prognameandversion [] -- | Print the commands list, modifying the template above based on -- the currently available addons. Missing addons will be removed, and -- extra addons will be added under Misc. printCommandsList :: [String] -> IO () printCommandsList addonsFound = putStr . unlines . concatMap adjustline $ commandsList prognameandversion (map ('+':) unknownCommandsFound) where commandsFound = map (' ':) builtinCommandNames ++ map ('+':) addonsFound unknownCommandsFound = addonsFound \\ knownCommands adjustline l | " hledger " `isPrefixOf` l = [l] adjustline l@('+':_) | cmd `notElem` commandsFound = [] where cmd = takeWhile (not . isSpace) l adjustline l = [l] -- 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 (words' $ query_ $ reportopts_ opts) $ Test.Tasty.defaultMain $ tests "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 = tests "Hledger.Cli" [ tests_Cli_Utils ,tests_Commands ] tests_Commands = tests "Commands" [ tests_Balance ,tests_Register ,tests_Aregister -- some more tests easiest to define here: ,tests "apply account directive" [ test "works" $ do let ignoresourcepos j = j{jtxns=map (\t -> t{tsourcepos=nullsourcepos}) (jtxns j)} sameParse str1 str2 = do j1 <- readJournal def Nothing str1 >>= either error' (return . ignoresourcepos) -- PARTIAL: j2 <- readJournal def Nothing str2 >>= either error' (return . ignoresourcepos) 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" ) ,test "preserves \"virtual\" posting type" $ do j <- readJournal def Nothing "apply account test\n2008/12/07 One\n (from) $-1\n (to) $1\n" >>= either error' return -- PARTIAL: let p = head $ tpostings $ head $ jtxns j paccount p @?= "test:from" ptype p @?= VirtualPosting ] ,test "alias directive" $ do j <- readJournal def Nothing "!alias expenses = equity:draw:personal\n1/1\n (expenses:food) 1\n" >>= either error' return -- PARTIAL: let p = head $ tpostings $ head $ jtxns j paccount p @?= "equity:draw:personal:food" ,test "Y default year directive" $ do j <- readJournal def Nothing defaultyear_journal_txt >>= either error' return -- PARTIAL: tdate (head $ jtxns j) @?= fromGregorian 2009 1 1 ,test "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"] -- ,test "journalCanonicaliseAmounts" ~: -- "use the greatest precision" ~: -- (map asprecision $ journalAmountAndPriceCommodities $ journalCanonicaliseAmounts $ journalWithAmounts ["1","2.00"]) @?= [2,2] -- don't know what this should do -- ,test "elideAccountName" ~: do -- (elideAccountName 50 "aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa" -- @?= "aa:aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa") -- (elideAccountName 20 "aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa" -- @?= "aa:aa:aaaaaaaaaaaaaa") ,test "show dollars" $ showAmount (usd 1) @?= "$1.00" ,test "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.19.1/Hledger/Cli/Commands/Accounts.hs0000644000000000000000000000730713722544246017360 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 #-} {-# LANGUAGE CPP #-} module Hledger.Cli.Commands.Accounts ( accountsmode ,accounts ) where #if !(MIN_VERSION_base(4,11,0)) import Data.Monoid #endif 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 -- | Command line options for this command. accountsmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Accounts.txt") ([flagNone ["declared"] (setboolopt "declared") "show account names declared with account directives" ,flagNone ["used"] (setboolopt "used") "show account names referenced by transactions" ] ++ 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, reportopts_=ropts} j = do -- 1. identify the accounts we'll show d <- getCurrentDay let tree = tree_ ropts declared = boolopt "declared" rawopts used = boolopt "used" rawopts q = queryFromOpts d ropts -- a depth limit will clip and exclude account names later, but we don't want to exclude accounts at this stage nodepthq = dbg1 "nodepthq" $ filterQuery (not . queryIsDepth) q -- just the acct: part of the query will be reapplied later, after clipping acctq = dbg1 "acctq" $ filterQuery queryIsAcct q depth = dbg1 "depth" $ queryDepth $ filterQuery queryIsDepth q matcheddeclaredaccts = dbg1 "matcheddeclaredaccts" $ filter (matchesAccount nodepthq) $ map fst $ jdeclaredaccounts j matchedusedaccts = dbg5 "matchedusedaccts" $ map paccount $ journalPostings $ filterJournalPostings nodepthq j accts = dbg5 "accts to show" $ -- no need to nub/sort, accountTree will if | declared && not used -> matcheddeclaredaccts | not declared && used -> matchedusedaccts | otherwise -> matcheddeclaredaccts ++ matchedusedaccts -- 2. sort them by declaration order and name, at each level of their tree structure sortedaccts = sortAccountNamesByDeclaration j tree accts -- 3. if there's a depth limit, depth-clip and remove any no longer useful items clippedaccts = dbg1 "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 depth) $ -- clip at depth if specified sortedaccts -- 4. print what remains as a list or tree, maybe applying --drop in the former case mapM_ (T.putStrLn . render) clippedaccts where render a = case accountlistmode_ ropts of ALTree -> T.replicate indent " " <> accountLeafName droppedName ALFlat -> droppedName where indent = 2 * (max 0 (accountNameLevel a - drop_ ropts) - 1) droppedName = accountNameDrop (drop_ ropts) a hledger-1.19.1/Hledger/Cli/Commands/Activity.hs0000644000000000000000000000314513700101030017341 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 import Data.Maybe import Text.Printf import Hledger import Hledger.Cli.CliOptions import Prelude hiding (putStr) import Hledger.Utils.UTF8IOCompat (putStr) 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{reportopts_=ropts} j = do d <- getCurrentDay putStr $ showHistogram ropts (queryFromOpts d ropts) j showHistogram :: ReportOpts -> Query -> Journal -> String showHistogram opts q j = concatMap (printDayWith countBar) spanps where i = interval_ opts interval | i == NoInterval = Days 1 | otherwise = i span' = queryDateSpan (date2_ opts) q `spanDefaultsFrom` journalDateSpan (date2_ opts) j spans = filter (DateSpan Nothing Nothing /=) $ splitSpan interval span' 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 b _, ps) = printf "%s %s\n" (show $ fromJust b) (f ps) countBar ps = replicate (length ps) barchar hledger-1.19.1/Hledger/Cli/Commands/Add.hs0000644000000000000000000006155113723502755016272 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 ,transactionsSimilarTo ) where import Prelude () import "base-compat-batteries" Prelude.Compat hiding (fail) 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 "base-compat-batteries" Data.List.Compat import qualified Data.Set as S import Data.Maybe import Data.Text (Text) import qualified Data.Text as T import Data.Time.Calendar (Day) import Data.Time.Format (formatTime, defaultTimeLocale, iso8601DateFormat) import Safe (headDef, headMay, atMay) import System.Console.CmdArgs.Explicit import System.Console.Haskeline (runInputT, defaultSettings, setComplete) import System.Console.Haskeline.Completion import System.Console.Wizard 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) 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 hPrintf stderr "Adding transactions to journal file %s\n" (journalFilePath j) showHelp today <- getCurrentDay let 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 hPrintf stderr "Skipping journal add due to debug mode.\n" return esJournal else do j' <- journalAddTransaction esJournal esOpts t hPrintf stderr "Saved.\n" return j' hPrintf stderr "Starting the next transaction (. or ctrl-D/ctrl-C to quit)\n" getAndAddTransactions es{esJournal=j, esDefDate=tdate t} ) `E.catch` (\(_::RestartTransactionException) -> hPrintf stderr "Restarting this transaction.\n" >> 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 (date, code) -> do let es' = es { esArgs = drop 1 esArgs , esDefDate = date } dateAndCodeString = formatTime defaultTimeLocale yyyymmddFormat date ++ (if T.null code then "" else " (" ++ T.unpack code ++ ")") yyyymmddFormat = iso8601DateFormat Nothing 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 = similarTransaction es 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 $ hPrintf stderr "Using this similar transaction for defaults:\n%s" (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{..} posting -> case (esPostings, posting) 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 Nothing 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 (amount, comment) -> do let posting = nullposting{paccount=T.pack $ stripbrackets account ,pamount=Mixed [amount] ,pcomment=comment ,ptype=accountNamePostingType $ T.pack account } amountAndCommentString = showAmount amount ++ (if T.null comment then "" else " ;" ++ T.unpack comment) prevAmountAndCmnt' = replaceNthOrAppend (length esPostings) amountAndCommentString (prevAmountAndCmnt prevInput) es' = es{esPostings=esPostings++[posting], 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 $ 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 -- Identify the closest recent match for this description in past transactions. similarTransaction :: EntryState -> Text -> Maybe Transaction similarTransaction EntryState{..} desc = let q = queryFromOptsOnly esToday $ reportopts_ esOpts historymatches = transactionsSimilarTo esJournal q desc bestmatch | null historymatches = Nothing | otherwise = Just $ snd $ head historymatches in bestmatch dateAndCodeWizard PrevInput{..} EntryState{..} = do let def = headDef (showDate esDefDate) esArgs retryMsg "A valid hledger smart date is required. Eg: 2014/2/14, 14, 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 Nothing 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 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 _ _ "<" = dbg1 $ Just Nothing parseAccountOrDotOrNull _ _ "." = dbg1 $ Just $ Just "." -- . always signals end of txn parseAccountOrDotOrNull "" True "" = dbg1 $ Just $ Just "" -- when there's no default and txn is balanced, "" also signals end of txn parseAccountOrDotOrNull def@(_:_) _ "" = dbg1 $ Just $ Just def -- when there's a default, "" means use that parseAccountOrDotOrNull _ _ s = dbg1 $ 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 dbg1 = 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 (\(a,b) -> pamount a == pamount b) $ zip esPostings ps) def = case (esArgs, mhistoricalp, followedhistoricalsofar) of (d:_,_,_) -> d (_,Just hp,True) -> showamt $ pamount hp _ | pnum > 1 && not (mixedAmountLooksZero balancingamt) -> showamt balancingamtfirstcommodity _ -> "" 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 = negate $ sum $ map pamount realps where realps = filter isReal esPostings balancingamtfirstcommodity = Mixed $ take 1 $ amounts balancingamt showamt = showMixedAmountWithPrecision -- 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"] descriptionCompleter :: Journal -> String -> CompletionFunc IO descriptionCompleter j = completer (map T.unpack $ 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 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 -> String -> IO () appendToJournalFileOrStdout f s | f == "-" = putStr s' | otherwise = appendFile f s' where s' = "\n" ++ ensureOneNewlineTerminated s -- | Replace a string's 0 or more terminating newlines with exactly one. ensureOneNewlineTerminated :: String -> String ensureOneNewlineTerminated = (++"\n") . reverse . dropWhile (=='\n') . reverse -- | Convert a string of journal data into a register report. registerFromString :: String -> IO String registerFromString s = do d <- getCurrentDay j <- readJournal' $ T.pack s return $ postingsReportAsText opts $ postingsReport ropts (queryFromOpts d ropts) j where ropts = defreportopts{empty_=True} opts = defcliopts{reportopts_=ropts} capitalize :: String -> String capitalize "" = "" capitalize (c:cs) = toUpper c : cs -- | Find the most similar and recent transactions matching the given -- transaction description and report query. Transactions are listed -- with their "relevancy" score, most relevant first. transactionsSimilarTo :: Journal -> Query -> Text -> [(Double,Transaction)] transactionsSimilarTo j q desc = sortBy compareRelevanceAndRecency $ filter ((> threshold).fst) [(compareDescriptions desc $ tdescription t, t) | t <- ts] where compareRelevanceAndRecency (n1,t1) (n2,t2) = compare (n2,tdate t2) (n1,tdate t1) ts = filter (q `matchesTransaction`) $ jtxns j threshold = 0 -- | Return a similarity measure, from 0 to 1, for two transaction -- descriptions. This is like compareStrings, but first strips out -- any numbers, to improve accuracy eg when there are bank transaction -- ids from imported data. compareDescriptions :: Text -> Text -> Double compareDescriptions s t = compareStrings s' t' where s' = simplify $ T.unpack s t' = simplify $ T.unpack t simplify = filter (not . (`elem` ("0123456789" :: String))) -- | Return a similarity measure, from 0 to 1, for two strings. This -- was based on Simon White's string similarity algorithm -- (http://www.catalysoft.com/articles/StrikeAMatch.html), later found -- to be https://en.wikipedia.org/wiki/S%C3%B8rensen%E2%80%93Dice_coefficient, -- modified to handle short strings better. -- Todo: check out http://nlp.fi.muni.cz/raslan/2008/raslan08.pdf#page=14 . 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 * commonpairs / totalpairs where pairs1 = S.fromList $ wordLetterPairs $ uppercase s1 pairs2 = S.fromList $ wordLetterPairs $ uppercase s2 commonpairs = fromIntegral $ S.size $ S.intersection pairs1 pairs2 totalpairs = fromIntegral $ S.size pairs1 + S.size pairs2 wordLetterPairs = concatMap letterPairs . words letterPairs (a:b:rest) = [a,b] : letterPairs (b:rest) letterPairs _ = [] hledger-1.19.1/Hledger/Cli/Commands/Aregister.hs0000644000000000000000000002566713724215705017534 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 Control.Monad (when) import Data.Aeson (toJSON) import Data.Aeson.Text (encodeToLazyText) import Data.List import Data.Maybe #if !(MIN_VERSION_base(4,11,0)) import Data.Semigroup ((<>)) #endif import qualified Data.Text as T import qualified Data.Text.Lazy as TL import Data.Time (addDays) import Safe (headDef) import System.Console.CmdArgs.Explicit import Hledger.Read.CsvReader (CSV, CsvRecord, printCSV) import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Utils 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 limit amount commodities shown to 2" -- flagNone ["cumulative"] (setboolopt "change") -- "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." ) ,outputFormatFlag ["txt","csv","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,reportopts_=ropts} j = do d <- getCurrentDay -- the first argument specifies the account, any remaining arguments are a filter query let args' = listofstringopt "args" rawopts when (null args') $ error' "aregister needs an account, please provide an account name or pattern" -- PARTIAL: let (apat:queryargs) = args' acct = headDef (error' $ show apat++" did not match any account") -- PARTIAL: . filterAccts $ journalAccountNames j filterAccts = case toRegexCI apat of Right re -> filter (regexMatch re . T.unpack) Left _ -> const [] -- gather report options inclusive = True -- tree_ ropts thisacctq = Acct $ (if inclusive then accountNameToAccountRegex else accountNameToAccountOnlyRegex) acct ropts' = ropts{ query_=unwords $ map quoteIfNeeded $ queryargs -- remove a depth limit for reportq, as in RegisterScreen, I forget why XXX ,depth_=Nothing -- always show historical balance ,balancetype_= HistoricalBalance } reportq = And [queryFromOpts d ropts', excludeforecastq (isJust $ forecast_ ropts)] where -- As in RegisterScreen, why ? XXX -- Except in forecast mode, exclude future/forecast transactions. excludeforecastq True = Any excludeforecastq False = -- not:date:tomorrow- not:tag:generated-transaction And [ Not (Date $ DateSpan (Just $ addDays 1 d) Nothing) ,Not generatedTransactionTag ] -- run the report -- TODO: need to also pass the queries so we can choose which date to render - move them into the report ? (balancelabel,items) = accountTransactionsReport ropts' j reportq thisacctq items' = (if empty_ ropts then id else filter (not . mixedAmountLooksZero . fifth6)) $ reverse items -- select renderer render | fmt=="json" = (++"\n") . T.unpack . TL.toStrict . encodeToLazyText . toJSON | fmt=="csv" = (++"\n") . printCSV . accountTransactionsReportAsCsv reportq thisacctq | fmt=="txt" = accountTransactionsReportAsText opts reportq thisacctq | otherwise = const $ error' $ unsupportedOutputFormatError fmt -- PARTIAL: where fmt = outputFormatFromOpts opts writeOutput opts $ render (balancelabel,items') accountTransactionsReportAsCsv :: Query -> Query -> AccountTransactionsReport -> CSV accountTransactionsReportAsCsv reportq thisacctq (_,is) = ["txnidx","date","code","description","otheraccounts","change","balance"] : map (accountTransactionsReportItemAsCsvRecord reportq thisacctq) is accountTransactionsReportItemAsCsvRecord :: Query -> Query -> AccountTransactionsReportItem -> CsvRecord accountTransactionsReportItemAsCsvRecord reportq thisacctq (t@Transaction{tindex,tcode,tdescription}, _, _issplit, otheracctsstr, change, balance) = [idx,date,code,desc,otheracctsstr,amt,bal] where idx = show tindex date = showDate $ transactionRegisterDate reportq thisacctq t code = T.unpack tcode desc = T.unpack tdescription amt = showMixedAmountOneLineWithoutPrice False change bal = showMixedAmountOneLineWithoutPrice False balance -- | Render a register report as plain text suitable for console output. accountTransactionsReportAsText :: CliOpts -> Query -> Query -> AccountTransactionsReport -> String accountTransactionsReportAsText copts@CliOpts{reportopts_=ReportOpts{no_elide_}} reportq thisacctq (_balancelabel,items) = unlines $ title : map (accountTransactionsReportItemAsText copts reportq thisacctq amtwidth balwidth) items where amtwidth = maximumStrict $ 12 : map (strWidth . showamt . itemamt) items balwidth = maximumStrict $ 12 : map (strWidth . showamt . itembal) items showamt | no_elide_ = showMixedAmountOneLineWithoutPrice False -- color_ | otherwise = showMixedAmountElided False itemamt (_,_,_,_,a,_) = a itembal (_,_,_,_,_,a) = a -- show a title indicating which account was picked, which can be confusing otherwise title = T.unpack $ maybe "" (("Transactions in "<>).(<>" and subaccounts:")) 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 . T.pack $ reString r -- Acct "^JS:expenses(:|$)" _ -> Nothing -- shouldn't happen -- | 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 -> String accountTransactionsReportItemAsText copts@CliOpts{reportopts_=ReportOpts{color_,no_elide_}} reportq thisacctq preferredamtwidth preferredbalwidth (t@Transaction{tdescription}, _, _issplit, otheracctsstr, change, balance) -- 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 = intercalate "\n" $ concat [fitString (Just datewidth) (Just datewidth) True True date ," " ,fitString (Just descwidth) (Just descwidth) True True desc ," " ,fitString (Just acctwidth) (Just acctwidth) True True accts ," " ,fitString (Just amtwidth) (Just amtwidth) True False amtfirstline ," " ,fitString (Just balwidth) (Just balwidth) True False balfirstline ] : [concat [spacer ,fitString (Just amtwidth) (Just amtwidth) True False a ," " ,fitString (Just balwidth) (Just balwidth) True False b ] | (a,b) <- zip amtrest balrest ] where -- calculate widths (totalwidth,mdescwidth) = registerWidthsFromOpts copts (datewidth, date) = (10, showDate $ transactionRegisterDate reportq thisacctq t) (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 desc = T.unpack tdescription accts = -- T.unpack $ elideAccountName acctwidth $ T.pack otheracctsstr showamt | no_elide_ = showMixedAmountOneLineWithoutPrice color_ | otherwise = showMixedAmountElided color_ amt = showamt change bal = showamt balance -- alternate behaviour, show null amounts as 0 instead of blank -- amt = if null amt' then "0" else amt' -- bal = if null bal' then "0" else bal' (amtlines, ballines) = (lines amt, lines bal) (amtlen, ballen) = (length amtlines, length ballines) numlines = max 1 (max amtlen ballen) (amtfirstline:amtrest) = take numlines $ amtlines ++ repeat "" -- posting amount is top-aligned (balfirstline:balrest) = take numlines $ replicate (numlines - ballen) "" ++ ballines -- balance amount is bottom-aligned spacer = replicate (totalwidth - (amtwidth + 2 + balwidth)) ' ' -- tests tests_Aregister = tests "Aregister" [ ] hledger-1.19.1/Hledger/Cli/Commands/Balance.hs0000644000000000000000000006520513725267334017132 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 kinds of multi-column balance report, indicated by the heading: * A \"period balance\" (or \"flow\") report (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.) * periodic: 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 * periodic: 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 * periodic: 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 * periodic: 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 OverloadedStrings #-} {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE NamedFieldPuns #-} module Hledger.Cli.Commands.Balance ( balancemode ,balance ,balanceReportAsText ,balanceReportItemAsText ,multiBalanceReportAsText ,multiBalanceReportAsCsv ,multiBalanceReportAsHtml ,multiBalanceReportHtmlRows ,balanceReportAsTable ,balanceReportTableAsText ,tests_Balance ) where import Data.List import Data.Maybe --import qualified Data.Map as Map import qualified Data.Text as T import qualified Data.Text.Lazy as TL import Data.Time (fromGregorian) import System.Console.CmdArgs.Explicit as C import Lucid as L import Text.Printf (printf) import Text.Tabular as T --import Text.Tabular.AsciiWide import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Utils import Hledger.Read.CsvReader (CSV, printCSV) -- | Command line options for this command. balancemode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Balance.txt") ([flagNone ["change"] (setboolopt "change") "show balance change in each period (default)" ,flagNone ["cumulative"] (setboolopt "cumulative") "show balance change accumulated across periods (in multicolumn reports)" ,flagNone ["historical","H"] (setboolopt "historical") "show historical ending balance in each period (includes postings before report start date)\n " ] ++ flattreeflags True ++ [flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "omit N leading account name parts (in flat mode)" ,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 ["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 ["pretty-tables"] (setboolopt "pretty-tables") "use unicode to display prettier tables" ,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" ,flagNone ["budget"] (setboolopt "budget") "show performance compared to budget goals defined by periodic transactions" ,outputFormatFlag ["txt","html","csv","json"] ,outputFileFlag ] ) [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- | The balance command, prints a balance report. balance :: CliOpts -> Journal -> IO () balance opts@CliOpts{rawopts_=rawopts,reportopts_=ropts@ReportOpts{..}} j = do d <- getCurrentDay case lineFormatFromOpts ropts of Left err -> error' $ unlines [err] -- PARTIAL: Right _ -> do let budget = boolopt "budget" rawopts multiperiod = interval_ /= NoInterval fmt = outputFormatFromOpts opts if budget then do -- single or multi period budget report reportspan <- reportSpan j ropts let budgetreport = dbg4 "budgetreport" $ budgetReport ropts assrt reportspan d j where assrt = not $ ignore_assertions_ $ inputopts_ opts render = case fmt of "txt" -> budgetReportAsText ropts "json" -> (++"\n") . TL.unpack . toJsonText _ -> const $ error' $ unsupportedOutputFormatError fmt writeOutput opts $ render budgetreport else if multiperiod then do -- multi period balance report let report = multiBalanceReport d ropts j render = case fmt of "txt" -> multiBalanceReportAsText ropts "csv" -> (++"\n") . printCSV . multiBalanceReportAsCsv ropts "html" -> (++"\n") . TL.unpack . L.renderText . multiBalanceReportAsHtml ropts "json" -> (++"\n") . TL.unpack . toJsonText _ -> const $ error' $ unsupportedOutputFormatError fmt writeOutput opts $ render report else do -- single period simple balance report let report = balanceReport ropts (queryFromOpts d ropts) j -- simple Ledger-style balance report render = case fmt of "txt" -> balanceReportAsText "csv" -> \ropts r -> (++ "\n") $ printCSV $ balanceReportAsCsv ropts r "json" -> const $ (++"\n") . TL.unpack . toJsonText _ -> const $ error' $ unsupportedOutputFormatError fmt writeOutput opts $ render ropts report -- rendering single-column balance reports -- | Render a single-column balance report as CSV. balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV balanceReportAsCsv opts (items, total) = ["account","balance"] : [[T.unpack a, showMixedAmountOneLineWithoutPrice False b] | (a, _, _, b) <- items] ++ if no_total_ opts then [] else [["total", showMixedAmountOneLineWithoutPrice False total]] -- | Render a single-column balance report as plain text. balanceReportAsText :: ReportOpts -> BalanceReport -> String balanceReportAsText opts ((items, total)) = unlines $ concat lines ++ t where fmt = lineFormatFromOpts opts lines = case fmt of Right fmt -> map (balanceReportItemAsText opts fmt) items Left err -> [[err]] t = if no_total_ opts then [] else case fmt of Right fmt -> let -- abuse renderBalanceReportItem to render the total with similar format acctcolwidth = maximum' [T.length fullname | (fullname, _, _, _) <- items] totallines = map rstrip $ renderBalanceReportItem opts fmt (T.replicate (acctcolwidth+1) " ", 0, total) -- with a custom format, extend the line to the full report width; -- otherwise show the usual 20-char line for compatibility overlinewidth | isJust (format_ opts) = maximum' $ map length $ concat lines | otherwise = defaultTotalFieldWidth overline = replicate overlinewidth '-' in overline : totallines Left _ -> [] {- :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 -> StringFormat -> BalanceReportItem -> [String] balanceReportItemAsText opts fmt (_, accountName, depth, amt) = renderBalanceReportItem opts fmt ( accountName, depth, normaliseMixedAmountSquashPricesForDisplay amt ) -- | Render a balance report item using the given StringFormat, generating one or more lines of text. renderBalanceReportItem :: ReportOpts -> StringFormat -> (AccountName, Int, MixedAmount) -> [String] renderBalanceReportItem opts fmt (acctname, depth, total) = lines $ case fmt of OneLine comps -> concatOneLine $ render1 comps TopAligned comps -> concatBottomPadded $ render comps BottomAligned comps -> concatTopPadded $ render comps where render1 = map (renderComponent1 opts (acctname, depth, total)) render = map (renderComponent opts (acctname, depth, total)) defaultTotalFieldWidth = 20 -- | Render one StringFormat component for a balance report item. renderComponent :: ReportOpts -> (AccountName, Int, MixedAmount) -> StringFormatComponent -> String renderComponent _ _ (FormatLiteral s) = s renderComponent opts (acctname, depth, total) (FormatField ljust min max field) = case field of DepthSpacerField -> formatString ljust Nothing max $ replicate d ' ' where d = case min of Just m -> depth * m Nothing -> depth AccountField -> formatString ljust min max (T.unpack acctname) TotalField -> fitStringMulti min max True False $ showMixedAmountWithoutPrice (color_ opts) total _ -> "" -- | Render one StringFormat component for a balance report item. -- This variant is for use with OneLine string formats; it squashes -- any multi-line rendered values onto one line, comma-and-space separated, -- while still complying with the width spec. renderComponent1 :: ReportOpts -> (AccountName, Int, MixedAmount) -> StringFormatComponent -> String renderComponent1 _ _ (FormatLiteral s) = s renderComponent1 opts (acctname, depth, total) (FormatField ljust min max field) = case field of AccountField -> formatString ljust min max ((intercalate ", " . lines) (indented (T.unpack acctname))) where -- better to indent the account name here rather than use a DepthField component -- so that it complies with width spec. Uses a fixed indent step size. indented = ((replicate (depth*2) ' ')++) TotalField -> fitStringMulti min max True False $ ((intercalate ", " . map strip . lines) (showamt total)) where showamt = showMixedAmountWithoutPrice (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{average_, row_total_} (PeriodicReport colspans items (PeriodicReportRow _ coltotals tot avg)) = maybetranspose $ ("Account" : map showDateSpan colspans ++ ["Total" | row_total_] ++ ["Average" | average_] ) : [T.unpack (displayFull a) : map (showMixedAmountOneLineWithoutPrice False) (amts ++ [rowtot | row_total_] ++ [rowavg | average_]) | PeriodicReportRow a amts rowtot rowavg <- items] ++ if no_total_ opts then [] else ["Total:" : map (showMixedAmountOneLineWithoutPrice False) ( coltotals ++ [tot | row_total_] ++ [avg | average_] )] where maybetranspose | transpose_ opts = transpose | otherwise = id -- | Render a multi-column balance report as HTML. multiBalanceReportAsHtml :: ReportOpts -> MultiBalanceReport -> Html () multiBalanceReportAsHtml ropts mbr = let (headingsrow,bodyrows,mtotalsrow) = multiBalanceReportHtmlRows ropts mbr in table_ $ mconcat $ [headingsrow] ++ bodyrows ++ maybeToList mtotalsrow -- | 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 ()], Maybe (Html ())) multiBalanceReportHtmlRows ropts mbr = let headingsrow:rest | transpose_ ropts = error' "Sorry, --transpose is not supported with HTML output yet" -- PARTIAL: | otherwise = multiBalanceReportAsCsv ropts mbr (bodyrows, mtotalsrow) | no_total_ ropts = (rest, Nothing) | otherwise = (init rest, Just $ last rest) in (multiBalanceReportHtmlHeadRow ropts headingsrow ,map (multiBalanceReportHtmlBodyRow ropts) bodyrows ,multiBalanceReportHtmlFootRow ropts <$> mtotalsrow -- TODO pad totals row with zeros when there are ) -- | Render one MultiBalanceReport heading row as a HTML table row. multiBalanceReportHtmlHeadRow :: ReportOpts -> [String] -> Html () multiBalanceReportHtmlHeadRow _ [] = mempty -- shouldn't happen multiBalanceReportHtmlHeadRow ropts (acct:rest) = let defstyle = style_ "" (amts,tot,avg) | row_total_ ropts && average_ ropts = (init $ init rest, [last $ init rest], [last rest]) | row_total_ ropts = (init rest, [last rest], []) | average_ ropts = (init rest, [], [last rest]) | otherwise = (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 -> [String] -> Html () multiBalanceReportHtmlBodyRow _ [] = mempty -- shouldn't happen multiBalanceReportHtmlBodyRow ropts (label:rest) = let defstyle = style_ "text-align:right" (amts,tot,avg) | row_total_ ropts && average_ ropts = (init $ init rest, [last $ init rest], [last rest]) | row_total_ ropts = (init rest, [last rest], []) | average_ ropts = (init rest, [], [last rest]) | otherwise = (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 -> [String] -> 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:rest) = let defstyle = style_ "text-align:right" (amts,tot,avg) | row_total_ ropts && average_ ropts = (init $ init rest, [last $ init rest], [last rest]) | row_total_ ropts = (init rest, [last rest], []) | average_ ropts = (init rest, [], [last rest]) | otherwise = (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 -> String multiBalanceReportAsText ropts@ReportOpts{..} r = title ++ "\n\n" ++ (balanceReportTableAsText ropts $ balanceReportAsTable ropts r) where multiperiod = interval_ /= NoInterval title = printf "%s in %s%s:" (case balancetype_ of PeriodChange -> "Balance changes" CumulativeChange -> "Ending balances (cumulative)" HistoricalBalance -> "Ending balances (historical)") (showDateSpan $ periodicReportSpan r) (case value_ of Just (AtCost _mc) -> ", valued at cost" Just (AtThen _mc) -> error' unsupportedValueThenError -- TODO -- ", valued at period ends" -- handled like AtEnd for now -- PARTIAL: Just (AtEnd _mc) -> ", valued at period ends" Just (AtNow _mc) -> ", current value" -- XXX duplicates the above Just (AtDefault _mc) | multiperiod -> ", valued at period ends" Just (AtDefault _mc) -> ", current value" Just (AtDate d _mc) -> ", valued at "++showDate d Nothing -> "") -- | Build a 'Table' from a multi-column balance report. balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table String String MixedAmount balanceReportAsTable opts@ReportOpts{average_, row_total_, balancetype_} (PeriodicReport spans items (PeriodicReportRow _ coltotals tot avg)) = maybetranspose $ addtotalrow $ Table (T.Group NoLine $ map Header accts) (T.Group NoLine $ map Header colheadings) (map rowvals items) where totalscolumn = row_total_ && balancetype_ `notElem` [CumulativeChange, HistoricalBalance] colheadings = map (reportPeriodName balancetype_ spans) spans ++ [" Total" | totalscolumn] ++ ["Average" | average_] accts = map renderacct items renderacct row = replicate ((prrDepth row - 1) * 2) ' ' ++ T.unpack (prrDisplayName row) rowvals (PeriodicReportRow _ as rowtot rowavg) = as ++ [rowtot | totalscolumn] ++ [rowavg | average_] addtotalrow | no_total_ opts = id | otherwise = (+----+ (row "" $ coltotals ++ [tot | totalscolumn && not (null coltotals)] ++ [avg | average_ && not (null coltotals)] )) maybetranspose | transpose_ opts = \(Table rh ch vals) -> Table ch rh (transpose vals) | otherwise = id -- | Given a table representing a multi-column balance report (for example, -- made using 'balanceReportAsTable'), render it in a format suitable for -- console output. Amounts with more than two commodities will be elided -- unless --no-elide is used. balanceReportTableAsText :: ReportOpts -> Table String String MixedAmount -> String balanceReportTableAsText ropts@ReportOpts{..} = tableAsText ropts showamt where showamt | no_elide_ = showMixedAmountOneLineWithoutPrice color_ | otherwise = showMixedAmountElided color_ tests_Balance = tests "Balance" [ tests "balanceReportAsText" [ test "unicode in balance layout" $ do j <- readJournal' "2009/01/01 * медвежья шкура\n расходы:покупки 100\n актив:наличные\n" let opts = defreportopts balanceReportAsText opts (balanceReport opts (queryFromOpts (fromGregorian 2008 11 26) opts) j) @?= unlines [" -100 актив:наличные" ," 100 расходы:покупки" ,"--------------------" ," 0" ] ] ] hledger-1.19.1/Hledger/Cli/Commands/Balancesheet.hs0000644000000000000000000000222013700101030020114 0ustar0000000000000000{-# 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=journalAssetAccountQuery ,cbcsubreportnormalsign=NormallyPositive ,cbcsubreportincreasestotal=True } ,CBCSubreportSpec{ cbcsubreporttitle="Liabilities" ,cbcsubreportquery=journalLiabilityAccountQuery ,cbcsubreportnormalsign=NormallyNegative ,cbcsubreportincreasestotal=False } ], cbctype = HistoricalBalance } balancesheetmode :: Mode RawOpts balancesheetmode = compoundBalanceCommandMode balancesheetSpec balancesheet :: CliOpts -> Journal -> IO () balancesheet = compoundBalanceCommand balancesheetSpec hledger-1.19.1/Hledger/Cli/Commands/Balancesheetequity.hs0000644000000000000000000000266613700101030021373 0ustar0000000000000000{-# LANGUAGE QuasiQuotes, 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=journalAssetAccountQuery ,cbcsubreportnormalsign=NormallyPositive ,cbcsubreportincreasestotal=True } ,CBCSubreportSpec{ cbcsubreporttitle="Liabilities" ,cbcsubreportquery=journalLiabilityAccountQuery ,cbcsubreportnormalsign=NormallyNegative ,cbcsubreportincreasestotal=False } ,CBCSubreportSpec{ cbcsubreporttitle="Equity" ,cbcsubreportquery=journalEquityAccountQuery ,cbcsubreportnormalsign=NormallyNegative ,cbcsubreportincreasestotal=False } ], cbctype = HistoricalBalance } balancesheetequitymode :: Mode RawOpts balancesheetequitymode = compoundBalanceCommandMode balancesheetequitySpec balancesheetequity :: CliOpts -> Journal -> IO () balancesheetequity = compoundBalanceCommand balancesheetequitySpec hledger-1.19.1/Hledger/Cli/Commands/Cashflow.hs0000644000000000000000000000210613700101030017307 0ustar0000000000000000{-# LANGUAGE QuasiQuotes, 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=journalCashAccountQuery ,cbcsubreportnormalsign=NormallyPositive ,cbcsubreportincreasestotal=True } ], cbctype = PeriodChange } cashflowmode :: Mode RawOpts cashflowmode = compoundBalanceCommandMode cashflowSpec cashflow :: CliOpts -> Journal -> IO () cashflow = compoundBalanceCommand cashflowSpec hledger-1.19.1/Hledger/Cli/Commands/Checkdates.hs0000755000000000000000000000457213700101030017613 0ustar0000000000000000{-# LANGUAGE NoOverloadedStrings #-} -- prevent trouble if turned on in ghci {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Checkdates ( checkdatesmode ,checkdates ) where import Hledger import Hledger.Cli.CliOptions import System.Console.CmdArgs.Explicit import System.Exit import Text.Printf checkdatesmode :: Mode RawOpts checkdatesmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Checkdates.txt") [flagNone ["strict"] (setboolopt "strict") "makes date comparing strict"] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") checkdates :: CliOpts -> Journal -> IO () checkdates CliOpts{rawopts_=rawopts,reportopts_=ropts} j = do d <- getCurrentDay let ropts_ = ropts{accountlistmode_=ALFlat} let q = queryFromOpts d ropts_ let ts = filter (q `matchesTransaction`) $ jtxns $ journalSelectingAmountFromOpts ropts j let strict = boolopt "strict" rawopts let date = transactionDateFn ropts let compare a b = if strict then date a < date b else date a <= date b case checkTransactions compare ts of FoldAcc{fa_previous=Nothing} -> putStrLn "ok (empty journal)" >> exitSuccess FoldAcc{fa_error=Nothing} -> putStrLn "ok" >> exitSuccess FoldAcc{fa_error=Just error, fa_previous=Just previous} -> (putStrLn $ printf ("ERROR: transaction out of%s date order" ++ "\nPrevious date: %s" ++ "\nDate: %s" ++ "\nLocation: %s" ++ "\nTransaction:\n\n%s") (if strict then " STRICT" else "") (show $ date previous) (show $ date error) (show $ tsourcepos error) (showTransaction error)) >> exitFailure data FoldAcc a b = FoldAcc { fa_error :: Maybe a , fa_previous :: Maybe b } foldWhile :: (a -> FoldAcc a b -> FoldAcc a b) -> FoldAcc a b -> [a] -> FoldAcc a b foldWhile _ acc [] = acc foldWhile fold acc (a:as) = case fold a acc of acc@FoldAcc{fa_error=Just _} -> acc acc -> foldWhile fold acc as checkTransactions :: (Transaction -> Transaction -> Bool) -> [Transaction] -> FoldAcc Transaction Transaction checkTransactions compare = foldWhile f FoldAcc{fa_error=Nothing, fa_previous=Nothing} where f current acc@FoldAcc{fa_previous=Nothing} = acc{fa_previous=Just current} f current acc@FoldAcc{fa_previous=Just previous} = if compare previous current then acc{fa_previous=Just current} else acc{fa_error=Just current} hledger-1.19.1/Hledger/Cli/Commands/Checkdupes.hs0000755000000000000000000000237513700101030017632 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Checkdupes ( checkdupesmode ,checkdupes ) where import Data.Function import Data.List import Data.List.Extra (nubSort) import qualified Data.Text as T import Hledger import Hledger.Cli.CliOptions import System.Console.CmdArgs.Explicit import Text.Printf checkdupesmode :: Mode RawOpts checkdupesmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Checkdupes.txt") [] [generalflagsgroup1] hiddenflags ([], Nothing) checkdupes _opts j = mapM_ render $ checkdupes' $ accountsNames j accountsNames :: Journal -> [(String, AccountName)] accountsNames j = map leafAndAccountName as where leafAndAccountName a = (T.unpack $ accountLeafName a, a) ps = journalPostings j as = nubSort $ map paccount ps checkdupes' :: (Ord k, Eq k) => [(k, v)] -> [(k, [v])] checkdupes' l = zip dupLeafs dupAccountNames where dupLeafs = map (fst . head) d dupAccountNames = map (map snd) d d = dupes' l dupes' = filter ((> 1) . length) . groupBy ((==) `on` fst) . sortBy (compare `on` fst) render :: (String, [AccountName]) -> IO () render (leafName, accountNameL) = printf "%s as %s\n" leafName (intercalate ", " (map T.unpack accountNameL)) hledger-1.19.1/Hledger/Cli/Commands/Close.hs0000755000000000000000000001613413722544246016647 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Close ( closemode ,close ) where import Control.Monad (when) import Data.Function (on) import Data.List (groupBy) import Data.Maybe import qualified Data.Text as T (pack) import Data.Time.Calendar import System.Console.CmdArgs.Explicit as C import Hledger import Hledger.Cli.CliOptions defclosingdesc = "closing balances" defopeningdesc = "opening balances" defclosingacct = "equity:opening/closing balances" defopeningacct = defclosingacct closemode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Close.txt") [flagNone ["close"] (setboolopt "close") "show just closing transaction" ,flagNone ["open"] (setboolopt "open") "show just opening transaction" ,flagReq ["close-desc"] (\s opts -> Right $ setopt "close-desc" s opts) "DESC" ("description for closing transaction (default: "++defclosingdesc++")") ,flagReq ["open-desc"] (\s opts -> Right $ setopt "open-desc" s opts) "DESC" ("description for opening transaction (default: "++defopeningdesc++")") ,flagReq ["close-acct"] (\s opts -> Right $ setopt "close-acct" s opts) "ACCT" ("account to transfer closing balances to (default: "++defclosingacct++")") ,flagReq ["open-acct"] (\s opts -> Right $ setopt "open-acct" s opts) "ACCT" ("account to transfer opening balances from (default: "++defopeningacct++")") ,flagNone ["explicit","x"] (setboolopt "explicit") "show all amounts explicitly" ,flagNone ["interleaved"] (setboolopt "interleaved") "keep equity and non-equity postings adjacent" ,flagNone ["show-costs"] (setboolopt "show-costs") "keep balances with different costs separate" ] [generalflagsgroup1] (hiddenflags ++ -- old close flags for compatibility, hidden [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 "[QUERY]") -- debugger, beware: close is incredibly devious. simple rules combine to make a horrid maze. -- tests are in tests/close.test. close CliOpts{rawopts_=rawopts, reportopts_=ropts} j = do today <- getCurrentDay let -- show opening entry, closing entry, or (default) both ? (opening, closing) = case (boolopt "open" rawopts, boolopt "close" rawopts) of (False, False) -> (True, True) (o, c) -> (o, c) -- descriptions to use for the closing/opening transactions closingdesc = fromMaybe (T.pack defclosingdesc) $ T.pack <$> maybestringopt "close-desc" rawopts openingdesc = fromMaybe (T.pack defopeningdesc) $ T.pack <$> maybestringopt "open-desc" rawopts -- accounts to close to and open from -- if only one is specified, it is used for both (closingacct, openingacct) = let (mc, mo) = (T.pack <$> maybestringopt "close-acct" rawopts, T.pack <$> maybestringopt "open-acct" rawopts) in case (mc, mo) of (Just c, Just o) -> (c, o) (Just c, Nothing) -> (c, c) (Nothing, Just o) -> (o, o) (Nothing, Nothing) -> (T.pack defclosingacct, T.pack defopeningacct) -- dates of the closing and opening transactions ropts_ = ropts{balancetype_=HistoricalBalance, accountlistmode_=ALFlat} q = queryFromOpts today ropts_ openingdate = fromMaybe today $ queryEndDate False q closingdate = addDays (-1) openingdate -- should we show the amount(s) on the equity posting(s) ? explicit = boolopt "explicit" rawopts -- should we preserve cost information ? normalise = case boolopt "show-costs" rawopts of True -> normaliseMixedAmount False -> normaliseMixedAmount . mixedAmountStripPrices -- the balances to close (acctbals,_) = balanceReport ropts_ q j totalamt = sum $ map (\(_,_,_,b) -> normalise b) acctbals -- since balance assertion amounts are required to be exact, the -- amounts in opening/closing transactions should be too (#941, #1137) precise = setFullPrecision -- interleave equity postings next to the corresponding closing posting, or put them all at the end ? interleaved = boolopt "interleaved" rawopts -- the closing transaction closingtxn = nulltransaction{tdate=closingdate, tdescription=closingdesc, tpostings=closingps} closingps = concat [ [posting{paccount = a ,pamount = mixed [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=closingacct, pamount=Mixed [precise b]} | interleaved] | -- get the balances for each commodity and transaction price (a,_,_,mb) <- acctbals , let bs = amounts $ normalise mb -- mark the last balance in each commodity with True , let bs' = concat [reverse $ zip (reverse bs) (True : repeat False) | bs <- groupBy ((==) `on` acommodity) bs] , (b, islast) <- bs' ] -- or a final multicommodity posting transferring all balances to equity -- (print will show this as multiple single-commodity postings) ++ [posting{paccount=closingacct, pamount=if explicit then mapMixedAmount precise totalamt else missingmixedamt} | not interleaved] -- the opening transaction openingtxn = nulltransaction{tdate=openingdate, tdescription=openingdesc, tpostings=openingps} openingps = concat [ [posting{paccount = a ,pamount = mixed [precise b] ,pbalanceassertion = case mcommoditysum of Just s -> Just nullassertion{baamount=precise s{aprice=Nothing}} Nothing -> Nothing } ] ++ [posting{paccount=openingacct, pamount=Mixed [precise $ negate b]} | interleaved] | (a,_,_,mb) <- acctbals , let bs = amounts $ normalise mb -- mark the last balance in each commodity with the unpriced sum in that commodity (for a balance assertion) , let bs' = concat [reverse $ zip (reverse bs) (Just commoditysum : repeat Nothing) | bs <- groupBy ((==) `on` acommodity) bs , let commoditysum = (sum bs)] , (b, mcommoditysum) <- bs' ] ++ [posting{paccount=openingacct, pamount=if explicit then mapMixedAmount precise (negate totalamt) else missingmixedamt} | not interleaved] -- print them when closing $ putStr $ showTransaction closingtxn when opening $ putStr $ showTransaction openingtxn hledger-1.19.1/Hledger/Cli/Commands/Codes.hs0000644000000000000000000000171013722544246016626 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{reportopts_=ropts@ReportOpts{empty_}} j = do d <- getCurrentDay let q = queryFromOpts d ropts ts = entriesReport ropts q j codes = (if empty_ then id else filter (not . T.null)) $ map tcode ts mapM_ T.putStrLn codes hledger-1.19.1/Hledger/Cli/Commands/Commodities.hs0000644000000000000000000000142213700101030020015 0ustar0000000000000000{-| The @commodities@ command lists commodity/currency symbols. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Commodities ( commoditiesmode ,commodities ) where import Control.Monad import Data.List.Extra (nubSort) import qualified Data.Map as M 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 j = do let cs = filter (/= "AUTO") $ nubSort $ M.keys (jcommodities j) ++ M.keys (jinferredcommodities j) forM_ cs T.putStrLn hledger-1.19.1/Hledger/Cli/Commands/Descriptions.hs0000644000000000000000000000170513722544246020243 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{reportopts_=ropts} j = do d <- getCurrentDay let q = queryFromOpts d ropts ts = entriesReport ropts q j descriptions = nubSort $ map tdescription ts mapM_ T.putStrLn descriptions hledger-1.19.1/Hledger/Cli/Commands/Diff.hs0000644000000000000000000000757613722544246016461 0ustar0000000000000000{-| The @diff@ command compares two diff. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Diff ( diffmode ,diff ) where import Data.List import Data.Function import Data.Ord import Data.Maybe import Data.Time import Data.Either import qualified Data.Text as T import System.Exit import Hledger import Prelude hiding (putStrLn) import Hledger.Utils.UTF8IOCompat (putStrLn) 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 } binBy :: Ord b => (a -> b) -> [a] -> [[a]] binBy f = groupBy ((==) `on` f) . sortBy (comparing f) 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 . binBy (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 ] readJournalFile' :: FilePath -> IO Journal readJournalFile' fn = readJournalFile definputopts {ignore_assertions_ = True} fn >>= either error' return -- PARTIAL: 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], reportopts_=ReportOpts{query_=acctName}} _ = do j1 <- readJournalFile' f1 j2 <- readJournalFile' f2 let acct = T.pack acctName 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_ (putStr . showTransaction) unmatchedtxn1 putStrLn "These transactions are in the second file only:\n" mapM_ (putStr . showTransaction) unmatchedtxn2 diff _ _ = do putStrLn "Please specify two input files. Usage: hledger diff -f FILE1 -f FILE2 FULLACCOUNTNAME" exitFailure hledger-1.19.1/Hledger/Cli/Commands/Help.hs0000644000000000000000000000523213700101030016434 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 Prelude () import "base-compat-batteries" Prelude.Compat import Data.Char import Data.List import Data.Maybe import Safe 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 Hledger.Utils.Debug helpmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Help.txt") [flagNone ["info"] (setboolopt "info") "show the manual with info" ,flagNone ["man"] (setboolopt "man") "show the manual with man" ,flagNone ["pager"] (setboolopt "pager") "show the manual with $PAGER or less" ,flagNone ["cat"] (setboolopt "cat") "show the manual on stdout" ,flagNone ["help","h"] (setboolopt "help") "show this help" ] [] [] ([], Just $ argsFlag "[MANUAL]") -- | List or display one of the hledger manuals in various formats. -- You can select a docs viewer with one of the `--info`, `--man`, `--pager`, `--cat` 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 topic = case args of [pat] -> headMay [t | t <- docTopics, map toLower pat `isInfixOf` t] _ -> Nothing [info, man, pager, cat] = [runInfoForTopic, runManForTopic, runPagerForTopic pagerprog, printHelpForTopic] viewer | boolopt "info" $ rawopts_ opts = info | boolopt "man" $ rawopts_ opts = man | boolopt "pager" $ rawopts_ opts = pager | boolopt "cat" $ rawopts_ opts = cat | not interactive = cat | "info" `elem` exes = info | "man" `elem` exes = man | pagerprog `elem` exes = pager | otherwise = cat case topic of Nothing -> putStrLn $ unlines [ "Please choose a manual by typing \"hledger help MANUAL\" (any substring is ok)." ,"A viewer (info, man, a pager, or stdout) will be auto-selected," ,"or type \"hledger help -h\" to see options. Manuals available:" ] ++ "\n " ++ unwords docTopics Just t -> viewer t hledger-1.19.1/Hledger/Cli/Commands/Files.hs0000644000000000000000000000154313723502755016637 0ustar0000000000000000{-| The @files@ command lists included files. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Files ( filesmode ,files ) where import Data.List import Safe import Hledger import Prelude hiding (putStrLn) import Hledger.Utils.UTF8IOCompat (putStrLn) 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) $ headMay args let files = maybe id (filter . regexMatch) regex $ map fst $ jfiles j mapM_ putStrLn files hledger-1.19.1/Hledger/Cli/Commands/Import.hs0000755000000000000000000000521613722544246017053 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Import ( importmode ,importcmd ) where import Control.Monad import Data.List 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 iopts' = iopts{new_=True, new_save_=not dryrun} case inputfiles of [] -> error' "please provide one or more input files as arguments" -- PARTIAL: fs -> do enewj <- readJournalFiles iopts' fs case enewj of Left e -> error' e Right newj -> 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 | dryrun -> do printf "; would import %d new transactions from %s:\n\n" (length newts) inputstr -- TODO how to force output here ? -- length (jtxns newj) `seq` print' opts{rawopts_=("explicit",""):rawopts} newj mapM_ (putStr . showTransaction) newts newts | catchup -> do printf "marked %s as caught up, skipping %d unimported transactions\n\n" inputstr (length newts) newts -> do -- 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\n" (length newts) inputstr hledger-1.19.1/Hledger/Cli/Commands/Incomestatement.hs0000644000000000000000000000231113700101030020676 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=journalRevenueAccountQuery ,cbcsubreportnormalsign=NormallyNegative ,cbcsubreportincreasestotal=True } ,CBCSubreportSpec{ cbcsubreporttitle="Expenses" ,cbcsubreportquery=journalExpenseAccountQuery ,cbcsubreportnormalsign=NormallyPositive ,cbcsubreportincreasestotal=False } ], cbctype = PeriodChange } incomestatementmode :: Mode RawOpts incomestatementmode = compoundBalanceCommandMode incomestatementSpec incomestatement :: CliOpts -> Journal -> IO () incomestatement = compoundBalanceCommand incomestatementSpec hledger-1.19.1/Hledger/Cli/Commands/Notes.hs0000644000000000000000000000164613722544246016671 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{reportopts_=ropts} j = do d <- getCurrentDay let q = queryFromOpts d ropts ts = entriesReport ropts q j notes = nubSort $ map transactionNote ts mapM_ T.putStrLn notes hledger-1.19.1/Hledger/Cli/Commands/Payees.hs0000644000000000000000000000166413722544246017027 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 #-} {-# LANGUAGE CPP #-} module Hledger.Cli.Commands.Payees ( payeesmode ,payees ) 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. payeesmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Payees.txt") [] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- | The payees command. payees :: CliOpts -> Journal -> IO () payees CliOpts{reportopts_=ropts} j = do d <- getCurrentDay let q = queryFromOpts d ropts ts = entriesReport ropts q j payees = nubSort $ map transactionPayee ts mapM_ T.putStrLn payees hledger-1.19.1/Hledger/Cli/Commands/Prices.hs0000755000000000000000000001007613723300774017023 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Prices ( pricesmode ,prices ) where import qualified Data.Map as M import Data.Maybe import Data.List import qualified Data.Text as T import Data.Time import Hledger import Hledger.Cli.CliOptions import System.Console.CmdArgs.Explicit pricesmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Prices.txt") [flagNone ["costs"] (setboolopt "costs") "print transaction prices from postings" ,flagNone ["inverted-costs"] (setboolopt "inverted-costs") "print transaction inverted prices from postings also"] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- XXX the original hledger-prices script always ignored assertions prices opts j = do d <- getCurrentDay let styles = journalCommodityStyles j q = queryFromOpts d (reportopts_ opts) ps = filter (matchesPosting q) $ allPostings j mprices = jpricedirectives j cprices = map (stylePriceDirectiveExceptPrecision styles) $ concatMap postingsPriceDirectivesFromCosts ps icprices = map (stylePriceDirectiveExceptPrecision styles) $ concatMap postingsPriceDirectivesFromCosts $ mapAmount invertPrice ps allprices = mprices ++ ifBoolOpt "costs" cprices ++ ifBoolOpt "inverted-costs" icprices mapM_ (putStrLn . showPriceDirective) $ sortOn pddate $ filter (matchesPriceDirective q) $ allprices where ifBoolOpt opt | boolopt opt $ rawopts_ opts = id | otherwise = const [] showPriceDirective :: PriceDirective -> String showPriceDirective mp = unwords ["P", show $ pddate mp, T.unpack . quoteCommoditySymbolIfNeeded $ pdcommodity mp, showAmountWithZeroCommodity $ pdamount mp] divideAmount' :: Quantity -> Amount -> Amount divideAmount' n a = a' where a' = (n `divideAmount` a) { astyle = style' } style' = (astyle a) { asprecision = precision' } extPrecision = (1+) . floor . logBase 10 $ (realToFrac n :: Double) precision' = case asprecision (astyle a) of NaturalPrecision -> NaturalPrecision Precision p -> Precision $ extPrecision + p -- XXX -- | Invert an amount's price for --invert-cost, somehow ? Unclear. invertPrice :: Amount -> Amount invertPrice a = case aprice a of Nothing -> a Just (UnitPrice pa) -> invertPrice -- normalize to TotalPrice a { aprice = Just $ TotalPrice pa' } where pa' = ((1 / aquantity a) `divideAmount` pa) { aprice = Nothing } Just (TotalPrice pa) -> a { aquantity = aquantity pa * signum (aquantity a), acommodity = acommodity pa, aprice = Just $ TotalPrice pa' } where pa' = pa { aquantity = abs $ aquantity a, acommodity = acommodity a, aprice = Nothing, astyle = astyle a } postingsPriceDirectivesFromCosts :: Posting -> [PriceDirective] postingsPriceDirectivesFromCosts p = mapMaybe (amountPriceDirectiveFromCost date) . amounts $ pamount p where date = fromMaybe (tdate . fromJust $ ptransaction p) $ pdate p amountPriceDirectiveFromCost :: Day -> Amount -> Maybe PriceDirective amountPriceDirectiveFromCost d a = case aprice a of Nothing -> Nothing Just (UnitPrice pa) -> Just PriceDirective { pddate = d, pdcommodity = acommodity a, pdamount = pa } Just (TotalPrice pa) -> Just PriceDirective { pddate = d, pdcommodity = acommodity a, pdamount = abs (aquantity a) `divideAmount'` pa } -- | Given a map of standard amount display styles, apply the -- appropriate one, if any, to this price directive's amount. -- But keep the number of decimal places unchanged. stylePriceDirectiveExceptPrecision :: M.Map CommoditySymbol AmountStyle -> PriceDirective -> PriceDirective stylePriceDirectiveExceptPrecision styles pd@PriceDirective{pdamount=a} = pd{pdamount = styleAmountExceptPrecision styles a} allPostings :: Journal -> [Posting] allPostings = concatMap tpostings . jtxns mapAmount :: (Amount -> Amount) -> [Posting] -> [Posting] mapAmount f = map pf where pf p = p { pamount = mf (pamount p) } mf = mixed . map f . amounts hledger-1.19.1/Hledger/Cli/Commands/Print.hs0000644000000000000000000001661013722544246016672 0ustar0000000000000000{-| A ledger-compatible @print@ command. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Print ( printmode ,print' -- ,entriesReportAsText ,originalTransaction ) where import Data.Maybe (isJust) import Data.Text (Text) import Data.List (intercalate) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import System.Console.CmdArgs.Explicit import Hledger.Read.CsvReader (CSV, printCSV) import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Utils import Hledger.Cli.Commands.Add ( transactionsSimilarTo ) printmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Print.txt") ([let arg = "STR" in flagReq ["match","m"] (\s opts -> Right $ setopt "match" s opts) arg ("show the transaction whose description is most similar to "++arg++", and is most recent") ,flagNone ["explicit","x"] (setboolopt "explicit") "show all amounts explicitly" ,flagNone ["new"] (setboolopt "new") "show only newer-dated transactions added in each file since last run" ,outputFormatFlag ["txt","csv","json","sql"] ,outputFileFlag ]) [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- | Print journal transactions in standard format. print' :: CliOpts -> Journal -> IO () print' opts j = do case maybestringopt "match" $ rawopts_ opts of Nothing -> printEntries opts j Just desc -> printMatch opts j $ T.pack desc printEntries :: CliOpts -> Journal -> IO () printEntries opts@CliOpts{reportopts_=ropts} j = do d <- getCurrentDay let q = queryFromOpts d ropts fmt = outputFormatFromOpts opts render = case fmt of "txt" -> entriesReportAsText opts "csv" -> (++"\n") . printCSV . entriesReportAsCsv "json" -> (++"\n") . TL.unpack . toJsonText "sql" -> entriesReportAsSql _ -> const $ error' $ unsupportedOutputFormatError fmt -- PARTIAL: writeOutput opts $ render $ entriesReport ropts q j entriesReportAsText :: CliOpts -> EntriesReport -> String entriesReportAsText opts = concatMap (showTransaction . whichtxn) where whichtxn -- With -x, use the fully-inferred txn with all amounts & txn prices explicit. | boolopt "explicit" (rawopts_ opts) -- Or also, if any of -B/-V/-X/--value are active. -- Because of #551, and because of print -V valuing only one -- posting when there's an implicit txn price. -- So -B/-V/-X/--value implies -x. Is this ok ? || (isJust $ value_ $ reportopts_ opts) = id -- By default, use the original as-written-in-the-journal txn. | otherwise = originalTransaction -- Replace this transaction's postings with the original postings if any, but keep the -- current possibly rewritten account names. originalTransaction t = t { tpostings = map originalPostingPreservingAccount $ tpostings t } -- Get the original posting if any, but keep the current possibly rewritten account name. originalPostingPreservingAccount p = (originalPosting p) { paccount = paccount p } -- XXX -- tests_showTransactions = [ -- "showTransactions" ~: do -- -- "print expenses" ~: -- do -- let opts = defreportopts{query_="expenses"} -- d <- getCurrentDay -- showTransactions opts (queryFromOpts d opts) samplejournal `is` unlines -- ["2008/06/03 * eat & shop" -- ," expenses:food $1" -- ," expenses:supplies $1" -- ," assets:cash $-2" -- ,"" -- ] -- -- , "print report with depth arg" ~: -- do -- let opts = defreportopts{depth_=Just 2} -- d <- getCurrentDay -- showTransactions opts (queryFromOpts d opts) samplejournal `is` unlines -- ["2008/01/01 income" -- ," assets:bank:checking $1" -- ," income:salary $-1" -- ,"" -- ,"2008/06/01 gift" -- ," assets:bank:checking $1" -- ," income:gifts $-1" -- ,"" -- ,"2008/06/03 * eat & shop" -- ," expenses:food $1" -- ," expenses:supplies $1" -- ," assets:cash $-2" -- ,"" -- ,"2008/12/31 * pay off" -- ," liabilities:debts $1" -- ," assets:bank:checking $-1" -- ,"" -- ] -- ] entriesReportAsSql :: EntriesReport -> String entriesReportAsSql txns = "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"++ "insert into postings(txnidx,date1,date2,status,code,description,comment,account,amount,commodity,credit,debit,posting_status,posting_comment) values\n"++ (intercalate "," (map values csv)) ++";\n" where values vs = "(" ++ (intercalate "," $ map toSql vs) ++ ")\n" toSql "" = "NULL" toSql s = "'" ++ (concatMap quoteChar s) ++ "'" quoteChar '\'' = "''" quoteChar c = [c] csv = concatMap transactionToCSV txns 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 -> show idx:date:date2:status:code:description:comment:p) (concatMap postingToCSV $ tpostings t) where idx = tindex t description = T.unpack $ tdescription t date = showDate (tdate t) date2 = maybe "" showDate (tdate2 t) status = show $ tstatus t code = T.unpack $ tcode t comment = chomp $ strip $ T.unpack $ 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_ = a{acommodity="",astyle=(astyle a){asdigitgroups=Nothing},aprice=Nothing} in let amount = showAmount a_ in let commodity = T.unpack c in let credit = if q < 0 then showAmount $ negate a_ else "" in let debit = if q >= 0 then showAmount a_ else "" in [account, amount, commodity, credit, debit, status, comment]) amounts where Mixed amounts = pamount p status = show $ pstatus p account = showAccountName Nothing (ptype p) (paccount p) comment = chomp $ strip $ T.unpack $ pcomment p -- --match -- | Print the transaction most closely and recently matching a description -- (and the query, if any). printMatch :: CliOpts -> Journal -> Text -> IO () printMatch CliOpts{reportopts_=ropts} j desc = do d <- getCurrentDay let q = queryFromOpts d ropts case similarTransaction' j q desc of Nothing -> putStrLn "no matches found." Just t -> putStr $ showTransaction t where -- Identify the closest recent match for this description in past transactions. similarTransaction' :: Journal -> Query -> Text -> Maybe Transaction similarTransaction' j q desc | null historymatches = Nothing | otherwise = Just $ snd $ head historymatches where historymatches = transactionsSimilarTo j q desc hledger-1.19.1/Hledger/Cli/Commands/Printunique.hs0000755000000000000000000000110313700101030020063 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Printunique ( printuniquemode ,printunique ) where import Data.List.Extra (nubSortOn) import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Commands.Print printuniquemode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Printunique.txt") [] [generalflagsgroup1] hiddenflags ([], Nothing) printunique opts j@Journal{jtxns=ts} = do print' opts j{jtxns=uniquify ts} where uniquify = nubSortOn thingToCompare thingToCompare = tdescription -- thingToCompare = tdate hledger-1.19.1/Hledger/Cli/Commands/Register.hs0000644000000000000000000002157313723300774017363 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.List import Data.Maybe -- import Data.Text (Text) import qualified Data.Text as T import qualified Data.Text.Lazy as TL import Data.Time (fromGregorian) import System.Console.CmdArgs.Explicit import Hledger.Read.CsvReader (CSV, CsvRecord, printCSV) import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Utils registermode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Register.txt") ([flagNone ["cumulative"] (setboolopt "change") "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." ) ,outputFormatFlag ["txt","csv","json"] ,outputFileFlag ]) [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") -- | Print a (posting) register report. register :: CliOpts -> Journal -> IO () register opts@CliOpts{reportopts_=ropts} j = do d <- getCurrentDay let fmt = outputFormatFromOpts opts render | fmt=="txt" = postingsReportAsText | fmt=="csv" = const ((++"\n") . printCSV . postingsReportAsCsv) | fmt=="json" = const ((++"\n") . TL.unpack . toJsonText) | otherwise = const $ error' $ unsupportedOutputFormatError fmt -- PARTIAL: writeOutput opts $ render opts $ postingsReport ropts (queryFromOpts d ropts) j 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 = show $ maybe 0 tindex $ ptransaction p date = showDate $ postingDate p -- XXX csv should show date2 with --date2 code = maybe "" (T.unpack . tcode) $ ptransaction p desc = T.unpack $ maybe "" tdescription $ ptransaction p acct = bracket $ T.unpack $ paccount p where bracket = case ptype p of BalancedVirtualPosting -> (\s -> "["++s++"]") VirtualPosting -> (\s -> "("++s++")") _ -> id amt = showMixedAmountOneLineWithoutPrice False $ pamount p bal = showMixedAmountOneLineWithoutPrice False b -- | Render a register report as plain text suitable for console output. postingsReportAsText :: CliOpts -> PostingsReport -> String postingsReportAsText opts (_,items) = unlines $ map (postingsReportItemAsText opts amtwidth balwidth) items where amtwidth = maximumStrict $ 12 : map (strWidth . showMixedAmount . itemamt) items balwidth = maximumStrict $ 12 : map (strWidth . showMixedAmount . itembal) items 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. -- postingsReportItemAsText :: CliOpts -> Int -> Int -> PostingsReportItem -> String postingsReportItemAsText opts preferredamtwidth preferredbalwidth (mdate, menddate, mdesc, p, b) = -- use elide*Width to be wide-char-aware -- trace (show (totalwidth, datewidth, descwidth, acctwidth, amtwidth, balwidth)) $ intercalate "\n" $ concat [fitString (Just datewidth) (Just datewidth) True True date ," " ,fitString (Just descwidth) (Just descwidth) True True desc ," " ,fitString (Just acctwidth) (Just acctwidth) True True acct ," " ,fitString (Just amtwidth) (Just amtwidth) True False amtfirstline ," " ,fitString (Just balwidth) (Just balwidth) True False balfirstline ] : [concat [spacer ,fitString (Just amtwidth) (Just amtwidth) True False a ," " ,fitString (Just balwidth) (Just balwidth) True False b ] | (a,b) <- zip amtrest balrest ] where -- calculate widths (totalwidth,mdescwidth) = registerWidthsFromOpts opts (datewidth, date) = case (mdate,menddate) of (Just _, Just _) -> (21, showDateSpan (DateSpan mdate menddate)) (Nothing, Just _) -> (21, "") (Just d, Nothing) -> (10, showDate d) _ -> (10, "") (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) | hasinterval = (0, remaining - 2) | otherwise = (w, remaining - 2 - w) where hasinterval = isJust menddate w = fromMaybe ((remaining - 2) `div` 2) mdescwidth -- gather content desc = fromMaybe "" mdesc acct = parenthesise $ T.unpack $ elideAccountName awidth $ paccount p where (parenthesise, awidth) = case ptype p of BalancedVirtualPosting -> (\s -> "["++s++"]", acctwidth-2) VirtualPosting -> (\s -> "("++s++")", acctwidth-2) _ -> (id,acctwidth) showamt = showMixedAmountWithoutPrice (color_ $ reportopts_ opts) amt = showamt $ pamount p bal = showamt b -- alternate behaviour, show null amounts as 0 instead of blank -- amt = if null amt' then "0" else amt' -- bal = if null bal' then "0" else bal' (amtlines, ballines) = (lines amt, lines bal) (amtlen, ballen) = (length amtlines, length ballines) numlines = max 1 (max amtlen ballen) (amtfirstline:amtrest) = take numlines $ amtlines ++ repeat "" -- posting amount is top-aligned (balfirstline:balrest) = take numlines $ replicate (numlines - ballen) "" ++ ballines -- balance amount is bottom-aligned spacer = replicate (totalwidth - (amtwidth + 2 + balwidth)) ' ' -- tests tests_Register = tests "Register" [ tests "postingsReportAsText" [ test "unicode in register layout" $ do j <- readJournal' "2009/01/01 * медвежья шкура\n расходы:покупки 100\n актив:наличные\n" let opts = defreportopts (postingsReportAsText defcliopts $ postingsReport opts (queryFromOpts (fromGregorian 2008 11 26) opts) j) @?= unlines ["2009-01-01 медвежья шкура расходы:покупки 100 100" ," актив:наличные -100 0"] ] ] hledger-1.19.1/Hledger/Cli/Commands/Registermatch.hs0000755000000000000000000000627713700101030020362 0ustar0000000000000000{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Registermatch ( registermatchmode ,registermatch ) where import Data.Char (toUpper) import Data.List import qualified Data.Text as T import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Commands.Register registermatchmode = hledgerCommandMode $(embedFileRelative "Hledger/Cli/Commands/Registermatch.txt") [] [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "DESC") registermatch :: CliOpts -> Journal -> IO () registermatch opts@CliOpts{rawopts_=rawopts,reportopts_=ropts} j = do let args' = listofstringopt "args" rawopts case args' of [desc] -> do d <- getCurrentDay let q = queryFromOptsOnly d ropts (_,pris) = postingsReport ropts q j ps = [p | (_,_,_,p,_) <- pris] case similarPosting ps desc of Nothing -> putStrLn "no matches found." Just p -> putStr $ postingsReportAsText opts ("",[pri]) where pri = (Just (postingDate p) ,Nothing ,Just $ T.unpack (maybe "" tdescription $ ptransaction p) ,p ,0) _ -> putStrLn "please provide one description argument." -- 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 _ = [] hledger-1.19.1/Hledger/Cli/Commands/Rewrite.hs0000755000000000000000000001366313722544246017227 0ustar0000000000000000{-# LANGUAGE OverloadedStrings, LambdaCase, DeriveTraversable, ViewPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Rewrite ( rewritemode ,rewrite ) where #if !(MIN_VERSION_base(4,11,0)) import Control.Monad.Writer #endif import Data.Functor.Identity import Data.List (sortOn, foldl') import qualified Data.Text as T import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Commands.Print import System.Console.CmdArgs.Explicit import Text.Printf import Text.Megaparsec 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,reportopts_=ropts} j@Journal{jtxns=ts} = do -- rewrite matched transactions d <- getCurrentDay let modifiers = transactionModifierFromOpts opts : jtxnmodifiers j let j' = j{jtxns=either error' id $ modifyTransactions d modifiers ts} -- PARTIAL: -- run the print command, showing all transactions, or show diffs printOrDiff rawopts opts{reportopts_=ropts{query_=""}} 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,reportopts_=ropts} = TransactionModifier{tmquerytxt=q, tmpostingrules=ps} where q = T.pack $ query_ ropts ps = map (parseposting . T.pack) $ listofstringopt "add-posting" rawopts parseposting t = either (error' . errorBundlePretty) id ep -- PARTIAL: where ep = runIdentity (runJournalParser (postingp 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 = [(originalTransaction t, originalTransaction t') | (t, t') <- zip (jtxns j) (jtxns j'), t /= t'] putStr $ renderPatch $ map (uncurry $ diffTxn j) changed type Chunk = (GenericSourcePos, [DiffLine String]) -- 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] -> String renderPatch = go Nothing . sortOn fst where go _ [] = "" go Nothing cs@((sourceFilePath -> fp, _):_) = fileHeader fp ++ go (Just (fp, 0)) cs go (Just (fp, _)) cs@((sourceFilePath -> fp', _):_) | fp /= fp' = go Nothing cs go (Just (fp, offs)) ((sourceFirstLine -> lineno, diffs):cs) = chunkHeader ++ chunk ++ go (Just (fp, offs + adds - dels)) cs where chunkHeader = printf "@@ -%d,%d +%d,%d @@\n" lineno dels (lineno+offs) adds where (dels, adds) = foldl' countDiff (0, 0) diffs chunk = concatMap renderLine diffs fileHeader fp = printf "--- %s\n+++ %s\n" fp fp 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 GenericSourcePos fp lineno _ -> (GenericSourcePos fp (lineno+1) 1, 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 String] diffs = concat . map (traverse showPostingLines . mapDiff) $ D.getDiff (tpostings t) (tpostings t') pos@(JournalSourcePos fp (line, line')) -> (pos, diffs) where -- We do diff for original lines vs generated ones. Often leads -- to big diff because of re-format effect. diffs :: [DiffLine String] diffs = map mapDiff $ D.getDiff source changed' source | Just contents <- lookup fp $ jfiles j = map T.unpack . drop (line-1) . take line' $ T.lines contents | otherwise = [] changed = lines $ showTransaction t' changed' | null changed = changed | 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.19.1/Hledger/Cli/Commands/Roi.hs0000644000000000000000000002235013723300774016322 0ustar0000000000000000{-# LANGUAGE ParallelListComp #-} {-# LANGUAGE TemplateHaskell #-} {-| 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.Function (on) import Data.List import Numeric.RootFinding import Data.Decimal import System.Console.CmdArgs.Explicit as CmdArgs import Text.Tabular as Tbl import Text.Tabular.AsciiWide as Ascii 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 Quantity -- value of investment at the beginning of day on spanBegin_ Quantity -- value of investment at the end of day on spanEnd_ [(Day,Quantity)] -- all deposits and withdrawals (but not changes of value) in the DateSpan [spanBegin_,spanEnd_) deriving (Show) roi :: CliOpts -> Journal -> IO () roi CliOpts{rawopts_=rawopts, reportopts_=ropts} j = do d <- getCurrentDay let investmentsQuery = queryFromOpts d $ ropts{query_ = stringopt "investment" rawopts,period_=PeriodAll} pnlQuery = queryFromOpts d $ ropts{query_ = stringopt "pnl" rawopts,period_=PeriodAll} showCashFlow = boolopt "cashflow" rawopts prettyTables = pretty_tables_ ropts trans = dbg3 "investments" $ jtxns $ filterJournalTransactions investmentsQuery j journalSpan = let dates = map transactionDate2 trans in DateSpan (Just $ minimum dates) (Just $ addDays 1 $ maximum dates) requestedSpan = periodAsDateSpan $ period_ ropts requestedInterval = interval_ ropts wholeSpan = spanDefaultsFrom requestedSpan journalSpan when (null trans) $ do putStrLn "No relevant transactions found. Check your investments query" exitFailure let spans = case requestedInterval of NoInterval -> [wholeSpan] interval -> splitSpan interval $ spanIntersect journalSpan wholeSpan tableBody <- forM spans $ \(DateSpan (Just spanBegin) (Just spanEnd)) -> do -- Spans are [spanBegin,spanEnd), and spanEnd is 1 day after then actual end date we are interested in let valueBefore = total trans (And [ investmentsQuery , Date (DateSpan Nothing (Just spanBegin))]) valueAfter = total trans (And [investmentsQuery , Date (DateSpan Nothing (Just spanEnd))]) cashFlow = calculateCashFlow trans (And [ Not investmentsQuery , Not pnlQuery , Date (DateSpan (Just spanBegin) (Just spanEnd)) ] ) thisSpan = dbg3 "processing span" $ OneSpan spanBegin spanEnd valueBefore valueAfter cashFlow irr <- internalRateOfReturn showCashFlow prettyTables thisSpan twr <- timeWeightedReturn showCashFlow prettyTables investmentsQuery trans thisSpan let cashFlowAmt = negate $ sum $ map snd cashFlow let smallIsZero x = if abs x < 0.01 then 0.0 else x return [ showDate spanBegin , showDate (addDays (-1) spanEnd) , show valueBefore , show cashFlowAmt , show valueAfter , show (valueAfter - (valueBefore + cashFlowAmt)) , printf "%0.2f%%" $ smallIsZero irr , printf "%0.2f%%" $ smallIsZero twr ] let table = Table (Tbl.Group NoLine (map (Header . show) (take (length tableBody) [1..]))) (Tbl.Group DoubleLine [ Tbl.Group SingleLine [Header "Begin", Header "End"] , Tbl.Group SingleLine [Header "Value (begin)", Header "Cashflow", Header "Value (end)", Header "PnL"] , Tbl.Group SingleLine [Header "IRR", Header "TWR"]]) tableBody putStrLn $ Ascii.render prettyTables id id id table timeWeightedReturn showCashFlow prettyTables investmentsQuery trans (OneSpan spanBegin spanEnd valueBefore valueAfter cashFlow) = do let initialUnitPrice = 100 let initialUnits = valueBefore / initialUnitPrice let cashflow = -- Aggregate all entries for a single day, assuming that intraday interest is negligible map (\date_cash -> let (dates, cash) = unzip date_cash in (head dates, sum cash)) $ groupBy ((==) `on` fst) $ sortOn fst $ map (\(d,a) -> (d, negate a)) $ filter ((/=0).snd) cashFlow let units = tail $ scanl (\(_, _, _, unitBalance) (date, amt) -> let valueOnDate = total trans (And [investmentsQuery, Date (DateSpan Nothing (Just date))]) unitPrice = if unitBalance == 0.0 then initialUnitPrice else valueOnDate / unitBalance unitsBoughtOrSold = amt / unitPrice in (valueOnDate, unitsBoughtOrSold, unitPrice, unitBalance + unitsBoughtOrSold)) (0, 0, 0, initialUnits) cashflow let finalUnitBalance = if null units then initialUnits else let (_,_,_,u) = last units in u finalUnitPrice = if finalUnitBalance == 0 then initialUnitPrice else valueAfter / finalUnitBalance totalTWR = roundTo 2 $ (finalUnitPrice - initialUnitPrice) years = fromIntegral (diffDays spanEnd spanBegin) / 365 :: Double annualizedTWR = 100*((1+(realToFrac totalTWR/100))**(1/years)-1) :: Double let s d = show $ roundTo 2 d when showCashFlow $ do printf "\nTWR cash flow for %s - %s\n" (showDate spanBegin) (showDate (addDays (-1) spanEnd)) let (dates', amounts') = unzip cashflow (valuesOnDate',unitsBoughtOrSold', unitPrices', unitBalances') = unzip4 units add x lst = if valueBefore/=0 then x:lst else lst dates = add spanBegin dates' amounts = add valueBefore amounts' unitsBoughtOrSold = add initialUnits unitsBoughtOrSold' unitPrices = add initialUnitPrice unitPrices' unitBalances = add initialUnits unitBalances' valuesOnDate = add 0 valuesOnDate' putStr $ Ascii.render prettyTables id id id (Table (Tbl.Group NoLine (map (Header . showDate) dates)) (Tbl.Group DoubleLine [ Tbl.Group SingleLine [Header "Portfolio value", Header "Unit balance"] , Tbl.Group SingleLine [Header "Cash", Header "Unit price", Header "Units"] , Tbl.Group SingleLine [Header "New Unit Balance"]]) [ [value, oldBalance, amt, prc, udelta, balance] | value <- map s valuesOnDate | oldBalance <- map s (0:unitBalances) | balance <- map s unitBalances | amt <- map s amounts | prc <- map s unitPrices | udelta <- map s unitsBoughtOrSold ]) printf "Final unit price: %s/%s=%s U.\nTotal TWR: %s%%.\nPeriod: %.2f years.\nAnnualized TWR: %.2f%%\n\n" (s valueAfter) (s finalUnitBalance) (s finalUnitPrice) (s totalTWR) years annualizedTWR return annualizedTWR internalRateOfReturn showCashFlow prettyTables (OneSpan spanBegin spanEnd valueBefore valueAfter cashFlow) = do let prefix = (spanBegin, negate valueBefore) postfix = (spanEnd, valueAfter) totalCF = filter ((/=0) . snd) $ prefix : (sortOn fst cashFlow) ++ [postfix] when showCashFlow $ do printf "\nIRR cash flow for %s - %s\n" (showDate spanBegin) (showDate (addDays (-1) spanEnd)) let (dates, amounts) = unzip totalCF putStrLn $ Ascii.render prettyTables id id id (Table (Tbl.Group NoLine (map (Header . showDate) dates)) (Tbl.Group SingleLine [Header "Amount"]) (map ((:[]) . show) amounts)) -- 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 spanEnd totalCF) of Root rate -> return ((rate-1)*100) NotBracketed -> error' "Error: No solution -- not bracketed." -- PARTIAL: SearchFailed -> error' "Error: Failed to find solution." type CashFlow = [(Day, Quantity)] interestSum :: Day -> CashFlow -> Double -> Double interestSum referenceDay cf rate = sum $ map go cf where go (t,m) = fromRational (toRational m) * (rate ** (fromIntegral (referenceDay `diffDays` t) / 365)) calculateCashFlow :: [Transaction] -> Query -> CashFlow calculateCashFlow trans query = map go trans where go t = (transactionDate2 t, total [t] query) total :: [Transaction] -> Query -> Quantity total trans query = unMix $ sumPostings $ filter (matchesPosting query) $ concatMap realPostings trans unMix :: MixedAmount -> Quantity unMix a = case (normaliseMixedAmount $ mixedAmountCost a) of (Mixed [a]) -> aquantity a _ -> error' "MixedAmount failed to normalize" -- PARTIAL: hledger-1.19.1/Hledger/Cli/Commands/Stats.hs0000644000000000000000000001133213722544246016670 0ustar0000000000000000{-| Print some statistics for the journal. -} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} module Hledger.Cli.Commands.Stats ( statsmode ,stats ) where import Data.List import Data.List.Extra (nubSort) import Data.Maybe import Data.Ord import Data.HashSet (size, fromList) -- import Data.Text (Text) import qualified Data.Text as T import Data.Time.Calendar import System.Console.CmdArgs.Explicit import Text.Printf import qualified Data.Map as Map import Hledger import Hledger.Cli.CliOptions import Prelude hiding (putStr) import Hledger.Cli.Utils (writeOutput) 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{reportopts_=reportopts_} j = do d <- getCurrentDay let q = queryFromOpts d reportopts_ l = ledgerFromJournal q j reportspan = (ledgerDateSpan l) `spanDefaultsFrom` (queryDateSpan False q) intervalspans = splitSpan (interval_ reportopts_) reportspan showstats = showLedgerStats l d s = intercalate "\n" $ map showstats intervalspans writeOutput opts s showLedgerStats :: Ledger -> Day -> DateSpan -> String showLedgerStats l today span = unlines $ map (\(label,value) -> concatBottomPadded [printf fmt1 label, value]) stats where fmt1 = "%-" ++ show w1 ++ "s: " -- fmt2 = "%-" ++ show w2 ++ "s" w1 = maximum $ map (length . fst) stats -- w2 = maximum $ map (length . show . snd) stats stats = [ ("Main file" :: String, path) -- ++ " (from " ++ source ++ ")") ,("Included files", unlines $ drop 1 $ journalFilePaths j) ,("Transactions span", printf "%s to %s (%d days)" (start span) (end span) 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 ] where j = ljournal l path = journalFilePath j ts = sortOn tdate $ filter (spanContainsDate span . tdate) $ jtxns j as = nub $ map paccount $ concatMap tpostings ts cs = either error' Map.keys $ commodityStylesFromAmounts $ concatMap (amounts . pamount) $ concatMap tpostings ts -- PARTIAL: lastdate | null ts = Nothing | otherwise = Just $ tdate $ last ts lastelapsed = fmap (diffDays today) lastdate showelapsed Nothing = "" showelapsed (Just days) = printf " (%d %s)" days' direction where days' = abs days direction | days >= 0 = "days ago" :: String | otherwise = "days from now" tnum = length ts start (DateSpan (Just d) _) = show d start _ = "" end (DateSpan _ (Just d)) = show d end _ = "" days = fromMaybe 0 $ daysInSpan span txnrate | days==0 = 0 | otherwise = fromIntegral tnum / 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.19.1/Hledger/Cli/Commands/Tags.hs0000755000000000000000000000310213723502755016467 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,reportopts_=ropts} j = do d <- getCurrentDay let args = listofstringopt "args" rawopts mtagpat <- mapM (either Fail.fail pure . toRegexCI) $ headMay args let queryargs = drop 1 args values = boolopt "values" rawopts parsed = boolopt "parsed" rawopts empty = empty_ ropts q = queryFromOpts d $ ropts{query_ = unwords $ map quoteIfNeeded queryargs} txns = filter (q `matchesTransaction`) $ jtxns $ journalSelectingAmountFromOpts ropts j tagsorvalues = (if parsed then id else nubSort) [ r | (t,v) <- concatMap transactionAllTags txns , maybe True (`regexMatch` T.unpack t) mtagpat , let r = if values then v else t , not (values && T.null v && not empty) ] mapM_ T.putStrLn tagsorvalues hledger-1.19.1/Hledger/Cli/CompoundBalanceCommand.hs0000644000000000000000000003322413722544246020366 0ustar0000000000000000{-# LANGUAGE OverloadedStrings, RecordWildCards, LambdaCase #-} {-| 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 import qualified Data.Text as TS import qualified Data.Text.Lazy as TL import Data.Time.Calendar import System.Console.CmdArgs.Explicit as C import Hledger.Read.CsvReader (CSV, printCSV) import Lucid as L hiding (value_) import Text.Tabular as T import Hledger import Hledger.Cli.Commands.Balance import Hledger.Cli.CliOptions import Hledger.Cli.Utils (unsupportedOutputFormatError, writeOutput) -- | 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], -- ^ subreport details cbctype :: BalanceType -- ^ the "balance" type (change, cumulative, historical) -- this report shows (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 ["change"] (setboolopt "change") ("show balance change in each period" ++ defType PeriodChange) ,flagNone ["cumulative"] (setboolopt "cumulative") ("show balance change accumulated across periods (in multicolumn reports)" ++ defType CumulativeChange ) ,flagNone ["historical","H"] (setboolopt "historical") ("show historical ending balance in each period (includes postings before report start date)" ++ defType HistoricalBalance ) ] ++ flattreeflags True ++ [flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "flat mode: omit N leading account name parts" ,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 ["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 ["pretty-tables"] (setboolopt "pretty-tables") "use unicode when displaying tables" ,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" ,outputFormatFlag ["txt","html","csv","json"] ,outputFileFlag ]) [generalflagsgroup1] hiddenflags ([], Just $ argsFlag "[QUERY]") where defType :: BalanceType -> String defType bt | bt == cbctype = " (default)" | otherwise = "" -- | Generate a runnable command from a compound balance command specification. compoundBalanceCommand :: CompoundBalanceCommandSpec -> (CliOpts -> Journal -> IO ()) compoundBalanceCommand CompoundBalanceCommandSpec{..} opts@CliOpts{reportopts_=ropts@ReportOpts{..}, rawopts_=rawopts} j = do today <- getCurrentDay let -- use the default balance type for this report, unless the user overrides mBalanceTypeOverride = choiceopt parse rawopts where parse = \case "historical" -> Just HistoricalBalance "cumulative" -> Just CumulativeChange "change" -> Just PeriodChange _ -> Nothing balancetype = fromMaybe cbctype mBalanceTypeOverride -- Set balance type in the report options. ropts' = ropts{balancetype_=balancetype} title = cbctitle ++ " " ++ titledatestr ++ maybe "" (' ':) mtitleclarification ++ valuationdesc where -- XXX #1078 the title of ending balance reports -- (HistoricalBalance) 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 balancetype of HistoricalBalance -> showEndDates enddates _ -> showDateSpan requestedspan where enddates = map (addDays (-1)) . mapMaybe spanEnd $ cbrDates cbr -- these spans will always have a definite end date requestedspan = queryDateSpan date2_ (queryFromOpts today ropts') `spanDefaultsFrom` journalDateSpan date2_ j -- when user overrides, add an indication to the report title mtitleclarification = flip fmap mBalanceTypeOverride $ \t -> case t of PeriodChange -> "(Balance Changes)" CumulativeChange -> "(Cumulative Ending Balances)" HistoricalBalance -> "(Historical Ending Balances)" valuationdesc = case value_ of Just (AtCost _mc) -> ", valued at cost" Just (AtThen _mc) -> error' unsupportedValueThenError -- TODO Just (AtEnd _mc) -> ", valued at period ends" Just (AtNow _mc) -> ", current value" Just (AtDefault _mc) | multiperiod -> ", valued at period ends" Just (AtDefault _mc) -> ", current value" Just (AtDate today _mc) -> ", valued at "++showDate today Nothing -> "" where multiperiod = interval_ /= NoInterval -- make a CompoundBalanceReport. cbr' = compoundBalanceReport today ropts' j cbcqueries cbr = cbr'{cbrTitle=title} -- render appropriately writeOutput opts $ case outputFormatFromOpts opts of "txt" -> compoundBalanceReportAsText ropts' cbr "csv" -> printCSV (compoundBalanceReportAsCsv ropts cbr) ++ "\n" "html" -> (++"\n") $ TL.unpack $ L.renderText $ compoundBalanceReportAsHtml ropts cbr "json" -> (++"\n") $ TL.unpack $ toJsonText cbr 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] -> String showEndDates es = case es of -- cf showPeriod (e:_:_) -> showdate e ++ ".." ++ showdate (last es) [e] -> showdate e [] -> "" where showdate = show -- | 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 -> CompoundBalanceReport -> String compoundBalanceReportAsText ropts (CompoundPeriodicReport title _colspans subreports (PeriodicReportRow _ coltotals grandtotal grandavg)) = title ++ "\n\n" ++ balanceReportTableAsText ropts bigtable' where bigtable = case map (subreportAsTable ropts) subreports of [] -> T.empty r:rs -> foldl' concatTables r rs bigtable' | no_total_ ropts || length subreports == 1 = bigtable | otherwise = bigtable +====+ row "Net:" ( coltotals ++ (if row_total_ ropts then [grandtotal] else []) ++ (if average_ ropts then [grandavg] else []) ) -- | Convert a named multi balance report to a table suitable for -- concatenating with others to make a compound balance report table. subreportAsTable ropts (title, r, _) = t where -- convert to table Table lefthdrs tophdrs cells = balanceReportAsTable ropts r -- tweak the layout t = Table (T.Group SingleLine [Header title, lefthdrs]) tophdrs ([]:cells) -- | Add the second table below the first, discarding its column headings. concatTables (Table hLeft hTop dat) (Table hLeft' _ dat') = Table (T.Group DoubleLine [hLeft, hLeft']) hTop (dat ++ dat') -- | 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 -> CompoundBalanceReport -> CSV compoundBalanceReportAsCsv ropts (CompoundPeriodicReport title colspans subreports (PeriodicReportRow _ coltotals grandtotal grandavg)) = addtotals $ padRow title : ("Account" : map showDateSpanMonthAbbrev 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 ropts (subreporttitle, multibalreport, _) = padRow subreporttitle : tail (multiBalanceReportAsCsv ropts multibalreport) padRow s = take numcols $ s : repeat "" where numcols | null subreports = 1 | otherwise = (1 +) $ -- account name column (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 = (++ ["Net:" : map (showMixedAmountOneLineWithoutPrice False) ( coltotals ++ (if row_total_ ropts then [grandtotal] else []) ++ (if average_ ropts then [grandavg] else []) ) ]) -- | Render a compound balance report as HTML. compoundBalanceReportAsHtml :: ReportOpts -> CompoundBalanceReport -> Html () compoundBalanceReportAsHtml ropts cbr = let CompoundPeriodicReport title colspans subreports (PeriodicReportRow _ coltotals grandtotal grandavg) = cbr colspanattr = colspan_ $ TS.pack $ show $ 1 + length colspans + (if row_total_ ropts then 1 else 0) + (if average_ ropts then 1 else 0) leftattr = style_ "text-align:left" blankrow = tr_ $ td_ [colspanattr] $ toHtmlRaw (" "::String) titlerows = [tr_ $ th_ [colspanattr, leftattr] $ h2_ $ toHtml title] ++ [thRow $ "" : map showDateSpanMonthAbbrev colspans ++ (if row_total_ ropts then ["Total"] else []) ++ (if average_ ropts then ["Average"] else []) ] thRow :: [String] -> 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 :: (String, MultiBalanceReport, Bool) -> [Html ()] subreportrows (subreporttitle, mbr, _increasestotal) = let (_,bodyrows,mtotalsrow) = multiBalanceReportHtmlRows ropts mbr in [tr_ $ th_ [colspanattr, leftattr] $ toHtml subreporttitle] ++ bodyrows ++ maybe [] (:[]) mtotalsrow ++ [blankrow] totalrows | no_total_ ropts || length subreports == 1 = [] | otherwise = let defstyle = style_ "text-align:right" in [tr_ $ mconcat $ th_ [class_ "", style_ "text-align:left"] "Net:" : [th_ [class_ "amount coltotal", defstyle] (toHtml $ showMixedAmountOneLineWithoutPrice False a) | a <- coltotals] ++ (if row_total_ ropts then [th_ [class_ "amount coltotal", defstyle] $ toHtml $ showMixedAmountOneLineWithoutPrice False grandtotal] else []) ++ (if average_ ropts then [th_ [class_ "amount colaverage", defstyle] $ toHtml $ showMixedAmountOneLineWithoutPrice False grandavg] else []) ] in do style_ (TS.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.19.1/app/hledger-cli.hs0000755000000000000000000000022313700077706014705 0ustar0000000000000000#!/usr/bin/env runhaskell -- the hledger command-line executable; see Hledger/Cli/Main.hs module Main (main) where import Hledger.Cli.Main (main) hledger-1.19.1/test/unittest.hs0000644000000000000000000000105713722544246014611 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.19.1/bench/bench.hs0000644000000000000000000000426713722544246014117 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.19.1/LICENSE0000644000000000000000000010451313302271456012417 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.19.1/Setup.hs0000644000000000000000000000005613302271456013043 0ustar0000000000000000import Distribution.Simple main = defaultMain hledger-1.19.1/hledger.cabal0000644000000000000000000002356513725533425014025 0ustar0000000000000000cabal-version: 1.12 -- This file has been generated from package.yaml by hpack version 0.33.0. -- -- see: https://github.com/sol/hpack -- -- hash: 6318476983e12bab8c8835a0781d94162a98e306fa19d4a916a2c750d4e353c4 name: hledger version: 1.19.1 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 tested-with: GHC==8.0.2, GHC==8.2.2, GHC==8.4.4, GHC==8.6.5, GHC==8.8.3, GHC==8.10.0.20200123 build-type: Simple extra-source-files: CHANGES.md README.md test/unittest.hs bench/10000x1000x10.journal hledger.1 hledger.txt hledger.info 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 embeddedfiles/hledger_journal.5 embeddedfiles/hledger_journal.txt embeddedfiles/hledger_journal.info embeddedfiles/hledger_csv.5 embeddedfiles/hledger_csv.txt embeddedfiles/hledger_csv.info embeddedfiles/hledger_timeclock.5 embeddedfiles/hledger_timeclock.txt embeddedfiles/hledger_timeclock.info embeddedfiles/hledger_timedot.5 embeddedfiles/hledger_timedot.txt embeddedfiles/hledger_timedot.info 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/Checkdates.txt Hledger/Cli/Commands/Checkdupes.txt Hledger/Cli/Commands/Close.txt Hledger/Cli/Commands/Codes.txt Hledger/Cli/Commands/Commodities.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/Printunique.txt Hledger/Cli/Commands/Register.txt Hledger/Cli/Commands/Registermatch.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.Main Hledger.Cli.CliOptions Hledger.Cli.DocFiles Hledger.Cli.Utils Hledger.Cli.Anon Hledger.Cli.Version 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.Checkdates Hledger.Cli.Commands.Checkdupes Hledger.Cli.Commands.Close Hledger.Cli.Commands.Codes Hledger.Cli.Commands.Commodities 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.Printunique Hledger.Cli.Commands.Register Hledger.Cli.Commands.Registermatch Hledger.Cli.Commands.Rewrite Hledger.Cli.Commands.Roi Hledger.Cli.Commands.Stats Hledger.Cli.Commands.Tags Hledger.Cli.CompoundBalanceCommand other-modules: Paths_hledger ghc-options: -Wall -fno-warn-unused-do-bind -fno-warn-name-shadowing -fno-warn-missing-signatures -fno-warn-type-defaults -fno-warn-orphans -optP-Wno-nonportable-include-path cpp-options: -DVERSION="1.19.1" build-depends: Decimal >=0.5.1 , Diff , aeson >=1 , ansi-terminal >=0.9 , base >=4.9 && <4.15 , base-compat-batteries >=0.10.1 && <0.12 , bytestring , cmdargs >=0.10 , containers , data-default >=0.5 , directory , extra >=1.6.3 , filepath , hashable >=1.2.4 , haskeline >=0.6 , hledger-lib >=1.19.1 && <1.20 , lucid , math-functions >=0.3.3.0 , megaparsec >=7.0.0 && <9.1 , mtl >=2.2.1 , old-time , parsec >=3 , pretty-show >=1.6.4 , process , regex-tdfa , safe >=0.2 , shakespeare >=2.0.2.2 , split >=0.1 , tabular >=0.2 , tasty >=1.2.3 , temporary , text >=0.11 , time >=1.5 , timeit , transformers , unordered-containers , utf8-string >=0.3.5 , utility-ht >=0.0.13 , wizards >=1.0 if (!(os(windows))) && (flag(terminfo)) build-depends: terminfo default-language: Haskell2010 executable hledger main-is: hledger-cli.hs other-modules: Paths_hledger hs-source-dirs: app ghc-options: -Wall -fno-warn-unused-do-bind -fno-warn-name-shadowing -fno-warn-missing-signatures -fno-warn-type-defaults -fno-warn-orphans -optP-Wno-nonportable-include-path cpp-options: -DVERSION="1.19.1" build-depends: Decimal >=0.5.1 , aeson >=1 , ansi-terminal >=0.9 , base >=4.9 && <4.15 , base-compat-batteries >=0.10.1 && <0.12 , bytestring , cmdargs >=0.10 , containers , data-default >=0.5 , directory , extra >=1.6.3 , filepath , haskeline >=0.6 , hledger , hledger-lib >=1.19.1 && <1.20 , math-functions >=0.3.3.0 , megaparsec >=7.0.0 && <9.1 , mtl >=2.2.1 , old-time , parsec >=3 , pretty-show >=1.6.4 , process , regex-tdfa , safe >=0.2 , shakespeare >=2.0.2.2 , split >=0.1 , tabular >=0.2 , tasty >=1.2.3 , temporary , text >=0.11 , time >=1.5 , timeit , transformers , unordered-containers , utf8-string >=0.3.5 , utility-ht >=0.0.13 , wizards >=1.0 if (!(os(windows))) && (flag(terminfo)) build-depends: terminfo if flag(threaded) ghc-options: -threaded default-language: Haskell2010 test-suite unittest type: exitcode-stdio-1.0 main-is: unittest.hs hs-source-dirs: test ghc-options: -Wall -fno-warn-unused-do-bind -fno-warn-name-shadowing -fno-warn-missing-signatures -fno-warn-type-defaults -fno-warn-orphans -optP-Wno-nonportable-include-path cpp-options: -DVERSION="1.19.1" build-depends: Decimal >=0.5.1 , aeson >=1 , ansi-terminal >=0.9 , base >=4.9 && <4.15 , base-compat-batteries >=0.10.1 && <0.12 , bytestring , cmdargs >=0.10 , containers , data-default >=0.5 , directory , extra >=1.6.3 , filepath , haskeline >=0.6 , hledger , hledger-lib >=1.19.1 && <1.20 , math-functions >=0.3.3.0 , megaparsec >=7.0.0 && <9.1 , mtl >=2.2.1 , old-time , parsec >=3 , pretty-show >=1.6.4 , process , regex-tdfa , safe >=0.2 , shakespeare >=2.0.2.2 , split >=0.1 , tabular >=0.2 , tasty >=1.2.3 , temporary , text >=0.11 , time >=1.5 , timeit , transformers , unordered-containers , utf8-string >=0.3.5 , utility-ht >=0.0.13 , wizards >=1.0 if (!(os(windows))) && (flag(terminfo)) build-depends: terminfo default-language: Haskell2010 benchmark bench type: exitcode-stdio-1.0 main-is: bench.hs hs-source-dirs: bench ghc-options: -Wall -fno-warn-unused-do-bind -fno-warn-name-shadowing -fno-warn-missing-signatures -fno-warn-type-defaults -fno-warn-orphans -optP-Wno-nonportable-include-path build-depends: Decimal >=0.5.1 , aeson >=1 , ansi-terminal >=0.9 , base >=4.9 && <4.15 , base-compat-batteries >=0.10.1 && <0.12 , bytestring , cmdargs >=0.10 , containers , criterion , data-default >=0.5 , directory , extra >=1.6.3 , filepath , haskeline >=0.6 , hledger , hledger-lib >=1.19.1 && <1.20 , html , math-functions >=0.3.3.0 , megaparsec >=7.0.0 && <9.1 , mtl >=2.2.1 , old-time , parsec >=3 , pretty-show >=1.6.4 , process , regex-tdfa , safe >=0.2 , shakespeare >=2.0.2.2 , split >=0.1 , tabular >=0.2 , tasty >=1.2.3 , temporary , text >=0.11 , time >=1.5 , timeit , transformers , unordered-containers , utf8-string >=0.3.5 , utility-ht >=0.0.13 , wizards >=1.0 buildable: False if (!(os(windows))) && (flag(terminfo)) build-depends: terminfo default-language: Haskell2010 hledger-1.19.1/CHANGES.md0000644000000000000000000023305213725533425013013 0ustar0000000000000000User-visible changes in the hledger command line tool and library. # 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 http://hledger.org/manual.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 http://hledger.org/release-notes or doc/release-notes.md. hledger-1.19.1/README.md0000644000000000000000000000043613722544246012676 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.19.1/bench/10000x1000x10.journal0000644000000000000000000454013613700077722015562 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.19.1/hledger.10000644000000000000000000042122513725533425013116 0ustar0000000000000000.\"t .TH "hledger" "1" "September 2020" "hledger 1.18.99" "hledger User Manuals" .SH NAME .PP hledger - a command-line accounting tool .SH SYNOPSIS .PP \f[C]hledger [-f FILE] COMMAND [OPTIONS] [ARGS]\f[R] .PD 0 .P .PD \f[C]hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS]\f[R] .PD 0 .P .PD \f[C]hledger\f[R] .SH DESCRIPTION .PP hledger is a reliable, 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). .PP This is hledger\[cq]s command-line interface (there are also terminal and web interfaces). Its basic function is to read a plain text file describing financial transactions (in accounting terms, a general journal) and print useful reports on standard output, or export them as CSV. hledger can also read some other file formats such as CSV files, translating them to journal format. Additionally, hledger lists other hledger-* executables found in the user\[cq]s $PATH and can invoke them as subcommands. .PP hledger reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]-f\f[R], or \f[C]$LEDGER_FILE\f[R], or \f[C]$HOME/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). If using \f[C]$LEDGER_FILE\f[R], note this must be a real environment variable, not a shell variable. You can specify standard input with \f[C]-f-\f[R]. .PP Transactions are dated movements of money between two (or more) named accounts, and are recorded with journal entries like this: .IP .nf \f[C] 2015/10/16 bought food expenses:food $10 assets:cash \f[R] .fi .PP For more about this format, see hledger_journal(5). .PP Most users use a text editor to edit the journal, usually with an editor mode such as ledger-mode for added convenience. hledger\[cq]s interactive add command is another way to record new transactions. hledger never changes existing transactions. .PP To get started, you can either save some entries like the above in \f[C]\[ti]/.hledger.journal\f[R], or run \f[C]hledger add\f[R] and follow the prompts. Then try some commands like \f[C]hledger print\f[R] or \f[C]hledger balance\f[R]. Run \f[C]hledger\f[R] with no arguments for a list of commands. .SH COMMON TASKS .PP Here are some quick examples of how to do some basic tasks with hledger. For more details, see the reference section below, the hledger_journal(5) manual, or the more extensive docs at https://hledger.org. .SS Getting help .IP .nf \f[C] $ hledger # show available commands $ hledger --help # show common options $ hledger CMD --help # show common and command options, and command help $ hledger help # show available manuals/topics $ hledger help hledger # show hledger manual as info/man/text (auto-chosen) $ hledger help journal --man # show the journal manual as a man page $ hledger help --help # show more detailed help for the help command \f[R] .fi .PP Find more docs, chat, mail list, reddit, issue tracker: https://hledger.org#help-feedback .SS Constructing command lines .PP hledger has an extensive and powerful command line interface. We strive to keep it simple and ergonomic, but you may run into one of the confusing real world details described in OPTIONS, below. If that happens, here are some tips that may help: .IP \[bu] 2 command-specific options must go after the command (it\[aq]s fine to put all options there) (\f[C]hledger CMD OPTS ARGS\f[R]) .IP \[bu] 2 running add-on executables directly simplifies command line parsing (\f[C]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 is being parsed, add \f[C]--debug=2\f[R]. .SS Starting a journal file .PP hledger looks for your accounting data in a journal file, \f[C]$HOME/.hledger.journal\f[R] by default: .IP .nf \f[C] $ 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. \f[R] .fi .PP You can override this by setting the \f[C]LEDGER_FILE\f[R] environment variable. 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 .nf \f[C] $ mkdir \[ti]/finance $ cd \[ti]/finance $ git init Initialized empty Git repository in /Users/simon/finance/.git/ $ touch 2020.journal $ echo \[dq]export LEDGER_FILE=$HOME/finance/2020.journal\[dq] >> \[ti]/.bashrc $ source \[ti]/.bashrc $ hledger stats Main file : /Users/simon/finance/2020.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 () \f[R] .fi .SS Setting opening balances .PP 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 .nf \f[C] 2020-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 \f[R] .fi .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[C]hledger add\f[R] and follow the prompts to record a similar transaction: .RS 2 .IP .nf \f[C] $ hledger add Adding transactions to journal file /Users/simon/finance/2020.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 [2020-02-07]: 2020-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): . 2020-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 [2020-01-01]: . \f[R] .fi .RE .PP If you\[aq]re using version control, this could be a good time to commit the journal. Eg: .IP .nf \f[C] $ git commit -m \[aq]initial balances\[aq] 2020.journal \f[R] .fi .SS Recording transactions .PP 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 .nf \f[C] 2020/1/10 * gift received assets:cash $20 income:gifts 2020.1.12 * farmers market expenses:food $13 assets:cash 2020-01-15 paycheck income:salary assets:bank:checking $1000 \f[R] .fi .SS Reconciling .PP 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[C]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[C]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 .nf \f[C] 2020-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc \f[R] .fi .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[C]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[C]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[C]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[C]*\f[R] marker. Eg in the paycheck transaction above, insert \f[C]*\f[R] between \f[C]2020-01-15\f[R] and \f[C]paycheck\f[R] .PP If you\[aq]re using version control, this can be another good time to commit: .IP .nf \f[C] $ git commit -m \[aq]txns\[aq] 2020.journal \f[R] .fi .SS Reporting .PP Here are some basic reports. .PP Show all transactions: .IP .nf \f[C] $ hledger print 2020-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 2020-01-10 * gift received assets:cash $20 income:gifts 2020-01-12 * farmers market expenses:food $13 assets:cash 2020-01-15 * paycheck income:salary assets:bank:checking $1000 2020-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc \f[R] .fi .PP Show account names, and their hierarchy: .IP .nf \f[C] $ hledger accounts --tree assets bank checking savings cash equity opening/closing balances expenses food misc income gifts salary liabilities creditcard \f[R] .fi .PP Show all account totals: .IP .nf \f[C] $ 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 \f[R] .fi .PP Show only asset and liability balances, as a flat list, limited to depth 2: .IP .nf \f[C] $ hledger bal assets liabilities --flat -2 $4000 assets:bank $105 assets:cash $-50 liabilities:creditcard -------------------- $4055 \f[R] .fi .PP Show the same thing without negative numbers, formatted as a simple balance sheet: .IP .nf \f[C] $ hledger bs --flat -2 Balance Sheet 2020-01-16 || 2020-01-16 ========================++============ Assets || ------------------------++------------ assets:bank || $4000 assets:cash || $105 ------------------------++------------ || $4105 ========================++============ Liabilities || ------------------------++------------ liabilities:creditcard || $50 ------------------------++------------ || $50 ========================++============ Net: || $4055 \f[R] .fi .PP The final total is your \[dq]net worth\[dq] on the end date. (Or use \f[C]bse\f[R] for a full balance sheet with equity.) .PP Show income and expense totals, formatted as an income statement: .IP .nf \f[C] hledger is Income Statement 2020-01-01-2020-01-16 || 2020-01-01-2020-01-16 ===============++======================= Revenues || ---------------++----------------------- income:gifts || $20 income:salary || $1000 ---------------++----------------------- || $1020 ===============++======================= Expenses || ---------------++----------------------- expenses:food || $13 expenses:misc || $2 ---------------++----------------------- || $15 ===============++======================= Net: || $1005 \f[R] .fi .PP The final total is your net income during this period. .PP Show transactions affecting your wallet, with running total: .IP .nf \f[C] $ hledger register cash 2020-01-01 opening balances assets:cash $100 $100 2020-01-10 gift received assets:cash $20 $120 2020-01-12 farmers market assets:cash $-13 $107 2020-01-16 adjust cash assets:cash $-2 $105 \f[R] .fi .PP Show weekly posting counts as a bar chart: .IP .nf \f[C] $ hledger activity -W 2019-12-30 ***** 2020-01-06 **** 2020-01-13 **** \f[R] .fi .SS Migrating to a new file .PP 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[C]git add\f[R] the new file. .SH OPTIONS .SS General options .PP To see general usage help, including general options which are supported by most hledger commands, run \f[C]hledger -h\f[R]. .PP General help options: .TP \f[B]\f[CB]-h --help\f[B]\f[R] show general usage (or after COMMAND, command usage) .TP \f[B]\f[CB]--version\f[B]\f[R] show version .TP \f[B]\f[CB]--debug[=N]\f[B]\f[R] show debug output (levels 1-9, default: 1) .PP General input options: .TP \f[B]\f[CB]-f FILE --file=FILE\f[B]\f[R] use a different input file. For stdin, use - (default: \f[C]$LEDGER_FILE\f[R] or \f[C]$HOME/.hledger.journal\f[R]) .TP \f[B]\f[CB]--rules-file=RULESFILE\f[B]\f[R] Conversion rules file to use when reading CSV (default: FILE.rules) .TP \f[B]\f[CB]--separator=CHAR\f[B]\f[R] Field separator to expect when reading CSV (default: \[aq],\[aq]) .TP \f[B]\f[CB]--alias=OLD=NEW\f[B]\f[R] rename accounts named OLD to NEW .TP \f[B]\f[CB]--anon\f[B]\f[R] anonymize accounts and payees .TP \f[B]\f[CB]--pivot FIELDNAME\f[B]\f[R] use some other field or tag for the account name .TP \f[B]\f[CB]-I --ignore-assertions\f[B]\f[R] disable balance assertion checks (note: does not disable balance assignments) .PP General reporting options: .TP \f[B]\f[CB]-b --begin=DATE\f[B]\f[R] include postings/txns on or after this date .TP \f[B]\f[CB]-e --end=DATE\f[B]\f[R] include postings/txns before this date .TP \f[B]\f[CB]-D --daily\f[B]\f[R] multiperiod/multicolumn report by day .TP \f[B]\f[CB]-W --weekly\f[B]\f[R] multiperiod/multicolumn report by week .TP \f[B]\f[CB]-M --monthly\f[B]\f[R] multiperiod/multicolumn report by month .TP \f[B]\f[CB]-Q --quarterly\f[B]\f[R] multiperiod/multicolumn report by quarter .TP \f[B]\f[CB]-Y --yearly\f[B]\f[R] multiperiod/multicolumn report by year .TP \f[B]\f[CB]-p --period=PERIODEXP\f[B]\f[R] set start date, end date, and/or reporting interval all at once using period expressions syntax .TP \f[B]\f[CB]--date2\f[B]\f[R] match the secondary date instead (see command help for other effects) .TP \f[B]\f[CB]-U --unmarked\f[B]\f[R] include only unmarked postings/txns (can combine with -P or -C) .TP \f[B]\f[CB]-P --pending\f[B]\f[R] include only pending postings/txns .TP \f[B]\f[CB]-C --cleared\f[B]\f[R] include only cleared postings/txns .TP \f[B]\f[CB]-R --real\f[B]\f[R] include only non-virtual postings .TP \f[B]\f[CB]-NUM --depth=NUM\f[B]\f[R] hide/aggregate accounts or postings more than NUM levels deep .TP \f[B]\f[CB]-E --empty\f[B]\f[R] show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) .TP \f[B]\f[CB]-B --cost\f[B]\f[R] convert amounts to their cost/selling amount at transaction time .TP \f[B]\f[CB]-V --market\f[B]\f[R] convert amounts to their market value in default valuation commodities .TP \f[B]\f[CB]-X --exchange=COMM\f[B]\f[R] convert amounts to their market value in commodity COMM .TP \f[B]\f[CB]--value\f[B]\f[R] convert amounts to cost or market value, more flexibly than -B/-V/-X .TP \f[B]\f[CB]--infer-value\f[B]\f[R] with -V/-X/--value, also infer market prices from transactions .TP \f[B]\f[CB]--auto\f[B]\f[R] apply automated posting rules to modify transactions. .TP \f[B]\f[CB]--forecast\f[B]\f[R] generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. .TP \f[B]\f[CB]--color=WHEN (or --colour=WHEN)\f[B]\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. .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. .SS Command options .PP To see options for a particular command, including command-specific options, run: \f[C]hledger COMMAND -h\f[R]. .PP Command-specific options must be written after the command name, eg: \f[C]hledger print -x\f[R]. .PP Additionally, if the command is an addon, you may need to put its options after a double-hyphen, eg: \f[C]hledger ui -- --watch\f[R]. Or, you can run the addon executable directly: \f[C]hledger-ui --watch\f[R]. .SS Command arguments .PP Most hledger commands accept arguments after the command name, which are often a query, filtering the data in some way. .PP You can save a set of command line options/arguments in a file, and then reuse them by writing \f[C]\[at]FILENAME\f[R] as a command line argument. Eg: \f[C]hledger bal \[at]foo.args\f[R]. (To prevent this, eg if you have an argument that begins with a literal \f[C]\[at]\f[R], precede it with \f[C]--\f[R], eg: \f[C]hledger bal -- \[at]ARG\f[R]). .PP Inside the argument file, each line should contain just one option or argument. Avoid the use of spaces, except inside quotes (or you\[aq]ll see a confusing error). Between a flag and its argument, use = (or nothing). Bad: .IP .nf \f[C] assets depth:2 -X USD \f[R] .fi .PP Good: .IP .nf \f[C] assets depth:2 -X=USD \f[R] .fi .PP For special characters (see below), use one less level of quoting than you would at the command prompt. Bad: .IP .nf \f[C] -X\[dq]$\[dq] \f[R] .fi .PP Good: .IP .nf \f[C] -X$ \f[R] .fi .PP See also: Save frequently used options. .SS Queries .PP One of hledger\[aq]s strengths is being able to quickly report on precise subsets of your data. Most commands accept an optional query expression, written as arguments after the command name, to filter the data by date, account name or other criteria. The syntax is similar to a web search: one or more space-separated search terms, quotes to enclose whitespace, prefixes to match specific fields, a not: prefix to negate the match. .PP We do not yet support arbitrary boolean combinations of search terms; instead most commands show transactions/postings/accounts which match (or negatively 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 instead shows 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 The following kinds of search terms can be used. Remember these can also be prefixed with \f[B]\f[CB]not:\f[B]\f[R], eg to exclude a particular subaccount. .TP \f[B]\f[R]\f[C]REGEX\f[R]\f[B], \f[R]\f[C]acct:REGEX\f[R]\f[B]\f[R] match account names by this regular expression. (With no prefix, \f[C]acct:\f[R] is assumed.) same as above .TP \f[B]\f[R]\f[C]amt:N, amt:N, amt:>=N\f[R]\f[B]\f[R] match postings with a single-commodity amount that is equal to, less than, or greater than N. (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. .TP \f[B]\f[R]\f[C]code:REGEX\f[R]\f[B]\f[R] match by transaction code (eg check number) .TP \f[B]\f[R]\f[C]cur:REGEX\f[R]\f[B]\f[R] match postings or transactions including any amounts whose currency/commodity symbol is fully matched by REGEX. (For a partial match, use \f[C].*REGEX.*\f[R]). Note, to match characters which are regex-significant, like the dollar sign (\f[C]$\f[R]), you need to prepend \f[C]\[rs]\f[R]. And when using the command line you need to add one more level of quoting to hide it from the shell, so eg do: \f[C]hledger print cur:\[aq]\[rs]$\[aq]\f[R] or \f[C]hledger print cur:\[rs]\[rs]$\f[R]. .TP \f[B]\f[R]\f[C]desc:REGEX\f[R]\f[B]\f[R] match transaction descriptions. .TP \f[B]\f[R]\f[C]date:PERIODEXPR\f[R]\f[B]\f[R] match dates within the specified period. PERIODEXPR is a period expression (with no report interval). Examples: \f[C]date:2016\f[R], \f[C]date:thismonth\f[R], \f[C]date:2000/2/1-2/15\f[R], \f[C]date:lastweek-\f[R]. If the \f[C]--date2\f[R] command line flag is present, this matches secondary dates instead. .TP \f[B]\f[R]\f[C]date2:PERIODEXPR\f[R]\f[B]\f[R] match secondary dates within the specified period. .TP \f[B]\f[R]\f[C]depth:N\f[R]\f[B]\f[R] match (or display, depending on command) accounts at or above this depth .TP \f[B]\f[R]\f[C]note:REGEX\f[R]\f[B]\f[R] match transaction notes (part of description right of \f[C]|\f[R], or whole description when there\[aq]s no \f[C]|\f[R]) .TP \f[B]\f[R]\f[C]payee:REGEX\f[R]\f[B]\f[R] match transaction payee/payer names (part of description left of \f[C]|\f[R], or whole description when there\[aq]s no \f[C]|\f[R]) .TP \f[B]\f[R]\f[C]real:, real:0\f[R]\f[B]\f[R] match real or virtual postings respectively .TP \f[B]\f[R]\f[C]status:, status:!, status:*\f[R]\f[B]\f[R] match unmarked, pending, or cleared transactions respectively .TP \f[B]\f[R]\f[C]tag:REGEX[=REGEX]\f[R]\f[B]\f[R] match by tag name, and optionally also by tag value. Note a tag: query is considered to match a transaction if it matches any of the postings. Also remember that postings inherit the tags of their parent transaction. .PP The following special search term is used automatically in hledger-web, only: .TP \f[B]\f[R]\f[C]inacct:ACCTNAME\f[R]\f[B]\f[R] tells hledger-web to show the transaction register for this account. Can be filtered further with \f[C]acct\f[R] etc. .PP Some of these can also be expressed as command-line options (eg \f[C]depth:2\f[R] is equivalent to \f[C]--depth 2\f[R]). Generally you can mix options and query arguments, and the resulting query will be their intersection (perhaps excluding the \f[C]-p/--period\f[R] option). .SS Special characters in arguments and queries .PP In shell command lines, option and argument values which contain \[dq]problematic\[dq] characters, ie spaces, and also characters significant to your shell such as \f[C]<\f[R], \f[C]>\f[R], \f[C](\f[R], \f[C])\f[R], \f[C]|\f[R] and \f[C]$\f[R], should be escaped by enclosing them in quotes or by writing backslashes before the characters. Eg: .PP \f[C]hledger register -p \[aq]last year\[aq] \[dq]accounts receivable (receivable|payable)\[dq] amt:\[rs]>100\f[R]. .SS More escaping .PP Characters significant both to the shell and in regular expressions may need one extra level of escaping. These include parentheses, the pipe symbol and the dollar sign. Eg, to match the dollar symbol, bash users should do: .PP \f[C]hledger balance cur:\[aq]\[rs]$\[aq]\f[R] .PP or: .PP \f[C]hledger balance cur:\[rs]\[rs]$\f[R] .SS Even more escaping .PP When hledger runs an addon executable (eg you type \f[C]hledger ui\f[R], hledger runs \f[C]hledger-ui\f[R]), it de-escapes command-line options and arguments once, so you might need to \f[I]triple\f[R]-escape. Eg in bash, running the ui command and matching the dollar sign, it\[aq]s: .PP \f[C]hledger ui cur:\[aq]\[rs]\[rs]$\[aq]\f[R] .PP or: .PP \f[C]hledger ui cur:\[rs]\[rs]\[rs]\[rs]$\f[R] .PP If you asked why \f[I]four\f[R] slashes above, this may help: .PP .TS tab(@); l l. T{ unescaped: T}@T{ \f[C]$\f[R] T} T{ escaped: T}@T{ \f[C]\[rs]$\f[R] T} T{ double-escaped: T}@T{ \f[C]\[rs]\[rs]$\f[R] T} T{ triple-escaped: T}@T{ \f[C]\[rs]\[rs]\[rs]\[rs]$\f[R] T} .TE .PP (The number of backslashes in fish shell is left as an exercise for the reader.) .PP You can always avoid the extra escaping for addons by running the addon directly: .PP \f[C]hledger-ui cur:\[rs]\[rs]$\f[R] .SS Less escaping .PP Inside an argument file, or in the search field of hledger-ui or hledger-web, or at a GHCI prompt, you need one less level of escaping than at the command line. And backslashes may work better than quotes. Eg: .PP \f[C]ghci> :main balance cur:\[rs]$\f[R] .SS Unicode characters .PP 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[C]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 Input files .PP hledger reads transactions from a data file (and the add command writes to it). By default this file is \f[C]$HOME/.hledger.journal\f[R] (or on Windows, something like \f[C]C:/Users/USER/.hledger.journal\f[R]). You can override this with the \f[C]$LEDGER_FILE\f[R] environment variable: .IP .nf \f[C] $ setenv LEDGER_FILE \[ti]/finance/2016.journal $ hledger stats \f[R] .fi .PP or with the \f[C]-f/--file\f[R] option: .IP .nf \f[C] $ hledger -f /some/file stats \f[R] .fi .PP The file name \f[C]-\f[R] (hyphen) means standard input: .IP .nf \f[C] $ cat some.journal | hledger -f- \f[R] .fi .PP 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(7.8n) lw(39.5n) lw(22.7n). T{ Reader: T}@T{ Reads: T}@T{ Used for file extensions: T} _ T{ \f[C]journal\f[R] T}@T{ hledger journal files and some Ledger journals, for transactions T}@T{ \f[C].journal\f[R] \f[C].j\f[R] \f[C].hledger\f[R] \f[C].ledger\f[R] T} T{ \f[C]timeclock\f[R] T}@T{ timeclock files, for precise time logging T}@T{ \f[C].timeclock\f[R] T} T{ \f[C]timedot\f[R] T}@T{ timedot files, for approximate time logging T}@T{ \f[C].timedot\f[R] T} T{ \f[C]csv\f[R] T}@T{ comma/semicolon/tab/other-separated values, for data import T}@T{ \f[C].csv\f[R] \f[C].ssv\f[R] \f[C].tsv\f[R] T} .TE .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[C]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 When you can\[aq]t ensure the right file extension, not to worry: you can force a specific reader/format by prefixing the file path with the format and a colon. Eg to read a .dat file as csv: .IP .nf \f[C] $ hledger -f csv:/some/csv-file.dat stats $ echo \[aq]i 2009/13/1 08:00:00\[aq] | hledger print -ftimeclock:- \f[R] .fi .PP You can specify multiple \f[C]-f\f[R] options, to read multiple files as one big journal. There are some limitations with this: .IP \[bu] 2 directives in one file will not affect the other files .IP \[bu] 2 balance assertions will not see any account balances from previous files .PP If you need either of those things, you can .IP \[bu] 2 use a single parent file which includes the others .IP \[bu] 2 or concatenate the files into one before reading, eg: \f[C]cat a.journal b.journal | hledger -f- CMD\f[R]. .SS Output destination .PP 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 .nf \f[C] $ hledger print > foo.txt \f[R] .fi .PP Some commands (print, register, stats, the balance commands) also provide the \f[C]-o/--output-file\f[R] option, which does the same thing without needing the shell. Eg: .IP .nf \f[C] $ hledger print -o foo.txt $ hledger print -o - # write to stdout (the default) \f[R] .fi .SS Output format .PP Some commands (print, register, the balance commands) offer a choice of output format. In addition to the usual plain text format (\f[C]txt\f[R]), there are CSV (\f[C]csv\f[R]), HTML (\f[C]html\f[R]), JSON (\f[C]json\f[R]) and SQL (\f[C]sql\f[R]). This is controlled by the \f[C]-O/--output-format\f[R] option: .IP .nf \f[C] $ hledger print -O csv \f[R] .fi .PP or, by a file extension specified with \f[C]-o/--output-file\f[R]: .IP .nf \f[C] $ hledger balancesheet -o foo.html # write HTML to foo.html \f[R] .fi .PP The \f[C]-O\f[R] option can be used to override the file extension if needed: .IP .nf \f[C] $ hledger balancesheet -o foo.txt -O html # write HTML to foo.txt \f[R] .fi .PP Some notes about JSON output: .IP \[bu] 2 This feature is marked experimental, and not yet much used; you should expect our JSON to evolve. Real-world feedback is welcome. .IP \[bu] 2 Our JSON is rather large and verbose, as it is quite 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) .PP Notes about SQL output: .IP \[bu] 2 SQL output is also marked experimental, and much like JSON could use real-world feedback. .IP \[bu] 2 SQL output is expected to work with sqlite, MySQL and PostgreSQL .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[C]delete\f[R] or \f[C]truncate\f[R] SQL statements) or drop tables completely as otherwise your postings will be duped. .SS Regular expressions .PP hledger uses regular expressions in a number of places: .IP \[bu] 2 query terms, on the command line and in the hledger-web search form: \f[C]REGEX\f[R], \f[C]desc:REGEX\f[R], \f[C]cur:REGEX\f[R], \f[C]tag:...=REGEX\f[R] .IP \[bu] 2 CSV rules conditional blocks: \f[C]if REGEX ...\f[R] .IP \[bu] 2 account alias directives and options: \f[C]alias /REGEX/ = REPLACEMENT\f[R], \f[C]--alias /REGEX/=REPLACEMENT\f[R] .PP 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[C]\[rs]b\f[R], \f[C]\[rs]B\f[R], \f[C]\[rs]<\f[R], \f[C]\[rs]>\f[R]) .IP "5." 3 they do not support backreferences; if you write \f[C]\[rs]1\f[R], it will match the digit \f[C]1\f[R]. Except when doing text replacement, eg in account aliases, where backreferences can be used in the replacement string to reference capturing groups in the search regexp. .IP "6." 3 they do not support mode modifiers (\f[C](?s)\f[R]), character classes (\f[C]\[rs]w\f[R], \f[C]\[rs]d\f[R]), or anything else not mentioned above. .PP Some things to note: .IP \[bu] 2 In the \f[C]alias\f[R] directive and \f[C]--alias\f[R] option, regular expressions must be enclosed in forward slashes (\f[C]/REGEX/\f[R]). Elsewhere in hledger, these are not required. .IP \[bu] 2 In queries, to match a regular expression metacharacter like \f[C]$\f[R] as a literal character, prepend a backslash. Eg to search for amounts with the dollar sign in hledger-web, write \f[C]cur:\[rs]$\f[R]. .IP \[bu] 2 On the command line, some metacharacters like \f[C]$\f[R] have a special meaning to the shell and so must be escaped at least once more. See Special characters. .SS Smart dates .PP hledger\[aq]s user interfaces accept a flexible \[dq]smart date\[dq] syntax (unlike dates in the journal file). Smart dates allow some english words, can be relative to today\[aq]s date, and can have less-significant date parts omitted (defaulting to 1). .PP Examples: .PP .TS tab(@); lw(24.2n) lw(45.8n). T{ \f[C]2004/10/1\f[R], \f[C]2004-01-01\f[R], \f[C]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[C]2004\f[R] T}@T{ start of year T} T{ \f[C]2004/10\f[R] T}@T{ start of month T} T{ \f[C]10/1\f[R] T}@T{ month and day in current year T} T{ \f[C]21\f[R] T}@T{ day in current month T} T{ \f[C]october, oct\f[R] T}@T{ start of month in current year T} T{ \f[C]yesterday, today, tomorrow\f[R] T}@T{ -1, 0, 1 days from today T} T{ \f[C]last/this/next day/week/month/quarter/year\f[R] T}@T{ -1, 0, 1 periods from the current period T} T{ \f[C]20181201\f[R] T}@T{ 8 digit YYYYMMDD with valid year month and day T} T{ \f[C]201812\f[R] T}@T{ 6 digit YYYYMM with valid year and month T} .TE .PP Counterexamples - malformed digit sequences might give surprising results: .PP .TS tab(@); lw(11.4n) lw(58.6n). T{ \f[C]201813\f[R] T}@T{ 6 digits with an invalid month is parsed as start of 6-digit year T} T{ \f[C]20181301\f[R] T}@T{ 8 digits with an invalid month is parsed as start of 8-digit year T} T{ \f[C]20181232\f[R] T}@T{ 8 digits with an invalid day gives an error T} T{ \f[C]201801012\f[R] T}@T{ 9+ digits beginning with a valid YYYYMMDD gives an error T} .TE .SS Report start & end date .PP Most hledger reports show the full span of time represented by the journal data, by default. So, the effective report start and end dates will be the earliest and latest transaction or posting dates found in the journal. .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[C]-b/--begin\f[R], \f[C]-e/--end\f[R], \f[C]-p/--period\f[R] or a \f[C]date:\f[R] query (described below). All of these accept the smart date syntax. .PP Some notes: .IP \[bu] 2 As in Ledger, end dates are exclusive, so you need to write the date \f[I]after\f[R] the last day you want to include. .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[C]date:\f[R] queries. That is, \f[C]date:2019-01 date:2019 -p\[aq]2000 to 2030\[aq]\f[R] yields January 2019, the smallest common time span. .PP Examples: .PP .TS tab(@); lw(12.4n) lw(57.6n). T{ \f[C]-b 2016/3/17\f[R] T}@T{ begin on St.\ Patrick\[cq]s day 2016 T} T{ \f[C]-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[C]-b thismonth\f[R] T}@T{ all transactions on or after the 1st of the current month T} T{ \f[C]-p thismonth\f[R] T}@T{ all transactions in the current month T} T{ \f[C]date:2016/3/17..\f[R] T}@T{ the above written as queries instead (\f[C]..\f[R] can also be replaced with \f[C]-\f[R]) T} T{ \f[C]date:..12/1\f[R] T}@T{ T} T{ \f[C]date:thismonth..\f[R] T}@T{ T} T{ \f[C]date:thismonth\f[R] T}@T{ T} .TE .SS Report intervals .PP A report interval can be specified so that commands like register, balance and activity will divide their reports into multiple subperiods. The basic intervals can be selected with one of \f[C]-D/--daily\f[R], \f[C]-W/--weekly\f[R], \f[C]-M/--monthly\f[R], \f[C]-Q/--quarterly\f[R], or \f[C]-Y/--yearly\f[R]. More complex intervals may be specified with a period expression. Report intervals can not be specified with a query. .SS Period expressions .PP The \f[C]-p/--period\f[R] option accepts period expressions, a shorthand way of expressing a start date, end date, and/or report interval all at once. .PP Here\[aq]s a basic period expression specifying the first quarter of 2009. Note, hledger always treats start dates as inclusive and end dates as exclusive: .PP \f[C]-p \[dq]from 2009/1/1 to 2009/4/1\[dq]\f[R] .PP Keywords like \[dq]from\[dq] and \[dq]to\[dq] are optional, and so are the spaces, as long as you don\[aq]t run two dates together. \[dq]to\[dq] can also be written as \[dq]..\[dq] or \[dq]-\[dq]. These are equivalent to the above: .PP .TS tab(@); l. T{ \f[C]-p \[dq]2009/1/1 2009/4/1\[dq]\f[R] T} T{ \f[C]-p2009/1/1to2009/4/1\f[R] T} T{ \f[C]-p2009/1/1..2009/4/1\f[R] T} .TE .PP Dates are smart dates, so if the current year is 2009, the above can also be written as: .PP .TS tab(@); l. T{ \f[C]-p \[dq]1/1 4/1\[dq]\f[R] T} T{ \f[C]-p \[dq]january-apr\[dq]\f[R] T} T{ \f[C]-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 in your journal: .PP .TS tab(@); l l. T{ \f[C]-p \[dq]from 2009/1/1\[dq]\f[R] T}@T{ everything after january 1, 2009 T} T{ \f[C]-p \[dq]from 2009/1\[dq]\f[R] T}@T{ the same T} T{ \f[C]-p \[dq]from 2009\[dq]\f[R] T}@T{ the same T} T{ \f[C]-p \[dq]to 2009\[dq]\f[R] T}@T{ everything before january 1, 2009 T} .TE .PP A single date with no \[dq]from\[dq] or \[dq]to\[dq] defines both the start and end date like so: .PP .TS tab(@); l l. T{ \f[C]-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[C]-p \[dq]2009/1\[dq]\f[R] T}@T{ the month of jan; equivalent to \[lq]2009/1/1 to 2009/2/1\[rq] T} T{ \f[C]-p \[dq]2009/1/1\[dq]\f[R] T}@T{ just that day; equivalent to \[lq]2009/1/1 to 2009/1/2\[rq] T} .TE .PP Or you can specify a single quarter like so: .PP .TS tab(@); l l. T{ \f[C]-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[C]-p \[dq]q4\[dq]\f[R] T}@T{ fourth quarter of the current year T} .TE .PP The argument of \f[C]-p\f[R] can also begin with, or be, a report interval expression. The basic report intervals are \f[C]daily\f[R], \f[C]weekly\f[R], \f[C]monthly\f[R], \f[C]quarterly\f[R], or \f[C]yearly\f[R], which have the same effect as the \f[C]-D\f[R],\f[C]-W\f[R],\f[C]-M\f[R],\f[C]-Q\f[R], or \f[C]-Y\f[R] flags. Between report interval and start/end dates (if any), the word \f[C]in\f[R] is optional. Examples: .PP .TS tab(@); l. T{ \f[C]-p \[dq]weekly from 2009/1/1 to 2009/4/1\[dq]\f[R] T} T{ \f[C]-p \[dq]monthly in 2008\[dq]\f[R] T} T{ \f[C]-p \[dq]quarterly\[dq]\f[R] T} .TE .PP Note that \f[C]weekly\f[R], \f[C]monthly\f[R], \f[C]quarterly\f[R] and \f[C]yearly\f[R] intervals will always start on the first day on week, month, quarter or year accordingly, and will end on the last day of same period, even if associated period expression specifies different explicit start and end date. .PP For example: .PP .TS tab(@); lw(25.5n) lw(44.5n). T{ \f[C]-p \[dq]weekly from 2009/1/1 to 2009/4/1\[dq]\f[R] T}@T{ starts on 2008/12/29, closest preceding Monday T} T{ \f[C]-p \[dq]monthly in 2008/11/25\[dq]\f[R] T}@T{ starts on 2018/11/01 T} T{ \f[C]-p \[dq]quarterly from 2009-05-05 to 2009-06-01\[dq]\f[R] T}@T{ starts on 2009/04/01, ends on 2009/06/30, which are first and last days of Q2 2009 T} T{ \f[C]-p \[dq]yearly from 2009-12-29\[dq]\f[R] T}@T{ starts on 2009/01/01, first day of 2009 T} .TE .PP The following more complex report intervals are also supported: \f[C]biweekly\f[R], \f[C]fortnightly\f[R], \f[C]bimonthly\f[R], \f[C]every day|week|month|quarter|year\f[R], \f[C]every N days|weeks|months|quarters|years\f[R]. .PP All of these will start on the first day of the requested period and end on the last one, as described above. .PP Examples: .PP .TS tab(@); lw(25.5n) lw(44.5n). T{ \f[C]-p \[dq]bimonthly from 2008\[dq]\f[R] T}@T{ periods will have boundaries on 2008/01/01, 2008/03/01, ... T} T{ \f[C]-p \[dq]every 2 weeks\[dq]\f[R] T}@T{ starts on closest preceding Monday T} T{ \f[C]-p \[dq]every 5 month from 2009/03\[dq]\f[R] T}@T{ periods will have boundaries on 2009/03/01, 2009/08/01, ... T} .TE .PP If you want intervals that start on arbitrary day of your choosing and span a week, month or year, you need to use any of the following: .PP \f[C]every Nth day of week\f[R], \f[C]every \f[R], \f[C]every Nth day [of month]\f[R], \f[C]every Nth weekday [of month]\f[R], \f[C]every MM/DD [of year]\f[R], \f[C]every Nth MMM [of year]\f[R], \f[C]every MMM Nth [of year]\f[R]. .PP Examples: .PP .TS tab(@); lw(23.9n) lw(46.1n). T{ \f[C]-p \[dq]every 2nd day of week\[dq]\f[R] T}@T{ periods will go from Tue to Tue T} T{ \f[C]-p \[dq]every Tue\[dq]\f[R] T}@T{ same T} T{ \f[C]-p \[dq]every 15th day\[dq]\f[R] T}@T{ period boundaries will be on 15th of each month T} T{ \f[C]-p \[dq]every 2nd Monday\[dq]\f[R] T}@T{ period boundaries will be on second Monday of each month T} T{ \f[C]-p \[dq]every 11/05\[dq]\f[R] T}@T{ yearly periods with boundaries on 5th of Nov T} T{ \f[C]-p \[dq]every 5th Nov\[dq]\f[R] T}@T{ same T} T{ \f[C]-p \[dq]every Nov 5th\[dq]\f[R] T}@T{ same T} .TE .PP Show historical balances at end of 15th each month (N is exclusive end date): .PP \f[C]hledger balance -H -p \[dq]every 16th day\[dq]\f[R] .PP Group postings from start of wednesday to end of next tuesday (N is start date and exclusive end date): .PP \f[C]hledger register checking -p \[dq]every 3rd day of week\[dq]\f[R] .SS Depth limiting .PP With the \f[C]--depth N\f[R] option (short form: \f[C]-N\f[R]), commands like account, balance and register will show only the uppermost accounts in the account tree, down to level N. Use this when you want a summary with less detail. This flag has the same effect as a \f[C]depth:\f[R] query argument (so \f[C]-2\f[R], \f[C]--depth=2\f[R] or \f[C]depth:2\f[R] are equivalent). .SS Pivoting .PP Normally hledger sums amounts, and organizes them in a hierarchy, based on account name. The \f[C]--pivot FIELD\f[R] option causes it to sum and organize hierarchy based on the value of some other field instead. FIELD can be: \f[C]code\f[R], \f[C]description\f[R], \f[C]payee\f[R], \f[C]note\f[R], or the full name (case insensitive) of any tag. As with account names, values containing \f[C]colon:separated:parts\f[R] will be displayed hierarchically in reports. .PP \f[C]--pivot\f[R] is a general option affecting all reports; you can think of hledger transforming the journal before any other processing, replacing every posting\[aq]s account name with the value of the specified field on that posting, inheriting it from the transaction or using a blank value if it\[aq]s not present. .PP An example: .IP .nf \f[C] 2016/02/16 Member Fee Payment assets:bank account 2 EUR income:member fees -2 EUR ; member: John Doe \f[R] .fi .PP Normal balance report showing account names: .IP .nf \f[C] $ hledger balance 2 EUR assets:bank account -2 EUR income:member fees -------------------- 0 \f[R] .fi .PP Pivoted balance report, using member: tag values instead: .IP .nf \f[C] $ hledger balance --pivot member 2 EUR -2 EUR John Doe -------------------- 0 \f[R] .fi .PP One way to show only amounts with a member: value (using a query, described below): .IP .nf \f[C] $ hledger balance --pivot member tag:member=. -2 EUR John Doe -------------------- -2 EUR \f[R] .fi .PP Another way (the acct: query matches against the pivoted \[dq]account name\[dq]): .IP .nf \f[C] $ hledger balance --pivot member acct:. -2 EUR John Doe -------------------- -2 EUR \f[R] .fi .SS Valuation .PP Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), or to market value (using some market price on a certain date). This is controlled by the \f[C]--value=TYPE[,COMMODITY]\f[R] option, but we also provide the simpler \f[C]-B\f[R]/\f[C]-V\f[R]/\f[C]-X\f[R] flags, and usually one of those is all you need. .SS -B: Cost .PP The \f[C]-B/--cost\f[R] flag converts amounts to their cost or sale amount at transaction time, if they have a transaction price specified. .SS -V: Value .PP The \f[C]-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 .PP The \f[C]-X/--exchange=COMM\f[R] option is like \f[C]-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 .PP Since market prices can change from day to day, market value reports have a valuation date (or more than one), which determines which market prices will be used. .PP For single period reports, if an explicit report end date is specified, that will be used as the valuation date; otherwise the valuation date is \[dq]today\[dq]. .PP For multiperiod reports, each column/period is valued on the last day of the period. .SS Market prices .PP \f[I](experimental)\f[R] .PP 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 (if the \f[C]--infer-value\f[R] flag is used) inferred from transaction prices. .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]chained market price\f[R]: a synthetic price formed by combining the shortest chain of market prices (any of the above types) leading from A to B. .PP Amounts for which no applicable market price can be found, are not converted. .SS --infer-value: market prices from transactions .PP \f[I](experimental)\f[R] .PP 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 transaction prices as additional market prices (as Ledger does) ? We could produce value reports without needing P directives at all. .PP Adding the \f[C]--infer-value\f[R] flag to \f[C]-V\f[R], \f[C]-X\f[R] or \f[C]--value\f[R] enables this. So for example, \f[C]hledger bs -V --infer-value\f[R] will get market prices both from P directives and from transactions. .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 Valuation section carefully, and try adding \f[C]--debug\f[R] or \f[C]--debug=2\f[R] to troubleshoot. .PP \f[C]--infer-value\f[R] can infer market prices from: .IP \[bu] 2 multicommodity transactions with explicit prices (\f[C]\[at]\f[R]/\f[C]\[at]\[at]\f[R]) .IP \[bu] 2 multicommodity transactions with implicit prices (no \f[C]\[at]\f[R], two commodities, unbalanced). (With these, the order of postings matters. \f[C]hledger print -x\f[R] can be useful for troubleshooting.) .IP \[bu] 2 but not, currently, from \[dq]more correct\[dq] multicommodity transactions (no \f[C]\[at]\f[R], multiple commodities, balanced). .SS Valuation commodity .PP \f[I](experimental)\f[R] .PP \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[C]--infer-value\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[C]-V\f[R] will convert, and to what. .IP \[bu] 2 If you have no P directives, and use the \f[C]--infer-value\f[R] flag, transaction prices determine it. .PP Amounts for which no valuation commodity can be found are not converted. .SS Simple valuation examples .PP Here are some quick examples of \f[C]-V\f[R]: .IP .nf \f[C] ; one euro is worth this many dollars from nov 1 P 2016/11/01 \[Eu] $1.10 ; purchase some euros on nov 3 2016/11/3 assets:euros \[Eu]100 assets:checking ; the euro is worth fewer dollars by dec 21 P 2016/12/21 \[Eu] $1.03 \f[R] .fi .PP How many euros do I have ? .IP .nf \f[C] $ hledger -f t.j bal -N euros \[Eu]100 assets:euros \f[R] .fi .PP What are they worth at end of nov 3 ? .IP .nf \f[C] $ hledger -f t.j bal -N euros -V -e 2016/11/4 $110.00 assets:euros \f[R] .fi .PP What are they worth after 2016/12/21 ? (no report end date specified, defaults to today) .IP .nf \f[C] $ hledger -f t.j bal -N euros -V $103.00 assets:euros \f[R] .fi .SS --value: Flexible valuation .PP \f[C]-B\f[R], \f[C]-V\f[R] and \f[C]-X\f[R] are special cases of the more general \f[C]--value\f[R] option: .IP .nf \f[C] --value=TYPE[,COMM] TYPE is cost, then, end, now or YYYY-MM-DD. COMM is an optional commodity symbol. Shows amounts converted to: - cost commodity using transaction prices (then optionally to COMM using market prices at period end(s)) - 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 \f[R] .fi .PP The TYPE part selects cost or value and valuation date: .TP \f[B]\f[CB]--value=cost\f[B]\f[R] Convert amounts to cost, using the prices recorded in transactions. .TP \f[B]\f[CB]--value=then\f[B]\f[R] Convert amounts to their value in the default valuation commodity, using market prices on each posting\[aq]s date. This is currently supported only by the print and register commands. .TP \f[B]\f[CB]--value=end\f[B]\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[B]\f[CB]--value=now\f[B]\f[R] Convert amounts to their value in the default valuation commodity using current market prices (as of when report is generated). .TP \f[B]\f[CB]--value=YYYY-MM-DD\f[B]\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[C],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 .PP Here are some examples showing the effect of \f[C]--value\f[R], as seen with \f[C]print\f[R]: .IP .nf \f[C] 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 \f[R] .fi .PP Show the cost of each posting: .IP .nf \f[C] $ hledger -f- print --value=cost 2000-01-01 (a) 5 B 2000-02-01 (a) 6 B 2000-03-01 (a) 7 B \f[R] .fi .PP Show the value as of the last day of the report period (2000-02-29): .IP .nf \f[C] $ hledger -f- print --value=end date:2000/01-2000/03 2000-01-01 (a) 2 B 2000-02-01 (a) 2 B \f[R] .fi .PP With no report period specified, that shows the value as of the last day of the journal (2000-03-01): .IP .nf \f[C] $ hledger -f- print --value=end 2000-01-01 (a) 3 B 2000-02-01 (a) 3 B 2000-03-01 (a) 3 B \f[R] .fi .PP Show the current value (the 2000-04-01 price is still in effect today): .IP .nf \f[C] $ hledger -f- print --value=now 2000-01-01 (a) 4 B 2000-02-01 (a) 4 B 2000-03-01 (a) 4 B \f[R] .fi .PP Show the value on 2000/01/15: .IP .nf \f[C] $ 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 \f[R] .fi .PP You may need to explicitly set a commodity\[aq]s display style, when reverse prices are used. Eg this output might be surprising: .IP .nf \f[C] P 2000-01-01 A 2B 2000-01-01 a 1B b \f[R] .fi .IP .nf \f[C] $ hledger print -x -X A 2000-01-01 a 0 b 0 \f[R] .fi .PP Explanation: because there\[aq]s no amount or commodity directive specifying a display style for A, 0.5A gets the default style, which shows no decimal digits. Because the displayed amount looks like zero, the commodity symbol and minus sign are not displayed either. Adding a commodity directive sets a more useful display style for A: .IP .nf \f[C] P 2000-01-01 A 2B commodity 0.00A 2000-01-01 a 1B b \f[R] .fi .IP .nf \f[C] $ hledger print -X A 2000-01-01 a 0.50A b -0.50A \f[R] .fi .SS Effect of valuation on reports .PP 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(11.7n) lw(11.2n) lw(11.9n) lw(13.1n) lw(12.4n) lw(9.8n). T{ Report type T}@T{ \f[C]-B\f[R], \f[C]--value=cost\f[R] T}@T{ \f[C]-V\f[R], \f[C]-X\f[R] T}@T{ \f[C]--value=then\f[R] T}@T{ \f[C]--value=end\f[R] T}@T{ \f[C]--value=DATE\f[R], \f[C]--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 (with -H) T}@T{ cost T}@T{ value at day before report or journal start T}@T{ not supported T}@T{ value at day before report or journal start T}@T{ value at DATE/today T} T{ posting amounts (no report interval) 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{ 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{ balances (no report interval) T}@T{ sums of costs T}@T{ value at report end or today of sums of postings T}@T{ not supported T}@T{ value at report or journal end of sums of postings T}@T{ value at DATE/today of sums of postings T} T{ balances (with report interval) T}@T{ sums of costs T}@T{ value at period ends of sums of postings T}@T{ not supported T}@T{ value at period ends of sums of postings T}@T{ value at DATE/today of sums of postings T} T{ starting balances (with report interval and -H) T}@T{ sums of costs of postings before report start T}@T{ sums of postings before report start T}@T{ not supported T}@T{ sums of postings before report start T}@T{ sums of postings before report start T} T{ budget amounts with --budget T}@T{ like balances T}@T{ like balances T}@T{ not supported T}@T{ like balances T}@T{ like balances T} T{ grand total (no report interval) T}@T{ sum of displayed values T}@T{ sum of displayed values T}@T{ not supported T}@T{ sum of displayed values T}@T{ sum of displayed values T} T{ row totals/averages (with report interval) T}@T{ sums/averages of displayed values T}@T{ sums/averages of displayed values T}@T{ not supported 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{ not supported T}@T{ sums of displayed values T}@T{ sums of displayed values T} T{ grand total/average T}@T{ sum/average of column totals T}@T{ sum/average of column totals T}@T{ not supported 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[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 COMMANDS .PP hledger provides a number of subcommands; \f[C]hledger\f[R] with no arguments shows a list. .PP If you install additional \f[C]hledger-*\f[R] packages, or if you put programs or scripts named \f[C]hledger-NAME\f[R] in your PATH, these will also be listed as subcommands. .PP Run a subcommand by writing its name as first argument (eg \f[C]hledger incomestatement\f[R]). You can also write one of the standard short aliases displayed in parentheses in the command list (\f[C]hledger b\f[R]), or any any unambiguous prefix of a command name (\f[C]hledger inc\f[R]). .PP Here are all the builtin commands in alphabetical order. See also \f[C]hledger\f[R] for a more organised command list, and \f[C]hledger CMD -h\f[R] for detailed command help. .SS accounts .PP accounts, a .PD 0 .P .PD Show account names. .PP This command lists account names, either declared with account directives (--declared), posted to (--used), or both (the default). With query arguments, only matched account names and account names referenced by matched postings are shown. It shows a flat list by default. With \f[C]--tree\f[R], it uses indentation to show the account hierarchy. In flat mode you can add \f[C]--drop N\f[R] to omit the first few account name components. Account names can be depth-clipped with \f[C]depth:N\f[R] or \f[C]--depth N\f[R] or \f[C]-N\f[R]. .PP Examples: .IP .nf \f[C] $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts \f[R] .fi .SS activity .PP activity .PD 0 .P .PD 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 .nf \f[C] $ hledger activity --quarterly 2008-01-01 ** 2008-04-01 ******* 2008-07-01 2008-10-01 ** \f[R] .fi .SS add .PP add .PD 0 .P .PD 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[C]add\f[R] command, which prompts interactively on the console for new transactions, and appends them to the journal file (if there are multiple \f[C]-f FILE\f[R] options, the first file is used.) Existing transactions are not changed. This is the only hledger command that writes to the journal file. .PP To use it, just run \f[C]hledger add\f[R] and follow the prompts. You can add as many transactions as you like; when you are finished, enter \f[C].\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, descriptions, dates (\f[C]yesterday\f[R], \f[C]today\f[R], \f[C]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[C]<\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 the tutorial for a detailed explanation): .IP .nf \f[C] $ 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]: $ \f[R] .fi .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 .PP aregister, areg .PD 0 .P .PD Show transactions affecting a particular account, and the account\[aq]s running balance. .PP \f[C]aregister\f[R] shows the transactions affecting a particular account (and its subaccounts), from the point of view of that account. Each line shows: .IP \[bu] 2 the transaction\[aq]s (or posting\[aq]s, see below) date .IP \[bu] 2 the names of the other account(s) involved .IP \[bu] 2 the net change to this account\[aq]s balance .IP \[bu] 2 the account\[aq]s historical running balance (including balance from transactions before the report start date). .PP With \f[C]aregister\f[R], each line represents a whole transaction - as in hledger-ui, hledger-web, and your bank statement. By contrast, the \f[C]register\f[R] command shows individual postings, across all accounts. You might prefer \f[C]aregister\f[R] for reconciling with real-world asset/liability accounts, and \f[C]register\f[R] for reviewing detailed revenues/expenses. .PP An account must be specified as the first argument, which should be the full account name or an account pattern (regular expression). aregister will show transactions in this account (the first one matched) and any of its subaccounts. .PP Any additional arguments form a query which will filter the transactions shown. .PP Transactions making a net change of zero are not shown by default; add the \f[C]-E/--empty\f[R] flag to show them. .SS aregister and custom posting dates .PP Transactions whose date is outside the report period can still be shown, if they have a posting to this account dated inside the report period. (And in this case it\[aq]s the posting date that is shown.) This ensures that \f[C]aregister\f[R] can show an accurate historical running balance, matching the one shown by \f[C]register -H\f[R] with the same arguments. .PP To filter strictly by transaction date instead, add the \f[C]--txn-dates\f[R] flag. If you use this flag and some of your postings have custom dates, it\[aq]s probably best to assume the running balance is wrong. .SS Output format .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], and \f[C]json\f[R]. .PP Examples: .PP Show all transactions and historical running balance in the first account whose name contains \[dq]checking\[dq]: .IP .nf \f[C] $ hledger areg checking \f[R] .fi .PP Show transactions and historical running balance in all asset accounts during july: .IP .nf \f[C] $ hledger areg assets date:jul \f[R] .fi .SS balance .PP balance, bal, b .PD 0 .P .PD Show accounts and their balances. .PP The balance command is hledger\[aq]s most versatile command. Note, despite the name, it is not always used for showing real-world account balances; the more accounting-aware balancesheet and incomestatement may be more convenient for that. .PP By default, it displays all accounts, and each account\[aq]s change in balance during the entire period of the journal. Balance changes are calculated by adding up the postings in each account. You can limit the postings matched, by a query, to see fewer accounts, changes over a different time period, changes from only cleared transactions, etc. .PP If you include an account\[aq]s complete history of postings in the report, the balance change is equivalent to the account\[aq]s current ending balance. For a real-world account, typically you won\[aq]t have all transactions in the journal; instead you\[aq]ll have all transactions after a certain date, and an \[dq]opening balances\[dq] transaction setting the correct starting balance on that date. Then the balance command will show real-world account balances. In some cases the -H/--historical flag is used to ensure this (more below). .PP The balance command can produce several styles of report: .SS Classic balance report .PP This is the original balance report, as found in Ledger. It usually looks like this: .IP .nf \f[C] $ hledger balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 \f[R] .fi .PP By default, accounts are displayed hierarchically, with subaccounts indented below their parent. At each level of the tree, accounts are sorted by account code if any, then by account name. Or with \f[C]-S/--sort-amount\f[R], by their balance amount, largest first. .PP \[dq]Boring\[dq] accounts, which contain a single interesting subaccount and no balance of their own, are elided into the following line for more compact output. (Eg above, the \[dq]liabilities\[dq] account.) Use \f[C]--no-elide\f[R] to prevent this. .PP Account balances are \[dq]inclusive\[dq] - they include the balances of any subaccounts. .PP Accounts which have zero balance (and no non-zero subaccounts) are omitted. Use \f[C]-E/--empty\f[R] to show them. .PP A final total is displayed by default; use \f[C]-N/--no-total\f[R] to suppress it, eg: .IP .nf \f[C] $ hledger balance -p 2008/6 expenses --no-total $2 expenses $1 food $1 supplies \f[R] .fi .SS Customising the classic balance report .PP You can customise the layout of classic balance reports with \f[C]--format FMT\f[R]: .IP .nf \f[C] $ hledger 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 \f[R] .fi .PP The FMT format string (plus a newline) specifies the formatting applied to each account/balance pair. It may contain any suitable text, with data fields interpolated like so: .PP \f[C]%[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[C]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[C]account\f[R] - the account\[aq]s name .IP \[bu] 2 \f[C]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[C]%_\f[R] - render on multiple lines, bottom-aligned (the default) .IP \[bu] 2 \f[C]%\[ha]\f[R] - render on multiple lines, top-aligned .IP \[bu] 2 \f[C]%,\f[R] - render on one line, comma-separated .PP There are some quirks. Eg in one-line mode, \f[C]%(depth_spacer)\f[R] has no effect, instead \f[C]%(account)\f[R] has indentation built in. Experimentation may be needed to get pleasing results. .PP Some example formats: .IP \[bu] 2 \f[C]%(total)\f[R] - the account\[aq]s total .IP \[bu] 2 \f[C]%-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[C]%,%-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[C]%20(total) %2(depth_spacer)%-(account)\f[R] - the default format for the single-column balance report .SS Colour support .PP In terminal output, when colour is enabled, the balance command shows negative amounts in red. .SS Flat mode .PP To see a flat list instead of the default hierarchical display, use \f[C]--flat\f[R]. In this mode, accounts (unless depth-clipped) show their full names and \[dq]exclusive\[dq] balance, excluding any subaccount balances. In this mode, you can also use \f[C]--drop N\f[R] to omit the first few account name components. .IP .nf \f[C] $ hledger balance -p 2008/6 expenses -N --flat --drop 1 $1 food $1 supplies \f[R] .fi .SS Depth limited balance reports .PP With \f[C]--depth N\f[R] or \f[C]depth:N\f[R] or just \f[C]-N\f[R], balance reports show accounts only to the specified numeric depth. This is very useful to summarise a complex set of accounts and get an overview. .IP .nf \f[C] $ hledger balance -N -1 $-1 assets $2 expenses $-2 income $1 liabilities \f[R] .fi .PP Flat-mode balance reports, which normally show exclusive balances, show inclusive balances at the depth limit. .SS Percentages .PP With \f[C]-%\f[R] or \f[C]--percent\f[R], balance reports show each account\[aq]s value expressed as a percentage of the column\[aq]s total. This is useful to get an overview of the relative sizes of account balances. For example to obtain an overview of expenses: .IP .nf \f[C] $ hledger balance expenses -% 100.0 % expenses 50.0 % food 50.0 % supplies -------------------- 100.0 % \f[R] .fi .PP Note that \f[C]--tree\f[R] does not have an effect on \f[C]-%\f[R]. The percentages are always relative to the total sum of each column, they are never relative to the parent account. .PP Since the percentages are relative to the columns sum, it is usually not useful to calculate percentages if the signs of the amounts are mixed. Although the results are technically correct, they are most likely useless. Especially in a balance report that sums up to zero (eg \f[C]hledger balance -B\f[R]) all percentage values will be zero. .PP This flag does not work if the report contains any mixed commodity accounts. If there are mixed commodity accounts in the report be sure to use \f[C]-V\f[R] or \f[C]-B\f[R] to coerce the report into using a single commodity. .SS Multicolumn balance report .PP Multicolumn or tabular balance reports are a very useful hledger feature, and usually the preferred style. They share many of the above features, but they show the report as a table, with columns representing time periods. This mode is activated by providing a reporting interval. .PP There are three types of multicolumn balance report, showing different information: .IP "1." 3 By default: each column shows the sum of postings in that period, ie the account\[aq]s change of balance in that period. This is useful eg for a monthly income statement: .RS 4 .IP .nf \f[C] $ hledger balance --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 \f[R] .fi .RE .IP "2." 3 With \f[C]--cumulative\f[R]: each column shows the ending balance for that period, accumulating the changes across periods, starting from 0 at the report start date: .RS 4 .IP .nf \f[C] $ hledger balance --quarterly income expenses -E --cumulative Ending balances (cumulative) in 2008: || 2008/03/31 2008/06/30 2008/09/30 2008/12/31 ===================++================================================= expenses:food || 0 $1 $1 $1 expenses:supplies || 0 $1 $1 $1 income:gifts || 0 $-1 $-1 $-1 income:salary || $-1 $-1 $-1 $-1 -------------------++------------------------------------------------- || $-1 0 0 0 \f[R] .fi .RE .IP "3." 3 With \f[C]--historical/-H\f[R]: each column shows the actual historical ending balance for that period, accumulating the changes across periods, starting from the actual balance at the report start date. This is useful eg for a multi-period balance sheet, and when you are showing only the data after a certain start date: .RS 4 .IP .nf \f[C] $ hledger balance \[ha]assets \[ha]liabilities --quarterly --historical --begin 2008/4/1 Ending balances (historical) in 2008/04/01-2008/12/31: || 2008/06/30 2008/09/30 2008/12/31 ======================++===================================== assets:bank:checking || $1 $1 0 assets:bank:saving || $1 $1 $1 assets:cash || $-2 $-2 $-2 liabilities:debts || 0 0 $1 ----------------------++------------------------------------- || 0 0 0 \f[R] .fi .RE .PP Note that \f[C]--cumulative\f[R] or \f[C]--historical/-H\f[R] disable \f[C]--row-total/-T\f[R], since summing end balances generally does not make sense. .PP Multicolumn balance reports display accounts in flat mode by default; to see the hierarchy, use \f[C]--tree\f[R]. .PP With a reporting interval (like \f[C]--quarterly\f[R] above), the report start/end dates will be adjusted if necessary so that they encompass the displayed report periods. This is so that the first and last periods will be \[dq]full\[dq] and comparable to the others. .PP The \f[C]-E/--empty\f[R] flag does two things in multicolumn balance reports: first, the report will show all columns within the specified report period (without -E, leading and trailing columns with all zeroes are not shown). Second, all accounts which existed at the report start date will be considered, not just the ones with activity during the report period (use -E to include low-activity accounts which would otherwise would be omitted). .PP The \f[C]-T/--row-total\f[R] flag adds an additional column showing the total for each row. .PP The \f[C]-A/--average\f[R] flag adds a column showing the average value in each row. .PP Here\[aq]s an example of all three: .IP .nf \f[C] $ hledger balance -Q income expenses --tree -ETA Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 Total Average ============++=================================================== expenses || 0 $2 0 0 $2 $1 food || 0 $1 0 0 $1 0 supplies || 0 $1 0 0 $1 0 income || $-1 $-1 0 0 $-2 $-1 gifts || 0 $-1 0 0 $-1 0 salary || $-1 0 0 0 $-1 0 ------------++--------------------------------------------------- || $-1 $1 0 0 0 0 (Average is rounded to the dollar here since all journal amounts are) \f[R] .fi .PP The \f[C]--transpose\f[R] flag can be used to exchange the rows and columns of a multicolumn report. .PP When showing multicommodity amounts, multicolumn balance reports will elide any amounts which have more than two commodities, since otherwise columns could get very wide. The \f[C]--no-elide\f[R] flag disables this. Hiding totals with the \f[C]-N/--no-total\f[R] flag can also help reduce the width of multicommodity reports. .PP When the report is still too wide, a good workaround is to pipe it into \f[C]less -RS\f[R] (-R for colour, -S to chop long lines). Eg: \f[C]hledger bal -D --color=yes | less -RS\f[R]. .SS Budget report .PP With \f[C]--budget\f[R], extra columns are displayed showing budget goals for each account and period, if any. Budget goals are defined by periodic transactions. This is very useful for comparing planned and actual income, expenses, time usage, etc. --budget is most often combined with a report interval. .PP For example, you can take average monthly expenses in the common expense categories to construct a minimal monthly budget: .IP .nf \f[C] ;; Budget \[ti] monthly income $2000 expenses:food $400 expenses:bus $50 expenses:movies $30 assets:bank:checking ;; Two months worth of expenses 2017-11-01 income $1950 expenses:food $396 expenses:bus $49 expenses:movies $30 expenses:supplies $20 assets:bank:checking 2017-12-01 income $2100 expenses:food $412 expenses:bus $53 expenses:gifts $100 assets:bank:checking \f[R] .fi .PP You can now see a monthly budget report: .IP .nf \f[C] $ hledger balance -M --budget Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] \f[R] .fi .PP This is different from a normal balance report in several ways: .IP \[bu] 2 Only accounts with budget goals during the report period are shown, by default. .IP \[bu] 2 In each column, in square brackets after the actual amount, budget goal amounts are shown, and the actual/goal percentage. (Note: budget goals should be in the same commodity as the actual amount.) .IP \[bu] 2 All parent accounts are always shown, even in flat mode. Eg assets, assets:bank, and expenses above. .IP \[bu] 2 Amounts always include all subaccounts, budgeted or unbudgeted, even in flat mode. .PP This means that the numbers displayed will not always add up! Eg above, the \f[C]expenses\f[R] actual amount includes the gifts and supplies transactions, but the \f[C]expenses:gifts\f[R] and \f[C]expenses:supplies\f[R] accounts are not shown, as they have no budget amounts declared. .PP This can be confusing. When you need to make things clearer, use the \f[C]-E/--empty\f[R] flag, which will reveal all accounts including unbudgeted ones, giving the full picture. Eg: .IP .nf \f[C] $ hledger balance -M --budget --empty Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:gifts || 0 $100 expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] expenses:supplies || $20 0 income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] \f[R] .fi .PP You can roll over unspent budgets to next period with \f[C]--cumulative\f[R]: .IP .nf \f[C] $ hledger balance -M --budget --cumulative Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank:checking || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] expenses || $495 [ 103% of $480] $1060 [ 110% of $960] expenses:bus || $49 [ 98% of $50] $102 [ 102% of $100] expenses:food || $396 [ 99% of $400] $808 [ 101% of $800] expenses:movies || $30 [ 100% of $30] $30 [ 50% of $60] income || $1950 [ 98% of $2000] $4050 [ 101% of $4000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] \f[R] .fi .PP For more examples, see Budgeting and Forecasting. .SS Nested budgets .PP You can add budgets to any account in your account hierarchy. If you have budgets on both parent account and some of its children, then budget(s) of the child account(s) would be added to the budget of their parent, much like account balances behave. .PP In the most simple case this means that once you add a budget to any account, all its parents would have budget as well. .PP To illustrate this, consider the following budget: .IP .nf \f[C] \[ti] monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities \f[R] .fi .PP With this, monthly budget for electronics is defined to be $100 and budget for personal expenses is an additional $1000, which implicitly means that budget for both \f[C]expenses:personal\f[R] and \f[C]expenses\f[R] is $1100. .PP Transactions in \f[C]expenses:personal:electronics\f[R] will be counted both towards its $100 budget and $1100 of \f[C]expenses:personal\f[R] , and transactions in any other subaccount of \f[C]expenses:personal\f[R] would be counted towards only towards the budget of \f[C]expenses:personal\f[R]. .PP For example, let\[aq]s consider these transactions: .IP .nf \f[C] \[ti] monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities 2019/01/01 Google home hub expenses:personal:electronics $90.00 liabilities $-90.00 2019/01/02 Phone screen protector expenses:personal:electronics:upgrades $10.00 liabilities 2019/01/02 Weekly train ticket expenses:personal:train tickets $153.00 liabilities 2019/01/03 Flowers expenses:personal $30.00 liabilities \f[R] .fi .PP As you can see, we have transactions in \f[C]expenses:personal:electronics:upgrades\f[R] and \f[C]expenses:personal:train tickets\f[R], and since both of these accounts are without explicitly defined budget, these transactions would be counted towards budgets of \f[C]expenses:personal:electronics\f[R] and \f[C]expenses:personal\f[R] accordingly: .IP .nf \f[C] $ hledger balance --budget -M Budget performance in 2019/01: || Jan ===============================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] liabilities || $-283.00 [ 26% of $-1100.00] -------------------------------++------------------------------- || 0 [ 0] \f[R] .fi .PP And with \f[C]--empty\f[R], we can get a better picture of budget allocation and consumption: .IP .nf \f[C] $ hledger balance --budget -M --empty Budget performance in 2019/01: || Jan ========================================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] expenses:personal:electronics:upgrades || $10.00 expenses:personal:train tickets || $153.00 liabilities || $-283.00 [ 26% of $-1100.00] ----------------------------------------++------------------------------- || 0 [ 0] \f[R] .fi .SS Output format .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], (multicolumn non-budget reports only) \f[C]html\f[R], and (experimental) \f[C]json\f[R]. .SS balancesheet .PP balancesheet, bs .PD 0 .P .PD 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 The asset and liability accounts shown are those accounts declared with the \f[C]Asset\f[R] or \f[C]Cash\f[R] or \f[C]Liability\f[R] type, or otherwise all accounts under a top-level \f[C]asset\f[R] or \f[C]liability\f[R] account (case insensitive, plurals allowed). .PP Example: .IP .nf \f[C] $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 \f[R] .fi .PP With a reporting interval, multiple columns will be shown, one for each report period. As with multicolumn balance reports, you can alter the report mode with \f[C]--change\f[R]/\f[C]--cumulative\f[R]/\f[C]--historical\f[R]. Normally balancesheet shows historical ending balances, which is what you need for a balance sheet; note this means it ignores report begin dates (and \f[C]-T/--row-total\f[R], since summing end balances generally does not make sense). Instead of absolute values percentages can be displayed with \f[C]-%\f[R]. .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], \f[C]html\f[R], and (experimental) \f[C]json\f[R]. .SS balancesheetequity .PP balancesheetequity, bse .PD 0 .P .PD 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 The asset, liability and equity accounts shown are those accounts declared with the \f[C]Asset\f[R], \f[C]Cash\f[R], \f[C]Liability\f[R] or \f[C]Equity\f[R] type, or otherwise all accounts under a top-level \f[C]asset\f[R], \f[C]liability\f[R] or \f[C]equity\f[R] account (case insensitive, plurals allowed). .PP Example: .IP .nf \f[C] $ 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 \f[R] .fi .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], \f[C]html\f[R], and (experimental) \f[C]json\f[R]. .SS cashflow .PP cashflow, cf .PD 0 .P .PD This command displays a cashflow statement, showing the inflows and outflows affecting \[dq]cash\[dq] (ie, liquid) assets. Amounts are shown with normal positive sign, as in conventional financial statements. .PP The \[dq]cash\[dq] accounts shown are those accounts declared with the \f[C]Cash\f[R] type, or otherwise all accounts under a top-level \f[C]asset\f[R] account (case insensitive, plural allowed) which do not have \f[C]fixed\f[R], \f[C]investment\f[R], \f[C]receivable\f[R] or \f[C]A/R\f[R] in their name. .PP Example: .IP .nf \f[C] $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 \f[R] .fi .PP With a reporting interval, multiple columns will be shown, one for each report period. Normally cashflow shows changes in assets per period, though as with multicolumn balance reports you can alter the report mode with \f[C]--change\f[R]/\f[C]--cumulative\f[R]/\f[C]--historical\f[R]. Instead of absolute values percentages can be displayed with \f[C]-%\f[R]. .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], \f[C]html\f[R], and (experimental) \f[C]json\f[R]. .SS check-dates .PP check-dates .PD 0 .P .PD Check that transactions are sorted by increasing date. With --date2, checks secondary dates instead. With --strict, dates must also be unique. With a query, only matched transactions\[aq] dates are checked. Reads the default journal file, or another specified with -f. .SS check-dupes .PP check-dupes .PD 0 .P .PD Reports account names having the same leaf but different prefixes. In other words, two or more leaves that are categorized differently. Reads the default journal file, or another specified as an argument. .PP An example: http://stefanorodighiero.net/software/hledger-dupes.html .SS close .PP close, equity .PD 0 .P .PD Prints a \[dq]closing balances\[dq] transaction and an \[dq]opening balances\[dq] transaction that bring account balances to and from zero, respectively. These can be added to your journal file(s), eg to bring asset/liability balances forward into a new journal file, or to close out revenues/expenses to retained earnings at the end of a period. .PP You can print just one of these transactions by using the \f[C]--close\f[R] or \f[C]--open\f[R] flag. You can customise their descriptions with the \f[C]--close-desc\f[R] and \f[C]--open-desc\f[R] options. .PP One amountless posting to \[dq]equity:opening/closing balances\[dq] is added to balance the transactions, by default. You can customise this account name with \f[C]--close-acct\f[R] and \f[C]--open-acct\f[R]; if you specify only one of these, it will be used for both. .PP With \f[C]--x/--explicit\f[R], the equity posting\[aq]s amount will be shown. And if it involves multiple commodities, a posting for each commodity will be shown, as with the print command. .PP With \f[C]--interleaved\f[R], the equity postings are shown next to the postings they balance, which makes troubleshooting easier. .PP By default, transaction prices in the journal are ignored when generating the closing/opening transactions. With \f[C]--show-costs\f[R], this cost information is preserved (\f[C]balance -B\f[R] reports will be unchanged after the transition). Separate postings are generated for each cost in each commodity. Note this can generate very large journal entries, if you have many foreign currency or investment transactions. .SS close usage .PP If you split your journal files by time (eg yearly), you will typically run this command at the end of the year, and save the closing transaction as last entry of the old file, and the opening transaction as the first entry of the new file. This makes the files self contained, so that correct balances are reported no matter which of them are loaded. Ie, if you load just one file, the balances are initialised correctly; or if you load several files, the redundant closing/opening transactions cancel each other out. (They will show up in print or register reports; you can exclude them with a query like \f[C]not:desc:\[aq](opening|closing) balances\[aq]\f[R].) .PP If you\[aq]re running a business, you might also use this command to \[dq]close the books\[dq] at the end of an accounting period, transferring income statement account balances to retained earnings. (You may want to change the equity account name to something like \[dq]equity:retained earnings\[dq].) .PP By default, the closing transaction is dated yesterday, the balances are calculated as of end of yesterday, and the opening transaction is dated today. To close on some other date, use: \f[C]hledger close -e OPENINGDATE\f[R]. Eg, to close/open on the 2018/2019 boundary, use \f[C]-e 2019\f[R]. You can also use -p or \f[C]date:PERIOD\f[R] (any starting date is ignored). .PP Both transactions will include balance assertions for the closed/reopened accounts. You probably shouldn\[aq]t use status or realness filters (like -C or -R or \f[C]status:\f[R]) with this command, or the generated balance assertions will depend on these flags. Likewise, if you run this command with --auto, the balance assertions will probably always require --auto. .PP Examples: .PP Carrying asset/liability balances into a new file for 2019: .IP .nf \f[C] $ hledger close -f 2018.journal -e 2019 assets liabilities --open # (copy/paste the output to the start of your 2019 journal file) $ hledger close -f 2018.journal -e 2019 assets liabilities --close # (copy/paste the output to the end of your 2018 journal file) \f[R] .fi .PP Now: .IP .nf \f[C] $ hledger bs -f 2019.journal # one file - balances are correct $ hledger bs -f 2018.journal -f 2019.journal # two files - balances still correct $ hledger bs -f 2018.journal not:desc:closing # to see year-end balances, must exclude closing txn \f[R] .fi .PP Transactions spanning the closing date can complicate matters, breaking balance assertions: .IP .nf \f[C] 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 assets:bank:checking -5 ; [2019/1/2] \f[R] .fi .PP Here\[aq]s one way to resolve that: .IP .nf \f[C] ; in 2018.journal: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 liabilities:pending ; in 2019.journal: 2019/1/2 clearance of last year\[aq]s pending transactions liabilities:pending 5 = 0 assets:checking \f[R] .fi .SS codes .PP codes .PD 0 .P .PD 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[C]-E\f[R]/\f[C]--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 .nf \f[C] 1/1 (123) (a) 1 1/1 () (a) 1 1/1 (a) 1 1/1 (126) (a) 1 \f[R] .fi .IP .nf \f[C] $ hledger codes 123 124 126 \f[R] .fi .IP .nf \f[C] $ hledger codes -E 123 124 126 \f[R] .fi .SS commodities .PP commodities .PD 0 .P .PD List all commodity/currency symbols used or declared in the journal. .SS descriptions .PP descriptions .PD 0 .P .PD 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 .nf \f[C] $ hledger descriptions Store Name Gas Station | Petrol Person A \f[R] .fi .SS diff .PP diff .PD 0 .P .PD 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 .nf \f[C] $ 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: \f[R] .fi .SS files .PP files .PD 0 .P .PD List all files included in the journal. With a REGEX argument, only file names matching the regular expression (case sensitive) are shown. .SS help .PP help .PD 0 .P .PD Show any of the hledger manuals. .PP The \f[C]help\f[R] command displays any of the main hledger manuals, in one of several ways. Run it with no argument to list the manuals, or provide a full or partial manual name to select one. .PP hledger manuals are available in several formats. hledger help will use the first of these display methods that it finds: info, man, $PAGER, less, stdout (or when non-interactive, just stdout). You can force a particular viewer with the \f[C]--info\f[R], \f[C]--man\f[R], \f[C]--pager\f[R], \f[C]--cat\f[R] flags. .PP Examples: .IP .nf \f[C] $ hledger help Please choose a manual by typing \[dq]hledger help MANUAL\[dq] (a substring is ok). Manuals: hledger hledger-ui hledger-web journal csv timeclock timedot \f[R] .fi .IP .nf \f[C] $ hledger help h --man hledger(1) hledger User Manuals hledger(1) NAME hledger - a command-line accounting tool SYNOPSIS hledger [-f FILE] COMMAND [OPTIONS] [ARGS] hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS] hledger DESCRIPTION hledger is a cross-platform program for tracking money, time, or any \&... \f[R] .fi .SS import .PP import .PD 0 .P .PD Read new transactions added to each FILE since last run, and add them to the main journal file. Or with --dry-run, just print the transactions that would be added. Or with --catchup, just mark all of the FILEs\[aq] transactions as imported, without actually importing any. .PP The input files are specified as arguments - no need to write -f before each one. So eg to add new transactions from all CSV files to the main journal, it\[aq]s just: \f[C]hledger import *.csv\f[R] .PP New transactions are detected in the same way as print --new: by assuming transactions are always added to the input files in increasing date order, and by saving \f[C].latest.FILE\f[R] state files. .PP The --dry-run output is in journal format, so you can filter it, eg to see only uncategorised transactions: .IP .nf \f[C] $ hledger import --dry ... | hledger -f- print unknown --ignore-assertions \f[R] .fi .SS Importing balance assignments .PP Entries added by import will have their posting amounts made explicit (like \f[C]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 .nf \f[C] $ hledger print IMPORTFILE [--new] >> $LEDGER_FILE \f[R] .fi .PP (If you think import should leave amounts implicit like print does, please test it and send a pull request.) .SS incomestatement .PP incomestatement, is .PD 0 .P .PD .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 The revenue and expense accounts shown are those accounts declared with the \f[C]Revenue\f[R] or \f[C]Expense\f[R] type, or otherwise all accounts under a top-level \f[C]revenue\f[R] or \f[C]income\f[R] or \f[C]expense\f[R] account (case insensitive, plurals allowed). .PP Example: .IP .nf \f[C] $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 \f[R] .fi .PP With a reporting interval, multiple columns will be shown, one for each report period. Normally incomestatement shows revenues/expenses per period, though as with multicolumn balance reports you can alter the report mode with \f[C]--change\f[R]/\f[C]--cumulative\f[R]/\f[C]--historical\f[R]. Instead of absolute values percentages can be displayed with \f[C]-%\f[R]. .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], \f[C]html\f[R], and (experimental) \f[C]json\f[R]. .SS notes .PP notes .PD 0 .P .PD 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 .nf \f[C] $ hledger notes Petrol Snacks \f[R] .fi .SS payees .PP payees .PD 0 .P .PD List the unique payee/payer names that appear in transactions. .PP This command lists the unique payee/payer names that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). .PP Example: .IP .nf \f[C] $ hledger payees Store Name Gas Station Person A \f[R] .fi .SS prices .PP prices .PD 0 .P .PD Print market price directives from the journal. With --costs, also print synthetic market prices based on transaction prices. With --inverted-costs, also print inverse prices based on transaction prices. Prices (and postings providing prices) can be filtered by a query. Price amounts are always displayed with their full precision. .SS print .PP print, txns, p .PD 0 .P .PD Show transaction journal entries, sorted by date. .PP The print command displays full journal entries (transactions) from the journal file in date order, tidily formatted. With --date2, transactions are sorted by secondary date instead. .PP print\[aq]s output is always a valid hledger journal. .PD 0 .P .PD It preserves all transaction information, but it does not preserve directives or inter-transaction comments .IP .nf \f[C] $ hledger print 2008/01/01 income assets:bank:checking $1 income:salary $-1 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 2008/12/31 * pay off liabilities:debts $1 assets:bank:checking $-1 \f[R] .fi .PP Normally, the journal entry\[aq]s explicit or implicit amount style is preserved. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, when a transaction price is implied but not written, it will not appear in the output. You can use the \f[C]-x\f[R]/\f[C]--explicit\f[R] flag to make all amounts and transaction prices explicit, which can be useful for troubleshooting or for making your journal more readable and robust against data entry errors. \f[C]-x\f[R] is also implied by using any of \f[C]-B\f[R],\f[C]-V\f[R],\f[C]-X\f[R],\f[C]--value\f[R]. .PP Note, \f[C]-x\f[R]/\f[C]--explicit\f[R] will cause postings with a multi-commodity amount (these can arise when a multi-commodity transaction has an implicit amount) to be split into multiple single-commodity postings, keeping the output parseable. .PP With \f[C]-B\f[R]/\f[C]--cost\f[R], amounts with transaction prices are converted to cost using that price. This can be used for troubleshooting. .PP With \f[C]-m\f[R]/\f[C]--match\f[R] and a STR argument, print will show at most one transaction: the one one whose description is most similar to STR, and is most recent. STR should contain at least two characters. If there is no similar-enough match, no transaction will be shown. .PP With \f[C]--new\f[R], for each FILE being read, hledger reads (and writes) a special state file (\f[C].latest.FILE\f[R] in the same directory), containing the latest transaction date(s) that were seen last time FILE was read. When this file is found, only transactions with newer dates (and new transactions on the latest date) are printed. This is useful for ignoring already-seen entries in import data, such as downloaded CSV files. Eg: .IP .nf \f[C] $ hledger -f bank1.csv print --new (shows transactions added since last print --new on this file) \f[R] .fi .PP This assumes that transactions added to FILE always have same or increasing dates, and that transactions on the same day do not get reordered. See also the import command. .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], and (experimental) \f[C]json\f[R] and \f[C]sql\f[R]. .PP Here\[aq]s an example of print\[aq]s CSV output: .IP .nf \f[C] $ 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] \f[R] .fi .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 print-unique .PP print-unique .PD 0 .P .PD Print transactions which do not reuse an already-seen description. .PP Example: .IP .nf \f[C] $ cat unique.journal 1/1 test (acct:one) 1 2/2 test (acct:two) 2 $ LEDGER_FILE=unique.journal hledger print-unique (-f option not supported) 2015/01/01 test (acct:one) 1 \f[R] .fi .SS register .PP register, reg, r .PD 0 .P .PD 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[C]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 .nf \f[C] $ 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 \f[R] .fi .PP With --date2, it shows and sorts by secondary date instead. .PP The \f[C]--historical\f[R]/\f[C]-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 .nf \f[C] $ 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 \f[R] .fi .PP The \f[C]--depth\f[R] option limits the amount of sub-account detail displayed. .PP The \f[C]--average\f[R]/\f[C]-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[C]--empty\f[R] (see below). It is affected by \f[C]--historical\f[R]. It works best when showing just one account and one commodity. .PP The \f[C]--related\f[R]/\f[C]-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[C]--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 .nf \f[C] $ hledger register --related --invert assets:checking \f[R] .fi .PP With a reporting interval, register shows summary postings, one per interval, aggregating the postings to each account: .IP .nf \f[C] $ hledger register --monthly income 2008/01 income:salary $-1 $-1 2008/06 income:gifts $-1 $-2 \f[R] .fi .PP Periods with no activity, and summary postings with a zero amount, are not shown by default; use the \f[C]--empty\f[R]/\f[C]-E\f[R] flag to see them: .IP .nf \f[C] $ 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 \f[R] .fi .PP Often, you\[aq]ll want to see just one line per interval. The \f[C]--depth\f[R] option helps with this, causing subaccounts to be aggregated: .IP .nf \f[C] $ hledger register --monthly assets --depth 1h 2008/01 assets $1 $1 2008/06 assets $-1 0 2008/12 assets $-1 $-1 \f[R] .fi .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. .SS Custom register output .PP register uses the full terminal width by default, except on windows. You can override this by setting the \f[C]COLUMNS\f[R] environment variable (not a bash shell variable) or by using the \f[C]--width\f[R]/\f[C]-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[C]--width W,D\f[R] . Here\[aq]s a diagram (won\[aq]t display correctly in --help): .IP .nf \f[C] <--------------------------------- width (W) ----------------------------------> date (10) description (D) account (W-41-D) amount (12) balance (12) DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA \f[R] .fi .PP and some examples: .IP .nf \f[C] $ 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 \f[R] .fi .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], and (experimental) \f[C]json\f[R]. .SS register-match .PP register-match .PD 0 .P .PD Print the one posting whose transaction description is closest to DESC, in the style of the register command. If there are multiple equally good matches, it shows the most recent. Query options (options, not arguments) can be used to restrict the search space. Helps ledger-autosync detect already-seen transactions when importing. .SS rewrite .PP rewrite .PD 0 .P .PD 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 .nf \f[C] $ 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 \f[R] .fi .PP rewrites.hledger may consist of entries like: .IP .nf \f[C] = \[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 \f[R] .fi .PP Note the single quotes to protect the dollar sign from bash, and the two spaces between account and amount. .PP More: .IP .nf \f[C] $ 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] \f[R] .fi .PP Argument for \f[C]--add-posting\f[R] option is a usual posting of transaction with an exception for amount specification. More precisely, you can use \f[C]\[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 .PP 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 .nf \f[C] $ rewrite-rules.journal \f[R] .fi .PP Make contents look like this: .IP .nf \f[C] = \[ha]income (liabilities:tax) *.33 = expenses:gifts budget:gifts *-1 assets:budget *1 \f[R] .fi .PP Note that \f[C]\[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 .nf \f[C] $ hledger rewrite -- -f input.journal -f rewrite-rules.journal > rewritten-tidy-output.journal \f[R] .fi .PP This is something similar to the commands pipeline: .IP .nf \f[C] $ 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 \f[R] .fi .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 .PP To use this tool for batch modification of your journal files you may find useful output in form of unified diff. .IP .nf \f[C] $ hledger rewrite -- --diff -f examples/sample.journal \[aq]\[ha]income\[aq] --add-posting \[aq](liabilities:tax) *.33\[aq] \f[R] .fi .PP Output might look like: .IP .nf \f[C] --- /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 \f[R] .fi .PP If you\[aq]ll pass this through \f[C]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[C]--file\f[R] options and \f[C]include\f[R] directives inside of these files. .PP Be careful. Whole transaction being re-formatted in a style of output from \f[C]hledger print\f[R]. .PP See also: .PP https://github.com/simonmichael/hledger/issues/99 .SS rewrite vs. print --auto .PP 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 .PP roi .PD 0 .P .PD Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. .PP This command assumes that you have account(s) that hold nothing but your investments and whenever you record current appraisal/valuation of these investments you offset unrealized profit and loss into account(s) that, again, hold nothing but unrealized profit and loss. .PP Any transactions affecting balance of investment account(s) and not originating from unrealized profit and loss account(s) are assumed to be your investments or withdrawals. .PP At a minimum, you need to supply a query (which could be just an account name) to select your investments with \f[C]--inv\f[R], and another query to identify your profit and loss transactions with \f[C]--pnl\f[R]. .PP It will compute and display the internalized rate of return (IRR) and time-weighted rate of return (TWR) for your investments for the time period requested. Both rates of return are annualized before display, regardless of the length of reporting interval. .SS stats .PP stats .PD 0 .P .PD Show some journal 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 Example: .IP .nf \f[C] $ hledger stats Main journal file : /src/hledger/examples/sample.journal Included journal files : Transactions span : 2008-01-01 to 2009-01-01 (366 days) Last transaction : 2008-12-31 (2333 days ago) 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 : 12 ($) \f[R] .fi .PP This command also supports output destination and output format selection. .SS tags .PP tags .PD 0 .P .PD List the unique tag names used in the journal. With a TAGREGEX argument, only tag names matching the regular expression (case insensitive) are shown. With QUERY arguments, only transactions matching the query are considered. .PP With the --values flag, the tags\[aq] unique values are listed instead. .PP With --parsed flag, all tags or values are shown in the order they are parsed from the input data, including duplicates. .PP With -E/--empty, any blank/empty values will also be shown, otherwise they are omitted. .SS test .PP test .PD 0 .P .PD 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 .nf \f[C] $ hledger test -- -pData.Amount --color=never \f[R] .fi .PP For help on these, see https://github.com/feuerbach/tasty#options (\f[C]-- --help\f[R] currently doesn\[aq]t show them). .SS Add-on commands .PP hledger also searches for external add-on commands, and will include these in the commands list. These are programs or scripts in your PATH whose name starts with \f[C]hledger-\f[R] and ends with a recognised file extension (currently: no extension, \f[C]bat\f[R],\f[C]com\f[R],\f[C]exe\f[R], \f[C]hs\f[R],\f[C]lhs\f[R],\f[C]pl\f[R],\f[C]py\f[R],\f[C]rb\f[R],\f[C]rkt\f[R],\f[C]sh\f[R]). .PP Add-ons can be invoked like any hledger command, but there are a few things to be aware of. Eg if the \f[C]hledger-web\f[R] add-on is installed, .IP \[bu] 2 \f[C]hledger -h web\f[R] shows hledger\[aq]s help, while \f[C]hledger web -h\f[R] shows hledger-web\[aq]s help. .IP \[bu] 2 Flags specific to the add-on must have a preceding \f[C]--\f[R] to hide them from hledger. So \f[C]hledger web --serve --port 9000\f[R] will be rejected; you must use \f[C]hledger web -- --serve --port 9000\f[R]. .IP \[bu] 2 You can always run add-ons directly if preferred: \f[C]hledger-web --serve --port 9000\f[R]. .PP Add-ons are a relatively easy way to add local features or experiment with new ideas. They can be written in any language, but haskell scripts have a big advantage: they can use the same hledger (and haskell) library functions that built-in commands do, for command-line options, journal parsing, reporting, etc. .PP Two important add-ons are the hledger-ui and hledger-web user interfaces. These are maintained and released along with hledger: .SS ui .PP hledger-ui provides an efficient terminal interface. .SS web .PP hledger-web provides a simple web interface. .PP Third party add-ons, maintained separately from hledger, include: .SS iadd .PP hledger-iadd is a more interactive, terminal UI replacement for the add command. .SS interest .PP hledger-interest generates interest transactions for an account according to various schemes. .PP A few more experimental or old add-ons can be found in hledger\[aq]s bin/ directory. These are typically prototypes and not guaranteed to work. .SH ENVIRONMENT .PP \f[B]LEDGER_FILE\f[R] The journal file path when not specified with \f[C]-f\f[R]. Default: \f[C]\[ti]/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). .PP A typical value is \f[C]\[ti]/DIR/YYYY.journal\f[R], where DIR is a version-controlled finance directory and YYYY is the current year. Or \f[C]\[ti]/DIR/current.journal\f[R], where current.journal is a symbolic link to YYYY.journal. .PP On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a \f[C]\[ti]/.MacOSX/environment.plist\f[R] file containing .IP .nf \f[C] { \[dq]LEDGER_FILE\[dq] : \[dq]\[ti]/finance/current.journal\[dq] } \f[R] .fi .PP To see the effect you may need to \f[C]killall Dock\f[R], or reboot. .PP \f[B]COLUMNS\f[R] The screen width used by the register command. Default: the full terminal width. .PP \f[B]NO_COLOR\f[R] If this variable exists with any value, hledger will not use ANSI color codes in terminal output. This overrides the --color/--colour option. .SH FILES .PP Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]-f\f[R], or \f[C]$LEDGER_FILE\f[R], or \f[C]$HOME/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). .SH LIMITATIONS .PP The need to precede addon command options with \f[C]--\f[R] when invoked from hledger is awkward. .PP When input data contains non-ascii characters, a suitable system locale must be configured (or there will be an unhelpful error). Eg on POSIX, set LANG to something other than C. .PP In a Microsoft Windows CMD window, non-ascii characters and colours are not supported. .PP On Windows, non-ascii characters may not display correctly when running a hledger built in CMD in MSYS/CYGWIN, or vice-versa. .PP In a Cygwin/MSYS/Mintty window, the tab key is not supported in hledger add. .PP Not all of Ledger\[aq]s journal file syntax is supported. See file format differences. .PP On large data files, hledger is slower and uses more memory than Ledger. .SH TROUBLESHOOTING .PP Here are some issues you might encounter when you run hledger (and remember you can also seek help from the IRC channel, mail list or bug tracker): .PP \f[B]Successfully installed, but \[dq]No command \[aq]hledger\[aq] found\[dq]\f[R] .PD 0 .P .PD stack and cabal install binaries into a special directory, which should be added to your PATH environment variable. Eg on unix-like systems, that is \[ti]/.local/bin and \[ti]/.cabal/bin respectively. .PP \f[B]I set a custom LEDGER_FILE, but hledger is still using the default file\f[R] .PD 0 .P .PD \f[C]LEDGER_FILE\f[R] should be a real environment variable, not just a shell variable. The command \f[C]env | grep LEDGER_FILE\f[R] should show it. You may need to use \f[C]export\f[R]. Here\[aq]s an explanation. .PP \f[B]Getting 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 to have a UTF-8-aware locale configured in the environment, otherwise they will fail with these kinds of errors when they encounter non-ascii characters. .PP To fix it, set the LANG environment variable to some locale which supports UTF-8. The locale you choose must be installed on your system. .PP Here\[aq]s an example of setting LANG temporarily, on Ubuntu GNU/Linux: .IP .nf \f[C] $ file my.journal my.journal: UTF-8 Unicode text # the file is UTF8-encoded $ echo $LANG C # LANG is set to the default locale, which does not support UTF8 $ locale -a # which locales are installed ? C en_US.utf8 # here\[aq]s a UTF8-aware one we can use POSIX $ LANG=en_US.utf8 hledger -f my.journal print # ensure it is used for this command \f[R] .fi .PP If available, \f[C]C.UTF-8\f[R] will also work. If your preferred locale isn\[aq]t listed by \f[C]locale -a\f[R], you might need to install it. Eg on Ubuntu/Debian: .IP .nf \f[C] $ apt-get install language-pack-fr $ locale -a C en_US.utf8 fr_BE.utf8 fr_CA.utf8 fr_CH.utf8 fr_FR.utf8 fr_LU.utf8 POSIX $ LANG=fr_FR.utf8 hledger -f my.journal print \f[R] .fi .PP Here\[aq]s how you could set it permanently, if you use a bash shell: .IP .nf \f[C] $ echo \[dq]export LANG=en_US.utf8\[dq] >>\[ti]/.bash_profile $ bash --login \f[R] .fi .PP Exact spelling and capitalisation may be important. Note the difference on MacOS (\f[C]UTF-8\f[R], not \f[C]utf8\f[R]). Some platforms (eg ubuntu) allow variant spellings, but others (eg macos) require it to be exact: .IP .nf \f[C] $ locale -a | grep -iE en_us.*utf en_US.UTF-8 $ LANG=en_US.UTF-8 hledger -f my.journal print \f[R] .fi .SH "REPORTING BUGS" Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) .SH AUTHORS Simon Michael and contributors .SH COPYRIGHT Copyright (C) 2007-2019 Simon Michael. .br Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5), ledger(1) http://hledger.org hledger-1.19.1/hledger.txt0000644000000000000000000045100013725533425013567 0ustar0000000000000000 hledger(1) hledger User Manuals hledger(1) NAME hledger - a command-line accounting tool SYNOPSIS hledger [-f FILE] COMMAND [OPTIONS] [ARGS] hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS] hledger DESCRIPTION hledger is a reliable, 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). This is hledger's command-line interface (there are also terminal and web interfaces). Its basic function is to read a plain text file de- scribing financial transactions (in accounting terms, a general jour- nal) and print useful reports on standard output, or export them as CSV. hledger can also read some other file formats such as CSV files, translating them to journal format. Additionally, hledger lists other hledger-* executables found in the user's $PATH and can invoke them as subcommands. hledger reads data from one or more files in hledger journal, time- clock, timedot, or CSV format specified with -f, or $LEDGER_FILE, or $HOME/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.journal). If using $LEDGER_FILE, note this must be a real environment variable, not a shell variable. You can specify standard input with -f-. Transactions are dated movements of money between two (or more) named accounts, and are recorded with journal entries like this: 2015/10/16 bought food expenses:food $10 assets:cash For more about this format, see hledger_journal(5). Most users use a text editor to edit the journal, usually with an edi- tor mode such as ledger-mode for added convenience. hledger's interac- tive add command is another way to record new transactions. hledger never changes existing transactions. To get started, you can either save some entries like the above in ~/.hledger.journal, or run hledger add and follow the prompts. Then try some commands like hledger print or hledger balance. Run hledger with no arguments for a list of commands. COMMON TASKS Here are some quick examples of how to do some basic tasks with hledger. For more details, see the reference section below, the hledger_journal(5) manual, or the more extensive docs at https://hledger.org. Getting help $ hledger # show available commands $ hledger --help # show common options $ hledger CMD --help # show common and command options, and command help $ hledger help # show available manuals/topics $ hledger help hledger # show hledger manual as info/man/text (auto-chosen) $ hledger help journal --man # show the journal manual as a man page $ hledger help --help # show more detailed help for the help command Find more docs, chat, mail list, reddit, issue tracker: https://hledger.org#help-feedback Constructing command lines hledger has an extensive and powerful command line interface. We strive to keep it simple and ergonomic, but you may run into one of the confusing real world details described in OPTIONS, below. If that hap- pens, here are some tips that may help: o command-specific options must go after the command (it's fine to put all options there) (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 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. 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 2020.journal $ echo "export LEDGER_FILE=$HOME/finance/2020.journal" >> ~/.bashrc $ source ~/.bashrc $ hledger stats Main file : /Users/simon/finance/2020.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 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: 2020-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/2020.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 [2020-02-07]: 2020-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): . 2020-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 [2020-01-01]: . If you're using version control, this could be a good time to commit the journal. Eg: $ git commit -m 'initial balances' 2020.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: 2020/1/10 * gift received assets:cash $20 income:gifts 2020.1.12 * farmers market expenses:food $13 assets:cash 2020-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: 2020-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 2020-01-15 and paycheck If you're using version control, this can be another good time to com- mit: $ git commit -m 'txns' 2020.journal Reporting Here are some basic reports. Show all transactions: $ hledger print 2020-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 2020-01-10 * gift received assets:cash $20 income:gifts 2020-01-12 * farmers market expenses:food $13 assets:cash 2020-01-15 * paycheck income:salary assets:bank:checking $1000 2020-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 --flat -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 --flat -2 Balance Sheet 2020-01-16 || 2020-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 2020-01-01-2020-01-16 || 2020-01-01-2020-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 2020-01-01 opening balances assets:cash $100 $100 2020-01-10 gift received assets:cash $20 $120 2020-01-12 farmers market assets:cash $-13 $107 2020-01-16 adjust cash assets:cash $-2 $105 Show weekly posting counts as a bar chart: $ hledger activity -W 2019-12-30 ***** 2020-01-06 **** 2020-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. OPTIONS General options To see general usage help, including general options which are sup- ported by most hledger commands, run hledger -h. General help options: -h --help show general usage (or after COMMAND, command usage) --version show 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 --anon anonymize accounts and payees --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) General reporting options: -b --begin=DATE include postings/txns on or after this date -e --end=DATE include postings/txns before this date -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) -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-value with -V/-X/--value, also infer market prices from transactions --auto apply automated posting rules to modify transactions. --forecast generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. --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. 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 options To see options for a particular command, including command-specific op- tions, run: hledger COMMAND -h. Command-specific options must be written after the command name, eg: hledger print -x. Additionally, if the command is an addon, you may need to put its op- tions after a double-hyphen, eg: hledger ui -- --watch. Or, you can run the addon executable directly: hledger-ui --watch. Command arguments Most hledger commands accept arguments after the command name, which are often a query, filtering the data in some way. You can save a set of command line options/arguments in a file, and then reuse them by writing @FILENAME as a command line argument. Eg: hledger bal @foo.args. (To prevent this, eg if you have an argument that begins with a literal @, precede it with --, eg: hledger bal -- @ARG). Inside the argument file, each line should contain just one option or argument. Avoid the use of spaces, except inside quotes (or you'll see a confusing error). Between a flag and its argument, use = (or noth- ing). Bad: assets depth:2 -X USD Good: assets depth:2 -X=USD For special characters (see below), use one less level of quoting than you would at the command prompt. Bad: -X"$" Good: -X$ See also: Save frequently used options. Queries One of hledger's strengths is being able to quickly report on precise subsets of your data. Most commands accept an optional query expres- sion, written as arguments after the command name, to filter the data by date, account name or other criteria. The syntax is similar to a web search: one or more space-separated search terms, quotes to enclose whitespace, prefixes to match specific fields, a not: prefix to negate the match. We do not yet support arbitrary boolean combinations of search terms; instead most commands show transactions/postings/accounts which match (or negatively 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 instead shows 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. The following kinds of search terms can be used. Remember these can also be prefixed with not:, eg to exclude a particular subaccount. REGEX, acct:REGEX match account names by this regular expression. (With no pre- fix, acct: is assumed.) same as above amt:N, amt:N, amt:>=N match postings with a single-commodity amount that is equal to, less than, or greater than N. (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 cur- rency/commodity symbol is fully matched by REGEX. (For a par- tial match, use .*REGEX.*). Note, to match characters which are regex-significant, like the dollar sign ($), you need to prepend \. And when using the command line you need to add one more level of quoting to hide it from the shell, so eg do: hledger print cur:'\$' or hledger print cur:\\$. desc:REGEX match transaction descriptions. date:PERIODEXPR match dates within the specified period. PERIODEXPR is a period expression (with no report interval). Examples: date:2016, date:thismonth, date:2000/2/1-2/15, date:lastweek-. If the --date2 command line flag is present, this matches secondary dates instead. date2:PERIODEXPR match secondary dates within the specified period. depth:N match (or display, depending on command) accounts at or above this depth note:REGEX match transaction notes (part of description right of |, or whole description when there's no |) payee:REGEX match transaction payee/payer names (part of description left of |, or whole description when there's no |) real:, real:0 match real or virtual postings respectively status:, status:!, status:* match unmarked, pending, or cleared transactions respectively tag:REGEX[=REGEX] match by tag name, and optionally also by tag value. Note a tag: query is considered to match a transaction if it matches any of the postings. Also remember that postings inherit the tags of their parent transaction. The following special search term is used automatically in hledger-web, only: inacct:ACCTNAME tells hledger-web to show the transaction register for this ac- count. Can be filtered further with acct etc. Some of these can also be expressed as command-line options (eg depth:2 is equivalent to --depth 2). Generally you can mix options and query arguments, and the resulting query will be their intersection (perhaps excluding the -p/--period option). Special characters in arguments and queries In shell command lines, option and argument values which contain "prob- lematic" characters, ie spaces, and also characters significant to your shell such as <, >, (, ), | and $, should be escaped by enclosing them in quotes or by writing backslashes before the characters. Eg: hledger register -p 'last year' "accounts receivable (receiv- able|payable)" amt:\>100. More escaping Characters significant both to the shell and in regular expressions may need one extra level of escaping. These include parentheses, the pipe symbol and the dollar sign. Eg, to match the dollar symbol, bash users should do: hledger balance cur:'\$' or: hledger balance cur:\\$ Even more escaping When hledger runs an addon executable (eg you type hledger ui, hledger runs hledger-ui), it de-escapes command-line options and arguments once, so you might need to triple-escape. Eg in bash, running the ui command and matching the dollar sign, it's: hledger ui cur:'\\$' or: hledger ui cur:\\\\$ If you asked why four slashes above, this may help: unescaped: $ escaped: \$ double-escaped: \\$ triple-escaped: \\\\$ (The number of backslashes in fish shell is left as an exercise for the reader.) You can always avoid the extra escaping for addons by running the addon directly: hledger-ui cur:\\$ Less escaping Inside an argument file, or in the search field of hledger-ui or hledger-web, or at a GHCI prompt, you need one less level of escaping than at the command line. And backslashes may work better than quotes. Eg: ghci> :main balance cur:\$ 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). Input files hledger reads transactions from a data file (and the add command writes to it). By default this file is $HOME/.hledger.journal (or on Windows, something like C:/Users/USER/.hledger.journal). You can override this with the $LEDGER_FILE environment variable: $ setenv LEDGER_FILE ~/finance/2016.journal $ hledger stats or with the -f/--file option: $ hledger -f /some/file stats The file name - (hyphen) means standard input: $ cat some.journal | hledger -f- 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 exten- sions: ----------------------------------------------------------------------------- journal hledger journal files and some Ledger .journal .j .hledger journals, for transactions .ledger time- timeclock files, for precise time log- .timeclock clock ging timedot timedot files, for approximate time .timedot logging csv comma/semicolon/tab/other-separated .csv .ssv .tsv values, for data import 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. When you can't ensure the right file extension, not to worry: you can force a specific reader/format by prefixing the file path with the for- mat and a colon. Eg to read a .dat file as csv: $ hledger -f csv:/some/csv-file.dat stats $ echo 'i 2009/13/1 08:00:00' | hledger print -ftimeclock:- You can specify multiple -f options, to read multiple files as one big journal. There are some limitations with this: o directives in one file will not affect the other files o balance assertions will not see any account balances from previous files If you need either of those things, you can o use a single parent file which includes the others o or concatenate the files into one before reading, eg: cat a.journal b.journal | hledger -f- CMD. 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 (print, register, the balance commands) offer a choice of output format. In addition to the usual plain text format (txt), there are CSV (csv), HTML (html), JSON (json) and SQL (sql). This is con- trolled by the -O/--output-format option: $ hledger print -O csv or, by a file extension specified with -o/--output-file: $ hledger balancesheet -o foo.html # write HTML to foo.html The -O option can be used to override the file extension if needed: $ hledger balancesheet -o foo.txt -O html # write HTML to foo.txt Some notes about JSON output: o This feature is marked experimental, and not yet much used; you should expect our JSON to evolve. Real-world feedback is welcome. o Our JSON is rather large and verbose, as it is quite a faithful rep- resentation 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. 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) Notes about SQL output: o SQL output is also marked experimental, and much like JSON could use real-world feedback. o SQL output is expected to work with sqlite, MySQL and PostgreSQL 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. Regular expressions hledger uses regular expressions in a number of places: o query terms, on the command line and in the hledger-web search form: REGEX, desc:REGEX, cur:REGEX, tag:...=REGEX o CSV rules conditional blocks: if REGEX ... o account alias directives and options: alias /REGEX/ = REPLACEMENT, --alias /REGEX/=REPLACEMENT 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. they do not support backreferences; if you write \1, it will match the digit 1. Except when doing text replacement, eg in account aliases, where backreferences can be used in the replacement string to reference capturing groups in the search regexp. 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. Smart dates hledger's user interfaces accept a flexible "smart date" syntax (unlike dates in the journal file). Smart dates allow some english words, can be relative to today's date, and can have less-significant date parts omitted (defaulting to 1). 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 20181201 8 digit YYYYMMDD with valid year month and day 201812 6 digit YYYYMM with valid year and month Counterexamples - malformed digit sequences might give surprising re- sults: 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 Report start & end date Most hledger reports show the full span of time represented by the journal data, by default. So, the effective report start and end dates will be the earliest and latest transaction or posting dates found in the journal. 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. Some notes: o As in Ledger, end dates are exclusive, so you need to write the date after the last day you want to include. 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. 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 Report intervals A report interval can be specified so that commands like register, bal- ance and activity will divide their reports into multiple subperiods. The basic intervals can be selected with one of -D/--daily, -W/--weekly, -M/--monthly, -Q/--quarterly, or -Y/--yearly. More com- plex intervals may be specified with a period expression. Report in- tervals can not be specified with a query. Period expressions The -p/--period option accepts period expressions, a shorthand way of expressing a start date, end date, and/or report interval all at once. Here's a basic period expression specifying the first quarter of 2009. Note, hledger always treats start dates as inclusive and end dates as exclusive: -p "from 2009/1/1 to 2009/4/1" Keywords like "from" and "to" are optional, and so are the spaces, as long as you don't run two dates together. "to" can also be written as ".." or "-". These 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, the above can also be written as: -p "1/1 4/1" -p "january-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 in your journal: -p "from 2009/1/1" everything after january 1, 2009 -p "from 2009/1" the same -p "from 2009" the same -p "to 2009" everything before january 1, 2009 A single date with no "from" or "to" defines both the start and end date like so: -p "2009" the year 2009; equivalent to "2009/1/1 to 2010/1/1" -p "2009/1" the month of jan; equiva- lent to "2009/1/1 to 2009/2/1" -p "2009/1/1" just that day; equivalent to "2009/1/1 to 2009/1/2" Or you can specify a single quarter like so: -p "2009Q1" first quarter of 2009, equivalent to "2009/1/1 to 2009/4/1" -p "q4" fourth quarter of the cur- rent year The argument of -p can also begin with, or be, a report interval ex- pression. The basic report intervals are daily, weekly, monthly, quar- terly, or yearly, which have the same effect as the -D,-W,-M,-Q, or -Y flags. Between report interval and start/end dates (if any), the word in is optional. Examples: -p "weekly from 2009/1/1 to 2009/4/1" -p "monthly in 2008" -p "quarterly" Note that weekly, monthly, quarterly and yearly intervals will always start on the first day on week, month, quarter or year accordingly, and will end on the last day of same period, even if associated period ex- pression specifies different explicit start and end date. For example: -p "weekly from 2009/1/1 starts on 2008/12/29, closest preceding Mon- to 2009/4/1" day -p "monthly in starts on 2018/11/01 2008/11/25" -p "quarterly from starts on 2009/04/01, ends on 2009/06/30, 2009-05-05 to 2009-06-01" which are first and last days of Q2 2009 -p "yearly from starts on 2009/01/01, first day of 2009 2009-12-29" The following more complex report intervals are also supported: bi- weekly, fortnightly, bimonthly, every day|week|month|quarter|year, ev- ery N days|weeks|months|quarters|years. All of these will start on the first day of the requested period and end on the last one, as described above. Examples: -p "bimonthly from 2008" periods will have boundaries on 2008/01/01, 2008/03/01, ... -p "every 2 weeks" starts on closest preceding Monday -p "every 5 month from periods will have boundaries on 2009/03/01, 2009/03" 2009/08/01, ... If you want intervals that start on arbitrary day of your choosing and span a week, month or year, you need to use any of the following: every Nth day of week, every , every Nth day [of month], every Nth weekday [of month], every MM/DD [of year], every Nth MMM [of year], every MMM Nth [of year]. Examples: -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 Nov -p "every 5th Nov" same -p "every Nov 5th" same Show historical balances at end of 15th each month (N is exclusive end date): hledger balance -H -p "every 16th day" Group postings from start of wednesday to end of next tuesday (N is start date and exclusive end date): hledger register checking -p "every 3rd day of week" Depth limiting With the --depth N option (short form: -N), commands like account, bal- ance and register will show only the uppermost accounts in the account tree, down to level N. Use this when you want a summary with less de- tail. This flag has the same effect as a depth: query argument (so -2, --depth=2 or depth:2 are equivalent). Pivoting Normally hledger sums amounts, and organizes them in a hierarchy, based on account name. The --pivot FIELD option causes it to sum and orga- nize hierarchy based on the value of some other field instead. FIELD can be: code, description, payee, note, or the full name (case insensi- tive) of any tag. As with account names, values containing colon:sepa- rated:parts will be displayed hierarchically in reports. --pivot is a general option affecting all reports; you can think of hledger transforming the journal before any other processing, replacing every posting's account name with the value of the specified field on that posting, inheriting it from the transaction or using a blank value if it's not present. An example: 2016/02/16 Member Fee Payment assets:bank account 2 EUR income:member fees -2 EUR ; member: John Doe Normal balance report showing account names: $ hledger balance 2 EUR assets:bank account -2 EUR income:member fees -------------------- 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, de- scribed below): $ 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 Valuation Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), or to market value (using some market price on a cer- tain date). This is controlled by the --value=TYPE[,COMMODITY] option, but we also provide the simpler -B/-V/-X flags, and usually one of those is all you need. -B: Cost The -B/--cost flag converts amounts to their cost or sale amount at transaction time, if they have a transaction price specified. -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 Since market prices can change from day to day, market value reports have a valuation date (or more than one), which determines which market prices will be used. For single period reports, if an explicit report end date is specified, that will be used as the valuation date; otherwise the valuation date is "today". For multiperiod reports, each column/period is valued on the last day of the period. Market prices (experimental) 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 (if the --infer-value flag is used) inferred from transac- tion prices. 2. A reverse market price: the inverse of a declared or inferred market price from B to A. 3. A chained market price: a synthetic price formed by combining the shortest chain of market prices (any of the above types) leading from A to B. Amounts for which no applicable market price can be found, are not con- verted. --infer-value: market prices from transactions (experimental) 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 transaction prices as additional market prices (as Ledger does) ? We could produce value reports without need- ing P directives at all. Adding the --infer-value flag to -V, -X or --value enables this. So for example, hledger bs -V --infer-value will get market prices both from P directives and from transactions. 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 Valuation section carefully, and try adding --debug or --debug=2 to troubleshoot. --infer-value 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 but not, currently, from "more correct" multicommodity transactions (no @, multiple commodities, balanced). Valuation commodity (experimental) 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-value 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-value flag, transac- tion prices 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 EUR $1.10 ; purchase some euros on nov 3 2016/11/3 assets:euros EUR100 assets:checking ; the euro is worth fewer dollars by dec 21 P 2016/12/21 EUR $1.03 How many euros do I have ? $ hledger -f t.j bal -N euros EUR100 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 -B, -V and -X are special cases of the more general --value option: --value=TYPE[,COMM] TYPE is cost, then, end, now or YYYY-MM-DD. COMM is an optional commodity symbol. Shows amounts converted to: - cost commodity using transaction prices (then optionally to COMM using market prices at period end(s)) - 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=cost Convert amounts to cost, using the prices recorded in transac- tions. --value=then Convert amounts to their value in the default valuation commod- ity, using market prices on each posting's date. This is cur- rently supported only by the print and register commands. --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 --value=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 You may need to explicitly set a commodity's display style, when re- verse prices are used. Eg this output might be surprising: P 2000-01-01 A 2B 2000-01-01 a 1B b $ hledger print -x -X A 2000-01-01 a 0 b 0 Explanation: because there's no amount or commodity directive specify- ing a display style for A, 0.5A gets the default style, which shows no decimal digits. Because the displayed amount looks like zero, the com- modity symbol and minus sign are not displayed either. Adding a com- modity directive sets a more useful display style for A: P 2000-01-01 A 2B commodity 0.00A 2000-01-01 a 1B b $ hledger print -X A 2000-01-01 a 0.50A b -0.50A 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 type -B, -V, -X --value=then --value=end --value=DATE, --value=cost --value=now ------------------------------------------------------------------------------------------ print posting cost value at re- value at value at re- value at amounts port end or posting date port or DATE/today today journal end balance as- unchanged unchanged unchanged unchanged unchanged sertions / assignments register starting cost value at day not supported value at day value at balance before re- before re- DATE/today (with -H) port or port or journal journal start start posting cost value at re- value at value at re- value at amounts (no port end or posting date port or DATE/today report in- today journal end terval) summary summarised value at pe- sum of post- value at pe- value at posting cost riod ends ings in in- riod ends DATE/today amounts terval, val- (with report ued at inter- interval) val start running to- sum/average sum/average sum/average sum/average sum/average tal/average of displayed of displayed of displayed of displayed of displayed values values values values values balance (bs, bse, cf, is..) balances (no sums of value at re- not supported value at re- value at report in- costs port end or port or DATE/today of terval) today of journal end sums of post- sums of of sums of ings postings postings balances sums of value at pe- not supported value at pe- value at (with report costs riod ends of riod ends of DATE/today of interval) sums of sums of sums of post- postings postings ings starting sums of sums of not supported sums of sums of post- balances costs of postings be- postings be- ings before (with report postings be- fore report fore report report start interval and fore report start start -H) start budget like bal- like bal- not supported like bal- like balances amounts with ances ances ances --budget grand total sum of dis- sum of dis- not supported sum of dis- sum of dis- (no report played val- played val- played val- played values interval) ues ues ues row to- sums/aver- sums/aver- not supported sums/aver- sums/averages tals/aver- ages of dis- ages of dis- ages of dis- of displayed ages (with played val- played val- played val- values report in- ues ues ues terval) column to- sums of dis- sums of dis- not supported sums of dis- sums of dis- tals played val- played val- played val- played values ues ues ues grand to- sum/average sum/average not supported sum/average sum/average tal/average of column of column of column of column to- totals totals totals tals 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). COMMANDS hledger provides a number of subcommands; hledger with no arguments shows a list. If you install additional hledger-* packages, or if you put programs or scripts named hledger-NAME in your PATH, these will also be listed as subcommands. Run a subcommand by writing its name as first argument (eg hledger in- comestatement). You can also write one of the standard short aliases displayed in parentheses in the command list (hledger b), or any any unambiguous prefix of a command name (hledger inc). Here are all the builtin commands in alphabetical order. See also hledger for a more organised command list, and hledger CMD -h for de- tailed command help. accounts accounts, a Show account names. This command lists account names, either declared with account direc- tives (--declared), posted to (--used), or both (the default). With query arguments, only matched account names and account names refer- enced by matched postings are shown. 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 com- ponents. Account names can be depth-clipped with depth:N or --depth N or -N. Examples: $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts activity 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 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 journal file (if there are multiple -f FILE options, the first file is used.) Existing transactions are not changed. This is the only hledger command that writes to the journal file. 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, descrip- tions, 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 the tutorial for a detailed explanation): $ 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 aregister, areg Show transactions affecting a particular account, and the account's running balance. aregister shows the transactions affecting a particular account (and its subaccounts), from the point of view of that account. Each line shows: o the transaction's (or posting's, see below) date o the names of the other account(s) involved o the net change to this account's balance o the account's historical running balance (including balance from transactions before the report start date). With aregister, each line represents a whole transaction - as in hledger-ui, hledger-web, and your bank statement. By contrast, the register command shows individual postings, across all accounts. You might prefer aregister for reconciling with real-world asset/liability accounts, and register for reviewing detailed revenues/expenses. An account must be specified as the first argument, which should be the full account name or an account pattern (regular expression). aregis- ter will show transactions in this account (the first one matched) and any of its subaccounts. Any additional arguments form a query which will filter the transac- tions shown. Transactions making a net change of zero are not shown by default; add the -E/--empty flag to show them. aregister and custom posting dates Transactions whose date is outside the report period can still be shown, if they have a posting to this account dated inside the report period. (And in this case it's the posting date that is shown.) This ensures that aregister can show an accurate historical running balance, matching the one shown by register -H with the same arguments. To filter strictly by transaction date instead, add the --txn-dates flag. If you use this flag and some of your postings have custom dates, it's probably best to assume the running balance is wrong. Output format This command also supports the output destination and output format op- tions The output formats supported are txt, csv, and json. Examples: Show all transactions and historical running balance in the first ac- count whose name contains "checking": $ hledger areg checking Show transactions and historical running balance in all asset accounts during july: $ hledger areg assets date:jul balance balance, bal, b Show accounts and their balances. The balance command is hledger's most versatile command. Note, despite the name, it is not always used for showing real-world account bal- ances; the more accounting-aware balancesheet and incomestatement may be more convenient for that. By default, it displays all accounts, and each account's change in bal- ance during the entire period of the journal. Balance changes are cal- culated by adding up the postings in each account. You can limit the postings matched, by a query, to see fewer accounts, changes over a different time period, changes from only cleared transactions, etc. If you include an account's complete history of postings in the report, the balance change is equivalent to the account's current ending bal- ance. For a real-world account, typically you won't have all transac- tions in the journal; instead you'll have all transactions after a cer- tain date, and an "opening balances" transaction setting the correct starting balance on that date. Then the balance command will show real-world account balances. In some cases the -H/--historical flag is used to ensure this (more below). The balance command can produce several styles of report: Classic balance report This is the original balance report, as found in Ledger. It usually looks like this: $ hledger balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 By default, accounts are displayed hierarchically, with subaccounts in- dented below their parent. At each level of the tree, accounts are sorted by account code if any, then by account name. Or with -S/--sort-amount, by their balance amount, largest first. "Boring" accounts, which contain a single interesting subaccount and no balance of their own, are elided into the following line for more com- pact output. (Eg above, the "liabilities" account.) Use --no-elide to prevent this. Account balances are "inclusive" - they include the balances of any subaccounts. Accounts which have zero balance (and no non-zero subaccounts) are omitted. Use -E/--empty to show them. A final total is displayed by default; use -N/--no-total to suppress it, eg: $ hledger balance -p 2008/6 expenses --no-total $2 expenses $1 food $1 supplies Customising the classic balance report You can customise the layout of classic balance reports with --format FMT: $ hledger 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 (plus a newline) specifies the formatting applied to each account/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 Colour support In terminal output, when colour is enabled, the balance command shows negative amounts in red. Flat mode To see a flat list instead of the default hierarchical display, use --flat. In this mode, accounts (unless depth-clipped) show their full names and "exclusive" balance, excluding any subaccount balances. In this mode, you can also use --drop N to omit the first few account name components. $ hledger balance -p 2008/6 expenses -N --flat --drop 1 $1 food $1 supplies Depth limited balance reports With --depth N or depth:N or just -N, balance reports show accounts only to the specified numeric depth. This is very useful to summarise a complex set of accounts and get an overview. $ hledger balance -N -1 $-1 assets $2 expenses $-2 income $1 liabilities Flat-mode balance reports, which normally show exclusive balances, show inclusive balances at the depth limit. Percentages With -% or --percent, balance reports show each account's value ex- pressed as a percentage of the column's total. This is useful to get an overview of the relative sizes of account balances. For example to obtain an overview of expenses: $ hledger balance expenses -% 100.0 % expenses 50.0 % food 50.0 % supplies -------------------- 100.0 % Note that --tree does not have an effect on -%. The percentages are always relative to the total sum of each column, they are never rela- tive to the parent account. Since the percentages are relative to the columns sum, it is usually not useful to calculate percentages if the signs of the amounts are mixed. Although the results are technically correct, they are most likely useless. Especially in a balance report that sums up to zero (eg hledger balance -B) all percentage values will be zero. This flag does not work if the report contains any mixed commodity ac- counts. If there are mixed commodity accounts in the report be sure to use -V or -B to coerce the report into using a single commodity. Multicolumn balance report Multicolumn or tabular balance reports are a very useful hledger fea- ture, and usually the preferred style. They share many of the above features, but they show the report as a table, with columns represent- ing time periods. This mode is activated by providing a reporting in- terval. There are three types of multicolumn balance report, showing different information: 1. By default: each column shows the sum of postings in that period, ie the account's change of balance in that period. This is useful eg for a monthly income statement: $ hledger balance --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 2. With --cumulative: each column shows the ending balance for that pe- riod, accumulating the changes across periods, starting from 0 at the report start date: $ hledger balance --quarterly income expenses -E --cumulative Ending balances (cumulative) in 2008: || 2008/03/31 2008/06/30 2008/09/30 2008/12/31 ===================++================================================= expenses:food || 0 $1 $1 $1 expenses:supplies || 0 $1 $1 $1 income:gifts || 0 $-1 $-1 $-1 income:salary || $-1 $-1 $-1 $-1 -------------------++------------------------------------------------- || $-1 0 0 0 3. With --historical/-H: each column shows the actual historical ending balance for that period, accumulating the changes across periods, starting from the actual balance at the report start date. This is useful eg for a multi-period balance sheet, and when you are showing only the data after a certain start date: $ hledger balance ^assets ^liabilities --quarterly --historical --begin 2008/4/1 Ending balances (historical) in 2008/04/01-2008/12/31: || 2008/06/30 2008/09/30 2008/12/31 ======================++===================================== assets:bank:checking || $1 $1 0 assets:bank:saving || $1 $1 $1 assets:cash || $-2 $-2 $-2 liabilities:debts || 0 0 $1 ----------------------++------------------------------------- || 0 0 0 Note that --cumulative or --historical/-H disable --row-total/-T, since summing end balances generally does not make sense. Multicolumn balance reports display accounts in flat mode by default; to see the hierarchy, use --tree. With a reporting interval (like --quarterly above), the report start/end dates will be adjusted if necessary so that they encompass the displayed report periods. This is so that the first and last peri- ods will be "full" and comparable to the others. The -E/--empty flag does two things in multicolumn balance reports: first, the report will show all columns within the specified report pe- riod (without -E, leading and trailing columns with all zeroes are not shown). Second, all accounts which existed at the report start date will be considered, not just the ones with activity during the report period (use -E to include low-activity accounts which would otherwise would be omitted). The -T/--row-total flag adds an additional column showing the total for each row. The -A/--average flag adds a column showing the average value in each row. Here's an example of all three: $ hledger balance -Q income expenses --tree -ETA Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 Total Average ============++=================================================== expenses || 0 $2 0 0 $2 $1 food || 0 $1 0 0 $1 0 supplies || 0 $1 0 0 $1 0 income || $-1 $-1 0 0 $-2 $-1 gifts || 0 $-1 0 0 $-1 0 salary || $-1 0 0 0 $-1 0 ------------++--------------------------------------------------- || $-1 $1 0 0 0 0 (Average is rounded to the dollar here since all journal amounts are) The --transpose flag can be used to exchange the rows and columns of a multicolumn report. When showing multicommodity amounts, multicolumn balance reports will elide any amounts which have more than two commodities, since otherwise columns could get very wide. The --no-elide flag disables this. Hid- ing totals with the -N/--no-total flag can also help reduce the width of multicommodity reports. When the report is still too wide, a good workaround is to pipe it into less -RS (-R for colour, -S to chop long lines). Eg: hledger bal -D --color=yes | less -RS. Budget report With --budget, extra columns are displayed showing budget goals for each account and period, if any. Budget goals are defined by periodic transactions. This is very useful for comparing planned and actual in- come, expenses, time usage, etc. --budget is most often combined with a report interval. For example, you can take average monthly expenses in the common ex- pense categories to construct a minimal monthly budget: ;; Budget ~ monthly income $2000 expenses:food $400 expenses:bus $50 expenses:movies $30 assets:bank:checking ;; Two months worth of expenses 2017-11-01 income $1950 expenses:food $396 expenses:bus $49 expenses:movies $30 expenses:supplies $20 assets:bank:checking 2017-12-01 income $2100 expenses:food $412 expenses:bus $53 expenses:gifts $100 assets:bank:checking You can now see a monthly budget report: $ hledger balance -M --budget Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] This is different from a normal balance report in several ways: o Only accounts with budget goals during the report period are shown, by default. o In each column, in square brackets after the actual amount, budget goal amounts are shown, and the actual/goal percentage. (Note: bud- get goals should be in the same commodity as the actual amount.) o All parent accounts are always shown, even in flat mode. Eg assets, assets:bank, and expenses above. o Amounts always include all subaccounts, budgeted or unbudgeted, even in flat mode. This means that the numbers displayed will not always add up! Eg above, the expenses actual amount includes the gifts and supplies transac- tions, but the expenses:gifts and expenses:supplies accounts are not shown, as they have no budget amounts declared. This can be confusing. When you need to make things clearer, use the -E/--empty flag, which will reveal all accounts including unbudgeted ones, giving the full picture. Eg: $ hledger balance -M --budget --empty Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:gifts || 0 $100 expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] expenses:supplies || $20 0 income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] You can roll over unspent budgets to next period with --cumulative: $ hledger balance -M --budget --cumulative Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank:checking || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] expenses || $495 [ 103% of $480] $1060 [ 110% of $960] expenses:bus || $49 [ 98% of $50] $102 [ 102% of $100] expenses:food || $396 [ 99% of $400] $808 [ 101% of $800] expenses:movies || $30 [ 100% of $30] $30 [ 50% of $60] income || $1950 [ 98% of $2000] $4050 [ 101% of $4000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] For more examples, see Budgeting and Forecasting. Nested budgets You can add budgets to any account in your account hierarchy. If you have budgets on both parent account and some of its children, then bud- get(s) of the child account(s) would be added to the budget of their parent, much like account balances behave. In the most simple case this means that once you add a budget to any account, all its parents would have budget as well. To illustrate this, consider the following budget: ~ monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities With this, monthly budget for electronics is defined to be $100 and budget for personal expenses is an additional $1000, which implicitly means that budget for both expenses:personal and expenses is $1100. Transactions in expenses:personal:electronics will be counted both to- wards its $100 budget and $1100 of expenses:personal , and transactions in any other subaccount of expenses:personal would be counted towards only towards the budget of expenses:personal. For example, let's consider these transactions: ~ monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities 2019/01/01 Google home hub expenses:personal:electronics $90.00 liabilities $-90.00 2019/01/02 Phone screen protector expenses:personal:electronics:upgrades $10.00 liabilities 2019/01/02 Weekly train ticket expenses:personal:train tickets $153.00 liabilities 2019/01/03 Flowers expenses:personal $30.00 liabilities As you can see, we have transactions in expenses:personal:electron- ics:upgrades and expenses:personal:train tickets, and since both of these accounts are without explicitly defined budget, these transac- tions would be counted towards budgets of expenses:personal:electronics and expenses:personal accordingly: $ hledger balance --budget -M Budget performance in 2019/01: || Jan ===============================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] liabilities || $-283.00 [ 26% of $-1100.00] -------------------------------++------------------------------- || 0 [ 0] And with --empty, we can get a better picture of budget allocation and consumption: $ hledger balance --budget -M --empty Budget performance in 2019/01: || Jan ========================================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] expenses:personal:electronics:upgrades || $10.00 expenses:personal:train tickets || $153.00 liabilities || $-283.00 [ 26% of $-1100.00] ----------------------------------------++------------------------------- || 0 [ 0] Output format This command also supports the output destination and output format op- tions The output formats supported are txt, csv, (multicolumn non-bud- get reports only) html, and (experimental) json. balancesheet 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. The asset and liability accounts shown are those accounts declared with the Asset or Cash or Liability type, or otherwise all accounts under a top-level asset or liability account (case insensitive, plurals al- lowed). Example: $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 With a reporting interval, multiple columns will be shown, one for each report period. As with multicolumn balance reports, you can alter the report mode with --change/--cumulative/--historical. Normally bal- ancesheet shows historical ending balances, which is what you need for a balance sheet; note this means it ignores report begin dates (and -T/--row-total, since summing end balances generally does not make sense). Instead of absolute values percentages can be displayed with -%. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, html, and (experimen- tal) json. balancesheetequity 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. The asset, liability and equity accounts shown are those accounts de- clared with the Asset, Cash, Liability or Equity type, or otherwise all accounts under a top-level asset, liability or equity account (case in- sensitive, plurals allowed). 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 also supports the output destination and output format op- tions The output formats supported are txt, csv, html, and (experimen- tal) json. cashflow cashflow, cf This command displays a cashflow statement, showing the inflows and outflows affecting "cash" (ie, liquid) assets. Amounts are shown with normal positive sign, as in conventional financial statements. The "cash" accounts shown are those accounts declared with the Cash type, or otherwise all accounts under a top-level asset account (case insensitive, plural allowed) which do not have fixed, investment, re- ceivable or A/R in their name. Example: $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 With a reporting interval, multiple columns will be shown, one for each report period. Normally cashflow shows changes in assets per period, though as with multicolumn balance reports you can alter the report mode with --change/--cumulative/--historical. Instead of absolute val- ues percentages can be displayed with -%. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, html, and (experimen- tal) json. check-dates check-dates Check that transactions are sorted by increasing date. With --date2, checks secondary dates instead. With --strict, dates must also be unique. With a query, only matched transactions' dates are checked. Reads the default journal file, or another specified with -f. check-dupes check-dupes Reports account names having the same leaf but different prefixes. In other words, two or more leaves that are categorized differently. Reads the default journal file, or another specified as an argument. An example: http://stefanorodighiero.net/software/hledger-dupes.html close close, equity Prints a "closing balances" transaction and an "opening balances" transaction that bring account balances to and from zero, respectively. These can be added to your journal file(s), eg to bring asset/liability balances forward into a new journal file, or to close out revenues/ex- penses to retained earnings at the end of a period. You can print just one of these transactions by using the --close or --open flag. You can customise their descriptions with the --close- desc and --open-desc options. One amountless posting to "equity:opening/closing balances" is added to balance the transactions, by default. You can customise this account name with --close-acct and --open-acct; if you specify only one of these, it will be used for both. With --x/--explicit, the equity posting's amount will be shown. And if it involves multiple commodities, a posting for each commodity will be shown, as with the print command. With --interleaved, the equity postings are shown next to the postings they balance, which makes troubleshooting easier. By default, transaction prices in the journal are ignored when generat- ing the closing/opening transactions. With --show-costs, this cost in- formation is preserved (balance -B reports will be unchanged after the transition). Separate postings are generated for each cost in each commodity. Note this can generate very large journal entries, if you have many foreign currency or investment transactions. close usage If you split your journal files by time (eg yearly), you will typically run this command at the end of the year, and save the closing transac- tion as last entry of the old file, and the opening transaction as the first entry of the new file. This makes the files self contained, so that correct balances are reported no matter which of them are loaded. Ie, if you load just one file, the balances are initialised correctly; or if you load several files, the redundant closing/opening transac- tions cancel each other out. (They will show up in print or register reports; you can exclude them with a query like not:desc:'(open- ing|closing) balances'.) If you're running a business, you might also use this command to "close the books" at the end of an accounting period, transferring income statement account balances to retained earnings. (You may want to change the equity account name to something like "equity:retained earn- ings".) By default, the closing transaction is dated yesterday, the balances are calculated as of end of yesterday, and the opening transaction is dated today. To close on some other date, use: hledger close -e OPEN- INGDATE. Eg, to close/open on the 2018/2019 boundary, use -e 2019. You can also use -p or date:PERIOD (any starting date is ignored). Both transactions will include balance assertions for the closed/re- opened accounts. You probably shouldn't use status or realness filters (like -C or -R or status:) with this command, or the generated balance assertions will depend on these flags. Likewise, if you run this com- mand with --auto, the balance assertions will probably always require --auto. Examples: Carrying asset/liability balances into a new file for 2019: $ hledger close -f 2018.journal -e 2019 assets liabilities --open # (copy/paste the output to the start of your 2019 journal file) $ hledger close -f 2018.journal -e 2019 assets liabilities --close # (copy/paste the output to the end of your 2018 journal file) Now: $ hledger bs -f 2019.journal # one file - balances are correct $ hledger bs -f 2018.journal -f 2019.journal # two files - balances still correct $ hledger bs -f 2018.journal not:desc:closing # to see year-end balances, must exclude closing txn Transactions spanning the closing date can complicate matters, breaking balance assertions: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 assets:bank:checking -5 ; [2019/1/2] Here's one way to resolve that: ; in 2018.journal: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 liabilities:pending ; in 2019.journal: 2019/1/2 clearance of last year's pending transactions liabilities:pending 5 = 0 assets:checking codes 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: 1/1 (123) (a) 1 1/1 () (a) 1 1/1 (a) 1 1/1 (126) (a) 1 $ hledger codes 123 124 126 $ hledger codes -E 123 124 126 commodities commodities List all commodity/currency symbols used or declared in the journal. descriptions 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 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 files List all files included in the journal. With a REGEX argument, only file names matching the regular expression (case sensitive) are shown. help help Show any of the hledger manuals. The help command displays any of the main hledger manuals, in one of several ways. Run it with no argument to list the manuals, or provide a full or partial manual name to select one. hledger manuals are available in several formats. hledger help will use the first of these display methods that it finds: info, man, $PAGER, less, stdout (or when non-interactive, just stdout). You can force a particular viewer with the --info, --man, --pager, --cat flags. Examples: $ hledger help Please choose a manual by typing "hledger help MANUAL" (a substring is ok). Manuals: hledger hledger-ui hledger-web journal csv timeclock timedot $ hledger help h --man hledger(1) hledger User Manuals hledger(1) NAME hledger - a command-line accounting tool SYNOPSIS hledger [-f FILE] COMMAND [OPTIONS] [ARGS] hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS] hledger DESCRIPTION hledger is a cross-platform program for tracking money, time, or any ... import import Read new transactions added to each FILE since last run, and add them to the main journal file. Or with --dry-run, just print the transac- tions that would be added. Or with --catchup, just mark all of the FILEs' transactions as imported, without actually importing any. The input files are specified as arguments - no need to write -f before each one. So eg to add new transactions from all CSV files to the main journal, it's just: hledger import *.csv New transactions are detected in the same way as print --new: by assum- ing transactions are always added to the input files in increasing date order, and by saving .latest.FILE state files. The --dry-run output is in journal format, so you can filter it, eg to see only uncategorised transactions: $ hledger import --dry ... | hledger -f- print unknown --ignore-assertions 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.) incomestatement 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. The revenue and expense accounts shown are those accounts declared with the Revenue or Expense type, or otherwise all accounts under a top- level revenue or income or expense account (case insensitive, plurals allowed). Example: $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 With a reporting interval, multiple columns will be shown, one for each report period. Normally incomestatement shows revenues/expenses per period, though as with multicolumn balance reports you can alter the report mode with --change/--cumulative/--historical. Instead of abso- lute values percentages can be displayed with -%. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, html, and (experimen- tal) json. notes 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 payees List the unique payee/payer names that appear in transactions. This command lists the unique payee/payer names that appear in transac- tions, in alphabetic order. You can add a query to select a subset of transactions. The payee/payer is the part of the transaction descrip- tion before a | character (or if there is no |, the whole description). Example: $ hledger payees Store Name Gas Station Person A prices prices Print market price directives from the journal. With --costs, also print synthetic market prices based on transaction prices. With --in- verted-costs, also print inverse prices based on transaction prices. Prices (and postings providing prices) can be filtered by a query. Price amounts are always displayed with their full precision. print print, txns, p Show transaction journal entries, sorted by date. The print command displays full journal entries (transactions) from the journal file in date order, tidily formatted. With --date2, transac- tions are sorted by secondary date instead. print's output is always a valid hledger journal. It preserves all transaction information, but it does not preserve di- rectives or inter-transaction comments $ hledger print 2008/01/01 income assets:bank:checking $1 income:salary $-1 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 2008/12/31 * pay off liabilities:debts $1 assets:bank:checking $-1 Normally, the journal entry's explicit or implicit amount style is pre- served. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, when a transaction price is im- plied but not written, it will not appear in the output. You can use the -x/--explicit flag to make all amounts and transaction prices ex- plicit, which 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. Note, -x/--explicit will cause postings with a multi-commodity amount (these can arise when a multi-commodity transaction has an implicit amount) to be split into multiple single-commodity postings, keeping the output parseable. With -B/--cost, amounts with transaction prices are converted to cost using that price. This can be used for troubleshooting. With -m/--match and a STR argument, print will show at most one trans- action: the one one whose description is most similar to STR, and is most recent. STR should contain at least two characters. If there is no similar-enough match, no transaction will be shown. With --new, for each FILE being read, hledger reads (and writes) a spe- cial state file (.latest.FILE in the same directory), containing the latest transaction date(s) that were seen last time FILE was read. When this file is found, only transactions with newer dates (and new transactions on the latest date) are printed. This is useful for ig- noring already-seen entries in import data, such as downloaded CSV files. Eg: $ hledger -f bank1.csv print --new (shows transactions added since last print --new on this file) This assumes that transactions added to FILE always have same or in- creasing dates, and that transactions on the same day do not get re- ordered. See also the import command. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, and (experimental) json and sql. 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.) print-unique print-unique Print transactions which do not reuse an already-seen description. Example: $ cat unique.journal 1/1 test (acct:one) 1 2/2 test (acct:two) 2 $ LEDGER_FILE=unique.journal hledger print-unique (-f option not supported) 2015/01/01 test (acct:one) 1 register register, reg, r 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. 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. 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, and (experimental) json. register-match register-match Print the one posting whose transaction description is closest to DESC, in the style of the register command. If there are multiple equally good matches, it shows the most recent. Query options (options, not arguments) can be used to restrict the search space. Helps ledger-au- tosync detect already-seen transactions when importing. rewrite 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 roi Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. This command assumes that you have account(s) that hold nothing but your investments and whenever you record current appraisal/valuation of these investments you offset unrealized profit and loss into account(s) that, again, hold nothing but unrealized profit and loss. Any transactions affecting balance of investment account(s) and not originating from unrealized profit and loss account(s) are assumed to be your investments or withdrawals. At a minimum, you need to supply a query (which could be just an ac- count name) to select your investments with --inv, and another query to identify your profit and loss transactions with --pnl. It will compute and display the internalized rate of return (IRR) and time-weighted rate of return (TWR) for your investments for the time period requested. Both rates of return are annualized before display, regardless of the length of reporting interval. stats stats Show some journal 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. Example: $ hledger stats Main journal file : /src/hledger/examples/sample.journal Included journal files : Transactions span : 2008-01-01 to 2009-01-01 (366 days) Last transaction : 2008-12-31 (2333 days ago) 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 : 12 ($) This command also supports output destination and output format selec- tion. tags tags List the unique tag names used in the journal. With a TAGREGEX argu- ment, only tag names matching the regular expression (case insensitive) are shown. With QUERY arguments, only transactions matching the query are considered. With the --values flag, the tags' unique values are listed instead. With --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. test 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). Add-on commands hledger also searches for external add-on commands, and will include these in the commands list. These are programs or scripts in your PATH whose name starts with hledger- and ends with a recognised file exten- sion (currently: no extension, bat,com,exe, hs,lhs,pl,py,rb,rkt,sh). Add-ons can be invoked like any hledger command, but there are a few things to be aware of. Eg if the hledger-web add-on is installed, o hledger -h web shows hledger's help, while hledger web -h shows hledger-web's help. o Flags specific to the add-on must have a preceding -- to hide them from hledger. So hledger web --serve --port 9000 will be rejected; you must use hledger web -- --serve --port 9000. o You can always run add-ons directly if preferred: hledger-web --serve --port 9000. Add-ons are a relatively easy way to add local features or experiment with new ideas. They can be written in any language, but haskell scripts have a big advantage: they can use the same hledger (and haskell) library functions that built-in commands do, for command-line options, journal parsing, reporting, etc. Two important add-ons are the hledger-ui and hledger-web user inter- faces. These are maintained and released along with hledger: ui hledger-ui provides an efficient terminal interface. web hledger-web provides a simple web interface. Third party add-ons, maintained separately from hledger, include: iadd hledger-iadd is a more interactive, terminal UI replacement for the add command. interest hledger-interest generates interest transactions for an account accord- ing to various schemes. A few more experimental or old add-ons can be found in hledger's bin/ directory. These are typically prototypes and not guaranteed to work. ENVIRONMENT LEDGER_FILE The journal file path when not specified with -f. Default: ~/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.jour- nal). A typical value is ~/DIR/YYYY.journal, where DIR is a version-con- trolled finance directory and YYYY is the current year. Or ~/DIR/cur- rent.journal, where current.journal is a symbolic link to YYYY.journal. On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a ~/.MacOSX/en- vironment.plist file containing { "LEDGER_FILE" : "~/finance/current.journal" } To see the effect you may need to killall Dock, or reboot. COLUMNS The screen width used by the register command. Default: the full terminal width. NO_COLOR If this variable exists with any value, hledger will not use ANSI color codes in terminal output. This overrides the --color/--colour option. FILES Reads data from one or more files in hledger journal, timeclock, time- dot, or CSV format specified with -f, or $LEDGER_FILE, or $HOME/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.journal). LIMITATIONS The need to precede addon command options with -- when invoked from hledger is awkward. When input data contains non-ascii characters, a suitable system locale must be configured (or there will be an unhelpful error). Eg on POSIX, set LANG to something other than C. In a Microsoft Windows CMD window, non-ascii characters and colours are not supported. On Windows, non-ascii characters may not display correctly when running a hledger built in CMD in MSYS/CYGWIN, or vice-versa. In a Cygwin/MSYS/Mintty window, the tab key is not supported in hledger add. Not all of Ledger's journal file syntax is supported. See file format differences. On large data files, hledger is slower and uses more memory than Ledger. TROUBLESHOOTING Here are some issues you might encounter when you run hledger (and re- member you can also seek help from the IRC channel, mail list or bug tracker): Successfully installed, but "No command 'hledger' found" stack and cabal install binaries into a special directory, which should be added to your PATH environment variable. Eg on unix-like systems, that is ~/.local/bin and ~/.cabal/bin respectively. I set a custom LEDGER_FILE, but hledger is still using the default file LEDGER_FILE should be a real environment variable, not just a shell variable. The command env | grep LEDGER_FILE should show it. You may need to use export. Here's an explanation. Getting errors like "Illegal byte sequence" or "Invalid or incomplete multibyte or wide character" or "commitAndReleaseBuffer: invalid argu- ment (invalid character)" Programs compiled with GHC (hledger, haskell build tools, etc.) need to have a UTF-8-aware locale configured in the environment, otherwise they will fail with these kinds of errors when they encounter non-ascii characters. To fix it, set the LANG environment variable to some locale which sup- ports UTF-8. The locale you choose must be installed on your system. Here's an example of setting LANG temporarily, on Ubuntu GNU/Linux: $ file my.journal my.journal: UTF-8 Unicode text # the file is UTF8-encoded $ echo $LANG C # LANG is set to the default locale, which does not support UTF8 $ locale -a # which locales are installed ? C en_US.utf8 # here's a UTF8-aware one we can use POSIX $ LANG=en_US.utf8 hledger -f my.journal print # ensure it is used for this command If available, C.UTF-8 will also work. If your preferred locale isn't listed by locale -a, you might need to install it. Eg on Ubuntu/De- bian: $ apt-get install language-pack-fr $ locale -a C en_US.utf8 fr_BE.utf8 fr_CA.utf8 fr_CH.utf8 fr_FR.utf8 fr_LU.utf8 POSIX $ LANG=fr_FR.utf8 hledger -f my.journal print Here's how you could set it permanently, if you use a bash shell: $ echo "export LANG=en_US.utf8" >>~/.bash_profile $ bash --login Exact spelling and capitalisation may be important. Note the differ- ence on MacOS (UTF-8, not utf8). Some platforms (eg ubuntu) allow variant spellings, but others (eg macos) require it to be exact: $ locale -a | grep -iE en_us.*utf en_US.UTF-8 $ LANG=en_US.UTF-8 hledger -f my.journal print REPORTING BUGS Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) AUTHORS Simon Michael and contributors COPYRIGHT Copyright (C) 2007-2019 Simon Michael. Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), hledger-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_time- dot(5), ledger(1) http://hledger.org hledger 1.18.99 September 2020 hledger(1) hledger-1.19.1/hledger.info0000644000000000000000000044153513725533425013717 0ustar0000000000000000This is hledger.info, produced by makeinfo version 6.7 from stdin.  File: hledger.info, Node: Top, Next: COMMON TASKS, Up: (dir) hledger(1) hledger 1.18.99 ************************** hledger - a command-line accounting tool 'hledger [-f FILE] COMMAND [OPTIONS] [ARGS]' 'hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS]' 'hledger' hledger is a reliable, 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). This is hledger's command-line interface (there are also terminal and web interfaces). Its basic function is to read a plain text file describing financial transactions (in accounting terms, a general journal) and print useful reports on standard output, or export them as CSV. hledger can also read some other file formats such as CSV files, translating them to journal format. Additionally, hledger lists other hledger-* executables found in the user's $PATH and can invoke them as subcommands. hledger reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with '-f', or '$LEDGER_FILE', or '$HOME/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal'). If using '$LEDGER_FILE', note this must be a real environment variable, not a shell variable. You can specify standard input with '-f-'. Transactions are dated movements of money between two (or more) named accounts, and are recorded with journal entries like this: 2015/10/16 bought food expenses:food $10 assets:cash For more about this format, see hledger_journal(5). Most users use a text editor to edit the journal, usually with an editor mode such as ledger-mode for added convenience. hledger's interactive add command is another way to record new transactions. hledger never changes existing transactions. To get started, you can either save some entries like the above in '~/.hledger.journal', or run 'hledger add' and follow the prompts. Then try some commands like 'hledger print' or 'hledger balance'. Run 'hledger' with no arguments for a list of commands. * Menu: * COMMON TASKS:: * OPTIONS:: * COMMANDS:: * ENVIRONMENT:: * FILES:: * LIMITATIONS:: * TROUBLESHOOTING::  File: hledger.info, Node: COMMON TASKS, Next: OPTIONS, Prev: Top, Up: Top 1 COMMON TASKS ************** Here are some quick examples of how to do some basic tasks with hledger. For more details, see the reference section below, the hledger_journal(5) manual, or the more extensive docs at https://hledger.org. * Menu: * Getting help:: * Constructing command lines:: * Starting a journal file:: * Setting opening balances:: * Recording transactions:: * Reconciling:: * Reporting:: * Migrating to a new file::  File: hledger.info, Node: Getting help, Next: Constructing command lines, Up: COMMON TASKS 1.1 Getting help ================ $ hledger # show available commands $ hledger --help # show common options $ hledger CMD --help # show common and command options, and command help $ hledger help # show available manuals/topics $ hledger help hledger # show hledger manual as info/man/text (auto-chosen) $ hledger help journal --man # show the journal manual as a man page $ hledger help --help # show more detailed help for the help command Find more docs, chat, mail list, reddit, issue tracker: https://hledger.org#help-feedback  File: hledger.info, Node: Constructing command lines, Next: Starting a journal file, Prev: Getting help, Up: COMMON TASKS 1.2 Constructing command lines ============================== hledger has an extensive and powerful command line interface. We strive to keep it simple and ergonomic, but you may run into one of the confusing real world details described in OPTIONS, below. If that happens, here are some tips that may help: * command-specific options must go after the command (it's fine to put all options there) ('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 is being parsed, add '--debug=2'.  File: hledger.info, Node: Starting a journal file, Next: Setting opening balances, Prev: Constructing command lines, Up: COMMON TASKS 1.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. 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 2020.journal $ echo "export LEDGER_FILE=$HOME/finance/2020.journal" >> ~/.bashrc $ source ~/.bashrc $ hledger stats Main file : /Users/simon/finance/2020.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 opening balances, Next: Recording transactions, Prev: Starting a journal file, Up: COMMON TASKS 1.4 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: 2020-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/2020.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 [2020-02-07]: 2020-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): . 2020-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 [2020-01-01]: . If you're using version control, this could be a good time to commit the journal. Eg: $ git commit -m 'initial balances' 2020.journal  File: hledger.info, Node: Recording transactions, Next: Reconciling, Prev: Setting opening balances, Up: COMMON TASKS 1.5 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: 2020/1/10 * gift received assets:cash $20 income:gifts 2020.1.12 * farmers market expenses:food $13 assets:cash 2020-01-15 paycheck income:salary assets:bank:checking $1000  File: hledger.info, Node: Reconciling, Next: Reporting, Prev: Recording transactions, Up: COMMON TASKS 1.6 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: 2020-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 '2020-01-15' and 'paycheck' If you're using version control, this can be another good time to commit: $ git commit -m 'txns' 2020.journal  File: hledger.info, Node: Reporting, Next: Migrating to a new file, Prev: Reconciling, Up: COMMON TASKS 1.7 Reporting ============= Here are some basic reports. Show all transactions: $ hledger print 2020-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 2020-01-10 * gift received assets:cash $20 income:gifts 2020-01-12 * farmers market expenses:food $13 assets:cash 2020-01-15 * paycheck income:salary assets:bank:checking $1000 2020-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 --flat -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 --flat -2 Balance Sheet 2020-01-16 || 2020-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 2020-01-01-2020-01-16 || 2020-01-01-2020-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 2020-01-01 opening balances assets:cash $100 $100 2020-01-10 gift received assets:cash $20 $120 2020-01-12 farmers market assets:cash $-13 $107 2020-01-16 adjust cash assets:cash $-2 $105 Show weekly posting counts as a bar chart: $ hledger activity -W 2019-12-30 ***** 2020-01-06 **** 2020-01-13 ****  File: hledger.info, Node: Migrating to a new file, Prev: Reporting, Up: COMMON TASKS 1.8 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: OPTIONS, Next: COMMANDS, Prev: COMMON TASKS, Up: Top 2 OPTIONS ********* * Menu: * General options:: * Command options:: * Command arguments:: * Queries:: * Special characters in arguments and queries:: * Unicode characters:: * Input files:: * Output destination:: * Output format:: * Regular expressions:: * Smart dates:: * Report start & end date:: * Report intervals:: * Period expressions:: * Depth limiting:: * Pivoting:: * Valuation::  File: hledger.info, Node: General options, Next: Command options, Up: OPTIONS 2.1 General options =================== To see general usage help, including general options which are supported by most hledger commands, run 'hledger -h'. General help options: '-h --help' show general usage (or after COMMAND, command usage) '--version' show 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 '--anon' anonymize accounts and payees '--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) General reporting options: '-b --begin=DATE' include postings/txns on or after this date '-e --end=DATE' include postings/txns before this date '-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) '-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-value' with -V/-X/-value, also infer market prices from transactions '--auto' apply automated posting rules to modify transactions. '--forecast' generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. '--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. 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 options, Next: Command arguments, Prev: General options, Up: OPTIONS 2.2 Command options =================== To see options for a particular command, including command-specific options, run: 'hledger COMMAND -h'. Command-specific options must be written after the command name, eg: 'hledger print -x'. Additionally, if the command is an addon, you may need to put its options after a double-hyphen, eg: 'hledger ui -- --watch'. Or, you can run the addon executable directly: 'hledger-ui --watch'.  File: hledger.info, Node: Command arguments, Next: Queries, Prev: Command options, Up: OPTIONS 2.3 Command arguments ===================== Most hledger commands accept arguments after the command name, which are often a query, filtering the data in some way. You can save a set of command line options/arguments in a file, and then reuse them by writing '@FILENAME' as a command line argument. Eg: 'hledger bal @foo.args'. (To prevent this, eg if you have an argument that begins with a literal '@', precede it with '--', eg: 'hledger bal -- @ARG'). Inside the argument file, each line should contain just one option or argument. Avoid the use of spaces, except inside quotes (or you'll see a confusing error). Between a flag and its argument, use = (or nothing). Bad: assets depth:2 -X USD Good: assets depth:2 -X=USD For special characters (see below), use one less level of quoting than you would at the command prompt. Bad: -X"$" Good: -X$ See also: Save frequently used options.  File: hledger.info, Node: Queries, Next: Special characters in arguments and queries, Prev: Command arguments, Up: OPTIONS 2.4 Queries =========== One of hledger's strengths is being able to quickly report on precise subsets of your data. Most commands accept an optional query expression, written as arguments after the command name, to filter the data by date, account name or other criteria. The syntax is similar to a web search: one or more space-separated search terms, quotes to enclose whitespace, prefixes to match specific fields, a not: prefix to negate the match. We do not yet support arbitrary boolean combinations of search terms; instead most commands show transactions/postings/accounts which match (or negatively 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 instead shows 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. The following kinds of search terms can be used. Remember these can also be prefixed with *'not:'*, eg to exclude a particular subaccount. *'REGEX', 'acct:REGEX'* match account names by this regular expression. (With no prefix, 'acct:' is assumed.) same as above *'amt:N, amt:N, amt:>=N'* match postings with a single-commodity amount that is equal to, less than, or greater than N. (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 characters which are regex-significant, like the dollar sign ('$'), you need to prepend '\'. And when using the command line you need to add one more level of quoting to hide it from the shell, so eg do: 'hledger print cur:'\$'' or 'hledger print cur:\\$'. *'desc:REGEX'* match transaction descriptions. *'date:PERIODEXPR'* match dates within the specified period. PERIODEXPR is a period expression (with no report interval). Examples: 'date:2016', 'date:thismonth', 'date:2000/2/1-2/15', 'date:lastweek-'. If the '--date2' command line flag is present, this matches secondary dates instead. *'date2:PERIODEXPR'* match secondary dates within the specified period. *'depth:N'* match (or display, depending on command) accounts at or above this depth *'note:REGEX'* match transaction notes (part of description right of '|', or whole description when there's no '|') *'payee:REGEX'* match transaction payee/payer names (part of description left of '|', or whole description when there's no '|') *'real:, real:0'* match real or virtual postings respectively *'status:, status:!, status:*'* match unmarked, pending, or cleared transactions respectively *'tag:REGEX[=REGEX]'* match by tag name, and optionally also by tag value. Note a tag: query is considered to match a transaction if it matches any of the postings. Also remember that postings inherit the tags of their parent transaction. The following special search term is used automatically in hledger-web, only: *'inacct:ACCTNAME'* tells hledger-web to show the transaction register for this account. Can be filtered further with 'acct' etc. Some of these can also be expressed as command-line options (eg 'depth:2' is equivalent to '--depth 2'). Generally you can mix options and query arguments, and the resulting query will be their intersection (perhaps excluding the '-p/--period' option).  File: hledger.info, Node: Special characters in arguments and queries, Next: Unicode characters, Prev: Queries, Up: OPTIONS 2.5 Special characters in arguments and queries =============================================== In shell command lines, option and argument values which contain "problematic" characters, ie spaces, and also characters significant to your shell such as '<', '>', '(', ')', '|' and '$', should be escaped by enclosing them in quotes or by writing backslashes before the characters. Eg: 'hledger register -p 'last year' "accounts receivable (receivable|payable)" amt:\>100'. * Menu: * More escaping:: * Even more escaping:: * Less escaping::  File: hledger.info, Node: More escaping, Next: Even more escaping, Up: Special characters in arguments and queries 2.5.1 More escaping ------------------- Characters significant both to the shell and in regular expressions may need one extra level of escaping. These include parentheses, the pipe symbol and the dollar sign. Eg, to match the dollar symbol, bash users should do: 'hledger balance cur:'\$'' or: 'hledger balance cur:\\$'  File: hledger.info, Node: Even more escaping, Next: Less escaping, Prev: More escaping, Up: Special characters in arguments and queries 2.5.2 Even more escaping ------------------------ When hledger runs an addon executable (eg you type 'hledger ui', hledger runs 'hledger-ui'), it de-escapes command-line options and arguments once, so you might need to _triple_-escape. Eg in bash, running the ui command and matching the dollar sign, it's: 'hledger ui cur:'\\$'' or: 'hledger ui cur:\\\\$' If you asked why _four_ slashes above, this may help: unescaped: '$' escaped: '\$' double-escaped: '\\$' triple-escaped: '\\\\$' (The number of backslashes in fish shell is left as an exercise for the reader.) You can always avoid the extra escaping for addons by running the addon directly: 'hledger-ui cur:\\$'  File: hledger.info, Node: Less escaping, Prev: Even more escaping, Up: Special characters in arguments and queries 2.5.3 Less escaping ------------------- Inside an argument file, or in the search field of hledger-ui or hledger-web, or at a GHCI prompt, you need one less level of escaping than at the command line. And backslashes may work better than quotes. Eg: 'ghci> :main balance cur:\$'  File: hledger.info, Node: Unicode characters, Next: Input files, Prev: Special characters in arguments and queries, Up: OPTIONS 2.6 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: Input files, Next: Output destination, Prev: Unicode characters, Up: OPTIONS 2.7 Input files =============== hledger reads transactions from a data file (and the add command writes to it). By default this file is '$HOME/.hledger.journal' (or on Windows, something like 'C:/Users/USER/.hledger.journal'). You can override this with the '$LEDGER_FILE' environment variable: $ setenv LEDGER_FILE ~/finance/2016.journal $ hledger stats or with the '-f/--file' option: $ hledger -f /some/file stats The file name '-' (hyphen) means standard input: $ cat some.journal | hledger -f- 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 Ledger '.journal' '.j' journals, for transactions '.hledger' '.ledger' 'timeclock'timeclock files, for precise time '.timeclock' logging 'timedot'timedot files, for approximate time '.timedot' logging 'csv' comma/semicolon/tab/other-separated '.csv' '.ssv' '.tsv' values, for data import 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. When you can't ensure the right file extension, not to worry: you can force a specific reader/format by prefixing the file path with the format and a colon. Eg to read a .dat file as csv: $ hledger -f csv:/some/csv-file.dat stats $ echo 'i 2009/13/1 08:00:00' | hledger print -ftimeclock:- You can specify multiple '-f' options, to read multiple files as one big journal. There are some limitations with this: * directives in one file will not affect the other files * balance assertions will not see any account balances from previous files If you need either of those things, you can * use a single parent file which includes the others * or concatenate the files into one before reading, eg: 'cat a.journal b.journal | hledger -f- CMD'.  File: hledger.info, Node: Output destination, Next: Output format, Prev: Input files, Up: OPTIONS 2.8 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: Regular expressions, Prev: Output destination, Up: OPTIONS 2.9 Output format ================= Some commands (print, register, the balance commands) offer a choice of output format. In addition to the usual plain text format ('txt'), there are CSV ('csv'), HTML ('html'), JSON ('json') and SQL ('sql'). This is controlled by the '-O/--output-format' option: $ hledger print -O csv or, by a file extension specified with '-o/--output-file': $ hledger balancesheet -o foo.html # write HTML to foo.html The '-O' option can be used to override the file extension if needed: $ hledger balancesheet -o foo.txt -O html # write HTML to foo.txt Some notes about JSON output: * This feature is marked experimental, and not yet much used; you should expect our JSON to evolve. Real-world feedback is welcome. * Our JSON is rather large and verbose, as it is quite 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) Notes about SQL output: * SQL output is also marked experimental, and much like JSON could use real-world feedback. * SQL output is expected to work with sqlite, MySQL and PostgreSQL * 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: Regular expressions, Next: Smart dates, Prev: Output format, Up: OPTIONS 2.10 Regular expressions ======================== hledger uses regular expressions in a number of places: * query terms, on the command line and in the hledger-web search form: 'REGEX', 'desc:REGEX', 'cur:REGEX', 'tag:...=REGEX' * CSV rules conditional blocks: 'if REGEX ...' * account alias directives and options: 'alias /REGEX/ = REPLACEMENT', '--alias /REGEX/=REPLACEMENT' 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. they do not support backreferences; if you write '\1', it will match the digit '1'. Except when doing text replacement, eg in account aliases, where backreferences can be used in the replacement string to reference capturing groups in the search regexp. 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: Smart dates, Next: Report start & end date, Prev: Regular expressions, Up: OPTIONS 2.11 Smart dates ================ hledger's user interfaces accept a flexible "smart date" syntax (unlike dates in the journal file). Smart dates allow some english words, can be relative to today's date, and can have less-significant date parts omitted (defaulting to 1). 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' '20181201' 8 digit YYYYMMDD with valid year month and day '201812' 6 digit YYYYMM with valid year and month 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  File: hledger.info, Node: Report start & end date, Next: Report intervals, Prev: Smart dates, Up: OPTIONS 2.12 Report start & end date ============================ Most hledger reports show the full span of time represented by the journal data, by default. So, the effective report start and end dates will be the earliest and latest transaction or posting dates found in the journal. 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. Some notes: * As in Ledger, end dates are exclusive, so you need to write the date _after_ the last day you want to include. * 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. 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: Report intervals, Next: Period expressions, Prev: Report start & end date, Up: OPTIONS 2.13 Report intervals ===================== A report interval can be specified so that commands like register, balance and activity will divide their reports into multiple subperiods. The basic intervals can be selected with one of '-D/--daily', '-W/--weekly', '-M/--monthly', '-Q/--quarterly', or '-Y/--yearly'. More complex intervals may be specified with a period expression. Report intervals can not be specified with a query.  File: hledger.info, Node: Period expressions, Next: Depth limiting, Prev: Report intervals, Up: OPTIONS 2.14 Period expressions ======================= The '-p/--period' option accepts period expressions, a shorthand way of expressing a start date, end date, and/or report interval all at once. Here's a basic period expression specifying the first quarter of 2009. Note, hledger always treats start dates as inclusive and end dates as exclusive: '-p "from 2009/1/1 to 2009/4/1"' Keywords like "from" and "to" are optional, and so are the spaces, as long as you don't run two dates together. "to" can also be written as ".." or "-". These 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, the above can also be written as: '-p "1/1 4/1"' '-p "january-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 in your journal: '-p "from 2009/1/1"' everything after january 1, 2009 '-p "from 2009/1"' the same '-p "from 2009"' the same '-p "to 2009"' everything before january 1, 2009 A single date with no "from" or "to" defines both the start and end date like so: '-p "2009"' the year 2009; equivalent to “2009/1/1 to 2010/1/1” '-p "2009/1"' the month of jan; equivalent to “2009/1/1 to 2009/2/1” '-p "2009/1/1"' just that day; equivalent to “2009/1/1 to 2009/1/2” Or you can specify a single quarter like so: '-p "2009Q1"' first quarter of 2009, equivalent to “2009/1/1 to 2009/4/1” '-p "q4"' fourth quarter of the current year The argument of '-p' can also begin with, or be, a report interval expression. The basic report intervals are 'daily', 'weekly', 'monthly', 'quarterly', or 'yearly', which have the same effect as the '-D','-W','-M','-Q', or '-Y' flags. Between report interval and start/end dates (if any), the word 'in' is optional. Examples: '-p "weekly from 2009/1/1 to 2009/4/1"' '-p "monthly in 2008"' '-p "quarterly"' Note that 'weekly', 'monthly', 'quarterly' and 'yearly' intervals will always start on the first day on week, month, quarter or year accordingly, and will end on the last day of same period, even if associated period expression specifies different explicit start and end date. For example: '-p "weekly from starts on 2008/12/29, closest preceding 2009/1/1 to 2009/4/1"' Monday '-p "monthly in starts on 2018/11/01 2008/11/25"' '-p "quarterly from starts on 2009/04/01, ends on 2009/06/30, 2009-05-05 to which are first and last days of Q2 2009 2009-06-01"' '-p "yearly from starts on 2009/01/01, first day of 2009 2009-12-29"' The following more complex report intervals are also supported: 'biweekly', 'fortnightly', 'bimonthly', 'every day|week|month|quarter|year', 'every N days|weeks|months|quarters|years'. All of these will start on the first day of the requested period and end on the last one, as described above. Examples: '-p "bimonthly from periods will have boundaries on 2008/01/01, 2008"' 2008/03/01, ... '-p "every 2 weeks"' starts on closest preceding Monday '-p "every 5 month from periods will have boundaries on 2009/03/01, 2009/03"' 2009/08/01, ... If you want intervals that start on arbitrary day of your choosing and span a week, month or year, you need to use any of the following: 'every Nth day of week', 'every ', 'every Nth day [of month]', 'every Nth weekday [of month]', 'every MM/DD [of year]', 'every Nth MMM [of year]', 'every MMM Nth [of year]'. Examples: '-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 period boundaries will be on second Monday of Monday"' each month '-p "every 11/05"' yearly periods with boundaries on 5th of Nov '-p "every 5th Nov"' same '-p "every Nov 5th"' same Show historical balances at end of 15th each month (N is exclusive end date): 'hledger balance -H -p "every 16th day"' Group postings from start of wednesday to end of next tuesday (N is start date and exclusive end date): 'hledger register checking -p "every 3rd day of week"'  File: hledger.info, Node: Depth limiting, Next: Pivoting, Prev: Period expressions, Up: OPTIONS 2.15 Depth limiting =================== With the '--depth N' option (short form: '-N'), commands like account, balance and register will show only the uppermost accounts in the account tree, down to level N. Use this when you want a summary with less detail. This flag has the same effect as a 'depth:' query argument (so '-2', '--depth=2' or 'depth:2' are equivalent).  File: hledger.info, Node: Pivoting, Next: Valuation, Prev: Depth limiting, Up: OPTIONS 2.16 Pivoting ============= Normally hledger sums amounts, and organizes them in a hierarchy, based on account name. The '--pivot FIELD' option causes it to sum and organize hierarchy based on the value of some other field instead. FIELD can be: 'code', 'description', 'payee', 'note', or the full name (case insensitive) of any tag. As with account names, values containing 'colon:separated:parts' will be displayed hierarchically in reports. '--pivot' is a general option affecting all reports; you can think of hledger transforming the journal before any other processing, replacing every posting's account name with the value of the specified field on that posting, inheriting it from the transaction or using a blank value if it's not present. An example: 2016/02/16 Member Fee Payment assets:bank account 2 EUR income:member fees -2 EUR ; member: John Doe Normal balance report showing account names: $ hledger balance 2 EUR assets:bank account -2 EUR income:member fees -------------------- 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, described below): $ 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  File: hledger.info, Node: Valuation, Prev: Pivoting, Up: OPTIONS 2.17 Valuation ============== Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), or to market value (using some market price on a certain date). This is controlled by the '--value=TYPE[,COMMODITY]' option, but we also provide the simpler '-B'/'-V'/'-X' flags, and usually one of those is all you need. * Menu: * -B Cost:: * -V Value:: * -X Value in specified commodity:: * Valuation date:: * Market prices:: * --infer-value market prices from transactions:: * Valuation commodity:: * Simple valuation examples:: * --value Flexible valuation:: * More valuation examples:: * Effect of valuation on reports::  File: hledger.info, Node: -B Cost, Next: -V Value, Up: Valuation 2.17.1 -B: Cost --------------- The '-B/--cost' flag converts amounts to their cost or sale amount at transaction time, if they have a transaction price specified.  File: hledger.info, Node: -V Value, Next: -X Value in specified commodity, Prev: -B Cost, Up: Valuation 2.17.2 -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: Valuation 2.17.3 -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: Market prices, Prev: -X Value in specified commodity, Up: Valuation 2.17.4 Valuation date --------------------- Since market prices can change from day to day, market value reports have a valuation date (or more than one), which determines which market prices will be used. For single period reports, if an explicit report end date is specified, that will be used as the valuation date; otherwise the valuation date is "today". For multiperiod reports, each column/period is valued on the last day of the period.  File: hledger.info, Node: Market prices, Next: --infer-value market prices from transactions, Prev: Valuation date, Up: Valuation 2.17.5 Market prices -------------------- _(experimental)_ 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 (if the '--infer-value' flag is used) inferred from transaction prices. 2. A _reverse market price_: the inverse of a declared or inferred market price from B to A. 3. A _chained market price_: a synthetic price formed by combining the shortest chain of market prices (any of the above types) leading from A to B. Amounts for which no applicable market price can be found, are not converted.  File: hledger.info, Node: --infer-value market prices from transactions, Next: Valuation commodity, Prev: Market prices, Up: Valuation 2.17.6 -infer-value: market prices from transactions ---------------------------------------------------- _(experimental)_ 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 transaction prices as additional market prices (as Ledger does) ? We could produce value reports without needing P directives at all. Adding the '--infer-value' flag to '-V', '-X' or '--value' enables this. So for example, 'hledger bs -V --infer-value' will get market prices both from P directives and from transactions. 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 Valuation section carefully, and try adding '--debug' or '--debug=2' to troubleshoot. '--infer-value' 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.) * but not, currently, from "more correct" multicommodity transactions (no '@', multiple commodities, balanced).  File: hledger.info, Node: Valuation commodity, Next: Simple valuation examples, Prev: --infer-value market prices from transactions, Up: Valuation 2.17.7 Valuation commodity -------------------------- _(experimental)_ *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-value' 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-value' flag, transaction prices 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: Valuation 2.17.8 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: Valuation 2.17.9 -value: Flexible valuation --------------------------------- '-B', '-V' and '-X' are special cases of the more general '--value' option: --value=TYPE[,COMM] TYPE is cost, then, end, now or YYYY-MM-DD. COMM is an optional commodity symbol. Shows amounts converted to: - cost commodity using transaction prices (then optionally to COMM using market prices at period end(s)) - 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=cost' Convert amounts to cost, using the prices recorded in transactions. '--value=then' Convert amounts to their value in the default valuation commodity, using market prices on each posting's date. This is currently supported only by the print and register commands. '--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: Effect of valuation on reports, Prev: --value Flexible valuation, Up: Valuation 2.17.10 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 --value=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 You may need to explicitly set a commodity's display style, when reverse prices are used. Eg this output might be surprising: P 2000-01-01 A 2B 2000-01-01 a 1B b $ hledger print -x -X A 2000-01-01 a 0 b 0 Explanation: because there's no amount or commodity directive specifying a display style for A, 0.5A gets the default style, which shows no decimal digits. Because the displayed amount looks like zero, the commodity symbol and minus sign are not displayed either. Adding a commodity directive sets a more useful display style for A: P 2000-01-01 A 2B commodity 0.00A 2000-01-01 a 1B b $ hledger print -X A 2000-01-01 a 0.50A b -0.50A  File: hledger.info, Node: Effect of valuation on reports, Prev: More valuation examples, Up: Valuation 2.17.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 '--value=cost' '--value=now' ------------------------------------------------------------------------------- *print* posting cost value at value at value at value at amounts report end posting date report or DATE/today or today journal end balance unchanged unchanged unchanged unchanged unchanged assertions / assignments *register* starting cost value at not value at value at balance day before supported day before DATE/today (with -H) report or report or journal journal start start posting cost value at value at value at value at amounts report end posting date report or DATE/today (no report or today journal end interval) summary summarised value at sum of value at value at posting cost period postings in period ends DATE/today amounts ends interval, (with valued at report interval interval) start running sum/average sum/average sum/average sum/average sum/average total/averageof of of displayed of of displayed displayed values displayed displayed values values values values *balance (bs, bse, cf, is..)* balances sums of value at not value at value at (no report costs report end supported report or DATE/today interval) or today journal end of sums of sums of of sums of of postings postings postings balances sums of value at not value at value at (with costs period supported period ends DATE/today report ends of of sums of of sums interval) sums of postings of postings postings starting sums of sums of not sums of sums of balances costs of postings supported postings postings (with postings before before before report before report report report interval report start start start and -H) start budget like like not like like amounts balances balances supported balances balances with -budget grand sum of sum of not sum of sum of total (no displayed displayed supported displayed displayed report values values values values interval) row sums/averagessums/averagesnot sums/averages sums/averages totals/averagesof of supported of of (with displayed displayed displayed displayed report values values values values interval) column sums of sums of not sums of sums of totals displayed displayed supported displayed displayed values values values values grand sum/average sum/average not sum/average sum/average total/averageof column of column supported of column of totals totals totals column totals *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: COMMANDS, Next: ENVIRONMENT, Prev: OPTIONS, Up: Top 3 COMMANDS ********** hledger provides a number of subcommands; 'hledger' with no arguments shows a list. If you install additional 'hledger-*' packages, or if you put programs or scripts named 'hledger-NAME' in your PATH, these will also be listed as subcommands. Run a subcommand by writing its name as first argument (eg 'hledger incomestatement'). You can also write one of the standard short aliases displayed in parentheses in the command list ('hledger b'), or any any unambiguous prefix of a command name ('hledger inc'). Here are all the builtin commands in alphabetical order. See also 'hledger' for a more organised command list, and 'hledger CMD -h' for detailed command help. * Menu: * accounts:: * activity:: * add:: * aregister:: * balance:: * balancesheet:: * balancesheetequity:: * cashflow:: * check-dates:: * check-dupes:: * close:: * codes:: * commodities:: * descriptions:: * diff:: * files:: * help:: * import:: * incomestatement:: * notes:: * payees:: * prices:: * print:: * print-unique:: * register:: * register-match:: * rewrite:: * roi:: * stats:: * tags:: * test:: * Add-on commands::  File: hledger.info, Node: accounts, Next: activity, Up: COMMANDS 3.1 accounts ============ accounts, a Show account names. This command lists account names, either declared with account directives (-declared), posted to (-used), or both (the default). With query arguments, only matched account names and account names referenced by matched postings are shown. 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'. Examples: $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts  File: hledger.info, Node: activity, Next: add, Prev: accounts, Up: COMMANDS 3.2 activity ============ 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: COMMANDS 3.3 add ======= 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 journal file (if there are multiple '-f FILE' options, the first file is used.) Existing transactions are not changed. This is the only hledger command that writes to the journal file. 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, 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 the tutorial for a detailed explanation): $ 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: COMMANDS 3.4 aregister ============= aregister, areg Show transactions affecting a particular account, and the account's running balance. 'aregister' shows the transactions affecting a particular account (and its subaccounts), from the point of view of that account. Each line shows: * the transaction's (or posting's, see below) date * the names of the other account(s) involved * the net change to this account's balance * the account's historical running balance (including balance from transactions before the report start date). With 'aregister', each line represents a whole transaction - as in hledger-ui, hledger-web, and your bank statement. By contrast, the 'register' command shows individual postings, across all accounts. You might prefer 'aregister' for reconciling with real-world asset/liability accounts, and 'register' for reviewing detailed revenues/expenses. An account must be specified as the first argument, which should be the full account name or an account pattern (regular expression). aregister will show transactions in this account (the first one matched) and any of its subaccounts. Any additional arguments form a query which will filter the transactions shown. Transactions making a net change of zero are not shown by default; add the '-E/--empty' flag to show them. * Menu: * aregister and custom posting dates:: * Output format::  File: hledger.info, Node: aregister and custom posting dates, Next: , Up: aregister 3.4.1 aregister and custom posting dates ---------------------------------------- Transactions whose date is outside the report period can still be shown, if they have a posting to this account dated inside the report period. (And in this case it's the posting date that is shown.) This ensures that 'aregister' can show an accurate historical running balance, matching the one shown by 'register -H' with the same arguments. To filter strictly by transaction date instead, add the '--txn-dates' flag. If you use this flag and some of your postings have custom dates, it's probably best to assume the running balance is wrong. 3.4.2 Output format ------------------- This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', and 'json'. Examples: Show all transactions and historical running balance in the first account whose name contains "checking": $ hledger areg checking Show transactions and historical running balance in all asset accounts during july: $ hledger areg assets date:jul  File: hledger.info, Node: balance, Next: balancesheet, Prev: aregister, Up: COMMANDS 3.5 balance =========== balance, bal, b Show accounts and their balances. The balance command is hledger's most versatile command. Note, despite the name, it is not always used for showing real-world account balances; the more accounting-aware balancesheet and incomestatement may be more convenient for that. By default, it displays all accounts, and each account's change in balance during the entire period of the journal. Balance changes are calculated by adding up the postings in each account. You can limit the postings matched, by a query, to see fewer accounts, changes over a different time period, changes from only cleared transactions, etc. If you include an account's complete history of postings in the report, the balance change is equivalent to the account's current ending balance. For a real-world account, typically you won't have all transactions in the journal; instead you'll have all transactions after a certain date, and an "opening balances" transaction setting the correct starting balance on that date. Then the balance command will show real-world account balances. In some cases the -H/-historical flag is used to ensure this (more below). The balance command can produce several styles of report: * Menu: * Classic balance report:: * Customising the classic balance report:: * Colour support:: * Flat mode:: * Depth limited balance reports:: * Percentages:: * Multicolumn balance report:: * Budget report:: * Output format::  File: hledger.info, Node: Classic balance report, Next: Customising the classic balance report, Up: balance 3.5.1 Classic balance report ---------------------------- This is the original balance report, as found in Ledger. It usually looks like this: $ hledger balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 By default, accounts are displayed hierarchically, with subaccounts indented below their parent. At each level of the tree, accounts are sorted by account code if any, then by account name. Or with '-S/--sort-amount', by their balance amount, largest first. "Boring" accounts, which contain a single interesting subaccount and no balance of their own, are elided into the following line for more compact output. (Eg above, the "liabilities" account.) Use '--no-elide' to prevent this. Account balances are "inclusive" - they include the balances of any subaccounts. Accounts which have zero balance (and no non-zero subaccounts) are omitted. Use '-E/--empty' to show them. A final total is displayed by default; use '-N/--no-total' to suppress it, eg: $ hledger balance -p 2008/6 expenses --no-total $2 expenses $1 food $1 supplies  File: hledger.info, Node: Customising the classic balance report, Next: Colour support, Prev: Classic balance report, Up: balance 3.5.2 Customising the classic balance report -------------------------------------------- You can customise the layout of classic balance reports with '--format FMT': $ hledger 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 (plus a newline) 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: Colour support, Next: Flat mode, Prev: Customising the classic balance report, Up: balance 3.5.3 Colour support -------------------- In terminal output, when colour is enabled, the balance command shows negative amounts in red.  File: hledger.info, Node: Flat mode, Next: Depth limited balance reports, Prev: Colour support, Up: balance 3.5.4 Flat mode --------------- To see a flat list instead of the default hierarchical display, use '--flat'. In this mode, accounts (unless depth-clipped) show their full names and "exclusive" balance, excluding any subaccount balances. In this mode, you can also use '--drop N' to omit the first few account name components. $ hledger balance -p 2008/6 expenses -N --flat --drop 1 $1 food $1 supplies  File: hledger.info, Node: Depth limited balance reports, Next: Percentages, Prev: Flat mode, Up: balance 3.5.5 Depth limited balance reports ----------------------------------- With '--depth N' or 'depth:N' or just '-N', balance reports show accounts only to the specified numeric depth. This is very useful to summarise a complex set of accounts and get an overview. $ hledger balance -N -1 $-1 assets $2 expenses $-2 income $1 liabilities Flat-mode balance reports, which normally show exclusive balances, show inclusive balances at the depth limit.  File: hledger.info, Node: Percentages, Next: Multicolumn balance report, Prev: Depth limited balance reports, Up: balance 3.5.6 Percentages ----------------- With '-%' or '--percent', balance reports show each account's value expressed as a percentage of the column's total. This is useful to get an overview of the relative sizes of account balances. For example to obtain an overview of expenses: $ hledger balance expenses -% 100.0 % expenses 50.0 % food 50.0 % supplies -------------------- 100.0 % Note that '--tree' does not have an effect on '-%'. The percentages are always relative to the total sum of each column, they are never relative to the parent account. Since the percentages are relative to the columns sum, it is usually not useful to calculate percentages if the signs of the amounts are mixed. Although the results are technically correct, they are most likely useless. Especially in a balance report that sums up to zero (eg 'hledger balance -B') all percentage values will be zero. This flag does not work if the report contains any mixed commodity accounts. If there are mixed commodity accounts in the report be sure to use '-V' or '-B' to coerce the report into using a single commodity.  File: hledger.info, Node: Multicolumn balance report, Next: Budget report, Prev: Percentages, Up: balance 3.5.7 Multicolumn balance report -------------------------------- Multicolumn or tabular balance reports are a very useful hledger feature, and usually the preferred style. They share many of the above features, but they show the report as a table, with columns representing time periods. This mode is activated by providing a reporting interval. There are three types of multicolumn balance report, showing different information: 1. By default: each column shows the sum of postings in that period, ie the account's change of balance in that period. This is useful eg for a monthly income statement: $ hledger balance --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 2. With '--cumulative': each column shows the ending balance for that period, accumulating the changes across periods, starting from 0 at the report start date: $ hledger balance --quarterly income expenses -E --cumulative Ending balances (cumulative) in 2008: || 2008/03/31 2008/06/30 2008/09/30 2008/12/31 ===================++================================================= expenses:food || 0 $1 $1 $1 expenses:supplies || 0 $1 $1 $1 income:gifts || 0 $-1 $-1 $-1 income:salary || $-1 $-1 $-1 $-1 -------------------++------------------------------------------------- || $-1 0 0 0 3. With '--historical/-H': each column shows the actual historical ending balance for that period, accumulating the changes across periods, starting from the actual balance at the report start date. This is useful eg for a multi-period balance sheet, and when you are showing only the data after a certain start date: $ hledger balance ^assets ^liabilities --quarterly --historical --begin 2008/4/1 Ending balances (historical) in 2008/04/01-2008/12/31: || 2008/06/30 2008/09/30 2008/12/31 ======================++===================================== assets:bank:checking || $1 $1 0 assets:bank:saving || $1 $1 $1 assets:cash || $-2 $-2 $-2 liabilities:debts || 0 0 $1 ----------------------++------------------------------------- || 0 0 0 Note that '--cumulative' or '--historical/-H' disable '--row-total/-T', since summing end balances generally does not make sense. Multicolumn balance reports display accounts in flat mode by default; to see the hierarchy, use '--tree'. With a reporting interval (like '--quarterly' above), the report start/end dates will be adjusted if necessary so that they encompass the displayed report periods. This is so that the first and last periods will be "full" and comparable to the others. The '-E/--empty' flag does two things in multicolumn balance reports: first, the report will show all columns within the specified report period (without -E, leading and trailing columns with all zeroes are not shown). Second, all accounts which existed at the report start date will be considered, not just the ones with activity during the report period (use -E to include low-activity accounts which would otherwise would be omitted). The '-T/--row-total' flag adds an additional column showing the total for each row. The '-A/--average' flag adds a column showing the average value in each row. Here's an example of all three: $ hledger balance -Q income expenses --tree -ETA Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 Total Average ============++=================================================== expenses || 0 $2 0 0 $2 $1 food || 0 $1 0 0 $1 0 supplies || 0 $1 0 0 $1 0 income || $-1 $-1 0 0 $-2 $-1 gifts || 0 $-1 0 0 $-1 0 salary || $-1 0 0 0 $-1 0 ------------++--------------------------------------------------- || $-1 $1 0 0 0 0 (Average is rounded to the dollar here since all journal amounts are) The '--transpose' flag can be used to exchange the rows and columns of a multicolumn report. When showing multicommodity amounts, multicolumn balance reports will elide any amounts which have more than two commodities, since otherwise columns could get very wide. The '--no-elide' flag disables this. Hiding totals with the '-N/--no-total' flag can also help reduce the width of multicommodity reports. When the report is still too wide, a good workaround is to pipe it into 'less -RS' (-R for colour, -S to chop long lines). Eg: 'hledger bal -D --color=yes | less -RS'.  File: hledger.info, Node: Budget report, Next: , Prev: Multicolumn balance report, Up: balance 3.5.8 Budget report ------------------- With '--budget', extra columns are displayed showing budget goals for each account and period, if any. Budget goals are defined by periodic transactions. This is very useful for comparing planned and actual income, expenses, time usage, etc. -budget is most often combined with a report interval. For example, you can take average monthly expenses in the common expense categories to construct a minimal monthly budget: ;; Budget ~ monthly income $2000 expenses:food $400 expenses:bus $50 expenses:movies $30 assets:bank:checking ;; Two months worth of expenses 2017-11-01 income $1950 expenses:food $396 expenses:bus $49 expenses:movies $30 expenses:supplies $20 assets:bank:checking 2017-12-01 income $2100 expenses:food $412 expenses:bus $53 expenses:gifts $100 assets:bank:checking You can now see a monthly budget report: $ hledger balance -M --budget Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] This is different from a normal balance report in several ways: * Only accounts with budget goals during the report period are shown, by default. * In each column, in square brackets after the actual amount, budget goal amounts are shown, and the actual/goal percentage. (Note: budget goals should be in the same commodity as the actual amount.) * All parent accounts are always shown, even in flat mode. Eg assets, assets:bank, and expenses above. * Amounts always include all subaccounts, budgeted or unbudgeted, even in flat mode. This means that the numbers displayed will not always add up! Eg above, the 'expenses' actual amount includes the gifts and supplies transactions, but the 'expenses:gifts' and 'expenses:supplies' accounts are not shown, as they have no budget amounts declared. This can be confusing. When you need to make things clearer, use the '-E/--empty' flag, which will reveal all accounts including unbudgeted ones, giving the full picture. Eg: $ hledger balance -M --budget --empty Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:gifts || 0 $100 expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] expenses:supplies || $20 0 income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] You can roll over unspent budgets to next period with '--cumulative': $ hledger balance -M --budget --cumulative Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank:checking || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] expenses || $495 [ 103% of $480] $1060 [ 110% of $960] expenses:bus || $49 [ 98% of $50] $102 [ 102% of $100] expenses:food || $396 [ 99% of $400] $808 [ 101% of $800] expenses:movies || $30 [ 100% of $30] $30 [ 50% of $60] income || $1950 [ 98% of $2000] $4050 [ 101% of $4000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] For more examples, see Budgeting and Forecasting. * Menu: * Nested budgets::  File: hledger.info, Node: Nested budgets, Up: Budget report 3.5.8.1 Nested budgets ...................... You can add budgets to any account in your account hierarchy. If you have budgets on both parent account and some of its children, then budget(s) of the child account(s) would be added to the budget of their parent, much like account balances behave. In the most simple case this means that once you add a budget to any account, all its parents would have budget as well. To illustrate this, consider the following budget: ~ monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities With this, monthly budget for electronics is defined to be $100 and budget for personal expenses is an additional $1000, which implicitly means that budget for both 'expenses:personal' and 'expenses' is $1100. Transactions in 'expenses:personal:electronics' will be counted both towards its $100 budget and $1100 of 'expenses:personal' , and transactions in any other subaccount of 'expenses:personal' would be counted towards only towards the budget of 'expenses:personal'. For example, let's consider these transactions: ~ monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities 2019/01/01 Google home hub expenses:personal:electronics $90.00 liabilities $-90.00 2019/01/02 Phone screen protector expenses:personal:electronics:upgrades $10.00 liabilities 2019/01/02 Weekly train ticket expenses:personal:train tickets $153.00 liabilities 2019/01/03 Flowers expenses:personal $30.00 liabilities As you can see, we have transactions in 'expenses:personal:electronics:upgrades' and 'expenses:personal:train tickets', and since both of these accounts are without explicitly defined budget, these transactions would be counted towards budgets of 'expenses:personal:electronics' and 'expenses:personal' accordingly: $ hledger balance --budget -M Budget performance in 2019/01: || Jan ===============================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] liabilities || $-283.00 [ 26% of $-1100.00] -------------------------------++------------------------------- || 0 [ 0] And with '--empty', we can get a better picture of budget allocation and consumption: $ hledger balance --budget -M --empty Budget performance in 2019/01: || Jan ========================================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] expenses:personal:electronics:upgrades || $10.00 expenses:personal:train tickets || $153.00 liabilities || $-283.00 [ 26% of $-1100.00] ----------------------------------------++------------------------------- || 0 [ 0] 3.5.9 Output format ------------------- This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', (multicolumn non-budget reports only) 'html', and (experimental) 'json'.  File: hledger.info, Node: balancesheet, Next: balancesheetequity, Prev: balance, Up: COMMANDS 3.6 balancesheet ================ 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. The asset and liability accounts shown are those accounts declared with the 'Asset' or 'Cash' or 'Liability' type, or otherwise all accounts under a top-level 'asset' or 'liability' account (case insensitive, plurals allowed). Example: $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 With a reporting interval, multiple columns will be shown, one for each report period. As with multicolumn balance reports, you can alter the report mode with '--change'/'--cumulative'/'--historical'. Normally balancesheet shows historical ending balances, which is what you need for a balance sheet; note this means it ignores report begin dates (and '-T/--row-total', since summing end balances generally does not make sense). Instead of absolute values percentages can be displayed with '-%'. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'html', and (experimental) 'json'.  File: hledger.info, Node: balancesheetequity, Next: cashflow, Prev: balancesheet, Up: COMMANDS 3.7 balancesheetequity ====================== 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. The asset, liability and equity accounts shown are those accounts declared with the 'Asset', 'Cash', 'Liability' or 'Equity' type, or otherwise all accounts under a top-level 'asset', 'liability' or 'equity' account (case insensitive, plurals allowed). 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 also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'html', and (experimental) 'json'.  File: hledger.info, Node: cashflow, Next: check-dates, Prev: balancesheetequity, Up: COMMANDS 3.8 cashflow ============ cashflow, cf This command displays a cashflow statement, showing the inflows and outflows affecting "cash" (ie, liquid) assets. Amounts are shown with normal positive sign, as in conventional financial statements. The "cash" accounts shown are those accounts declared with the 'Cash' type, or otherwise all accounts under a top-level 'asset' account (case insensitive, plural allowed) which do not have 'fixed', 'investment', 'receivable' or 'A/R' in their name. Example: $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 With a reporting interval, multiple columns will be shown, one for each report period. Normally cashflow shows changes in assets per period, though as with multicolumn balance reports you can alter the report mode with '--change'/'--cumulative'/'--historical'. Instead of absolute values percentages can be displayed with '-%'. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'html', and (experimental) 'json'.  File: hledger.info, Node: check-dates, Next: check-dupes, Prev: cashflow, Up: COMMANDS 3.9 check-dates =============== check-dates Check that transactions are sorted by increasing date. With -date2, checks secondary dates instead. With -strict, dates must also be unique. With a query, only matched transactions' dates are checked. Reads the default journal file, or another specified with -f.  File: hledger.info, Node: check-dupes, Next: close, Prev: check-dates, Up: COMMANDS 3.10 check-dupes ================ check-dupes Reports account names having the same leaf but different prefixes. In other words, two or more leaves that are categorized differently. Reads the default journal file, or another specified as an argument. An example: http://stefanorodighiero.net/software/hledger-dupes.html  File: hledger.info, Node: close, Next: codes, Prev: check-dupes, Up: COMMANDS 3.11 close ========== close, equity Prints a "closing balances" transaction and an "opening balances" transaction that bring account balances to and from zero, respectively. These can be added to your journal file(s), eg to bring asset/liability balances forward into a new journal file, or to close out revenues/expenses to retained earnings at the end of a period. You can print just one of these transactions by using the '--close' or '--open' flag. You can customise their descriptions with the '--close-desc' and '--open-desc' options. One amountless posting to "equity:opening/closing balances" is added to balance the transactions, by default. You can customise this account name with '--close-acct' and '--open-acct'; if you specify only one of these, it will be used for both. With '--x/--explicit', the equity posting's amount will be shown. And if it involves multiple commodities, a posting for each commodity will be shown, as with the print command. With '--interleaved', the equity postings are shown next to the postings they balance, which makes troubleshooting easier. By default, transaction prices in the journal are ignored when generating the closing/opening transactions. With '--show-costs', this cost information is preserved ('balance -B' reports will be unchanged after the transition). Separate postings are generated for each cost in each commodity. Note this can generate very large journal entries, if you have many foreign currency or investment transactions. * Menu: * close usage::  File: hledger.info, Node: close usage, Up: close 3.11.1 close usage ------------------ If you split your journal files by time (eg yearly), you will typically run this command at the end of the year, and save the closing transaction as last entry of the old file, and the opening transaction as the first entry of the new file. This makes the files self contained, so that correct balances are reported no matter which of them are loaded. Ie, if you load just one file, the balances are initialised correctly; or if you load several files, the redundant closing/opening transactions cancel each other out. (They will show up in print or register reports; you can exclude them with a query like 'not:desc:'(opening|closing) balances''.) If you're running a business, you might also use this command to "close the books" at the end of an accounting period, transferring income statement account balances to retained earnings. (You may want to change the equity account name to something like "equity:retained earnings".) By default, the closing transaction is dated yesterday, the balances are calculated as of end of yesterday, and the opening transaction is dated today. To close on some other date, use: 'hledger close -e OPENINGDATE'. Eg, to close/open on the 2018/2019 boundary, use '-e 2019'. You can also use -p or 'date:PERIOD' (any starting date is ignored). Both transactions will include balance assertions for the closed/reopened accounts. You probably shouldn't use status or realness filters (like -C or -R or 'status:') with this command, or the generated balance assertions will depend on these flags. Likewise, if you run this command with -auto, the balance assertions will probably always require -auto. Examples: Carrying asset/liability balances into a new file for 2019: $ hledger close -f 2018.journal -e 2019 assets liabilities --open # (copy/paste the output to the start of your 2019 journal file) $ hledger close -f 2018.journal -e 2019 assets liabilities --close # (copy/paste the output to the end of your 2018 journal file) Now: $ hledger bs -f 2019.journal # one file - balances are correct $ hledger bs -f 2018.journal -f 2019.journal # two files - balances still correct $ hledger bs -f 2018.journal not:desc:closing # to see year-end balances, must exclude closing txn Transactions spanning the closing date can complicate matters, breaking balance assertions: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 assets:bank:checking -5 ; [2019/1/2] Here's one way to resolve that: ; in 2018.journal: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 liabilities:pending ; in 2019.journal: 2019/1/2 clearance of last year's pending transactions liabilities:pending 5 = 0 assets:checking  File: hledger.info, Node: codes, Next: commodities, Prev: close, Up: COMMANDS 3.12 codes ========== 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: 1/1 (123) (a) 1 1/1 () (a) 1 1/1 (a) 1 1/1 (126) (a) 1 $ hledger codes 123 124 126 $ hledger codes -E 123 124 126  File: hledger.info, Node: commodities, Next: descriptions, Prev: codes, Up: COMMANDS 3.13 commodities ================ commodities List all commodity/currency symbols used or declared in the journal.  File: hledger.info, Node: descriptions, Next: diff, Prev: commodities, Up: COMMANDS 3.14 descriptions ================= 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: COMMANDS 3.15 diff ========= 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: COMMANDS 3.16 files ========== 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: COMMANDS 3.17 help ========= help Show any of the hledger manuals. The 'help' command displays any of the main hledger manuals, in one of several ways. Run it with no argument to list the manuals, or provide a full or partial manual name to select one. hledger manuals are available in several formats. hledger help will use the first of these display methods that it finds: info, man, $PAGER, less, stdout (or when non-interactive, just stdout). You can force a particular viewer with the '--info', '--man', '--pager', '--cat' flags. Examples: $ hledger help Please choose a manual by typing "hledger help MANUAL" (a substring is ok). Manuals: hledger hledger-ui hledger-web journal csv timeclock timedot $ hledger help h --man hledger(1) hledger User Manuals hledger(1) NAME hledger - a command-line accounting tool SYNOPSIS hledger [-f FILE] COMMAND [OPTIONS] [ARGS] hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS] hledger DESCRIPTION hledger is a cross-platform program for tracking money, time, or any ...  File: hledger.info, Node: import, Next: incomestatement, Prev: help, Up: COMMANDS 3.18 import =========== import Read new transactions added to each FILE since last run, and add them to the main journal file. Or with -dry-run, just print the transactions that would be added. Or with -catchup, just mark all of the FILEs' transactions as imported, without actually importing any. The input files are specified as arguments - no need to write -f before each one. So eg to add new transactions from all CSV files to the main journal, it's just: 'hledger import *.csv' New transactions are detected in the same way as print -new: by assuming transactions are always added to the input files in increasing date order, and by saving '.latest.FILE' state files. The -dry-run output is in journal format, so you can filter it, eg to see only uncategorised transactions: $ hledger import --dry ... | hledger -f- print unknown --ignore-assertions * Menu: * Importing balance assignments::  File: hledger.info, Node: Importing balance assignments, Up: import 3.18.1 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: incomestatement, Next: notes, Prev: import, Up: COMMANDS 3.19 incomestatement ==================== 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. The revenue and expense accounts shown are those accounts declared with the 'Revenue' or 'Expense' type, or otherwise all accounts under a top-level 'revenue' or 'income' or 'expense' account (case insensitive, plurals allowed). Example: $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 With a reporting interval, multiple columns will be shown, one for each report period. Normally incomestatement shows revenues/expenses per period, though as with multicolumn balance reports you can alter the report mode with '--change'/'--cumulative'/'--historical'. Instead of absolute values percentages can be displayed with '-%'. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'html', and (experimental) 'json'.  File: hledger.info, Node: notes, Next: payees, Prev: incomestatement, Up: COMMANDS 3.20 notes ========== 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: COMMANDS 3.21 payees =========== payees List the unique payee/payer names that appear in transactions. This command lists the unique payee/payer names that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). Example: $ hledger payees Store Name Gas Station Person A  File: hledger.info, Node: prices, Next: print, Prev: payees, Up: COMMANDS 3.22 prices =========== prices Print market price directives from the journal. With -costs, also print synthetic market prices based on transaction prices. With -inverted-costs, also print inverse prices based on transaction prices. Prices (and postings providing prices) can be filtered by a query. Price amounts are always displayed with their full precision.  File: hledger.info, Node: print, Next: print-unique, Prev: prices, Up: COMMANDS 3.23 print ========== print, txns, p Show transaction journal entries, sorted by date. The print command displays full journal entries (transactions) from the journal file in date order, tidily formatted. With -date2, transactions are sorted by secondary date instead. print's output is always a valid hledger journal. It preserves all transaction information, but it does not preserve directives or inter-transaction comments $ hledger print 2008/01/01 income assets:bank:checking $1 income:salary $-1 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 2008/12/31 * pay off liabilities:debts $1 assets:bank:checking $-1 Normally, the journal entry's explicit or implicit amount style is preserved. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, when a transaction price is implied but not written, it will not appear in the output. You can use the '-x'/'--explicit' flag to make all amounts and transaction prices explicit, which 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'. Note, '-x'/'--explicit' will cause postings with a multi-commodity amount (these can arise when a multi-commodity transaction has an implicit amount) to be split into multiple single-commodity postings, keeping the output parseable. With '-B'/'--cost', amounts with transaction prices are converted to cost using that price. This can be used for troubleshooting. With '-m'/'--match' and a STR argument, print will show at most one transaction: the one one whose description is most similar to STR, and is most recent. STR should contain at least two characters. If there is no similar-enough match, no transaction will be shown. With '--new', for each FILE being read, hledger reads (and writes) a special state file ('.latest.FILE' in the same directory), containing the latest transaction date(s) that were seen last time FILE was read. When this file is found, only transactions with newer dates (and new transactions on the latest date) are printed. This is useful for ignoring already-seen entries in import data, such as downloaded CSV files. Eg: $ hledger -f bank1.csv print --new (shows transactions added since last print --new on this file) This assumes that transactions added to FILE always have same or increasing dates, and that transactions on the same day do not get reordered. See also the import command. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', and (experimental) 'json' and 'sql'. 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: print-unique, Next: register, Prev: print, Up: COMMANDS 3.24 print-unique ================= print-unique Print transactions which do not reuse an already-seen description. Example: $ cat unique.journal 1/1 test (acct:one) 1 2/2 test (acct:two) 2 $ LEDGER_FILE=unique.journal hledger print-unique (-f option not supported) 2015/01/01 test (acct:one) 1  File: hledger.info, Node: register, Next: register-match, Prev: print-unique, Up: COMMANDS 3.25 register ============= register, reg, r 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. 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. * Menu: * Custom register output::  File: hledger.info, Node: Custom register output, Up: register 3.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', and (experimental) 'json'.  File: hledger.info, Node: register-match, Next: rewrite, Prev: register, Up: COMMANDS 3.26 register-match =================== register-match Print the one posting whose transaction description is closest to DESC, in the style of the register command. If there are multiple equally good matches, it shows the most recent. Query options (options, not arguments) can be used to restrict the search space. Helps ledger-autosync detect already-seen transactions when importing.  File: hledger.info, Node: rewrite, Next: roi, Prev: register-match, Up: COMMANDS 3.27 rewrite ============ 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::  File: hledger.info, Node: Re-write rules in a file, Up: rewrite 3.27.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. * Menu: * Diff output format:: * rewrite vs print --auto::  File: hledger.info, Node: Diff output format, Next: rewrite vs print --auto, Up: Re-write rules in a file 3.27.1.1 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: Re-write rules in a file 3.27.1.2 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: COMMANDS 3.28 roi ======== roi Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. This command assumes that you have account(s) that hold nothing but your investments and whenever you record current appraisal/valuation of these investments you offset unrealized profit and loss into account(s) that, again, hold nothing but unrealized profit and loss. Any transactions affecting balance of investment account(s) and not originating from unrealized profit and loss account(s) are assumed to be your investments or withdrawals. At a minimum, you need to supply a query (which could be just an account name) to select your investments with '--inv', and another query to identify your profit and loss transactions with '--pnl'. It will compute and display the internalized rate of return (IRR) and time-weighted rate of return (TWR) for your investments for the time period requested. Both rates of return are annualized before display, regardless of the length of reporting interval.  File: hledger.info, Node: stats, Next: tags, Prev: roi, Up: COMMANDS 3.29 stats ========== stats Show some journal 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. Example: $ hledger stats Main journal file : /src/hledger/examples/sample.journal Included journal files : Transactions span : 2008-01-01 to 2009-01-01 (366 days) Last transaction : 2008-12-31 (2333 days ago) 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 : 12 ($) This command also supports output destination and output format selection.  File: hledger.info, Node: tags, Next: test, Prev: stats, Up: COMMANDS 3.30 tags ========= tags List the unique tag names used in the journal. With a TAGREGEX argument, only tag names matching the regular expression (case insensitive) are shown. With QUERY arguments, only transactions matching the query are considered. With the -values flag, the tags' unique values are listed instead. With -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.  File: hledger.info, Node: test, Next: Add-on commands, Prev: tags, Up: COMMANDS 3.31 test ========= 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: Add-on commands, Prev: test, Up: COMMANDS 3.32 Add-on commands ==================== hledger also searches for external add-on commands, and will include these in the commands list. These are programs or scripts in your PATH whose name starts with 'hledger-' and ends with a recognised file extension (currently: no extension, 'bat','com','exe', 'hs','lhs','pl','py','rb','rkt','sh'). Add-ons can be invoked like any hledger command, but there are a few things to be aware of. Eg if the 'hledger-web' add-on is installed, * 'hledger -h web' shows hledger's help, while 'hledger web -h' shows hledger-web's help. * Flags specific to the add-on must have a preceding '--' to hide them from hledger. So 'hledger web --serve --port 9000' will be rejected; you must use 'hledger web -- --serve --port 9000'. * You can always run add-ons directly if preferred: 'hledger-web --serve --port 9000'. Add-ons are a relatively easy way to add local features or experiment with new ideas. They can be written in any language, but haskell scripts have a big advantage: they can use the same hledger (and haskell) library functions that built-in commands do, for command-line options, journal parsing, reporting, etc. Two important add-ons are the hledger-ui and hledger-web user interfaces. These are maintained and released along with hledger: * Menu: * ui:: * web:: * iadd:: * interest::  File: hledger.info, Node: ui, Next: web, Up: Add-on commands 3.32.1 ui --------- hledger-ui provides an efficient terminal interface.  File: hledger.info, Node: web, Next: iadd, Prev: ui, Up: Add-on commands 3.32.2 web ---------- hledger-web provides a simple web interface. Third party add-ons, maintained separately from hledger, include:  File: hledger.info, Node: iadd, Next: interest, Prev: web, Up: Add-on commands 3.32.3 iadd ----------- hledger-iadd is a more interactive, terminal UI replacement for the add command.  File: hledger.info, Node: interest, Prev: iadd, Up: Add-on commands 3.32.4 interest --------------- hledger-interest generates interest transactions for an account according to various schemes. A few more experimental or old add-ons can be found in hledger's bin/ directory. These are typically prototypes and not guaranteed to work.  File: hledger.info, Node: ENVIRONMENT, Next: FILES, Prev: COMMANDS, Up: Top 4 ENVIRONMENT ************* *LEDGER_FILE* The journal file path when not specified with '-f'. Default: '~/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal'). A typical value is '~/DIR/YYYY.journal', where DIR is a version-controlled finance directory and YYYY is the current year. Or '~/DIR/current.journal', where current.journal is a symbolic link to YYYY.journal. On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a '~/.MacOSX/environment.plist' file containing { "LEDGER_FILE" : "~/finance/current.journal" } To see the effect you may need to 'killall Dock', or reboot. *COLUMNS* The screen width used by the register command. Default: the full terminal width. *NO_COLOR* If this variable exists with any value, hledger will not use ANSI color codes in terminal output. This overrides the -color/-colour option.  File: hledger.info, Node: FILES, Next: LIMITATIONS, Prev: ENVIRONMENT, Up: Top 5 FILES ******* Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with '-f', or '$LEDGER_FILE', or '$HOME/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal').  File: hledger.info, Node: LIMITATIONS, Next: TROUBLESHOOTING, Prev: FILES, Up: Top 6 LIMITATIONS ************* The need to precede addon command options with '--' when invoked from hledger is awkward. When input data contains non-ascii characters, a suitable system locale must be configured (or there will be an unhelpful error). Eg on POSIX, set LANG to something other than C. In a Microsoft Windows CMD window, non-ascii characters and colours are not supported. On Windows, non-ascii characters may not display correctly when running a hledger built in CMD in MSYS/CYGWIN, or vice-versa. In a Cygwin/MSYS/Mintty window, the tab key is not supported in hledger add. Not all of Ledger's journal file syntax is supported. See file format differences. On large data files, hledger is slower and uses more memory than Ledger.  File: hledger.info, Node: TROUBLESHOOTING, Prev: LIMITATIONS, Up: Top 7 TROUBLESHOOTING ***************** Here are some issues you might encounter when you run hledger (and remember you can also seek help from the IRC channel, mail list or bug tracker): *Successfully installed, but "No command 'hledger' found"* stack and cabal install binaries into a special directory, which should be added to your PATH environment variable. Eg on unix-like systems, that is ~/.local/bin and ~/.cabal/bin respectively. *I set a custom LEDGER_FILE, but hledger is still using the default file* 'LEDGER_FILE' should be a real environment variable, not just a shell variable. The command 'env | grep LEDGER_FILE' should show it. You may need to use 'export'. Here's an explanation. *Getting 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 to have a UTF-8-aware locale configured in the environment, otherwise they will fail with these kinds of errors when they encounter non-ascii characters. To fix it, set the LANG environment variable to some locale which supports UTF-8. The locale you choose must be installed on your system. Here's an example of setting LANG temporarily, on Ubuntu GNU/Linux: $ file my.journal my.journal: UTF-8 Unicode text # the file is UTF8-encoded $ echo $LANG C # LANG is set to the default locale, which does not support UTF8 $ locale -a # which locales are installed ? C en_US.utf8 # here's a UTF8-aware one we can use POSIX $ LANG=en_US.utf8 hledger -f my.journal print # ensure it is used for this command If available, 'C.UTF-8' will also work. If your preferred locale isn't listed by 'locale -a', you might need to install it. Eg on Ubuntu/Debian: $ apt-get install language-pack-fr $ locale -a C en_US.utf8 fr_BE.utf8 fr_CA.utf8 fr_CH.utf8 fr_FR.utf8 fr_LU.utf8 POSIX $ LANG=fr_FR.utf8 hledger -f my.journal print Here's how you could set it permanently, if you use a bash shell: $ echo "export LANG=en_US.utf8" >>~/.bash_profile $ bash --login Exact spelling and capitalisation may be important. Note the difference on MacOS ('UTF-8', not 'utf8'). Some platforms (eg ubuntu) allow variant spellings, but others (eg macos) require it to be exact: $ locale -a | grep -iE en_us.*utf en_US.UTF-8 $ LANG=en_US.UTF-8 hledger -f my.journal print  Tag Table: Node: Top68 Node: COMMON TASKS2321 Ref: #common-tasks2433 Node: Getting help2840 Ref: #getting-help2972 Node: Constructing command lines3525 Ref: #constructing-command-lines3717 Node: Starting a journal file4414 Ref: #starting-a-journal-file4612 Node: Setting opening balances5800 Ref: #setting-opening-balances5996 Node: Recording transactions9137 Ref: #recording-transactions9317 Node: Reconciling9873 Ref: #reconciling10016 Node: Reporting12273 Ref: #reporting12413 Node: Migrating to a new file16412 Ref: #migrating-to-a-new-file16560 Node: OPTIONS16859 Ref: #options16966 Node: General options17336 Ref: #general-options17461 Node: Command options20767 Ref: #command-options20918 Node: Command arguments21316 Ref: #command-arguments21463 Node: Queries22343 Ref: #queries22498 Node: Special characters in arguments and queries26460 Ref: #special-characters-in-arguments-and-queries26688 Node: More escaping27139 Ref: #more-escaping27301 Node: Even more escaping27597 Ref: #even-more-escaping27791 Node: Less escaping28462 Ref: #less-escaping28624 Node: Unicode characters28869 Ref: #unicode-characters29051 Node: Input files30463 Ref: #input-files30606 Node: Output destination32905 Ref: #output-destination33057 Node: Output format33482 Ref: #output-format33632 Node: Regular expressions35799 Ref: #regular-expressions35956 Node: Smart dates37692 Ref: #smart-dates37843 Node: Report start & end date39204 Ref: #report-start-end-date39376 Node: Report intervals40873 Ref: #report-intervals41038 Node: Period expressions41428 Ref: #period-expressions41588 Node: Depth limiting45920 Ref: #depth-limiting46064 Node: Pivoting46396 Ref: #pivoting46519 Node: Valuation48195 Ref: #valuation48297 Node: -B Cost48986 Ref: #b-cost49090 Node: -V Value49223 Ref: #v-value49369 Node: -X Value in specified commodity49564 Ref: #x-value-in-specified-commodity49763 Node: Valuation date49912 Ref: #valuation-date50080 Node: Market prices50490 Ref: #market-prices50670 Node: --infer-value market prices from transactions51447 Ref: #infer-value-market-prices-from-transactions51696 Node: Valuation commodity52978 Ref: #valuation-commodity53187 Node: Simple valuation examples54413 Ref: #simple-valuation-examples54615 Node: --value Flexible valuation55274 Ref: #value-flexible-valuation55482 Node: More valuation examples57429 Ref: #more-valuation-examples57638 Node: Effect of valuation on reports59643 Ref: #effect-of-valuation-on-reports59831 Node: COMMANDS65352 Ref: #commands65460 Node: accounts66568 Ref: #accounts66666 Node: activity67365 Ref: #activity67475 Node: add67858 Ref: #add67959 Node: aregister70752 Ref: #aregister70864 Node: aregister and custom posting dates72237 Ref: #aregister-and-custom-posting-dates72410 Ref: #output-format-173003 Node: balance73408 Ref: #balance73525 Node: Classic balance report74983 Ref: #classic-balance-report75156 Node: Customising the classic balance report76540 Ref: #customising-the-classic-balance-report76768 Node: Colour support78844 Ref: #colour-support79011 Node: Flat mode79107 Ref: #flat-mode79255 Node: Depth limited balance reports79668 Ref: #depth-limited-balance-reports79853 Node: Percentages80309 Ref: #percentages80475 Node: Multicolumn balance report81612 Ref: #multicolumn-balance-report81792 Node: Budget report87389 Ref: #budget-report87532 Node: Nested budgets92798 Ref: #nested-budgets92910 Ref: #output-format-296391 Node: balancesheet96588 Ref: #balancesheet96724 Node: balancesheetequity98236 Ref: #balancesheetequity98385 Node: cashflow99461 Ref: #cashflow99589 Node: check-dates100805 Ref: #check-dates100932 Node: check-dupes101211 Ref: #check-dupes101337 Node: close101630 Ref: #close101738 Node: close usage103260 Ref: #close-usage103353 Node: codes106166 Ref: #codes106274 Node: commodities106986 Ref: #commodities107113 Node: descriptions107195 Ref: #descriptions107323 Node: diff107627 Ref: #diff107733 Node: files108780 Ref: #files108880 Node: help109027 Ref: #help109127 Node: import110208 Ref: #import110322 Node: Importing balance assignments111215 Ref: #importing-balance-assignments111363 Node: incomestatement112012 Ref: #incomestatement112145 Node: notes113490 Ref: #notes113603 Node: payees113971 Ref: #payees114077 Node: prices114497 Ref: #prices114603 Node: print114944 Ref: #print115054 Node: print-unique119850 Ref: #print-unique119976 Node: register120261 Ref: #register120388 Node: Custom register output124837 Ref: #custom-register-output124966 Node: register-match126303 Ref: #register-match126437 Node: rewrite126788 Ref: #rewrite126903 Node: Re-write rules in a file128758 Ref: #re-write-rules-in-a-file128892 Node: Diff output format130102 Ref: #diff-output-format130271 Node: rewrite vs print --auto131363 Ref: #rewrite-vs.-print---auto131542 Node: roi132098 Ref: #roi132196 Node: stats133208 Ref: #stats133307 Node: tags134095 Ref: #tags134193 Node: test134712 Ref: #test134820 Node: Add-on commands135567 Ref: #add-on-commands135684 Node: ui137027 Ref: #ui137115 Node: web137169 Ref: #web137272 Node: iadd137388 Ref: #iadd137499 Node: interest137581 Ref: #interest137688 Node: ENVIRONMENT137928 Ref: #environment138040 Node: FILES139025 Ref: #files-1139128 Node: LIMITATIONS139341 Ref: #limitations139460 Node: TROUBLESHOOTING140202 Ref: #troubleshooting140315  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.19.1/embeddedfiles/hledger.10000644000000000000000000042122513725533425015672 0ustar0000000000000000.\"t .TH "hledger" "1" "September 2020" "hledger 1.18.99" "hledger User Manuals" .SH NAME .PP hledger - a command-line accounting tool .SH SYNOPSIS .PP \f[C]hledger [-f FILE] COMMAND [OPTIONS] [ARGS]\f[R] .PD 0 .P .PD \f[C]hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS]\f[R] .PD 0 .P .PD \f[C]hledger\f[R] .SH DESCRIPTION .PP hledger is a reliable, 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). .PP This is hledger\[cq]s command-line interface (there are also terminal and web interfaces). Its basic function is to read a plain text file describing financial transactions (in accounting terms, a general journal) and print useful reports on standard output, or export them as CSV. hledger can also read some other file formats such as CSV files, translating them to journal format. Additionally, hledger lists other hledger-* executables found in the user\[cq]s $PATH and can invoke them as subcommands. .PP hledger reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]-f\f[R], or \f[C]$LEDGER_FILE\f[R], or \f[C]$HOME/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). If using \f[C]$LEDGER_FILE\f[R], note this must be a real environment variable, not a shell variable. You can specify standard input with \f[C]-f-\f[R]. .PP Transactions are dated movements of money between two (or more) named accounts, and are recorded with journal entries like this: .IP .nf \f[C] 2015/10/16 bought food expenses:food $10 assets:cash \f[R] .fi .PP For more about this format, see hledger_journal(5). .PP Most users use a text editor to edit the journal, usually with an editor mode such as ledger-mode for added convenience. hledger\[cq]s interactive add command is another way to record new transactions. hledger never changes existing transactions. .PP To get started, you can either save some entries like the above in \f[C]\[ti]/.hledger.journal\f[R], or run \f[C]hledger add\f[R] and follow the prompts. Then try some commands like \f[C]hledger print\f[R] or \f[C]hledger balance\f[R]. Run \f[C]hledger\f[R] with no arguments for a list of commands. .SH COMMON TASKS .PP Here are some quick examples of how to do some basic tasks with hledger. For more details, see the reference section below, the hledger_journal(5) manual, or the more extensive docs at https://hledger.org. .SS Getting help .IP .nf \f[C] $ hledger # show available commands $ hledger --help # show common options $ hledger CMD --help # show common and command options, and command help $ hledger help # show available manuals/topics $ hledger help hledger # show hledger manual as info/man/text (auto-chosen) $ hledger help journal --man # show the journal manual as a man page $ hledger help --help # show more detailed help for the help command \f[R] .fi .PP Find more docs, chat, mail list, reddit, issue tracker: https://hledger.org#help-feedback .SS Constructing command lines .PP hledger has an extensive and powerful command line interface. We strive to keep it simple and ergonomic, but you may run into one of the confusing real world details described in OPTIONS, below. If that happens, here are some tips that may help: .IP \[bu] 2 command-specific options must go after the command (it\[aq]s fine to put all options there) (\f[C]hledger CMD OPTS ARGS\f[R]) .IP \[bu] 2 running add-on executables directly simplifies command line parsing (\f[C]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 is being parsed, add \f[C]--debug=2\f[R]. .SS Starting a journal file .PP hledger looks for your accounting data in a journal file, \f[C]$HOME/.hledger.journal\f[R] by default: .IP .nf \f[C] $ 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. \f[R] .fi .PP You can override this by setting the \f[C]LEDGER_FILE\f[R] environment variable. 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 .nf \f[C] $ mkdir \[ti]/finance $ cd \[ti]/finance $ git init Initialized empty Git repository in /Users/simon/finance/.git/ $ touch 2020.journal $ echo \[dq]export LEDGER_FILE=$HOME/finance/2020.journal\[dq] >> \[ti]/.bashrc $ source \[ti]/.bashrc $ hledger stats Main file : /Users/simon/finance/2020.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 () \f[R] .fi .SS Setting opening balances .PP 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 .nf \f[C] 2020-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 \f[R] .fi .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[C]hledger add\f[R] and follow the prompts to record a similar transaction: .RS 2 .IP .nf \f[C] $ hledger add Adding transactions to journal file /Users/simon/finance/2020.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 [2020-02-07]: 2020-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): . 2020-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 [2020-01-01]: . \f[R] .fi .RE .PP If you\[aq]re using version control, this could be a good time to commit the journal. Eg: .IP .nf \f[C] $ git commit -m \[aq]initial balances\[aq] 2020.journal \f[R] .fi .SS Recording transactions .PP 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 .nf \f[C] 2020/1/10 * gift received assets:cash $20 income:gifts 2020.1.12 * farmers market expenses:food $13 assets:cash 2020-01-15 paycheck income:salary assets:bank:checking $1000 \f[R] .fi .SS Reconciling .PP 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[C]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[C]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 .nf \f[C] 2020-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc \f[R] .fi .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[C]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[C]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[C]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[C]*\f[R] marker. Eg in the paycheck transaction above, insert \f[C]*\f[R] between \f[C]2020-01-15\f[R] and \f[C]paycheck\f[R] .PP If you\[aq]re using version control, this can be another good time to commit: .IP .nf \f[C] $ git commit -m \[aq]txns\[aq] 2020.journal \f[R] .fi .SS Reporting .PP Here are some basic reports. .PP Show all transactions: .IP .nf \f[C] $ hledger print 2020-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 2020-01-10 * gift received assets:cash $20 income:gifts 2020-01-12 * farmers market expenses:food $13 assets:cash 2020-01-15 * paycheck income:salary assets:bank:checking $1000 2020-01-16 * adjust cash assets:cash $-2 = $105 expenses:misc \f[R] .fi .PP Show account names, and their hierarchy: .IP .nf \f[C] $ hledger accounts --tree assets bank checking savings cash equity opening/closing balances expenses food misc income gifts salary liabilities creditcard \f[R] .fi .PP Show all account totals: .IP .nf \f[C] $ 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 \f[R] .fi .PP Show only asset and liability balances, as a flat list, limited to depth 2: .IP .nf \f[C] $ hledger bal assets liabilities --flat -2 $4000 assets:bank $105 assets:cash $-50 liabilities:creditcard -------------------- $4055 \f[R] .fi .PP Show the same thing without negative numbers, formatted as a simple balance sheet: .IP .nf \f[C] $ hledger bs --flat -2 Balance Sheet 2020-01-16 || 2020-01-16 ========================++============ Assets || ------------------------++------------ assets:bank || $4000 assets:cash || $105 ------------------------++------------ || $4105 ========================++============ Liabilities || ------------------------++------------ liabilities:creditcard || $50 ------------------------++------------ || $50 ========================++============ Net: || $4055 \f[R] .fi .PP The final total is your \[dq]net worth\[dq] on the end date. (Or use \f[C]bse\f[R] for a full balance sheet with equity.) .PP Show income and expense totals, formatted as an income statement: .IP .nf \f[C] hledger is Income Statement 2020-01-01-2020-01-16 || 2020-01-01-2020-01-16 ===============++======================= Revenues || ---------------++----------------------- income:gifts || $20 income:salary || $1000 ---------------++----------------------- || $1020 ===============++======================= Expenses || ---------------++----------------------- expenses:food || $13 expenses:misc || $2 ---------------++----------------------- || $15 ===============++======================= Net: || $1005 \f[R] .fi .PP The final total is your net income during this period. .PP Show transactions affecting your wallet, with running total: .IP .nf \f[C] $ hledger register cash 2020-01-01 opening balances assets:cash $100 $100 2020-01-10 gift received assets:cash $20 $120 2020-01-12 farmers market assets:cash $-13 $107 2020-01-16 adjust cash assets:cash $-2 $105 \f[R] .fi .PP Show weekly posting counts as a bar chart: .IP .nf \f[C] $ hledger activity -W 2019-12-30 ***** 2020-01-06 **** 2020-01-13 **** \f[R] .fi .SS Migrating to a new file .PP 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[C]git add\f[R] the new file. .SH OPTIONS .SS General options .PP To see general usage help, including general options which are supported by most hledger commands, run \f[C]hledger -h\f[R]. .PP General help options: .TP \f[B]\f[CB]-h --help\f[B]\f[R] show general usage (or after COMMAND, command usage) .TP \f[B]\f[CB]--version\f[B]\f[R] show version .TP \f[B]\f[CB]--debug[=N]\f[B]\f[R] show debug output (levels 1-9, default: 1) .PP General input options: .TP \f[B]\f[CB]-f FILE --file=FILE\f[B]\f[R] use a different input file. For stdin, use - (default: \f[C]$LEDGER_FILE\f[R] or \f[C]$HOME/.hledger.journal\f[R]) .TP \f[B]\f[CB]--rules-file=RULESFILE\f[B]\f[R] Conversion rules file to use when reading CSV (default: FILE.rules) .TP \f[B]\f[CB]--separator=CHAR\f[B]\f[R] Field separator to expect when reading CSV (default: \[aq],\[aq]) .TP \f[B]\f[CB]--alias=OLD=NEW\f[B]\f[R] rename accounts named OLD to NEW .TP \f[B]\f[CB]--anon\f[B]\f[R] anonymize accounts and payees .TP \f[B]\f[CB]--pivot FIELDNAME\f[B]\f[R] use some other field or tag for the account name .TP \f[B]\f[CB]-I --ignore-assertions\f[B]\f[R] disable balance assertion checks (note: does not disable balance assignments) .PP General reporting options: .TP \f[B]\f[CB]-b --begin=DATE\f[B]\f[R] include postings/txns on or after this date .TP \f[B]\f[CB]-e --end=DATE\f[B]\f[R] include postings/txns before this date .TP \f[B]\f[CB]-D --daily\f[B]\f[R] multiperiod/multicolumn report by day .TP \f[B]\f[CB]-W --weekly\f[B]\f[R] multiperiod/multicolumn report by week .TP \f[B]\f[CB]-M --monthly\f[B]\f[R] multiperiod/multicolumn report by month .TP \f[B]\f[CB]-Q --quarterly\f[B]\f[R] multiperiod/multicolumn report by quarter .TP \f[B]\f[CB]-Y --yearly\f[B]\f[R] multiperiod/multicolumn report by year .TP \f[B]\f[CB]-p --period=PERIODEXP\f[B]\f[R] set start date, end date, and/or reporting interval all at once using period expressions syntax .TP \f[B]\f[CB]--date2\f[B]\f[R] match the secondary date instead (see command help for other effects) .TP \f[B]\f[CB]-U --unmarked\f[B]\f[R] include only unmarked postings/txns (can combine with -P or -C) .TP \f[B]\f[CB]-P --pending\f[B]\f[R] include only pending postings/txns .TP \f[B]\f[CB]-C --cleared\f[B]\f[R] include only cleared postings/txns .TP \f[B]\f[CB]-R --real\f[B]\f[R] include only non-virtual postings .TP \f[B]\f[CB]-NUM --depth=NUM\f[B]\f[R] hide/aggregate accounts or postings more than NUM levels deep .TP \f[B]\f[CB]-E --empty\f[B]\f[R] show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) .TP \f[B]\f[CB]-B --cost\f[B]\f[R] convert amounts to their cost/selling amount at transaction time .TP \f[B]\f[CB]-V --market\f[B]\f[R] convert amounts to their market value in default valuation commodities .TP \f[B]\f[CB]-X --exchange=COMM\f[B]\f[R] convert amounts to their market value in commodity COMM .TP \f[B]\f[CB]--value\f[B]\f[R] convert amounts to cost or market value, more flexibly than -B/-V/-X .TP \f[B]\f[CB]--infer-value\f[B]\f[R] with -V/-X/--value, also infer market prices from transactions .TP \f[B]\f[CB]--auto\f[B]\f[R] apply automated posting rules to modify transactions. .TP \f[B]\f[CB]--forecast\f[B]\f[R] generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. .TP \f[B]\f[CB]--color=WHEN (or --colour=WHEN)\f[B]\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. .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. .SS Command options .PP To see options for a particular command, including command-specific options, run: \f[C]hledger COMMAND -h\f[R]. .PP Command-specific options must be written after the command name, eg: \f[C]hledger print -x\f[R]. .PP Additionally, if the command is an addon, you may need to put its options after a double-hyphen, eg: \f[C]hledger ui -- --watch\f[R]. Or, you can run the addon executable directly: \f[C]hledger-ui --watch\f[R]. .SS Command arguments .PP Most hledger commands accept arguments after the command name, which are often a query, filtering the data in some way. .PP You can save a set of command line options/arguments in a file, and then reuse them by writing \f[C]\[at]FILENAME\f[R] as a command line argument. Eg: \f[C]hledger bal \[at]foo.args\f[R]. (To prevent this, eg if you have an argument that begins with a literal \f[C]\[at]\f[R], precede it with \f[C]--\f[R], eg: \f[C]hledger bal -- \[at]ARG\f[R]). .PP Inside the argument file, each line should contain just one option or argument. Avoid the use of spaces, except inside quotes (or you\[aq]ll see a confusing error). Between a flag and its argument, use = (or nothing). Bad: .IP .nf \f[C] assets depth:2 -X USD \f[R] .fi .PP Good: .IP .nf \f[C] assets depth:2 -X=USD \f[R] .fi .PP For special characters (see below), use one less level of quoting than you would at the command prompt. Bad: .IP .nf \f[C] -X\[dq]$\[dq] \f[R] .fi .PP Good: .IP .nf \f[C] -X$ \f[R] .fi .PP See also: Save frequently used options. .SS Queries .PP One of hledger\[aq]s strengths is being able to quickly report on precise subsets of your data. Most commands accept an optional query expression, written as arguments after the command name, to filter the data by date, account name or other criteria. The syntax is similar to a web search: one or more space-separated search terms, quotes to enclose whitespace, prefixes to match specific fields, a not: prefix to negate the match. .PP We do not yet support arbitrary boolean combinations of search terms; instead most commands show transactions/postings/accounts which match (or negatively 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 instead shows 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 The following kinds of search terms can be used. Remember these can also be prefixed with \f[B]\f[CB]not:\f[B]\f[R], eg to exclude a particular subaccount. .TP \f[B]\f[R]\f[C]REGEX\f[R]\f[B], \f[R]\f[C]acct:REGEX\f[R]\f[B]\f[R] match account names by this regular expression. (With no prefix, \f[C]acct:\f[R] is assumed.) same as above .TP \f[B]\f[R]\f[C]amt:N, amt:N, amt:>=N\f[R]\f[B]\f[R] match postings with a single-commodity amount that is equal to, less than, or greater than N. (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. .TP \f[B]\f[R]\f[C]code:REGEX\f[R]\f[B]\f[R] match by transaction code (eg check number) .TP \f[B]\f[R]\f[C]cur:REGEX\f[R]\f[B]\f[R] match postings or transactions including any amounts whose currency/commodity symbol is fully matched by REGEX. (For a partial match, use \f[C].*REGEX.*\f[R]). Note, to match characters which are regex-significant, like the dollar sign (\f[C]$\f[R]), you need to prepend \f[C]\[rs]\f[R]. And when using the command line you need to add one more level of quoting to hide it from the shell, so eg do: \f[C]hledger print cur:\[aq]\[rs]$\[aq]\f[R] or \f[C]hledger print cur:\[rs]\[rs]$\f[R]. .TP \f[B]\f[R]\f[C]desc:REGEX\f[R]\f[B]\f[R] match transaction descriptions. .TP \f[B]\f[R]\f[C]date:PERIODEXPR\f[R]\f[B]\f[R] match dates within the specified period. PERIODEXPR is a period expression (with no report interval). Examples: \f[C]date:2016\f[R], \f[C]date:thismonth\f[R], \f[C]date:2000/2/1-2/15\f[R], \f[C]date:lastweek-\f[R]. If the \f[C]--date2\f[R] command line flag is present, this matches secondary dates instead. .TP \f[B]\f[R]\f[C]date2:PERIODEXPR\f[R]\f[B]\f[R] match secondary dates within the specified period. .TP \f[B]\f[R]\f[C]depth:N\f[R]\f[B]\f[R] match (or display, depending on command) accounts at or above this depth .TP \f[B]\f[R]\f[C]note:REGEX\f[R]\f[B]\f[R] match transaction notes (part of description right of \f[C]|\f[R], or whole description when there\[aq]s no \f[C]|\f[R]) .TP \f[B]\f[R]\f[C]payee:REGEX\f[R]\f[B]\f[R] match transaction payee/payer names (part of description left of \f[C]|\f[R], or whole description when there\[aq]s no \f[C]|\f[R]) .TP \f[B]\f[R]\f[C]real:, real:0\f[R]\f[B]\f[R] match real or virtual postings respectively .TP \f[B]\f[R]\f[C]status:, status:!, status:*\f[R]\f[B]\f[R] match unmarked, pending, or cleared transactions respectively .TP \f[B]\f[R]\f[C]tag:REGEX[=REGEX]\f[R]\f[B]\f[R] match by tag name, and optionally also by tag value. Note a tag: query is considered to match a transaction if it matches any of the postings. Also remember that postings inherit the tags of their parent transaction. .PP The following special search term is used automatically in hledger-web, only: .TP \f[B]\f[R]\f[C]inacct:ACCTNAME\f[R]\f[B]\f[R] tells hledger-web to show the transaction register for this account. Can be filtered further with \f[C]acct\f[R] etc. .PP Some of these can also be expressed as command-line options (eg \f[C]depth:2\f[R] is equivalent to \f[C]--depth 2\f[R]). Generally you can mix options and query arguments, and the resulting query will be their intersection (perhaps excluding the \f[C]-p/--period\f[R] option). .SS Special characters in arguments and queries .PP In shell command lines, option and argument values which contain \[dq]problematic\[dq] characters, ie spaces, and also characters significant to your shell such as \f[C]<\f[R], \f[C]>\f[R], \f[C](\f[R], \f[C])\f[R], \f[C]|\f[R] and \f[C]$\f[R], should be escaped by enclosing them in quotes or by writing backslashes before the characters. Eg: .PP \f[C]hledger register -p \[aq]last year\[aq] \[dq]accounts receivable (receivable|payable)\[dq] amt:\[rs]>100\f[R]. .SS More escaping .PP Characters significant both to the shell and in regular expressions may need one extra level of escaping. These include parentheses, the pipe symbol and the dollar sign. Eg, to match the dollar symbol, bash users should do: .PP \f[C]hledger balance cur:\[aq]\[rs]$\[aq]\f[R] .PP or: .PP \f[C]hledger balance cur:\[rs]\[rs]$\f[R] .SS Even more escaping .PP When hledger runs an addon executable (eg you type \f[C]hledger ui\f[R], hledger runs \f[C]hledger-ui\f[R]), it de-escapes command-line options and arguments once, so you might need to \f[I]triple\f[R]-escape. Eg in bash, running the ui command and matching the dollar sign, it\[aq]s: .PP \f[C]hledger ui cur:\[aq]\[rs]\[rs]$\[aq]\f[R] .PP or: .PP \f[C]hledger ui cur:\[rs]\[rs]\[rs]\[rs]$\f[R] .PP If you asked why \f[I]four\f[R] slashes above, this may help: .PP .TS tab(@); l l. T{ unescaped: T}@T{ \f[C]$\f[R] T} T{ escaped: T}@T{ \f[C]\[rs]$\f[R] T} T{ double-escaped: T}@T{ \f[C]\[rs]\[rs]$\f[R] T} T{ triple-escaped: T}@T{ \f[C]\[rs]\[rs]\[rs]\[rs]$\f[R] T} .TE .PP (The number of backslashes in fish shell is left as an exercise for the reader.) .PP You can always avoid the extra escaping for addons by running the addon directly: .PP \f[C]hledger-ui cur:\[rs]\[rs]$\f[R] .SS Less escaping .PP Inside an argument file, or in the search field of hledger-ui or hledger-web, or at a GHCI prompt, you need one less level of escaping than at the command line. And backslashes may work better than quotes. Eg: .PP \f[C]ghci> :main balance cur:\[rs]$\f[R] .SS Unicode characters .PP 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[C]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 Input files .PP hledger reads transactions from a data file (and the add command writes to it). By default this file is \f[C]$HOME/.hledger.journal\f[R] (or on Windows, something like \f[C]C:/Users/USER/.hledger.journal\f[R]). You can override this with the \f[C]$LEDGER_FILE\f[R] environment variable: .IP .nf \f[C] $ setenv LEDGER_FILE \[ti]/finance/2016.journal $ hledger stats \f[R] .fi .PP or with the \f[C]-f/--file\f[R] option: .IP .nf \f[C] $ hledger -f /some/file stats \f[R] .fi .PP The file name \f[C]-\f[R] (hyphen) means standard input: .IP .nf \f[C] $ cat some.journal | hledger -f- \f[R] .fi .PP 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(7.8n) lw(39.5n) lw(22.7n). T{ Reader: T}@T{ Reads: T}@T{ Used for file extensions: T} _ T{ \f[C]journal\f[R] T}@T{ hledger journal files and some Ledger journals, for transactions T}@T{ \f[C].journal\f[R] \f[C].j\f[R] \f[C].hledger\f[R] \f[C].ledger\f[R] T} T{ \f[C]timeclock\f[R] T}@T{ timeclock files, for precise time logging T}@T{ \f[C].timeclock\f[R] T} T{ \f[C]timedot\f[R] T}@T{ timedot files, for approximate time logging T}@T{ \f[C].timedot\f[R] T} T{ \f[C]csv\f[R] T}@T{ comma/semicolon/tab/other-separated values, for data import T}@T{ \f[C].csv\f[R] \f[C].ssv\f[R] \f[C].tsv\f[R] T} .TE .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[C]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 When you can\[aq]t ensure the right file extension, not to worry: you can force a specific reader/format by prefixing the file path with the format and a colon. Eg to read a .dat file as csv: .IP .nf \f[C] $ hledger -f csv:/some/csv-file.dat stats $ echo \[aq]i 2009/13/1 08:00:00\[aq] | hledger print -ftimeclock:- \f[R] .fi .PP You can specify multiple \f[C]-f\f[R] options, to read multiple files as one big journal. There are some limitations with this: .IP \[bu] 2 directives in one file will not affect the other files .IP \[bu] 2 balance assertions will not see any account balances from previous files .PP If you need either of those things, you can .IP \[bu] 2 use a single parent file which includes the others .IP \[bu] 2 or concatenate the files into one before reading, eg: \f[C]cat a.journal b.journal | hledger -f- CMD\f[R]. .SS Output destination .PP 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 .nf \f[C] $ hledger print > foo.txt \f[R] .fi .PP Some commands (print, register, stats, the balance commands) also provide the \f[C]-o/--output-file\f[R] option, which does the same thing without needing the shell. Eg: .IP .nf \f[C] $ hledger print -o foo.txt $ hledger print -o - # write to stdout (the default) \f[R] .fi .SS Output format .PP Some commands (print, register, the balance commands) offer a choice of output format. In addition to the usual plain text format (\f[C]txt\f[R]), there are CSV (\f[C]csv\f[R]), HTML (\f[C]html\f[R]), JSON (\f[C]json\f[R]) and SQL (\f[C]sql\f[R]). This is controlled by the \f[C]-O/--output-format\f[R] option: .IP .nf \f[C] $ hledger print -O csv \f[R] .fi .PP or, by a file extension specified with \f[C]-o/--output-file\f[R]: .IP .nf \f[C] $ hledger balancesheet -o foo.html # write HTML to foo.html \f[R] .fi .PP The \f[C]-O\f[R] option can be used to override the file extension if needed: .IP .nf \f[C] $ hledger balancesheet -o foo.txt -O html # write HTML to foo.txt \f[R] .fi .PP Some notes about JSON output: .IP \[bu] 2 This feature is marked experimental, and not yet much used; you should expect our JSON to evolve. Real-world feedback is welcome. .IP \[bu] 2 Our JSON is rather large and verbose, as it is quite 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) .PP Notes about SQL output: .IP \[bu] 2 SQL output is also marked experimental, and much like JSON could use real-world feedback. .IP \[bu] 2 SQL output is expected to work with sqlite, MySQL and PostgreSQL .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[C]delete\f[R] or \f[C]truncate\f[R] SQL statements) or drop tables completely as otherwise your postings will be duped. .SS Regular expressions .PP hledger uses regular expressions in a number of places: .IP \[bu] 2 query terms, on the command line and in the hledger-web search form: \f[C]REGEX\f[R], \f[C]desc:REGEX\f[R], \f[C]cur:REGEX\f[R], \f[C]tag:...=REGEX\f[R] .IP \[bu] 2 CSV rules conditional blocks: \f[C]if REGEX ...\f[R] .IP \[bu] 2 account alias directives and options: \f[C]alias /REGEX/ = REPLACEMENT\f[R], \f[C]--alias /REGEX/=REPLACEMENT\f[R] .PP 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[C]\[rs]b\f[R], \f[C]\[rs]B\f[R], \f[C]\[rs]<\f[R], \f[C]\[rs]>\f[R]) .IP "5." 3 they do not support backreferences; if you write \f[C]\[rs]1\f[R], it will match the digit \f[C]1\f[R]. Except when doing text replacement, eg in account aliases, where backreferences can be used in the replacement string to reference capturing groups in the search regexp. .IP "6." 3 they do not support mode modifiers (\f[C](?s)\f[R]), character classes (\f[C]\[rs]w\f[R], \f[C]\[rs]d\f[R]), or anything else not mentioned above. .PP Some things to note: .IP \[bu] 2 In the \f[C]alias\f[R] directive and \f[C]--alias\f[R] option, regular expressions must be enclosed in forward slashes (\f[C]/REGEX/\f[R]). Elsewhere in hledger, these are not required. .IP \[bu] 2 In queries, to match a regular expression metacharacter like \f[C]$\f[R] as a literal character, prepend a backslash. Eg to search for amounts with the dollar sign in hledger-web, write \f[C]cur:\[rs]$\f[R]. .IP \[bu] 2 On the command line, some metacharacters like \f[C]$\f[R] have a special meaning to the shell and so must be escaped at least once more. See Special characters. .SS Smart dates .PP hledger\[aq]s user interfaces accept a flexible \[dq]smart date\[dq] syntax (unlike dates in the journal file). Smart dates allow some english words, can be relative to today\[aq]s date, and can have less-significant date parts omitted (defaulting to 1). .PP Examples: .PP .TS tab(@); lw(24.2n) lw(45.8n). T{ \f[C]2004/10/1\f[R], \f[C]2004-01-01\f[R], \f[C]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[C]2004\f[R] T}@T{ start of year T} T{ \f[C]2004/10\f[R] T}@T{ start of month T} T{ \f[C]10/1\f[R] T}@T{ month and day in current year T} T{ \f[C]21\f[R] T}@T{ day in current month T} T{ \f[C]october, oct\f[R] T}@T{ start of month in current year T} T{ \f[C]yesterday, today, tomorrow\f[R] T}@T{ -1, 0, 1 days from today T} T{ \f[C]last/this/next day/week/month/quarter/year\f[R] T}@T{ -1, 0, 1 periods from the current period T} T{ \f[C]20181201\f[R] T}@T{ 8 digit YYYYMMDD with valid year month and day T} T{ \f[C]201812\f[R] T}@T{ 6 digit YYYYMM with valid year and month T} .TE .PP Counterexamples - malformed digit sequences might give surprising results: .PP .TS tab(@); lw(11.4n) lw(58.6n). T{ \f[C]201813\f[R] T}@T{ 6 digits with an invalid month is parsed as start of 6-digit year T} T{ \f[C]20181301\f[R] T}@T{ 8 digits with an invalid month is parsed as start of 8-digit year T} T{ \f[C]20181232\f[R] T}@T{ 8 digits with an invalid day gives an error T} T{ \f[C]201801012\f[R] T}@T{ 9+ digits beginning with a valid YYYYMMDD gives an error T} .TE .SS Report start & end date .PP Most hledger reports show the full span of time represented by the journal data, by default. So, the effective report start and end dates will be the earliest and latest transaction or posting dates found in the journal. .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[C]-b/--begin\f[R], \f[C]-e/--end\f[R], \f[C]-p/--period\f[R] or a \f[C]date:\f[R] query (described below). All of these accept the smart date syntax. .PP Some notes: .IP \[bu] 2 As in Ledger, end dates are exclusive, so you need to write the date \f[I]after\f[R] the last day you want to include. .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[C]date:\f[R] queries. That is, \f[C]date:2019-01 date:2019 -p\[aq]2000 to 2030\[aq]\f[R] yields January 2019, the smallest common time span. .PP Examples: .PP .TS tab(@); lw(12.4n) lw(57.6n). T{ \f[C]-b 2016/3/17\f[R] T}@T{ begin on St.\ Patrick\[cq]s day 2016 T} T{ \f[C]-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[C]-b thismonth\f[R] T}@T{ all transactions on or after the 1st of the current month T} T{ \f[C]-p thismonth\f[R] T}@T{ all transactions in the current month T} T{ \f[C]date:2016/3/17..\f[R] T}@T{ the above written as queries instead (\f[C]..\f[R] can also be replaced with \f[C]-\f[R]) T} T{ \f[C]date:..12/1\f[R] T}@T{ T} T{ \f[C]date:thismonth..\f[R] T}@T{ T} T{ \f[C]date:thismonth\f[R] T}@T{ T} .TE .SS Report intervals .PP A report interval can be specified so that commands like register, balance and activity will divide their reports into multiple subperiods. The basic intervals can be selected with one of \f[C]-D/--daily\f[R], \f[C]-W/--weekly\f[R], \f[C]-M/--monthly\f[R], \f[C]-Q/--quarterly\f[R], or \f[C]-Y/--yearly\f[R]. More complex intervals may be specified with a period expression. Report intervals can not be specified with a query. .SS Period expressions .PP The \f[C]-p/--period\f[R] option accepts period expressions, a shorthand way of expressing a start date, end date, and/or report interval all at once. .PP Here\[aq]s a basic period expression specifying the first quarter of 2009. Note, hledger always treats start dates as inclusive and end dates as exclusive: .PP \f[C]-p \[dq]from 2009/1/1 to 2009/4/1\[dq]\f[R] .PP Keywords like \[dq]from\[dq] and \[dq]to\[dq] are optional, and so are the spaces, as long as you don\[aq]t run two dates together. \[dq]to\[dq] can also be written as \[dq]..\[dq] or \[dq]-\[dq]. These are equivalent to the above: .PP .TS tab(@); l. T{ \f[C]-p \[dq]2009/1/1 2009/4/1\[dq]\f[R] T} T{ \f[C]-p2009/1/1to2009/4/1\f[R] T} T{ \f[C]-p2009/1/1..2009/4/1\f[R] T} .TE .PP Dates are smart dates, so if the current year is 2009, the above can also be written as: .PP .TS tab(@); l. T{ \f[C]-p \[dq]1/1 4/1\[dq]\f[R] T} T{ \f[C]-p \[dq]january-apr\[dq]\f[R] T} T{ \f[C]-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 in your journal: .PP .TS tab(@); l l. T{ \f[C]-p \[dq]from 2009/1/1\[dq]\f[R] T}@T{ everything after january 1, 2009 T} T{ \f[C]-p \[dq]from 2009/1\[dq]\f[R] T}@T{ the same T} T{ \f[C]-p \[dq]from 2009\[dq]\f[R] T}@T{ the same T} T{ \f[C]-p \[dq]to 2009\[dq]\f[R] T}@T{ everything before january 1, 2009 T} .TE .PP A single date with no \[dq]from\[dq] or \[dq]to\[dq] defines both the start and end date like so: .PP .TS tab(@); l l. T{ \f[C]-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[C]-p \[dq]2009/1\[dq]\f[R] T}@T{ the month of jan; equivalent to \[lq]2009/1/1 to 2009/2/1\[rq] T} T{ \f[C]-p \[dq]2009/1/1\[dq]\f[R] T}@T{ just that day; equivalent to \[lq]2009/1/1 to 2009/1/2\[rq] T} .TE .PP Or you can specify a single quarter like so: .PP .TS tab(@); l l. T{ \f[C]-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[C]-p \[dq]q4\[dq]\f[R] T}@T{ fourth quarter of the current year T} .TE .PP The argument of \f[C]-p\f[R] can also begin with, or be, a report interval expression. The basic report intervals are \f[C]daily\f[R], \f[C]weekly\f[R], \f[C]monthly\f[R], \f[C]quarterly\f[R], or \f[C]yearly\f[R], which have the same effect as the \f[C]-D\f[R],\f[C]-W\f[R],\f[C]-M\f[R],\f[C]-Q\f[R], or \f[C]-Y\f[R] flags. Between report interval and start/end dates (if any), the word \f[C]in\f[R] is optional. Examples: .PP .TS tab(@); l. T{ \f[C]-p \[dq]weekly from 2009/1/1 to 2009/4/1\[dq]\f[R] T} T{ \f[C]-p \[dq]monthly in 2008\[dq]\f[R] T} T{ \f[C]-p \[dq]quarterly\[dq]\f[R] T} .TE .PP Note that \f[C]weekly\f[R], \f[C]monthly\f[R], \f[C]quarterly\f[R] and \f[C]yearly\f[R] intervals will always start on the first day on week, month, quarter or year accordingly, and will end on the last day of same period, even if associated period expression specifies different explicit start and end date. .PP For example: .PP .TS tab(@); lw(25.5n) lw(44.5n). T{ \f[C]-p \[dq]weekly from 2009/1/1 to 2009/4/1\[dq]\f[R] T}@T{ starts on 2008/12/29, closest preceding Monday T} T{ \f[C]-p \[dq]monthly in 2008/11/25\[dq]\f[R] T}@T{ starts on 2018/11/01 T} T{ \f[C]-p \[dq]quarterly from 2009-05-05 to 2009-06-01\[dq]\f[R] T}@T{ starts on 2009/04/01, ends on 2009/06/30, which are first and last days of Q2 2009 T} T{ \f[C]-p \[dq]yearly from 2009-12-29\[dq]\f[R] T}@T{ starts on 2009/01/01, first day of 2009 T} .TE .PP The following more complex report intervals are also supported: \f[C]biweekly\f[R], \f[C]fortnightly\f[R], \f[C]bimonthly\f[R], \f[C]every day|week|month|quarter|year\f[R], \f[C]every N days|weeks|months|quarters|years\f[R]. .PP All of these will start on the first day of the requested period and end on the last one, as described above. .PP Examples: .PP .TS tab(@); lw(25.5n) lw(44.5n). T{ \f[C]-p \[dq]bimonthly from 2008\[dq]\f[R] T}@T{ periods will have boundaries on 2008/01/01, 2008/03/01, ... T} T{ \f[C]-p \[dq]every 2 weeks\[dq]\f[R] T}@T{ starts on closest preceding Monday T} T{ \f[C]-p \[dq]every 5 month from 2009/03\[dq]\f[R] T}@T{ periods will have boundaries on 2009/03/01, 2009/08/01, ... T} .TE .PP If you want intervals that start on arbitrary day of your choosing and span a week, month or year, you need to use any of the following: .PP \f[C]every Nth day of week\f[R], \f[C]every \f[R], \f[C]every Nth day [of month]\f[R], \f[C]every Nth weekday [of month]\f[R], \f[C]every MM/DD [of year]\f[R], \f[C]every Nth MMM [of year]\f[R], \f[C]every MMM Nth [of year]\f[R]. .PP Examples: .PP .TS tab(@); lw(23.9n) lw(46.1n). T{ \f[C]-p \[dq]every 2nd day of week\[dq]\f[R] T}@T{ periods will go from Tue to Tue T} T{ \f[C]-p \[dq]every Tue\[dq]\f[R] T}@T{ same T} T{ \f[C]-p \[dq]every 15th day\[dq]\f[R] T}@T{ period boundaries will be on 15th of each month T} T{ \f[C]-p \[dq]every 2nd Monday\[dq]\f[R] T}@T{ period boundaries will be on second Monday of each month T} T{ \f[C]-p \[dq]every 11/05\[dq]\f[R] T}@T{ yearly periods with boundaries on 5th of Nov T} T{ \f[C]-p \[dq]every 5th Nov\[dq]\f[R] T}@T{ same T} T{ \f[C]-p \[dq]every Nov 5th\[dq]\f[R] T}@T{ same T} .TE .PP Show historical balances at end of 15th each month (N is exclusive end date): .PP \f[C]hledger balance -H -p \[dq]every 16th day\[dq]\f[R] .PP Group postings from start of wednesday to end of next tuesday (N is start date and exclusive end date): .PP \f[C]hledger register checking -p \[dq]every 3rd day of week\[dq]\f[R] .SS Depth limiting .PP With the \f[C]--depth N\f[R] option (short form: \f[C]-N\f[R]), commands like account, balance and register will show only the uppermost accounts in the account tree, down to level N. Use this when you want a summary with less detail. This flag has the same effect as a \f[C]depth:\f[R] query argument (so \f[C]-2\f[R], \f[C]--depth=2\f[R] or \f[C]depth:2\f[R] are equivalent). .SS Pivoting .PP Normally hledger sums amounts, and organizes them in a hierarchy, based on account name. The \f[C]--pivot FIELD\f[R] option causes it to sum and organize hierarchy based on the value of some other field instead. FIELD can be: \f[C]code\f[R], \f[C]description\f[R], \f[C]payee\f[R], \f[C]note\f[R], or the full name (case insensitive) of any tag. As with account names, values containing \f[C]colon:separated:parts\f[R] will be displayed hierarchically in reports. .PP \f[C]--pivot\f[R] is a general option affecting all reports; you can think of hledger transforming the journal before any other processing, replacing every posting\[aq]s account name with the value of the specified field on that posting, inheriting it from the transaction or using a blank value if it\[aq]s not present. .PP An example: .IP .nf \f[C] 2016/02/16 Member Fee Payment assets:bank account 2 EUR income:member fees -2 EUR ; member: John Doe \f[R] .fi .PP Normal balance report showing account names: .IP .nf \f[C] $ hledger balance 2 EUR assets:bank account -2 EUR income:member fees -------------------- 0 \f[R] .fi .PP Pivoted balance report, using member: tag values instead: .IP .nf \f[C] $ hledger balance --pivot member 2 EUR -2 EUR John Doe -------------------- 0 \f[R] .fi .PP One way to show only amounts with a member: value (using a query, described below): .IP .nf \f[C] $ hledger balance --pivot member tag:member=. -2 EUR John Doe -------------------- -2 EUR \f[R] .fi .PP Another way (the acct: query matches against the pivoted \[dq]account name\[dq]): .IP .nf \f[C] $ hledger balance --pivot member acct:. -2 EUR John Doe -------------------- -2 EUR \f[R] .fi .SS Valuation .PP Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), or to market value (using some market price on a certain date). This is controlled by the \f[C]--value=TYPE[,COMMODITY]\f[R] option, but we also provide the simpler \f[C]-B\f[R]/\f[C]-V\f[R]/\f[C]-X\f[R] flags, and usually one of those is all you need. .SS -B: Cost .PP The \f[C]-B/--cost\f[R] flag converts amounts to their cost or sale amount at transaction time, if they have a transaction price specified. .SS -V: Value .PP The \f[C]-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 .PP The \f[C]-X/--exchange=COMM\f[R] option is like \f[C]-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 .PP Since market prices can change from day to day, market value reports have a valuation date (or more than one), which determines which market prices will be used. .PP For single period reports, if an explicit report end date is specified, that will be used as the valuation date; otherwise the valuation date is \[dq]today\[dq]. .PP For multiperiod reports, each column/period is valued on the last day of the period. .SS Market prices .PP \f[I](experimental)\f[R] .PP 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 (if the \f[C]--infer-value\f[R] flag is used) inferred from transaction prices. .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]chained market price\f[R]: a synthetic price formed by combining the shortest chain of market prices (any of the above types) leading from A to B. .PP Amounts for which no applicable market price can be found, are not converted. .SS --infer-value: market prices from transactions .PP \f[I](experimental)\f[R] .PP 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 transaction prices as additional market prices (as Ledger does) ? We could produce value reports without needing P directives at all. .PP Adding the \f[C]--infer-value\f[R] flag to \f[C]-V\f[R], \f[C]-X\f[R] or \f[C]--value\f[R] enables this. So for example, \f[C]hledger bs -V --infer-value\f[R] will get market prices both from P directives and from transactions. .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 Valuation section carefully, and try adding \f[C]--debug\f[R] or \f[C]--debug=2\f[R] to troubleshoot. .PP \f[C]--infer-value\f[R] can infer market prices from: .IP \[bu] 2 multicommodity transactions with explicit prices (\f[C]\[at]\f[R]/\f[C]\[at]\[at]\f[R]) .IP \[bu] 2 multicommodity transactions with implicit prices (no \f[C]\[at]\f[R], two commodities, unbalanced). (With these, the order of postings matters. \f[C]hledger print -x\f[R] can be useful for troubleshooting.) .IP \[bu] 2 but not, currently, from \[dq]more correct\[dq] multicommodity transactions (no \f[C]\[at]\f[R], multiple commodities, balanced). .SS Valuation commodity .PP \f[I](experimental)\f[R] .PP \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[C]--infer-value\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[C]-V\f[R] will convert, and to what. .IP \[bu] 2 If you have no P directives, and use the \f[C]--infer-value\f[R] flag, transaction prices determine it. .PP Amounts for which no valuation commodity can be found are not converted. .SS Simple valuation examples .PP Here are some quick examples of \f[C]-V\f[R]: .IP .nf \f[C] ; one euro is worth this many dollars from nov 1 P 2016/11/01 \[Eu] $1.10 ; purchase some euros on nov 3 2016/11/3 assets:euros \[Eu]100 assets:checking ; the euro is worth fewer dollars by dec 21 P 2016/12/21 \[Eu] $1.03 \f[R] .fi .PP How many euros do I have ? .IP .nf \f[C] $ hledger -f t.j bal -N euros \[Eu]100 assets:euros \f[R] .fi .PP What are they worth at end of nov 3 ? .IP .nf \f[C] $ hledger -f t.j bal -N euros -V -e 2016/11/4 $110.00 assets:euros \f[R] .fi .PP What are they worth after 2016/12/21 ? (no report end date specified, defaults to today) .IP .nf \f[C] $ hledger -f t.j bal -N euros -V $103.00 assets:euros \f[R] .fi .SS --value: Flexible valuation .PP \f[C]-B\f[R], \f[C]-V\f[R] and \f[C]-X\f[R] are special cases of the more general \f[C]--value\f[R] option: .IP .nf \f[C] --value=TYPE[,COMM] TYPE is cost, then, end, now or YYYY-MM-DD. COMM is an optional commodity symbol. Shows amounts converted to: - cost commodity using transaction prices (then optionally to COMM using market prices at period end(s)) - 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 \f[R] .fi .PP The TYPE part selects cost or value and valuation date: .TP \f[B]\f[CB]--value=cost\f[B]\f[R] Convert amounts to cost, using the prices recorded in transactions. .TP \f[B]\f[CB]--value=then\f[B]\f[R] Convert amounts to their value in the default valuation commodity, using market prices on each posting\[aq]s date. This is currently supported only by the print and register commands. .TP \f[B]\f[CB]--value=end\f[B]\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[B]\f[CB]--value=now\f[B]\f[R] Convert amounts to their value in the default valuation commodity using current market prices (as of when report is generated). .TP \f[B]\f[CB]--value=YYYY-MM-DD\f[B]\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[C],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 .PP Here are some examples showing the effect of \f[C]--value\f[R], as seen with \f[C]print\f[R]: .IP .nf \f[C] 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 \f[R] .fi .PP Show the cost of each posting: .IP .nf \f[C] $ hledger -f- print --value=cost 2000-01-01 (a) 5 B 2000-02-01 (a) 6 B 2000-03-01 (a) 7 B \f[R] .fi .PP Show the value as of the last day of the report period (2000-02-29): .IP .nf \f[C] $ hledger -f- print --value=end date:2000/01-2000/03 2000-01-01 (a) 2 B 2000-02-01 (a) 2 B \f[R] .fi .PP With no report period specified, that shows the value as of the last day of the journal (2000-03-01): .IP .nf \f[C] $ hledger -f- print --value=end 2000-01-01 (a) 3 B 2000-02-01 (a) 3 B 2000-03-01 (a) 3 B \f[R] .fi .PP Show the current value (the 2000-04-01 price is still in effect today): .IP .nf \f[C] $ hledger -f- print --value=now 2000-01-01 (a) 4 B 2000-02-01 (a) 4 B 2000-03-01 (a) 4 B \f[R] .fi .PP Show the value on 2000/01/15: .IP .nf \f[C] $ 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 \f[R] .fi .PP You may need to explicitly set a commodity\[aq]s display style, when reverse prices are used. Eg this output might be surprising: .IP .nf \f[C] P 2000-01-01 A 2B 2000-01-01 a 1B b \f[R] .fi .IP .nf \f[C] $ hledger print -x -X A 2000-01-01 a 0 b 0 \f[R] .fi .PP Explanation: because there\[aq]s no amount or commodity directive specifying a display style for A, 0.5A gets the default style, which shows no decimal digits. Because the displayed amount looks like zero, the commodity symbol and minus sign are not displayed either. Adding a commodity directive sets a more useful display style for A: .IP .nf \f[C] P 2000-01-01 A 2B commodity 0.00A 2000-01-01 a 1B b \f[R] .fi .IP .nf \f[C] $ hledger print -X A 2000-01-01 a 0.50A b -0.50A \f[R] .fi .SS Effect of valuation on reports .PP 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(11.7n) lw(11.2n) lw(11.9n) lw(13.1n) lw(12.4n) lw(9.8n). T{ Report type T}@T{ \f[C]-B\f[R], \f[C]--value=cost\f[R] T}@T{ \f[C]-V\f[R], \f[C]-X\f[R] T}@T{ \f[C]--value=then\f[R] T}@T{ \f[C]--value=end\f[R] T}@T{ \f[C]--value=DATE\f[R], \f[C]--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 (with -H) T}@T{ cost T}@T{ value at day before report or journal start T}@T{ not supported T}@T{ value at day before report or journal start T}@T{ value at DATE/today T} T{ posting amounts (no report interval) 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{ 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{ balances (no report interval) T}@T{ sums of costs T}@T{ value at report end or today of sums of postings T}@T{ not supported T}@T{ value at report or journal end of sums of postings T}@T{ value at DATE/today of sums of postings T} T{ balances (with report interval) T}@T{ sums of costs T}@T{ value at period ends of sums of postings T}@T{ not supported T}@T{ value at period ends of sums of postings T}@T{ value at DATE/today of sums of postings T} T{ starting balances (with report interval and -H) T}@T{ sums of costs of postings before report start T}@T{ sums of postings before report start T}@T{ not supported T}@T{ sums of postings before report start T}@T{ sums of postings before report start T} T{ budget amounts with --budget T}@T{ like balances T}@T{ like balances T}@T{ not supported T}@T{ like balances T}@T{ like balances T} T{ grand total (no report interval) T}@T{ sum of displayed values T}@T{ sum of displayed values T}@T{ not supported T}@T{ sum of displayed values T}@T{ sum of displayed values T} T{ row totals/averages (with report interval) T}@T{ sums/averages of displayed values T}@T{ sums/averages of displayed values T}@T{ not supported 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{ not supported T}@T{ sums of displayed values T}@T{ sums of displayed values T} T{ grand total/average T}@T{ sum/average of column totals T}@T{ sum/average of column totals T}@T{ not supported 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[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 COMMANDS .PP hledger provides a number of subcommands; \f[C]hledger\f[R] with no arguments shows a list. .PP If you install additional \f[C]hledger-*\f[R] packages, or if you put programs or scripts named \f[C]hledger-NAME\f[R] in your PATH, these will also be listed as subcommands. .PP Run a subcommand by writing its name as first argument (eg \f[C]hledger incomestatement\f[R]). You can also write one of the standard short aliases displayed in parentheses in the command list (\f[C]hledger b\f[R]), or any any unambiguous prefix of a command name (\f[C]hledger inc\f[R]). .PP Here are all the builtin commands in alphabetical order. See also \f[C]hledger\f[R] for a more organised command list, and \f[C]hledger CMD -h\f[R] for detailed command help. .SS accounts .PP accounts, a .PD 0 .P .PD Show account names. .PP This command lists account names, either declared with account directives (--declared), posted to (--used), or both (the default). With query arguments, only matched account names and account names referenced by matched postings are shown. It shows a flat list by default. With \f[C]--tree\f[R], it uses indentation to show the account hierarchy. In flat mode you can add \f[C]--drop N\f[R] to omit the first few account name components. Account names can be depth-clipped with \f[C]depth:N\f[R] or \f[C]--depth N\f[R] or \f[C]-N\f[R]. .PP Examples: .IP .nf \f[C] $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts \f[R] .fi .SS activity .PP activity .PD 0 .P .PD 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 .nf \f[C] $ hledger activity --quarterly 2008-01-01 ** 2008-04-01 ******* 2008-07-01 2008-10-01 ** \f[R] .fi .SS add .PP add .PD 0 .P .PD 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[C]add\f[R] command, which prompts interactively on the console for new transactions, and appends them to the journal file (if there are multiple \f[C]-f FILE\f[R] options, the first file is used.) Existing transactions are not changed. This is the only hledger command that writes to the journal file. .PP To use it, just run \f[C]hledger add\f[R] and follow the prompts. You can add as many transactions as you like; when you are finished, enter \f[C].\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, descriptions, dates (\f[C]yesterday\f[R], \f[C]today\f[R], \f[C]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[C]<\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 the tutorial for a detailed explanation): .IP .nf \f[C] $ 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]: $ \f[R] .fi .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 .PP aregister, areg .PD 0 .P .PD Show transactions affecting a particular account, and the account\[aq]s running balance. .PP \f[C]aregister\f[R] shows the transactions affecting a particular account (and its subaccounts), from the point of view of that account. Each line shows: .IP \[bu] 2 the transaction\[aq]s (or posting\[aq]s, see below) date .IP \[bu] 2 the names of the other account(s) involved .IP \[bu] 2 the net change to this account\[aq]s balance .IP \[bu] 2 the account\[aq]s historical running balance (including balance from transactions before the report start date). .PP With \f[C]aregister\f[R], each line represents a whole transaction - as in hledger-ui, hledger-web, and your bank statement. By contrast, the \f[C]register\f[R] command shows individual postings, across all accounts. You might prefer \f[C]aregister\f[R] for reconciling with real-world asset/liability accounts, and \f[C]register\f[R] for reviewing detailed revenues/expenses. .PP An account must be specified as the first argument, which should be the full account name or an account pattern (regular expression). aregister will show transactions in this account (the first one matched) and any of its subaccounts. .PP Any additional arguments form a query which will filter the transactions shown. .PP Transactions making a net change of zero are not shown by default; add the \f[C]-E/--empty\f[R] flag to show them. .SS aregister and custom posting dates .PP Transactions whose date is outside the report period can still be shown, if they have a posting to this account dated inside the report period. (And in this case it\[aq]s the posting date that is shown.) This ensures that \f[C]aregister\f[R] can show an accurate historical running balance, matching the one shown by \f[C]register -H\f[R] with the same arguments. .PP To filter strictly by transaction date instead, add the \f[C]--txn-dates\f[R] flag. If you use this flag and some of your postings have custom dates, it\[aq]s probably best to assume the running balance is wrong. .SS Output format .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], and \f[C]json\f[R]. .PP Examples: .PP Show all transactions and historical running balance in the first account whose name contains \[dq]checking\[dq]: .IP .nf \f[C] $ hledger areg checking \f[R] .fi .PP Show transactions and historical running balance in all asset accounts during july: .IP .nf \f[C] $ hledger areg assets date:jul \f[R] .fi .SS balance .PP balance, bal, b .PD 0 .P .PD Show accounts and their balances. .PP The balance command is hledger\[aq]s most versatile command. Note, despite the name, it is not always used for showing real-world account balances; the more accounting-aware balancesheet and incomestatement may be more convenient for that. .PP By default, it displays all accounts, and each account\[aq]s change in balance during the entire period of the journal. Balance changes are calculated by adding up the postings in each account. You can limit the postings matched, by a query, to see fewer accounts, changes over a different time period, changes from only cleared transactions, etc. .PP If you include an account\[aq]s complete history of postings in the report, the balance change is equivalent to the account\[aq]s current ending balance. For a real-world account, typically you won\[aq]t have all transactions in the journal; instead you\[aq]ll have all transactions after a certain date, and an \[dq]opening balances\[dq] transaction setting the correct starting balance on that date. Then the balance command will show real-world account balances. In some cases the -H/--historical flag is used to ensure this (more below). .PP The balance command can produce several styles of report: .SS Classic balance report .PP This is the original balance report, as found in Ledger. It usually looks like this: .IP .nf \f[C] $ hledger balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 \f[R] .fi .PP By default, accounts are displayed hierarchically, with subaccounts indented below their parent. At each level of the tree, accounts are sorted by account code if any, then by account name. Or with \f[C]-S/--sort-amount\f[R], by their balance amount, largest first. .PP \[dq]Boring\[dq] accounts, which contain a single interesting subaccount and no balance of their own, are elided into the following line for more compact output. (Eg above, the \[dq]liabilities\[dq] account.) Use \f[C]--no-elide\f[R] to prevent this. .PP Account balances are \[dq]inclusive\[dq] - they include the balances of any subaccounts. .PP Accounts which have zero balance (and no non-zero subaccounts) are omitted. Use \f[C]-E/--empty\f[R] to show them. .PP A final total is displayed by default; use \f[C]-N/--no-total\f[R] to suppress it, eg: .IP .nf \f[C] $ hledger balance -p 2008/6 expenses --no-total $2 expenses $1 food $1 supplies \f[R] .fi .SS Customising the classic balance report .PP You can customise the layout of classic balance reports with \f[C]--format FMT\f[R]: .IP .nf \f[C] $ hledger 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 \f[R] .fi .PP The FMT format string (plus a newline) specifies the formatting applied to each account/balance pair. It may contain any suitable text, with data fields interpolated like so: .PP \f[C]%[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[C]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[C]account\f[R] - the account\[aq]s name .IP \[bu] 2 \f[C]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[C]%_\f[R] - render on multiple lines, bottom-aligned (the default) .IP \[bu] 2 \f[C]%\[ha]\f[R] - render on multiple lines, top-aligned .IP \[bu] 2 \f[C]%,\f[R] - render on one line, comma-separated .PP There are some quirks. Eg in one-line mode, \f[C]%(depth_spacer)\f[R] has no effect, instead \f[C]%(account)\f[R] has indentation built in. Experimentation may be needed to get pleasing results. .PP Some example formats: .IP \[bu] 2 \f[C]%(total)\f[R] - the account\[aq]s total .IP \[bu] 2 \f[C]%-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[C]%,%-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[C]%20(total) %2(depth_spacer)%-(account)\f[R] - the default format for the single-column balance report .SS Colour support .PP In terminal output, when colour is enabled, the balance command shows negative amounts in red. .SS Flat mode .PP To see a flat list instead of the default hierarchical display, use \f[C]--flat\f[R]. In this mode, accounts (unless depth-clipped) show their full names and \[dq]exclusive\[dq] balance, excluding any subaccount balances. In this mode, you can also use \f[C]--drop N\f[R] to omit the first few account name components. .IP .nf \f[C] $ hledger balance -p 2008/6 expenses -N --flat --drop 1 $1 food $1 supplies \f[R] .fi .SS Depth limited balance reports .PP With \f[C]--depth N\f[R] or \f[C]depth:N\f[R] or just \f[C]-N\f[R], balance reports show accounts only to the specified numeric depth. This is very useful to summarise a complex set of accounts and get an overview. .IP .nf \f[C] $ hledger balance -N -1 $-1 assets $2 expenses $-2 income $1 liabilities \f[R] .fi .PP Flat-mode balance reports, which normally show exclusive balances, show inclusive balances at the depth limit. .SS Percentages .PP With \f[C]-%\f[R] or \f[C]--percent\f[R], balance reports show each account\[aq]s value expressed as a percentage of the column\[aq]s total. This is useful to get an overview of the relative sizes of account balances. For example to obtain an overview of expenses: .IP .nf \f[C] $ hledger balance expenses -% 100.0 % expenses 50.0 % food 50.0 % supplies -------------------- 100.0 % \f[R] .fi .PP Note that \f[C]--tree\f[R] does not have an effect on \f[C]-%\f[R]. The percentages are always relative to the total sum of each column, they are never relative to the parent account. .PP Since the percentages are relative to the columns sum, it is usually not useful to calculate percentages if the signs of the amounts are mixed. Although the results are technically correct, they are most likely useless. Especially in a balance report that sums up to zero (eg \f[C]hledger balance -B\f[R]) all percentage values will be zero. .PP This flag does not work if the report contains any mixed commodity accounts. If there are mixed commodity accounts in the report be sure to use \f[C]-V\f[R] or \f[C]-B\f[R] to coerce the report into using a single commodity. .SS Multicolumn balance report .PP Multicolumn or tabular balance reports are a very useful hledger feature, and usually the preferred style. They share many of the above features, but they show the report as a table, with columns representing time periods. This mode is activated by providing a reporting interval. .PP There are three types of multicolumn balance report, showing different information: .IP "1." 3 By default: each column shows the sum of postings in that period, ie the account\[aq]s change of balance in that period. This is useful eg for a monthly income statement: .RS 4 .IP .nf \f[C] $ hledger balance --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 \f[R] .fi .RE .IP "2." 3 With \f[C]--cumulative\f[R]: each column shows the ending balance for that period, accumulating the changes across periods, starting from 0 at the report start date: .RS 4 .IP .nf \f[C] $ hledger balance --quarterly income expenses -E --cumulative Ending balances (cumulative) in 2008: || 2008/03/31 2008/06/30 2008/09/30 2008/12/31 ===================++================================================= expenses:food || 0 $1 $1 $1 expenses:supplies || 0 $1 $1 $1 income:gifts || 0 $-1 $-1 $-1 income:salary || $-1 $-1 $-1 $-1 -------------------++------------------------------------------------- || $-1 0 0 0 \f[R] .fi .RE .IP "3." 3 With \f[C]--historical/-H\f[R]: each column shows the actual historical ending balance for that period, accumulating the changes across periods, starting from the actual balance at the report start date. This is useful eg for a multi-period balance sheet, and when you are showing only the data after a certain start date: .RS 4 .IP .nf \f[C] $ hledger balance \[ha]assets \[ha]liabilities --quarterly --historical --begin 2008/4/1 Ending balances (historical) in 2008/04/01-2008/12/31: || 2008/06/30 2008/09/30 2008/12/31 ======================++===================================== assets:bank:checking || $1 $1 0 assets:bank:saving || $1 $1 $1 assets:cash || $-2 $-2 $-2 liabilities:debts || 0 0 $1 ----------------------++------------------------------------- || 0 0 0 \f[R] .fi .RE .PP Note that \f[C]--cumulative\f[R] or \f[C]--historical/-H\f[R] disable \f[C]--row-total/-T\f[R], since summing end balances generally does not make sense. .PP Multicolumn balance reports display accounts in flat mode by default; to see the hierarchy, use \f[C]--tree\f[R]. .PP With a reporting interval (like \f[C]--quarterly\f[R] above), the report start/end dates will be adjusted if necessary so that they encompass the displayed report periods. This is so that the first and last periods will be \[dq]full\[dq] and comparable to the others. .PP The \f[C]-E/--empty\f[R] flag does two things in multicolumn balance reports: first, the report will show all columns within the specified report period (without -E, leading and trailing columns with all zeroes are not shown). Second, all accounts which existed at the report start date will be considered, not just the ones with activity during the report period (use -E to include low-activity accounts which would otherwise would be omitted). .PP The \f[C]-T/--row-total\f[R] flag adds an additional column showing the total for each row. .PP The \f[C]-A/--average\f[R] flag adds a column showing the average value in each row. .PP Here\[aq]s an example of all three: .IP .nf \f[C] $ hledger balance -Q income expenses --tree -ETA Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 Total Average ============++=================================================== expenses || 0 $2 0 0 $2 $1 food || 0 $1 0 0 $1 0 supplies || 0 $1 0 0 $1 0 income || $-1 $-1 0 0 $-2 $-1 gifts || 0 $-1 0 0 $-1 0 salary || $-1 0 0 0 $-1 0 ------------++--------------------------------------------------- || $-1 $1 0 0 0 0 (Average is rounded to the dollar here since all journal amounts are) \f[R] .fi .PP The \f[C]--transpose\f[R] flag can be used to exchange the rows and columns of a multicolumn report. .PP When showing multicommodity amounts, multicolumn balance reports will elide any amounts which have more than two commodities, since otherwise columns could get very wide. The \f[C]--no-elide\f[R] flag disables this. Hiding totals with the \f[C]-N/--no-total\f[R] flag can also help reduce the width of multicommodity reports. .PP When the report is still too wide, a good workaround is to pipe it into \f[C]less -RS\f[R] (-R for colour, -S to chop long lines). Eg: \f[C]hledger bal -D --color=yes | less -RS\f[R]. .SS Budget report .PP With \f[C]--budget\f[R], extra columns are displayed showing budget goals for each account and period, if any. Budget goals are defined by periodic transactions. This is very useful for comparing planned and actual income, expenses, time usage, etc. --budget is most often combined with a report interval. .PP For example, you can take average monthly expenses in the common expense categories to construct a minimal monthly budget: .IP .nf \f[C] ;; Budget \[ti] monthly income $2000 expenses:food $400 expenses:bus $50 expenses:movies $30 assets:bank:checking ;; Two months worth of expenses 2017-11-01 income $1950 expenses:food $396 expenses:bus $49 expenses:movies $30 expenses:supplies $20 assets:bank:checking 2017-12-01 income $2100 expenses:food $412 expenses:bus $53 expenses:gifts $100 assets:bank:checking \f[R] .fi .PP You can now see a monthly budget report: .IP .nf \f[C] $ hledger balance -M --budget Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] \f[R] .fi .PP This is different from a normal balance report in several ways: .IP \[bu] 2 Only accounts with budget goals during the report period are shown, by default. .IP \[bu] 2 In each column, in square brackets after the actual amount, budget goal amounts are shown, and the actual/goal percentage. (Note: budget goals should be in the same commodity as the actual amount.) .IP \[bu] 2 All parent accounts are always shown, even in flat mode. Eg assets, assets:bank, and expenses above. .IP \[bu] 2 Amounts always include all subaccounts, budgeted or unbudgeted, even in flat mode. .PP This means that the numbers displayed will not always add up! Eg above, the \f[C]expenses\f[R] actual amount includes the gifts and supplies transactions, but the \f[C]expenses:gifts\f[R] and \f[C]expenses:supplies\f[R] accounts are not shown, as they have no budget amounts declared. .PP This can be confusing. When you need to make things clearer, use the \f[C]-E/--empty\f[R] flag, which will reveal all accounts including unbudgeted ones, giving the full picture. Eg: .IP .nf \f[C] $ hledger balance -M --budget --empty Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:gifts || 0 $100 expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] expenses:supplies || $20 0 income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] \f[R] .fi .PP You can roll over unspent budgets to next period with \f[C]--cumulative\f[R]: .IP .nf \f[C] $ hledger balance -M --budget --cumulative Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank:checking || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] expenses || $495 [ 103% of $480] $1060 [ 110% of $960] expenses:bus || $49 [ 98% of $50] $102 [ 102% of $100] expenses:food || $396 [ 99% of $400] $808 [ 101% of $800] expenses:movies || $30 [ 100% of $30] $30 [ 50% of $60] income || $1950 [ 98% of $2000] $4050 [ 101% of $4000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] \f[R] .fi .PP For more examples, see Budgeting and Forecasting. .SS Nested budgets .PP You can add budgets to any account in your account hierarchy. If you have budgets on both parent account and some of its children, then budget(s) of the child account(s) would be added to the budget of their parent, much like account balances behave. .PP In the most simple case this means that once you add a budget to any account, all its parents would have budget as well. .PP To illustrate this, consider the following budget: .IP .nf \f[C] \[ti] monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities \f[R] .fi .PP With this, monthly budget for electronics is defined to be $100 and budget for personal expenses is an additional $1000, which implicitly means that budget for both \f[C]expenses:personal\f[R] and \f[C]expenses\f[R] is $1100. .PP Transactions in \f[C]expenses:personal:electronics\f[R] will be counted both towards its $100 budget and $1100 of \f[C]expenses:personal\f[R] , and transactions in any other subaccount of \f[C]expenses:personal\f[R] would be counted towards only towards the budget of \f[C]expenses:personal\f[R]. .PP For example, let\[aq]s consider these transactions: .IP .nf \f[C] \[ti] monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities 2019/01/01 Google home hub expenses:personal:electronics $90.00 liabilities $-90.00 2019/01/02 Phone screen protector expenses:personal:electronics:upgrades $10.00 liabilities 2019/01/02 Weekly train ticket expenses:personal:train tickets $153.00 liabilities 2019/01/03 Flowers expenses:personal $30.00 liabilities \f[R] .fi .PP As you can see, we have transactions in \f[C]expenses:personal:electronics:upgrades\f[R] and \f[C]expenses:personal:train tickets\f[R], and since both of these accounts are without explicitly defined budget, these transactions would be counted towards budgets of \f[C]expenses:personal:electronics\f[R] and \f[C]expenses:personal\f[R] accordingly: .IP .nf \f[C] $ hledger balance --budget -M Budget performance in 2019/01: || Jan ===============================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] liabilities || $-283.00 [ 26% of $-1100.00] -------------------------------++------------------------------- || 0 [ 0] \f[R] .fi .PP And with \f[C]--empty\f[R], we can get a better picture of budget allocation and consumption: .IP .nf \f[C] $ hledger balance --budget -M --empty Budget performance in 2019/01: || Jan ========================================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] expenses:personal:electronics:upgrades || $10.00 expenses:personal:train tickets || $153.00 liabilities || $-283.00 [ 26% of $-1100.00] ----------------------------------------++------------------------------- || 0 [ 0] \f[R] .fi .SS Output format .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], (multicolumn non-budget reports only) \f[C]html\f[R], and (experimental) \f[C]json\f[R]. .SS balancesheet .PP balancesheet, bs .PD 0 .P .PD 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 The asset and liability accounts shown are those accounts declared with the \f[C]Asset\f[R] or \f[C]Cash\f[R] or \f[C]Liability\f[R] type, or otherwise all accounts under a top-level \f[C]asset\f[R] or \f[C]liability\f[R] account (case insensitive, plurals allowed). .PP Example: .IP .nf \f[C] $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 \f[R] .fi .PP With a reporting interval, multiple columns will be shown, one for each report period. As with multicolumn balance reports, you can alter the report mode with \f[C]--change\f[R]/\f[C]--cumulative\f[R]/\f[C]--historical\f[R]. Normally balancesheet shows historical ending balances, which is what you need for a balance sheet; note this means it ignores report begin dates (and \f[C]-T/--row-total\f[R], since summing end balances generally does not make sense). Instead of absolute values percentages can be displayed with \f[C]-%\f[R]. .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], \f[C]html\f[R], and (experimental) \f[C]json\f[R]. .SS balancesheetequity .PP balancesheetequity, bse .PD 0 .P .PD 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 The asset, liability and equity accounts shown are those accounts declared with the \f[C]Asset\f[R], \f[C]Cash\f[R], \f[C]Liability\f[R] or \f[C]Equity\f[R] type, or otherwise all accounts under a top-level \f[C]asset\f[R], \f[C]liability\f[R] or \f[C]equity\f[R] account (case insensitive, plurals allowed). .PP Example: .IP .nf \f[C] $ 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 \f[R] .fi .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], \f[C]html\f[R], and (experimental) \f[C]json\f[R]. .SS cashflow .PP cashflow, cf .PD 0 .P .PD This command displays a cashflow statement, showing the inflows and outflows affecting \[dq]cash\[dq] (ie, liquid) assets. Amounts are shown with normal positive sign, as in conventional financial statements. .PP The \[dq]cash\[dq] accounts shown are those accounts declared with the \f[C]Cash\f[R] type, or otherwise all accounts under a top-level \f[C]asset\f[R] account (case insensitive, plural allowed) which do not have \f[C]fixed\f[R], \f[C]investment\f[R], \f[C]receivable\f[R] or \f[C]A/R\f[R] in their name. .PP Example: .IP .nf \f[C] $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 \f[R] .fi .PP With a reporting interval, multiple columns will be shown, one for each report period. Normally cashflow shows changes in assets per period, though as with multicolumn balance reports you can alter the report mode with \f[C]--change\f[R]/\f[C]--cumulative\f[R]/\f[C]--historical\f[R]. Instead of absolute values percentages can be displayed with \f[C]-%\f[R]. .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], \f[C]html\f[R], and (experimental) \f[C]json\f[R]. .SS check-dates .PP check-dates .PD 0 .P .PD Check that transactions are sorted by increasing date. With --date2, checks secondary dates instead. With --strict, dates must also be unique. With a query, only matched transactions\[aq] dates are checked. Reads the default journal file, or another specified with -f. .SS check-dupes .PP check-dupes .PD 0 .P .PD Reports account names having the same leaf but different prefixes. In other words, two or more leaves that are categorized differently. Reads the default journal file, or another specified as an argument. .PP An example: http://stefanorodighiero.net/software/hledger-dupes.html .SS close .PP close, equity .PD 0 .P .PD Prints a \[dq]closing balances\[dq] transaction and an \[dq]opening balances\[dq] transaction that bring account balances to and from zero, respectively. These can be added to your journal file(s), eg to bring asset/liability balances forward into a new journal file, or to close out revenues/expenses to retained earnings at the end of a period. .PP You can print just one of these transactions by using the \f[C]--close\f[R] or \f[C]--open\f[R] flag. You can customise their descriptions with the \f[C]--close-desc\f[R] and \f[C]--open-desc\f[R] options. .PP One amountless posting to \[dq]equity:opening/closing balances\[dq] is added to balance the transactions, by default. You can customise this account name with \f[C]--close-acct\f[R] and \f[C]--open-acct\f[R]; if you specify only one of these, it will be used for both. .PP With \f[C]--x/--explicit\f[R], the equity posting\[aq]s amount will be shown. And if it involves multiple commodities, a posting for each commodity will be shown, as with the print command. .PP With \f[C]--interleaved\f[R], the equity postings are shown next to the postings they balance, which makes troubleshooting easier. .PP By default, transaction prices in the journal are ignored when generating the closing/opening transactions. With \f[C]--show-costs\f[R], this cost information is preserved (\f[C]balance -B\f[R] reports will be unchanged after the transition). Separate postings are generated for each cost in each commodity. Note this can generate very large journal entries, if you have many foreign currency or investment transactions. .SS close usage .PP If you split your journal files by time (eg yearly), you will typically run this command at the end of the year, and save the closing transaction as last entry of the old file, and the opening transaction as the first entry of the new file. This makes the files self contained, so that correct balances are reported no matter which of them are loaded. Ie, if you load just one file, the balances are initialised correctly; or if you load several files, the redundant closing/opening transactions cancel each other out. (They will show up in print or register reports; you can exclude them with a query like \f[C]not:desc:\[aq](opening|closing) balances\[aq]\f[R].) .PP If you\[aq]re running a business, you might also use this command to \[dq]close the books\[dq] at the end of an accounting period, transferring income statement account balances to retained earnings. (You may want to change the equity account name to something like \[dq]equity:retained earnings\[dq].) .PP By default, the closing transaction is dated yesterday, the balances are calculated as of end of yesterday, and the opening transaction is dated today. To close on some other date, use: \f[C]hledger close -e OPENINGDATE\f[R]. Eg, to close/open on the 2018/2019 boundary, use \f[C]-e 2019\f[R]. You can also use -p or \f[C]date:PERIOD\f[R] (any starting date is ignored). .PP Both transactions will include balance assertions for the closed/reopened accounts. You probably shouldn\[aq]t use status or realness filters (like -C or -R or \f[C]status:\f[R]) with this command, or the generated balance assertions will depend on these flags. Likewise, if you run this command with --auto, the balance assertions will probably always require --auto. .PP Examples: .PP Carrying asset/liability balances into a new file for 2019: .IP .nf \f[C] $ hledger close -f 2018.journal -e 2019 assets liabilities --open # (copy/paste the output to the start of your 2019 journal file) $ hledger close -f 2018.journal -e 2019 assets liabilities --close # (copy/paste the output to the end of your 2018 journal file) \f[R] .fi .PP Now: .IP .nf \f[C] $ hledger bs -f 2019.journal # one file - balances are correct $ hledger bs -f 2018.journal -f 2019.journal # two files - balances still correct $ hledger bs -f 2018.journal not:desc:closing # to see year-end balances, must exclude closing txn \f[R] .fi .PP Transactions spanning the closing date can complicate matters, breaking balance assertions: .IP .nf \f[C] 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 assets:bank:checking -5 ; [2019/1/2] \f[R] .fi .PP Here\[aq]s one way to resolve that: .IP .nf \f[C] ; in 2018.journal: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 liabilities:pending ; in 2019.journal: 2019/1/2 clearance of last year\[aq]s pending transactions liabilities:pending 5 = 0 assets:checking \f[R] .fi .SS codes .PP codes .PD 0 .P .PD 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[C]-E\f[R]/\f[C]--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 .nf \f[C] 1/1 (123) (a) 1 1/1 () (a) 1 1/1 (a) 1 1/1 (126) (a) 1 \f[R] .fi .IP .nf \f[C] $ hledger codes 123 124 126 \f[R] .fi .IP .nf \f[C] $ hledger codes -E 123 124 126 \f[R] .fi .SS commodities .PP commodities .PD 0 .P .PD List all commodity/currency symbols used or declared in the journal. .SS descriptions .PP descriptions .PD 0 .P .PD 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 .nf \f[C] $ hledger descriptions Store Name Gas Station | Petrol Person A \f[R] .fi .SS diff .PP diff .PD 0 .P .PD 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 .nf \f[C] $ 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: \f[R] .fi .SS files .PP files .PD 0 .P .PD List all files included in the journal. With a REGEX argument, only file names matching the regular expression (case sensitive) are shown. .SS help .PP help .PD 0 .P .PD Show any of the hledger manuals. .PP The \f[C]help\f[R] command displays any of the main hledger manuals, in one of several ways. Run it with no argument to list the manuals, or provide a full or partial manual name to select one. .PP hledger manuals are available in several formats. hledger help will use the first of these display methods that it finds: info, man, $PAGER, less, stdout (or when non-interactive, just stdout). You can force a particular viewer with the \f[C]--info\f[R], \f[C]--man\f[R], \f[C]--pager\f[R], \f[C]--cat\f[R] flags. .PP Examples: .IP .nf \f[C] $ hledger help Please choose a manual by typing \[dq]hledger help MANUAL\[dq] (a substring is ok). Manuals: hledger hledger-ui hledger-web journal csv timeclock timedot \f[R] .fi .IP .nf \f[C] $ hledger help h --man hledger(1) hledger User Manuals hledger(1) NAME hledger - a command-line accounting tool SYNOPSIS hledger [-f FILE] COMMAND [OPTIONS] [ARGS] hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS] hledger DESCRIPTION hledger is a cross-platform program for tracking money, time, or any \&... \f[R] .fi .SS import .PP import .PD 0 .P .PD Read new transactions added to each FILE since last run, and add them to the main journal file. Or with --dry-run, just print the transactions that would be added. Or with --catchup, just mark all of the FILEs\[aq] transactions as imported, without actually importing any. .PP The input files are specified as arguments - no need to write -f before each one. So eg to add new transactions from all CSV files to the main journal, it\[aq]s just: \f[C]hledger import *.csv\f[R] .PP New transactions are detected in the same way as print --new: by assuming transactions are always added to the input files in increasing date order, and by saving \f[C].latest.FILE\f[R] state files. .PP The --dry-run output is in journal format, so you can filter it, eg to see only uncategorised transactions: .IP .nf \f[C] $ hledger import --dry ... | hledger -f- print unknown --ignore-assertions \f[R] .fi .SS Importing balance assignments .PP Entries added by import will have their posting amounts made explicit (like \f[C]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 .nf \f[C] $ hledger print IMPORTFILE [--new] >> $LEDGER_FILE \f[R] .fi .PP (If you think import should leave amounts implicit like print does, please test it and send a pull request.) .SS incomestatement .PP incomestatement, is .PD 0 .P .PD .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 The revenue and expense accounts shown are those accounts declared with the \f[C]Revenue\f[R] or \f[C]Expense\f[R] type, or otherwise all accounts under a top-level \f[C]revenue\f[R] or \f[C]income\f[R] or \f[C]expense\f[R] account (case insensitive, plurals allowed). .PP Example: .IP .nf \f[C] $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 \f[R] .fi .PP With a reporting interval, multiple columns will be shown, one for each report period. Normally incomestatement shows revenues/expenses per period, though as with multicolumn balance reports you can alter the report mode with \f[C]--change\f[R]/\f[C]--cumulative\f[R]/\f[C]--historical\f[R]. Instead of absolute values percentages can be displayed with \f[C]-%\f[R]. .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], \f[C]html\f[R], and (experimental) \f[C]json\f[R]. .SS notes .PP notes .PD 0 .P .PD 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 .nf \f[C] $ hledger notes Petrol Snacks \f[R] .fi .SS payees .PP payees .PD 0 .P .PD List the unique payee/payer names that appear in transactions. .PP This command lists the unique payee/payer names that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). .PP Example: .IP .nf \f[C] $ hledger payees Store Name Gas Station Person A \f[R] .fi .SS prices .PP prices .PD 0 .P .PD Print market price directives from the journal. With --costs, also print synthetic market prices based on transaction prices. With --inverted-costs, also print inverse prices based on transaction prices. Prices (and postings providing prices) can be filtered by a query. Price amounts are always displayed with their full precision. .SS print .PP print, txns, p .PD 0 .P .PD Show transaction journal entries, sorted by date. .PP The print command displays full journal entries (transactions) from the journal file in date order, tidily formatted. With --date2, transactions are sorted by secondary date instead. .PP print\[aq]s output is always a valid hledger journal. .PD 0 .P .PD It preserves all transaction information, but it does not preserve directives or inter-transaction comments .IP .nf \f[C] $ hledger print 2008/01/01 income assets:bank:checking $1 income:salary $-1 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 2008/12/31 * pay off liabilities:debts $1 assets:bank:checking $-1 \f[R] .fi .PP Normally, the journal entry\[aq]s explicit or implicit amount style is preserved. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, when a transaction price is implied but not written, it will not appear in the output. You can use the \f[C]-x\f[R]/\f[C]--explicit\f[R] flag to make all amounts and transaction prices explicit, which can be useful for troubleshooting or for making your journal more readable and robust against data entry errors. \f[C]-x\f[R] is also implied by using any of \f[C]-B\f[R],\f[C]-V\f[R],\f[C]-X\f[R],\f[C]--value\f[R]. .PP Note, \f[C]-x\f[R]/\f[C]--explicit\f[R] will cause postings with a multi-commodity amount (these can arise when a multi-commodity transaction has an implicit amount) to be split into multiple single-commodity postings, keeping the output parseable. .PP With \f[C]-B\f[R]/\f[C]--cost\f[R], amounts with transaction prices are converted to cost using that price. This can be used for troubleshooting. .PP With \f[C]-m\f[R]/\f[C]--match\f[R] and a STR argument, print will show at most one transaction: the one one whose description is most similar to STR, and is most recent. STR should contain at least two characters. If there is no similar-enough match, no transaction will be shown. .PP With \f[C]--new\f[R], for each FILE being read, hledger reads (and writes) a special state file (\f[C].latest.FILE\f[R] in the same directory), containing the latest transaction date(s) that were seen last time FILE was read. When this file is found, only transactions with newer dates (and new transactions on the latest date) are printed. This is useful for ignoring already-seen entries in import data, such as downloaded CSV files. Eg: .IP .nf \f[C] $ hledger -f bank1.csv print --new (shows transactions added since last print --new on this file) \f[R] .fi .PP This assumes that transactions added to FILE always have same or increasing dates, and that transactions on the same day do not get reordered. See also the import command. .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], and (experimental) \f[C]json\f[R] and \f[C]sql\f[R]. .PP Here\[aq]s an example of print\[aq]s CSV output: .IP .nf \f[C] $ 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] \f[R] .fi .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 print-unique .PP print-unique .PD 0 .P .PD Print transactions which do not reuse an already-seen description. .PP Example: .IP .nf \f[C] $ cat unique.journal 1/1 test (acct:one) 1 2/2 test (acct:two) 2 $ LEDGER_FILE=unique.journal hledger print-unique (-f option not supported) 2015/01/01 test (acct:one) 1 \f[R] .fi .SS register .PP register, reg, r .PD 0 .P .PD 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[C]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 .nf \f[C] $ 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 \f[R] .fi .PP With --date2, it shows and sorts by secondary date instead. .PP The \f[C]--historical\f[R]/\f[C]-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 .nf \f[C] $ 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 \f[R] .fi .PP The \f[C]--depth\f[R] option limits the amount of sub-account detail displayed. .PP The \f[C]--average\f[R]/\f[C]-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[C]--empty\f[R] (see below). It is affected by \f[C]--historical\f[R]. It works best when showing just one account and one commodity. .PP The \f[C]--related\f[R]/\f[C]-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[C]--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 .nf \f[C] $ hledger register --related --invert assets:checking \f[R] .fi .PP With a reporting interval, register shows summary postings, one per interval, aggregating the postings to each account: .IP .nf \f[C] $ hledger register --monthly income 2008/01 income:salary $-1 $-1 2008/06 income:gifts $-1 $-2 \f[R] .fi .PP Periods with no activity, and summary postings with a zero amount, are not shown by default; use the \f[C]--empty\f[R]/\f[C]-E\f[R] flag to see them: .IP .nf \f[C] $ 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 \f[R] .fi .PP Often, you\[aq]ll want to see just one line per interval. The \f[C]--depth\f[R] option helps with this, causing subaccounts to be aggregated: .IP .nf \f[C] $ hledger register --monthly assets --depth 1h 2008/01 assets $1 $1 2008/06 assets $-1 0 2008/12 assets $-1 $-1 \f[R] .fi .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. .SS Custom register output .PP register uses the full terminal width by default, except on windows. You can override this by setting the \f[C]COLUMNS\f[R] environment variable (not a bash shell variable) or by using the \f[C]--width\f[R]/\f[C]-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[C]--width W,D\f[R] . Here\[aq]s a diagram (won\[aq]t display correctly in --help): .IP .nf \f[C] <--------------------------------- width (W) ----------------------------------> date (10) description (D) account (W-41-D) amount (12) balance (12) DDDDDDDDDD dddddddddddddddddddd aaaaaaaaaaaaaaaaaaa AAAAAAAAAAAA AAAAAAAAAAAA \f[R] .fi .PP and some examples: .IP .nf \f[C] $ 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 \f[R] .fi .PP This command also supports the output destination and output format options The output formats supported are \f[C]txt\f[R], \f[C]csv\f[R], and (experimental) \f[C]json\f[R]. .SS register-match .PP register-match .PD 0 .P .PD Print the one posting whose transaction description is closest to DESC, in the style of the register command. If there are multiple equally good matches, it shows the most recent. Query options (options, not arguments) can be used to restrict the search space. Helps ledger-autosync detect already-seen transactions when importing. .SS rewrite .PP rewrite .PD 0 .P .PD 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 .nf \f[C] $ 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 \f[R] .fi .PP rewrites.hledger may consist of entries like: .IP .nf \f[C] = \[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 \f[R] .fi .PP Note the single quotes to protect the dollar sign from bash, and the two spaces between account and amount. .PP More: .IP .nf \f[C] $ 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] \f[R] .fi .PP Argument for \f[C]--add-posting\f[R] option is a usual posting of transaction with an exception for amount specification. More precisely, you can use \f[C]\[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 .PP 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 .nf \f[C] $ rewrite-rules.journal \f[R] .fi .PP Make contents look like this: .IP .nf \f[C] = \[ha]income (liabilities:tax) *.33 = expenses:gifts budget:gifts *-1 assets:budget *1 \f[R] .fi .PP Note that \f[C]\[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 .nf \f[C] $ hledger rewrite -- -f input.journal -f rewrite-rules.journal > rewritten-tidy-output.journal \f[R] .fi .PP This is something similar to the commands pipeline: .IP .nf \f[C] $ 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 \f[R] .fi .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 .PP To use this tool for batch modification of your journal files you may find useful output in form of unified diff. .IP .nf \f[C] $ hledger rewrite -- --diff -f examples/sample.journal \[aq]\[ha]income\[aq] --add-posting \[aq](liabilities:tax) *.33\[aq] \f[R] .fi .PP Output might look like: .IP .nf \f[C] --- /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 \f[R] .fi .PP If you\[aq]ll pass this through \f[C]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[C]--file\f[R] options and \f[C]include\f[R] directives inside of these files. .PP Be careful. Whole transaction being re-formatted in a style of output from \f[C]hledger print\f[R]. .PP See also: .PP https://github.com/simonmichael/hledger/issues/99 .SS rewrite vs. print --auto .PP 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 .PP roi .PD 0 .P .PD Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. .PP This command assumes that you have account(s) that hold nothing but your investments and whenever you record current appraisal/valuation of these investments you offset unrealized profit and loss into account(s) that, again, hold nothing but unrealized profit and loss. .PP Any transactions affecting balance of investment account(s) and not originating from unrealized profit and loss account(s) are assumed to be your investments or withdrawals. .PP At a minimum, you need to supply a query (which could be just an account name) to select your investments with \f[C]--inv\f[R], and another query to identify your profit and loss transactions with \f[C]--pnl\f[R]. .PP It will compute and display the internalized rate of return (IRR) and time-weighted rate of return (TWR) for your investments for the time period requested. Both rates of return are annualized before display, regardless of the length of reporting interval. .SS stats .PP stats .PD 0 .P .PD Show some journal 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 Example: .IP .nf \f[C] $ hledger stats Main journal file : /src/hledger/examples/sample.journal Included journal files : Transactions span : 2008-01-01 to 2009-01-01 (366 days) Last transaction : 2008-12-31 (2333 days ago) 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 : 12 ($) \f[R] .fi .PP This command also supports output destination and output format selection. .SS tags .PP tags .PD 0 .P .PD List the unique tag names used in the journal. With a TAGREGEX argument, only tag names matching the regular expression (case insensitive) are shown. With QUERY arguments, only transactions matching the query are considered. .PP With the --values flag, the tags\[aq] unique values are listed instead. .PP With --parsed flag, all tags or values are shown in the order they are parsed from the input data, including duplicates. .PP With -E/--empty, any blank/empty values will also be shown, otherwise they are omitted. .SS test .PP test .PD 0 .P .PD 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 .nf \f[C] $ hledger test -- -pData.Amount --color=never \f[R] .fi .PP For help on these, see https://github.com/feuerbach/tasty#options (\f[C]-- --help\f[R] currently doesn\[aq]t show them). .SS Add-on commands .PP hledger also searches for external add-on commands, and will include these in the commands list. These are programs or scripts in your PATH whose name starts with \f[C]hledger-\f[R] and ends with a recognised file extension (currently: no extension, \f[C]bat\f[R],\f[C]com\f[R],\f[C]exe\f[R], \f[C]hs\f[R],\f[C]lhs\f[R],\f[C]pl\f[R],\f[C]py\f[R],\f[C]rb\f[R],\f[C]rkt\f[R],\f[C]sh\f[R]). .PP Add-ons can be invoked like any hledger command, but there are a few things to be aware of. Eg if the \f[C]hledger-web\f[R] add-on is installed, .IP \[bu] 2 \f[C]hledger -h web\f[R] shows hledger\[aq]s help, while \f[C]hledger web -h\f[R] shows hledger-web\[aq]s help. .IP \[bu] 2 Flags specific to the add-on must have a preceding \f[C]--\f[R] to hide them from hledger. So \f[C]hledger web --serve --port 9000\f[R] will be rejected; you must use \f[C]hledger web -- --serve --port 9000\f[R]. .IP \[bu] 2 You can always run add-ons directly if preferred: \f[C]hledger-web --serve --port 9000\f[R]. .PP Add-ons are a relatively easy way to add local features or experiment with new ideas. They can be written in any language, but haskell scripts have a big advantage: they can use the same hledger (and haskell) library functions that built-in commands do, for command-line options, journal parsing, reporting, etc. .PP Two important add-ons are the hledger-ui and hledger-web user interfaces. These are maintained and released along with hledger: .SS ui .PP hledger-ui provides an efficient terminal interface. .SS web .PP hledger-web provides a simple web interface. .PP Third party add-ons, maintained separately from hledger, include: .SS iadd .PP hledger-iadd is a more interactive, terminal UI replacement for the add command. .SS interest .PP hledger-interest generates interest transactions for an account according to various schemes. .PP A few more experimental or old add-ons can be found in hledger\[aq]s bin/ directory. These are typically prototypes and not guaranteed to work. .SH ENVIRONMENT .PP \f[B]LEDGER_FILE\f[R] The journal file path when not specified with \f[C]-f\f[R]. Default: \f[C]\[ti]/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). .PP A typical value is \f[C]\[ti]/DIR/YYYY.journal\f[R], where DIR is a version-controlled finance directory and YYYY is the current year. Or \f[C]\[ti]/DIR/current.journal\f[R], where current.journal is a symbolic link to YYYY.journal. .PP On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a \f[C]\[ti]/.MacOSX/environment.plist\f[R] file containing .IP .nf \f[C] { \[dq]LEDGER_FILE\[dq] : \[dq]\[ti]/finance/current.journal\[dq] } \f[R] .fi .PP To see the effect you may need to \f[C]killall Dock\f[R], or reboot. .PP \f[B]COLUMNS\f[R] The screen width used by the register command. Default: the full terminal width. .PP \f[B]NO_COLOR\f[R] If this variable exists with any value, hledger will not use ANSI color codes in terminal output. This overrides the --color/--colour option. .SH FILES .PP Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]-f\f[R], or \f[C]$LEDGER_FILE\f[R], or \f[C]$HOME/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). .SH LIMITATIONS .PP The need to precede addon command options with \f[C]--\f[R] when invoked from hledger is awkward. .PP When input data contains non-ascii characters, a suitable system locale must be configured (or there will be an unhelpful error). Eg on POSIX, set LANG to something other than C. .PP In a Microsoft Windows CMD window, non-ascii characters and colours are not supported. .PP On Windows, non-ascii characters may not display correctly when running a hledger built in CMD in MSYS/CYGWIN, or vice-versa. .PP In a Cygwin/MSYS/Mintty window, the tab key is not supported in hledger add. .PP Not all of Ledger\[aq]s journal file syntax is supported. See file format differences. .PP On large data files, hledger is slower and uses more memory than Ledger. .SH TROUBLESHOOTING .PP Here are some issues you might encounter when you run hledger (and remember you can also seek help from the IRC channel, mail list or bug tracker): .PP \f[B]Successfully installed, but \[dq]No command \[aq]hledger\[aq] found\[dq]\f[R] .PD 0 .P .PD stack and cabal install binaries into a special directory, which should be added to your PATH environment variable. Eg on unix-like systems, that is \[ti]/.local/bin and \[ti]/.cabal/bin respectively. .PP \f[B]I set a custom LEDGER_FILE, but hledger is still using the default file\f[R] .PD 0 .P .PD \f[C]LEDGER_FILE\f[R] should be a real environment variable, not just a shell variable. The command \f[C]env | grep LEDGER_FILE\f[R] should show it. You may need to use \f[C]export\f[R]. Here\[aq]s an explanation. .PP \f[B]Getting 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 to have a UTF-8-aware locale configured in the environment, otherwise they will fail with these kinds of errors when they encounter non-ascii characters. .PP To fix it, set the LANG environment variable to some locale which supports UTF-8. The locale you choose must be installed on your system. .PP Here\[aq]s an example of setting LANG temporarily, on Ubuntu GNU/Linux: .IP .nf \f[C] $ file my.journal my.journal: UTF-8 Unicode text # the file is UTF8-encoded $ echo $LANG C # LANG is set to the default locale, which does not support UTF8 $ locale -a # which locales are installed ? C en_US.utf8 # here\[aq]s a UTF8-aware one we can use POSIX $ LANG=en_US.utf8 hledger -f my.journal print # ensure it is used for this command \f[R] .fi .PP If available, \f[C]C.UTF-8\f[R] will also work. If your preferred locale isn\[aq]t listed by \f[C]locale -a\f[R], you might need to install it. Eg on Ubuntu/Debian: .IP .nf \f[C] $ apt-get install language-pack-fr $ locale -a C en_US.utf8 fr_BE.utf8 fr_CA.utf8 fr_CH.utf8 fr_FR.utf8 fr_LU.utf8 POSIX $ LANG=fr_FR.utf8 hledger -f my.journal print \f[R] .fi .PP Here\[aq]s how you could set it permanently, if you use a bash shell: .IP .nf \f[C] $ echo \[dq]export LANG=en_US.utf8\[dq] >>\[ti]/.bash_profile $ bash --login \f[R] .fi .PP Exact spelling and capitalisation may be important. Note the difference on MacOS (\f[C]UTF-8\f[R], not \f[C]utf8\f[R]). Some platforms (eg ubuntu) allow variant spellings, but others (eg macos) require it to be exact: .IP .nf \f[C] $ locale -a | grep -iE en_us.*utf en_US.UTF-8 $ LANG=en_US.UTF-8 hledger -f my.journal print \f[R] .fi .SH "REPORTING BUGS" Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) .SH AUTHORS Simon Michael and contributors .SH COPYRIGHT Copyright (C) 2007-2019 Simon Michael. .br Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5), ledger(1) http://hledger.org hledger-1.19.1/embeddedfiles/hledger.txt0000644000000000000000000045100013725533425016343 0ustar0000000000000000 hledger(1) hledger User Manuals hledger(1) NAME hledger - a command-line accounting tool SYNOPSIS hledger [-f FILE] COMMAND [OPTIONS] [ARGS] hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS] hledger DESCRIPTION hledger is a reliable, 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). This is hledger's command-line interface (there are also terminal and web interfaces). Its basic function is to read a plain text file de- scribing financial transactions (in accounting terms, a general jour- nal) and print useful reports on standard output, or export them as CSV. hledger can also read some other file formats such as CSV files, translating them to journal format. Additionally, hledger lists other hledger-* executables found in the user's $PATH and can invoke them as subcommands. hledger reads data from one or more files in hledger journal, time- clock, timedot, or CSV format specified with -f, or $LEDGER_FILE, or $HOME/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.journal). If using $LEDGER_FILE, note this must be a real environment variable, not a shell variable. You can specify standard input with -f-. Transactions are dated movements of money between two (or more) named accounts, and are recorded with journal entries like this: 2015/10/16 bought food expenses:food $10 assets:cash For more about this format, see hledger_journal(5). Most users use a text editor to edit the journal, usually with an edi- tor mode such as ledger-mode for added convenience. hledger's interac- tive add command is another way to record new transactions. hledger never changes existing transactions. To get started, you can either save some entries like the above in ~/.hledger.journal, or run hledger add and follow the prompts. Then try some commands like hledger print or hledger balance. Run hledger with no arguments for a list of commands. COMMON TASKS Here are some quick examples of how to do some basic tasks with hledger. For more details, see the reference section below, the hledger_journal(5) manual, or the more extensive docs at https://hledger.org. Getting help $ hledger # show available commands $ hledger --help # show common options $ hledger CMD --help # show common and command options, and command help $ hledger help # show available manuals/topics $ hledger help hledger # show hledger manual as info/man/text (auto-chosen) $ hledger help journal --man # show the journal manual as a man page $ hledger help --help # show more detailed help for the help command Find more docs, chat, mail list, reddit, issue tracker: https://hledger.org#help-feedback Constructing command lines hledger has an extensive and powerful command line interface. We strive to keep it simple and ergonomic, but you may run into one of the confusing real world details described in OPTIONS, below. If that hap- pens, here are some tips that may help: o command-specific options must go after the command (it's fine to put all options there) (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 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. 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 2020.journal $ echo "export LEDGER_FILE=$HOME/finance/2020.journal" >> ~/.bashrc $ source ~/.bashrc $ hledger stats Main file : /Users/simon/finance/2020.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 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: 2020-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/2020.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 [2020-02-07]: 2020-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): . 2020-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 [2020-01-01]: . If you're using version control, this could be a good time to commit the journal. Eg: $ git commit -m 'initial balances' 2020.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: 2020/1/10 * gift received assets:cash $20 income:gifts 2020.1.12 * farmers market expenses:food $13 assets:cash 2020-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: 2020-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 2020-01-15 and paycheck If you're using version control, this can be another good time to com- mit: $ git commit -m 'txns' 2020.journal Reporting Here are some basic reports. Show all transactions: $ hledger print 2020-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 2020-01-10 * gift received assets:cash $20 income:gifts 2020-01-12 * farmers market expenses:food $13 assets:cash 2020-01-15 * paycheck income:salary assets:bank:checking $1000 2020-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 --flat -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 --flat -2 Balance Sheet 2020-01-16 || 2020-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 2020-01-01-2020-01-16 || 2020-01-01-2020-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 2020-01-01 opening balances assets:cash $100 $100 2020-01-10 gift received assets:cash $20 $120 2020-01-12 farmers market assets:cash $-13 $107 2020-01-16 adjust cash assets:cash $-2 $105 Show weekly posting counts as a bar chart: $ hledger activity -W 2019-12-30 ***** 2020-01-06 **** 2020-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. OPTIONS General options To see general usage help, including general options which are sup- ported by most hledger commands, run hledger -h. General help options: -h --help show general usage (or after COMMAND, command usage) --version show 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 --anon anonymize accounts and payees --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) General reporting options: -b --begin=DATE include postings/txns on or after this date -e --end=DATE include postings/txns before this date -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) -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-value with -V/-X/--value, also infer market prices from transactions --auto apply automated posting rules to modify transactions. --forecast generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. --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. 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 options To see options for a particular command, including command-specific op- tions, run: hledger COMMAND -h. Command-specific options must be written after the command name, eg: hledger print -x. Additionally, if the command is an addon, you may need to put its op- tions after a double-hyphen, eg: hledger ui -- --watch. Or, you can run the addon executable directly: hledger-ui --watch. Command arguments Most hledger commands accept arguments after the command name, which are often a query, filtering the data in some way. You can save a set of command line options/arguments in a file, and then reuse them by writing @FILENAME as a command line argument. Eg: hledger bal @foo.args. (To prevent this, eg if you have an argument that begins with a literal @, precede it with --, eg: hledger bal -- @ARG). Inside the argument file, each line should contain just one option or argument. Avoid the use of spaces, except inside quotes (or you'll see a confusing error). Between a flag and its argument, use = (or noth- ing). Bad: assets depth:2 -X USD Good: assets depth:2 -X=USD For special characters (see below), use one less level of quoting than you would at the command prompt. Bad: -X"$" Good: -X$ See also: Save frequently used options. Queries One of hledger's strengths is being able to quickly report on precise subsets of your data. Most commands accept an optional query expres- sion, written as arguments after the command name, to filter the data by date, account name or other criteria. The syntax is similar to a web search: one or more space-separated search terms, quotes to enclose whitespace, prefixes to match specific fields, a not: prefix to negate the match. We do not yet support arbitrary boolean combinations of search terms; instead most commands show transactions/postings/accounts which match (or negatively 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 instead shows 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. The following kinds of search terms can be used. Remember these can also be prefixed with not:, eg to exclude a particular subaccount. REGEX, acct:REGEX match account names by this regular expression. (With no pre- fix, acct: is assumed.) same as above amt:N, amt:N, amt:>=N match postings with a single-commodity amount that is equal to, less than, or greater than N. (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 cur- rency/commodity symbol is fully matched by REGEX. (For a par- tial match, use .*REGEX.*). Note, to match characters which are regex-significant, like the dollar sign ($), you need to prepend \. And when using the command line you need to add one more level of quoting to hide it from the shell, so eg do: hledger print cur:'\$' or hledger print cur:\\$. desc:REGEX match transaction descriptions. date:PERIODEXPR match dates within the specified period. PERIODEXPR is a period expression (with no report interval). Examples: date:2016, date:thismonth, date:2000/2/1-2/15, date:lastweek-. If the --date2 command line flag is present, this matches secondary dates instead. date2:PERIODEXPR match secondary dates within the specified period. depth:N match (or display, depending on command) accounts at or above this depth note:REGEX match transaction notes (part of description right of |, or whole description when there's no |) payee:REGEX match transaction payee/payer names (part of description left of |, or whole description when there's no |) real:, real:0 match real or virtual postings respectively status:, status:!, status:* match unmarked, pending, or cleared transactions respectively tag:REGEX[=REGEX] match by tag name, and optionally also by tag value. Note a tag: query is considered to match a transaction if it matches any of the postings. Also remember that postings inherit the tags of their parent transaction. The following special search term is used automatically in hledger-web, only: inacct:ACCTNAME tells hledger-web to show the transaction register for this ac- count. Can be filtered further with acct etc. Some of these can also be expressed as command-line options (eg depth:2 is equivalent to --depth 2). Generally you can mix options and query arguments, and the resulting query will be their intersection (perhaps excluding the -p/--period option). Special characters in arguments and queries In shell command lines, option and argument values which contain "prob- lematic" characters, ie spaces, and also characters significant to your shell such as <, >, (, ), | and $, should be escaped by enclosing them in quotes or by writing backslashes before the characters. Eg: hledger register -p 'last year' "accounts receivable (receiv- able|payable)" amt:\>100. More escaping Characters significant both to the shell and in regular expressions may need one extra level of escaping. These include parentheses, the pipe symbol and the dollar sign. Eg, to match the dollar symbol, bash users should do: hledger balance cur:'\$' or: hledger balance cur:\\$ Even more escaping When hledger runs an addon executable (eg you type hledger ui, hledger runs hledger-ui), it de-escapes command-line options and arguments once, so you might need to triple-escape. Eg in bash, running the ui command and matching the dollar sign, it's: hledger ui cur:'\\$' or: hledger ui cur:\\\\$ If you asked why four slashes above, this may help: unescaped: $ escaped: \$ double-escaped: \\$ triple-escaped: \\\\$ (The number of backslashes in fish shell is left as an exercise for the reader.) You can always avoid the extra escaping for addons by running the addon directly: hledger-ui cur:\\$ Less escaping Inside an argument file, or in the search field of hledger-ui or hledger-web, or at a GHCI prompt, you need one less level of escaping than at the command line. And backslashes may work better than quotes. Eg: ghci> :main balance cur:\$ 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). Input files hledger reads transactions from a data file (and the add command writes to it). By default this file is $HOME/.hledger.journal (or on Windows, something like C:/Users/USER/.hledger.journal). You can override this with the $LEDGER_FILE environment variable: $ setenv LEDGER_FILE ~/finance/2016.journal $ hledger stats or with the -f/--file option: $ hledger -f /some/file stats The file name - (hyphen) means standard input: $ cat some.journal | hledger -f- 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 exten- sions: ----------------------------------------------------------------------------- journal hledger journal files and some Ledger .journal .j .hledger journals, for transactions .ledger time- timeclock files, for precise time log- .timeclock clock ging timedot timedot files, for approximate time .timedot logging csv comma/semicolon/tab/other-separated .csv .ssv .tsv values, for data import 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. When you can't ensure the right file extension, not to worry: you can force a specific reader/format by prefixing the file path with the for- mat and a colon. Eg to read a .dat file as csv: $ hledger -f csv:/some/csv-file.dat stats $ echo 'i 2009/13/1 08:00:00' | hledger print -ftimeclock:- You can specify multiple -f options, to read multiple files as one big journal. There are some limitations with this: o directives in one file will not affect the other files o balance assertions will not see any account balances from previous files If you need either of those things, you can o use a single parent file which includes the others o or concatenate the files into one before reading, eg: cat a.journal b.journal | hledger -f- CMD. 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 (print, register, the balance commands) offer a choice of output format. In addition to the usual plain text format (txt), there are CSV (csv), HTML (html), JSON (json) and SQL (sql). This is con- trolled by the -O/--output-format option: $ hledger print -O csv or, by a file extension specified with -o/--output-file: $ hledger balancesheet -o foo.html # write HTML to foo.html The -O option can be used to override the file extension if needed: $ hledger balancesheet -o foo.txt -O html # write HTML to foo.txt Some notes about JSON output: o This feature is marked experimental, and not yet much used; you should expect our JSON to evolve. Real-world feedback is welcome. o Our JSON is rather large and verbose, as it is quite a faithful rep- resentation 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. 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) Notes about SQL output: o SQL output is also marked experimental, and much like JSON could use real-world feedback. o SQL output is expected to work with sqlite, MySQL and PostgreSQL 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. Regular expressions hledger uses regular expressions in a number of places: o query terms, on the command line and in the hledger-web search form: REGEX, desc:REGEX, cur:REGEX, tag:...=REGEX o CSV rules conditional blocks: if REGEX ... o account alias directives and options: alias /REGEX/ = REPLACEMENT, --alias /REGEX/=REPLACEMENT 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. they do not support backreferences; if you write \1, it will match the digit 1. Except when doing text replacement, eg in account aliases, where backreferences can be used in the replacement string to reference capturing groups in the search regexp. 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. Smart dates hledger's user interfaces accept a flexible "smart date" syntax (unlike dates in the journal file). Smart dates allow some english words, can be relative to today's date, and can have less-significant date parts omitted (defaulting to 1). 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 20181201 8 digit YYYYMMDD with valid year month and day 201812 6 digit YYYYMM with valid year and month Counterexamples - malformed digit sequences might give surprising re- sults: 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 Report start & end date Most hledger reports show the full span of time represented by the journal data, by default. So, the effective report start and end dates will be the earliest and latest transaction or posting dates found in the journal. 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. Some notes: o As in Ledger, end dates are exclusive, so you need to write the date after the last day you want to include. 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. 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 Report intervals A report interval can be specified so that commands like register, bal- ance and activity will divide their reports into multiple subperiods. The basic intervals can be selected with one of -D/--daily, -W/--weekly, -M/--monthly, -Q/--quarterly, or -Y/--yearly. More com- plex intervals may be specified with a period expression. Report in- tervals can not be specified with a query. Period expressions The -p/--period option accepts period expressions, a shorthand way of expressing a start date, end date, and/or report interval all at once. Here's a basic period expression specifying the first quarter of 2009. Note, hledger always treats start dates as inclusive and end dates as exclusive: -p "from 2009/1/1 to 2009/4/1" Keywords like "from" and "to" are optional, and so are the spaces, as long as you don't run two dates together. "to" can also be written as ".." or "-". These 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, the above can also be written as: -p "1/1 4/1" -p "january-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 in your journal: -p "from 2009/1/1" everything after january 1, 2009 -p "from 2009/1" the same -p "from 2009" the same -p "to 2009" everything before january 1, 2009 A single date with no "from" or "to" defines both the start and end date like so: -p "2009" the year 2009; equivalent to "2009/1/1 to 2010/1/1" -p "2009/1" the month of jan; equiva- lent to "2009/1/1 to 2009/2/1" -p "2009/1/1" just that day; equivalent to "2009/1/1 to 2009/1/2" Or you can specify a single quarter like so: -p "2009Q1" first quarter of 2009, equivalent to "2009/1/1 to 2009/4/1" -p "q4" fourth quarter of the cur- rent year The argument of -p can also begin with, or be, a report interval ex- pression. The basic report intervals are daily, weekly, monthly, quar- terly, or yearly, which have the same effect as the -D,-W,-M,-Q, or -Y flags. Between report interval and start/end dates (if any), the word in is optional. Examples: -p "weekly from 2009/1/1 to 2009/4/1" -p "monthly in 2008" -p "quarterly" Note that weekly, monthly, quarterly and yearly intervals will always start on the first day on week, month, quarter or year accordingly, and will end on the last day of same period, even if associated period ex- pression specifies different explicit start and end date. For example: -p "weekly from 2009/1/1 starts on 2008/12/29, closest preceding Mon- to 2009/4/1" day -p "monthly in starts on 2018/11/01 2008/11/25" -p "quarterly from starts on 2009/04/01, ends on 2009/06/30, 2009-05-05 to 2009-06-01" which are first and last days of Q2 2009 -p "yearly from starts on 2009/01/01, first day of 2009 2009-12-29" The following more complex report intervals are also supported: bi- weekly, fortnightly, bimonthly, every day|week|month|quarter|year, ev- ery N days|weeks|months|quarters|years. All of these will start on the first day of the requested period and end on the last one, as described above. Examples: -p "bimonthly from 2008" periods will have boundaries on 2008/01/01, 2008/03/01, ... -p "every 2 weeks" starts on closest preceding Monday -p "every 5 month from periods will have boundaries on 2009/03/01, 2009/03" 2009/08/01, ... If you want intervals that start on arbitrary day of your choosing and span a week, month or year, you need to use any of the following: every Nth day of week, every , every Nth day [of month], every Nth weekday [of month], every MM/DD [of year], every Nth MMM [of year], every MMM Nth [of year]. Examples: -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 Nov -p "every 5th Nov" same -p "every Nov 5th" same Show historical balances at end of 15th each month (N is exclusive end date): hledger balance -H -p "every 16th day" Group postings from start of wednesday to end of next tuesday (N is start date and exclusive end date): hledger register checking -p "every 3rd day of week" Depth limiting With the --depth N option (short form: -N), commands like account, bal- ance and register will show only the uppermost accounts in the account tree, down to level N. Use this when you want a summary with less de- tail. This flag has the same effect as a depth: query argument (so -2, --depth=2 or depth:2 are equivalent). Pivoting Normally hledger sums amounts, and organizes them in a hierarchy, based on account name. The --pivot FIELD option causes it to sum and orga- nize hierarchy based on the value of some other field instead. FIELD can be: code, description, payee, note, or the full name (case insensi- tive) of any tag. As with account names, values containing colon:sepa- rated:parts will be displayed hierarchically in reports. --pivot is a general option affecting all reports; you can think of hledger transforming the journal before any other processing, replacing every posting's account name with the value of the specified field on that posting, inheriting it from the transaction or using a blank value if it's not present. An example: 2016/02/16 Member Fee Payment assets:bank account 2 EUR income:member fees -2 EUR ; member: John Doe Normal balance report showing account names: $ hledger balance 2 EUR assets:bank account -2 EUR income:member fees -------------------- 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, de- scribed below): $ 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 Valuation Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), or to market value (using some market price on a cer- tain date). This is controlled by the --value=TYPE[,COMMODITY] option, but we also provide the simpler -B/-V/-X flags, and usually one of those is all you need. -B: Cost The -B/--cost flag converts amounts to their cost or sale amount at transaction time, if they have a transaction price specified. -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 Since market prices can change from day to day, market value reports have a valuation date (or more than one), which determines which market prices will be used. For single period reports, if an explicit report end date is specified, that will be used as the valuation date; otherwise the valuation date is "today". For multiperiod reports, each column/period is valued on the last day of the period. Market prices (experimental) 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 (if the --infer-value flag is used) inferred from transac- tion prices. 2. A reverse market price: the inverse of a declared or inferred market price from B to A. 3. A chained market price: a synthetic price formed by combining the shortest chain of market prices (any of the above types) leading from A to B. Amounts for which no applicable market price can be found, are not con- verted. --infer-value: market prices from transactions (experimental) 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 transaction prices as additional market prices (as Ledger does) ? We could produce value reports without need- ing P directives at all. Adding the --infer-value flag to -V, -X or --value enables this. So for example, hledger bs -V --infer-value will get market prices both from P directives and from transactions. 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 Valuation section carefully, and try adding --debug or --debug=2 to troubleshoot. --infer-value 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 but not, currently, from "more correct" multicommodity transactions (no @, multiple commodities, balanced). Valuation commodity (experimental) 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-value 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-value flag, transac- tion prices 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 EUR $1.10 ; purchase some euros on nov 3 2016/11/3 assets:euros EUR100 assets:checking ; the euro is worth fewer dollars by dec 21 P 2016/12/21 EUR $1.03 How many euros do I have ? $ hledger -f t.j bal -N euros EUR100 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 -B, -V and -X are special cases of the more general --value option: --value=TYPE[,COMM] TYPE is cost, then, end, now or YYYY-MM-DD. COMM is an optional commodity symbol. Shows amounts converted to: - cost commodity using transaction prices (then optionally to COMM using market prices at period end(s)) - 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=cost Convert amounts to cost, using the prices recorded in transac- tions. --value=then Convert amounts to their value in the default valuation commod- ity, using market prices on each posting's date. This is cur- rently supported only by the print and register commands. --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 --value=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 You may need to explicitly set a commodity's display style, when re- verse prices are used. Eg this output might be surprising: P 2000-01-01 A 2B 2000-01-01 a 1B b $ hledger print -x -X A 2000-01-01 a 0 b 0 Explanation: because there's no amount or commodity directive specify- ing a display style for A, 0.5A gets the default style, which shows no decimal digits. Because the displayed amount looks like zero, the com- modity symbol and minus sign are not displayed either. Adding a com- modity directive sets a more useful display style for A: P 2000-01-01 A 2B commodity 0.00A 2000-01-01 a 1B b $ hledger print -X A 2000-01-01 a 0.50A b -0.50A 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 type -B, -V, -X --value=then --value=end --value=DATE, --value=cost --value=now ------------------------------------------------------------------------------------------ print posting cost value at re- value at value at re- value at amounts port end or posting date port or DATE/today today journal end balance as- unchanged unchanged unchanged unchanged unchanged sertions / assignments register starting cost value at day not supported value at day value at balance before re- before re- DATE/today (with -H) port or port or journal journal start start posting cost value at re- value at value at re- value at amounts (no port end or posting date port or DATE/today report in- today journal end terval) summary summarised value at pe- sum of post- value at pe- value at posting cost riod ends ings in in- riod ends DATE/today amounts terval, val- (with report ued at inter- interval) val start running to- sum/average sum/average sum/average sum/average sum/average tal/average of displayed of displayed of displayed of displayed of displayed values values values values values balance (bs, bse, cf, is..) balances (no sums of value at re- not supported value at re- value at report in- costs port end or port or DATE/today of terval) today of journal end sums of post- sums of of sums of ings postings postings balances sums of value at pe- not supported value at pe- value at (with report costs riod ends of riod ends of DATE/today of interval) sums of sums of sums of post- postings postings ings starting sums of sums of not supported sums of sums of post- balances costs of postings be- postings be- ings before (with report postings be- fore report fore report report start interval and fore report start start -H) start budget like bal- like bal- not supported like bal- like balances amounts with ances ances ances --budget grand total sum of dis- sum of dis- not supported sum of dis- sum of dis- (no report played val- played val- played val- played values interval) ues ues ues row to- sums/aver- sums/aver- not supported sums/aver- sums/averages tals/aver- ages of dis- ages of dis- ages of dis- of displayed ages (with played val- played val- played val- values report in- ues ues ues terval) column to- sums of dis- sums of dis- not supported sums of dis- sums of dis- tals played val- played val- played val- played values ues ues ues grand to- sum/average sum/average not supported sum/average sum/average tal/average of column of column of column of column to- totals totals totals tals 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). COMMANDS hledger provides a number of subcommands; hledger with no arguments shows a list. If you install additional hledger-* packages, or if you put programs or scripts named hledger-NAME in your PATH, these will also be listed as subcommands. Run a subcommand by writing its name as first argument (eg hledger in- comestatement). You can also write one of the standard short aliases displayed in parentheses in the command list (hledger b), or any any unambiguous prefix of a command name (hledger inc). Here are all the builtin commands in alphabetical order. See also hledger for a more organised command list, and hledger CMD -h for de- tailed command help. accounts accounts, a Show account names. This command lists account names, either declared with account direc- tives (--declared), posted to (--used), or both (the default). With query arguments, only matched account names and account names refer- enced by matched postings are shown. 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 com- ponents. Account names can be depth-clipped with depth:N or --depth N or -N. Examples: $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts activity 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 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 journal file (if there are multiple -f FILE options, the first file is used.) Existing transactions are not changed. This is the only hledger command that writes to the journal file. 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, descrip- tions, 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 the tutorial for a detailed explanation): $ 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 aregister, areg Show transactions affecting a particular account, and the account's running balance. aregister shows the transactions affecting a particular account (and its subaccounts), from the point of view of that account. Each line shows: o the transaction's (or posting's, see below) date o the names of the other account(s) involved o the net change to this account's balance o the account's historical running balance (including balance from transactions before the report start date). With aregister, each line represents a whole transaction - as in hledger-ui, hledger-web, and your bank statement. By contrast, the register command shows individual postings, across all accounts. You might prefer aregister for reconciling with real-world asset/liability accounts, and register for reviewing detailed revenues/expenses. An account must be specified as the first argument, which should be the full account name or an account pattern (regular expression). aregis- ter will show transactions in this account (the first one matched) and any of its subaccounts. Any additional arguments form a query which will filter the transac- tions shown. Transactions making a net change of zero are not shown by default; add the -E/--empty flag to show them. aregister and custom posting dates Transactions whose date is outside the report period can still be shown, if they have a posting to this account dated inside the report period. (And in this case it's the posting date that is shown.) This ensures that aregister can show an accurate historical running balance, matching the one shown by register -H with the same arguments. To filter strictly by transaction date instead, add the --txn-dates flag. If you use this flag and some of your postings have custom dates, it's probably best to assume the running balance is wrong. Output format This command also supports the output destination and output format op- tions The output formats supported are txt, csv, and json. Examples: Show all transactions and historical running balance in the first ac- count whose name contains "checking": $ hledger areg checking Show transactions and historical running balance in all asset accounts during july: $ hledger areg assets date:jul balance balance, bal, b Show accounts and their balances. The balance command is hledger's most versatile command. Note, despite the name, it is not always used for showing real-world account bal- ances; the more accounting-aware balancesheet and incomestatement may be more convenient for that. By default, it displays all accounts, and each account's change in bal- ance during the entire period of the journal. Balance changes are cal- culated by adding up the postings in each account. You can limit the postings matched, by a query, to see fewer accounts, changes over a different time period, changes from only cleared transactions, etc. If you include an account's complete history of postings in the report, the balance change is equivalent to the account's current ending bal- ance. For a real-world account, typically you won't have all transac- tions in the journal; instead you'll have all transactions after a cer- tain date, and an "opening balances" transaction setting the correct starting balance on that date. Then the balance command will show real-world account balances. In some cases the -H/--historical flag is used to ensure this (more below). The balance command can produce several styles of report: Classic balance report This is the original balance report, as found in Ledger. It usually looks like this: $ hledger balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 By default, accounts are displayed hierarchically, with subaccounts in- dented below their parent. At each level of the tree, accounts are sorted by account code if any, then by account name. Or with -S/--sort-amount, by their balance amount, largest first. "Boring" accounts, which contain a single interesting subaccount and no balance of their own, are elided into the following line for more com- pact output. (Eg above, the "liabilities" account.) Use --no-elide to prevent this. Account balances are "inclusive" - they include the balances of any subaccounts. Accounts which have zero balance (and no non-zero subaccounts) are omitted. Use -E/--empty to show them. A final total is displayed by default; use -N/--no-total to suppress it, eg: $ hledger balance -p 2008/6 expenses --no-total $2 expenses $1 food $1 supplies Customising the classic balance report You can customise the layout of classic balance reports with --format FMT: $ hledger 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 (plus a newline) specifies the formatting applied to each account/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 Colour support In terminal output, when colour is enabled, the balance command shows negative amounts in red. Flat mode To see a flat list instead of the default hierarchical display, use --flat. In this mode, accounts (unless depth-clipped) show their full names and "exclusive" balance, excluding any subaccount balances. In this mode, you can also use --drop N to omit the first few account name components. $ hledger balance -p 2008/6 expenses -N --flat --drop 1 $1 food $1 supplies Depth limited balance reports With --depth N or depth:N or just -N, balance reports show accounts only to the specified numeric depth. This is very useful to summarise a complex set of accounts and get an overview. $ hledger balance -N -1 $-1 assets $2 expenses $-2 income $1 liabilities Flat-mode balance reports, which normally show exclusive balances, show inclusive balances at the depth limit. Percentages With -% or --percent, balance reports show each account's value ex- pressed as a percentage of the column's total. This is useful to get an overview of the relative sizes of account balances. For example to obtain an overview of expenses: $ hledger balance expenses -% 100.0 % expenses 50.0 % food 50.0 % supplies -------------------- 100.0 % Note that --tree does not have an effect on -%. The percentages are always relative to the total sum of each column, they are never rela- tive to the parent account. Since the percentages are relative to the columns sum, it is usually not useful to calculate percentages if the signs of the amounts are mixed. Although the results are technically correct, they are most likely useless. Especially in a balance report that sums up to zero (eg hledger balance -B) all percentage values will be zero. This flag does not work if the report contains any mixed commodity ac- counts. If there are mixed commodity accounts in the report be sure to use -V or -B to coerce the report into using a single commodity. Multicolumn balance report Multicolumn or tabular balance reports are a very useful hledger fea- ture, and usually the preferred style. They share many of the above features, but they show the report as a table, with columns represent- ing time periods. This mode is activated by providing a reporting in- terval. There are three types of multicolumn balance report, showing different information: 1. By default: each column shows the sum of postings in that period, ie the account's change of balance in that period. This is useful eg for a monthly income statement: $ hledger balance --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 2. With --cumulative: each column shows the ending balance for that pe- riod, accumulating the changes across periods, starting from 0 at the report start date: $ hledger balance --quarterly income expenses -E --cumulative Ending balances (cumulative) in 2008: || 2008/03/31 2008/06/30 2008/09/30 2008/12/31 ===================++================================================= expenses:food || 0 $1 $1 $1 expenses:supplies || 0 $1 $1 $1 income:gifts || 0 $-1 $-1 $-1 income:salary || $-1 $-1 $-1 $-1 -------------------++------------------------------------------------- || $-1 0 0 0 3. With --historical/-H: each column shows the actual historical ending balance for that period, accumulating the changes across periods, starting from the actual balance at the report start date. This is useful eg for a multi-period balance sheet, and when you are showing only the data after a certain start date: $ hledger balance ^assets ^liabilities --quarterly --historical --begin 2008/4/1 Ending balances (historical) in 2008/04/01-2008/12/31: || 2008/06/30 2008/09/30 2008/12/31 ======================++===================================== assets:bank:checking || $1 $1 0 assets:bank:saving || $1 $1 $1 assets:cash || $-2 $-2 $-2 liabilities:debts || 0 0 $1 ----------------------++------------------------------------- || 0 0 0 Note that --cumulative or --historical/-H disable --row-total/-T, since summing end balances generally does not make sense. Multicolumn balance reports display accounts in flat mode by default; to see the hierarchy, use --tree. With a reporting interval (like --quarterly above), the report start/end dates will be adjusted if necessary so that they encompass the displayed report periods. This is so that the first and last peri- ods will be "full" and comparable to the others. The -E/--empty flag does two things in multicolumn balance reports: first, the report will show all columns within the specified report pe- riod (without -E, leading and trailing columns with all zeroes are not shown). Second, all accounts which existed at the report start date will be considered, not just the ones with activity during the report period (use -E to include low-activity accounts which would otherwise would be omitted). The -T/--row-total flag adds an additional column showing the total for each row. The -A/--average flag adds a column showing the average value in each row. Here's an example of all three: $ hledger balance -Q income expenses --tree -ETA Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 Total Average ============++=================================================== expenses || 0 $2 0 0 $2 $1 food || 0 $1 0 0 $1 0 supplies || 0 $1 0 0 $1 0 income || $-1 $-1 0 0 $-2 $-1 gifts || 0 $-1 0 0 $-1 0 salary || $-1 0 0 0 $-1 0 ------------++--------------------------------------------------- || $-1 $1 0 0 0 0 (Average is rounded to the dollar here since all journal amounts are) The --transpose flag can be used to exchange the rows and columns of a multicolumn report. When showing multicommodity amounts, multicolumn balance reports will elide any amounts which have more than two commodities, since otherwise columns could get very wide. The --no-elide flag disables this. Hid- ing totals with the -N/--no-total flag can also help reduce the width of multicommodity reports. When the report is still too wide, a good workaround is to pipe it into less -RS (-R for colour, -S to chop long lines). Eg: hledger bal -D --color=yes | less -RS. Budget report With --budget, extra columns are displayed showing budget goals for each account and period, if any. Budget goals are defined by periodic transactions. This is very useful for comparing planned and actual in- come, expenses, time usage, etc. --budget is most often combined with a report interval. For example, you can take average monthly expenses in the common ex- pense categories to construct a minimal monthly budget: ;; Budget ~ monthly income $2000 expenses:food $400 expenses:bus $50 expenses:movies $30 assets:bank:checking ;; Two months worth of expenses 2017-11-01 income $1950 expenses:food $396 expenses:bus $49 expenses:movies $30 expenses:supplies $20 assets:bank:checking 2017-12-01 income $2100 expenses:food $412 expenses:bus $53 expenses:gifts $100 assets:bank:checking You can now see a monthly budget report: $ hledger balance -M --budget Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] This is different from a normal balance report in several ways: o Only accounts with budget goals during the report period are shown, by default. o In each column, in square brackets after the actual amount, budget goal amounts are shown, and the actual/goal percentage. (Note: bud- get goals should be in the same commodity as the actual amount.) o All parent accounts are always shown, even in flat mode. Eg assets, assets:bank, and expenses above. o Amounts always include all subaccounts, budgeted or unbudgeted, even in flat mode. This means that the numbers displayed will not always add up! Eg above, the expenses actual amount includes the gifts and supplies transac- tions, but the expenses:gifts and expenses:supplies accounts are not shown, as they have no budget amounts declared. This can be confusing. When you need to make things clearer, use the -E/--empty flag, which will reveal all accounts including unbudgeted ones, giving the full picture. Eg: $ hledger balance -M --budget --empty Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:gifts || 0 $100 expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] expenses:supplies || $20 0 income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] You can roll over unspent budgets to next period with --cumulative: $ hledger balance -M --budget --cumulative Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank:checking || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] expenses || $495 [ 103% of $480] $1060 [ 110% of $960] expenses:bus || $49 [ 98% of $50] $102 [ 102% of $100] expenses:food || $396 [ 99% of $400] $808 [ 101% of $800] expenses:movies || $30 [ 100% of $30] $30 [ 50% of $60] income || $1950 [ 98% of $2000] $4050 [ 101% of $4000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] For more examples, see Budgeting and Forecasting. Nested budgets You can add budgets to any account in your account hierarchy. If you have budgets on both parent account and some of its children, then bud- get(s) of the child account(s) would be added to the budget of their parent, much like account balances behave. In the most simple case this means that once you add a budget to any account, all its parents would have budget as well. To illustrate this, consider the following budget: ~ monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities With this, monthly budget for electronics is defined to be $100 and budget for personal expenses is an additional $1000, which implicitly means that budget for both expenses:personal and expenses is $1100. Transactions in expenses:personal:electronics will be counted both to- wards its $100 budget and $1100 of expenses:personal , and transactions in any other subaccount of expenses:personal would be counted towards only towards the budget of expenses:personal. For example, let's consider these transactions: ~ monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities 2019/01/01 Google home hub expenses:personal:electronics $90.00 liabilities $-90.00 2019/01/02 Phone screen protector expenses:personal:electronics:upgrades $10.00 liabilities 2019/01/02 Weekly train ticket expenses:personal:train tickets $153.00 liabilities 2019/01/03 Flowers expenses:personal $30.00 liabilities As you can see, we have transactions in expenses:personal:electron- ics:upgrades and expenses:personal:train tickets, and since both of these accounts are without explicitly defined budget, these transac- tions would be counted towards budgets of expenses:personal:electronics and expenses:personal accordingly: $ hledger balance --budget -M Budget performance in 2019/01: || Jan ===============================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] liabilities || $-283.00 [ 26% of $-1100.00] -------------------------------++------------------------------- || 0 [ 0] And with --empty, we can get a better picture of budget allocation and consumption: $ hledger balance --budget -M --empty Budget performance in 2019/01: || Jan ========================================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] expenses:personal:electronics:upgrades || $10.00 expenses:personal:train tickets || $153.00 liabilities || $-283.00 [ 26% of $-1100.00] ----------------------------------------++------------------------------- || 0 [ 0] Output format This command also supports the output destination and output format op- tions The output formats supported are txt, csv, (multicolumn non-bud- get reports only) html, and (experimental) json. balancesheet 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. The asset and liability accounts shown are those accounts declared with the Asset or Cash or Liability type, or otherwise all accounts under a top-level asset or liability account (case insensitive, plurals al- lowed). Example: $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 With a reporting interval, multiple columns will be shown, one for each report period. As with multicolumn balance reports, you can alter the report mode with --change/--cumulative/--historical. Normally bal- ancesheet shows historical ending balances, which is what you need for a balance sheet; note this means it ignores report begin dates (and -T/--row-total, since summing end balances generally does not make sense). Instead of absolute values percentages can be displayed with -%. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, html, and (experimen- tal) json. balancesheetequity 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. The asset, liability and equity accounts shown are those accounts de- clared with the Asset, Cash, Liability or Equity type, or otherwise all accounts under a top-level asset, liability or equity account (case in- sensitive, plurals allowed). 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 also supports the output destination and output format op- tions The output formats supported are txt, csv, html, and (experimen- tal) json. cashflow cashflow, cf This command displays a cashflow statement, showing the inflows and outflows affecting "cash" (ie, liquid) assets. Amounts are shown with normal positive sign, as in conventional financial statements. The "cash" accounts shown are those accounts declared with the Cash type, or otherwise all accounts under a top-level asset account (case insensitive, plural allowed) which do not have fixed, investment, re- ceivable or A/R in their name. Example: $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 With a reporting interval, multiple columns will be shown, one for each report period. Normally cashflow shows changes in assets per period, though as with multicolumn balance reports you can alter the report mode with --change/--cumulative/--historical. Instead of absolute val- ues percentages can be displayed with -%. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, html, and (experimen- tal) json. check-dates check-dates Check that transactions are sorted by increasing date. With --date2, checks secondary dates instead. With --strict, dates must also be unique. With a query, only matched transactions' dates are checked. Reads the default journal file, or another specified with -f. check-dupes check-dupes Reports account names having the same leaf but different prefixes. In other words, two or more leaves that are categorized differently. Reads the default journal file, or another specified as an argument. An example: http://stefanorodighiero.net/software/hledger-dupes.html close close, equity Prints a "closing balances" transaction and an "opening balances" transaction that bring account balances to and from zero, respectively. These can be added to your journal file(s), eg to bring asset/liability balances forward into a new journal file, or to close out revenues/ex- penses to retained earnings at the end of a period. You can print just one of these transactions by using the --close or --open flag. You can customise their descriptions with the --close- desc and --open-desc options. One amountless posting to "equity:opening/closing balances" is added to balance the transactions, by default. You can customise this account name with --close-acct and --open-acct; if you specify only one of these, it will be used for both. With --x/--explicit, the equity posting's amount will be shown. And if it involves multiple commodities, a posting for each commodity will be shown, as with the print command. With --interleaved, the equity postings are shown next to the postings they balance, which makes troubleshooting easier. By default, transaction prices in the journal are ignored when generat- ing the closing/opening transactions. With --show-costs, this cost in- formation is preserved (balance -B reports will be unchanged after the transition). Separate postings are generated for each cost in each commodity. Note this can generate very large journal entries, if you have many foreign currency or investment transactions. close usage If you split your journal files by time (eg yearly), you will typically run this command at the end of the year, and save the closing transac- tion as last entry of the old file, and the opening transaction as the first entry of the new file. This makes the files self contained, so that correct balances are reported no matter which of them are loaded. Ie, if you load just one file, the balances are initialised correctly; or if you load several files, the redundant closing/opening transac- tions cancel each other out. (They will show up in print or register reports; you can exclude them with a query like not:desc:'(open- ing|closing) balances'.) If you're running a business, you might also use this command to "close the books" at the end of an accounting period, transferring income statement account balances to retained earnings. (You may want to change the equity account name to something like "equity:retained earn- ings".) By default, the closing transaction is dated yesterday, the balances are calculated as of end of yesterday, and the opening transaction is dated today. To close on some other date, use: hledger close -e OPEN- INGDATE. Eg, to close/open on the 2018/2019 boundary, use -e 2019. You can also use -p or date:PERIOD (any starting date is ignored). Both transactions will include balance assertions for the closed/re- opened accounts. You probably shouldn't use status or realness filters (like -C or -R or status:) with this command, or the generated balance assertions will depend on these flags. Likewise, if you run this com- mand with --auto, the balance assertions will probably always require --auto. Examples: Carrying asset/liability balances into a new file for 2019: $ hledger close -f 2018.journal -e 2019 assets liabilities --open # (copy/paste the output to the start of your 2019 journal file) $ hledger close -f 2018.journal -e 2019 assets liabilities --close # (copy/paste the output to the end of your 2018 journal file) Now: $ hledger bs -f 2019.journal # one file - balances are correct $ hledger bs -f 2018.journal -f 2019.journal # two files - balances still correct $ hledger bs -f 2018.journal not:desc:closing # to see year-end balances, must exclude closing txn Transactions spanning the closing date can complicate matters, breaking balance assertions: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 assets:bank:checking -5 ; [2019/1/2] Here's one way to resolve that: ; in 2018.journal: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 liabilities:pending ; in 2019.journal: 2019/1/2 clearance of last year's pending transactions liabilities:pending 5 = 0 assets:checking codes 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: 1/1 (123) (a) 1 1/1 () (a) 1 1/1 (a) 1 1/1 (126) (a) 1 $ hledger codes 123 124 126 $ hledger codes -E 123 124 126 commodities commodities List all commodity/currency symbols used or declared in the journal. descriptions 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 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 files List all files included in the journal. With a REGEX argument, only file names matching the regular expression (case sensitive) are shown. help help Show any of the hledger manuals. The help command displays any of the main hledger manuals, in one of several ways. Run it with no argument to list the manuals, or provide a full or partial manual name to select one. hledger manuals are available in several formats. hledger help will use the first of these display methods that it finds: info, man, $PAGER, less, stdout (or when non-interactive, just stdout). You can force a particular viewer with the --info, --man, --pager, --cat flags. Examples: $ hledger help Please choose a manual by typing "hledger help MANUAL" (a substring is ok). Manuals: hledger hledger-ui hledger-web journal csv timeclock timedot $ hledger help h --man hledger(1) hledger User Manuals hledger(1) NAME hledger - a command-line accounting tool SYNOPSIS hledger [-f FILE] COMMAND [OPTIONS] [ARGS] hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS] hledger DESCRIPTION hledger is a cross-platform program for tracking money, time, or any ... import import Read new transactions added to each FILE since last run, and add them to the main journal file. Or with --dry-run, just print the transac- tions that would be added. Or with --catchup, just mark all of the FILEs' transactions as imported, without actually importing any. The input files are specified as arguments - no need to write -f before each one. So eg to add new transactions from all CSV files to the main journal, it's just: hledger import *.csv New transactions are detected in the same way as print --new: by assum- ing transactions are always added to the input files in increasing date order, and by saving .latest.FILE state files. The --dry-run output is in journal format, so you can filter it, eg to see only uncategorised transactions: $ hledger import --dry ... | hledger -f- print unknown --ignore-assertions 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.) incomestatement 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. The revenue and expense accounts shown are those accounts declared with the Revenue or Expense type, or otherwise all accounts under a top- level revenue or income or expense account (case insensitive, plurals allowed). Example: $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 With a reporting interval, multiple columns will be shown, one for each report period. Normally incomestatement shows revenues/expenses per period, though as with multicolumn balance reports you can alter the report mode with --change/--cumulative/--historical. Instead of abso- lute values percentages can be displayed with -%. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, html, and (experimen- tal) json. notes 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 payees List the unique payee/payer names that appear in transactions. This command lists the unique payee/payer names that appear in transac- tions, in alphabetic order. You can add a query to select a subset of transactions. The payee/payer is the part of the transaction descrip- tion before a | character (or if there is no |, the whole description). Example: $ hledger payees Store Name Gas Station Person A prices prices Print market price directives from the journal. With --costs, also print synthetic market prices based on transaction prices. With --in- verted-costs, also print inverse prices based on transaction prices. Prices (and postings providing prices) can be filtered by a query. Price amounts are always displayed with their full precision. print print, txns, p Show transaction journal entries, sorted by date. The print command displays full journal entries (transactions) from the journal file in date order, tidily formatted. With --date2, transac- tions are sorted by secondary date instead. print's output is always a valid hledger journal. It preserves all transaction information, but it does not preserve di- rectives or inter-transaction comments $ hledger print 2008/01/01 income assets:bank:checking $1 income:salary $-1 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 2008/12/31 * pay off liabilities:debts $1 assets:bank:checking $-1 Normally, the journal entry's explicit or implicit amount style is pre- served. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, when a transaction price is im- plied but not written, it will not appear in the output. You can use the -x/--explicit flag to make all amounts and transaction prices ex- plicit, which 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. Note, -x/--explicit will cause postings with a multi-commodity amount (these can arise when a multi-commodity transaction has an implicit amount) to be split into multiple single-commodity postings, keeping the output parseable. With -B/--cost, amounts with transaction prices are converted to cost using that price. This can be used for troubleshooting. With -m/--match and a STR argument, print will show at most one trans- action: the one one whose description is most similar to STR, and is most recent. STR should contain at least two characters. If there is no similar-enough match, no transaction will be shown. With --new, for each FILE being read, hledger reads (and writes) a spe- cial state file (.latest.FILE in the same directory), containing the latest transaction date(s) that were seen last time FILE was read. When this file is found, only transactions with newer dates (and new transactions on the latest date) are printed. This is useful for ig- noring already-seen entries in import data, such as downloaded CSV files. Eg: $ hledger -f bank1.csv print --new (shows transactions added since last print --new on this file) This assumes that transactions added to FILE always have same or in- creasing dates, and that transactions on the same day do not get re- ordered. See also the import command. This command also supports the output destination and output format op- tions The output formats supported are txt, csv, and (experimental) json and sql. 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.) print-unique print-unique Print transactions which do not reuse an already-seen description. Example: $ cat unique.journal 1/1 test (acct:one) 1 2/2 test (acct:two) 2 $ LEDGER_FILE=unique.journal hledger print-unique (-f option not supported) 2015/01/01 test (acct:one) 1 register register, reg, r 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. 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. 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, and (experimental) json. register-match register-match Print the one posting whose transaction description is closest to DESC, in the style of the register command. If there are multiple equally good matches, it shows the most recent. Query options (options, not arguments) can be used to restrict the search space. Helps ledger-au- tosync detect already-seen transactions when importing. rewrite 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 roi Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. This command assumes that you have account(s) that hold nothing but your investments and whenever you record current appraisal/valuation of these investments you offset unrealized profit and loss into account(s) that, again, hold nothing but unrealized profit and loss. Any transactions affecting balance of investment account(s) and not originating from unrealized profit and loss account(s) are assumed to be your investments or withdrawals. At a minimum, you need to supply a query (which could be just an ac- count name) to select your investments with --inv, and another query to identify your profit and loss transactions with --pnl. It will compute and display the internalized rate of return (IRR) and time-weighted rate of return (TWR) for your investments for the time period requested. Both rates of return are annualized before display, regardless of the length of reporting interval. stats stats Show some journal 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. Example: $ hledger stats Main journal file : /src/hledger/examples/sample.journal Included journal files : Transactions span : 2008-01-01 to 2009-01-01 (366 days) Last transaction : 2008-12-31 (2333 days ago) 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 : 12 ($) This command also supports output destination and output format selec- tion. tags tags List the unique tag names used in the journal. With a TAGREGEX argu- ment, only tag names matching the regular expression (case insensitive) are shown. With QUERY arguments, only transactions matching the query are considered. With the --values flag, the tags' unique values are listed instead. With --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. test 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). Add-on commands hledger also searches for external add-on commands, and will include these in the commands list. These are programs or scripts in your PATH whose name starts with hledger- and ends with a recognised file exten- sion (currently: no extension, bat,com,exe, hs,lhs,pl,py,rb,rkt,sh). Add-ons can be invoked like any hledger command, but there are a few things to be aware of. Eg if the hledger-web add-on is installed, o hledger -h web shows hledger's help, while hledger web -h shows hledger-web's help. o Flags specific to the add-on must have a preceding -- to hide them from hledger. So hledger web --serve --port 9000 will be rejected; you must use hledger web -- --serve --port 9000. o You can always run add-ons directly if preferred: hledger-web --serve --port 9000. Add-ons are a relatively easy way to add local features or experiment with new ideas. They can be written in any language, but haskell scripts have a big advantage: they can use the same hledger (and haskell) library functions that built-in commands do, for command-line options, journal parsing, reporting, etc. Two important add-ons are the hledger-ui and hledger-web user inter- faces. These are maintained and released along with hledger: ui hledger-ui provides an efficient terminal interface. web hledger-web provides a simple web interface. Third party add-ons, maintained separately from hledger, include: iadd hledger-iadd is a more interactive, terminal UI replacement for the add command. interest hledger-interest generates interest transactions for an account accord- ing to various schemes. A few more experimental or old add-ons can be found in hledger's bin/ directory. These are typically prototypes and not guaranteed to work. ENVIRONMENT LEDGER_FILE The journal file path when not specified with -f. Default: ~/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.jour- nal). A typical value is ~/DIR/YYYY.journal, where DIR is a version-con- trolled finance directory and YYYY is the current year. Or ~/DIR/cur- rent.journal, where current.journal is a symbolic link to YYYY.journal. On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a ~/.MacOSX/en- vironment.plist file containing { "LEDGER_FILE" : "~/finance/current.journal" } To see the effect you may need to killall Dock, or reboot. COLUMNS The screen width used by the register command. Default: the full terminal width. NO_COLOR If this variable exists with any value, hledger will not use ANSI color codes in terminal output. This overrides the --color/--colour option. FILES Reads data from one or more files in hledger journal, timeclock, time- dot, or CSV format specified with -f, or $LEDGER_FILE, or $HOME/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.journal). LIMITATIONS The need to precede addon command options with -- when invoked from hledger is awkward. When input data contains non-ascii characters, a suitable system locale must be configured (or there will be an unhelpful error). Eg on POSIX, set LANG to something other than C. In a Microsoft Windows CMD window, non-ascii characters and colours are not supported. On Windows, non-ascii characters may not display correctly when running a hledger built in CMD in MSYS/CYGWIN, or vice-versa. In a Cygwin/MSYS/Mintty window, the tab key is not supported in hledger add. Not all of Ledger's journal file syntax is supported. See file format differences. On large data files, hledger is slower and uses more memory than Ledger. TROUBLESHOOTING Here are some issues you might encounter when you run hledger (and re- member you can also seek help from the IRC channel, mail list or bug tracker): Successfully installed, but "No command 'hledger' found" stack and cabal install binaries into a special directory, which should be added to your PATH environment variable. Eg on unix-like systems, that is ~/.local/bin and ~/.cabal/bin respectively. I set a custom LEDGER_FILE, but hledger is still using the default file LEDGER_FILE should be a real environment variable, not just a shell variable. The command env | grep LEDGER_FILE should show it. You may need to use export. Here's an explanation. Getting errors like "Illegal byte sequence" or "Invalid or incomplete multibyte or wide character" or "commitAndReleaseBuffer: invalid argu- ment (invalid character)" Programs compiled with GHC (hledger, haskell build tools, etc.) need to have a UTF-8-aware locale configured in the environment, otherwise they will fail with these kinds of errors when they encounter non-ascii characters. To fix it, set the LANG environment variable to some locale which sup- ports UTF-8. The locale you choose must be installed on your system. Here's an example of setting LANG temporarily, on Ubuntu GNU/Linux: $ file my.journal my.journal: UTF-8 Unicode text # the file is UTF8-encoded $ echo $LANG C # LANG is set to the default locale, which does not support UTF8 $ locale -a # which locales are installed ? C en_US.utf8 # here's a UTF8-aware one we can use POSIX $ LANG=en_US.utf8 hledger -f my.journal print # ensure it is used for this command If available, C.UTF-8 will also work. If your preferred locale isn't listed by locale -a, you might need to install it. Eg on Ubuntu/De- bian: $ apt-get install language-pack-fr $ locale -a C en_US.utf8 fr_BE.utf8 fr_CA.utf8 fr_CH.utf8 fr_FR.utf8 fr_LU.utf8 POSIX $ LANG=fr_FR.utf8 hledger -f my.journal print Here's how you could set it permanently, if you use a bash shell: $ echo "export LANG=en_US.utf8" >>~/.bash_profile $ bash --login Exact spelling and capitalisation may be important. Note the differ- ence on MacOS (UTF-8, not utf8). Some platforms (eg ubuntu) allow variant spellings, but others (eg macos) require it to be exact: $ locale -a | grep -iE en_us.*utf en_US.UTF-8 $ LANG=en_US.UTF-8 hledger -f my.journal print REPORTING BUGS Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) AUTHORS Simon Michael and contributors COPYRIGHT Copyright (C) 2007-2019 Simon Michael. Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), hledger-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_time- dot(5), ledger(1) http://hledger.org hledger 1.18.99 September 2020 hledger(1) hledger-1.19.1/embeddedfiles/hledger.info0000644000000000000000000044153513725533425016473 0ustar0000000000000000This is hledger.info, produced by makeinfo version 6.7 from stdin.  File: hledger.info, Node: Top, Next: COMMON TASKS, Up: (dir) hledger(1) hledger 1.18.99 ************************** hledger - a command-line accounting tool 'hledger [-f FILE] COMMAND [OPTIONS] [ARGS]' 'hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS]' 'hledger' hledger is a reliable, 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). This is hledger's command-line interface (there are also terminal and web interfaces). Its basic function is to read a plain text file describing financial transactions (in accounting terms, a general journal) and print useful reports on standard output, or export them as CSV. hledger can also read some other file formats such as CSV files, translating them to journal format. Additionally, hledger lists other hledger-* executables found in the user's $PATH and can invoke them as subcommands. hledger reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with '-f', or '$LEDGER_FILE', or '$HOME/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal'). If using '$LEDGER_FILE', note this must be a real environment variable, not a shell variable. You can specify standard input with '-f-'. Transactions are dated movements of money between two (or more) named accounts, and are recorded with journal entries like this: 2015/10/16 bought food expenses:food $10 assets:cash For more about this format, see hledger_journal(5). Most users use a text editor to edit the journal, usually with an editor mode such as ledger-mode for added convenience. hledger's interactive add command is another way to record new transactions. hledger never changes existing transactions. To get started, you can either save some entries like the above in '~/.hledger.journal', or run 'hledger add' and follow the prompts. Then try some commands like 'hledger print' or 'hledger balance'. Run 'hledger' with no arguments for a list of commands. * Menu: * COMMON TASKS:: * OPTIONS:: * COMMANDS:: * ENVIRONMENT:: * FILES:: * LIMITATIONS:: * TROUBLESHOOTING::  File: hledger.info, Node: COMMON TASKS, Next: OPTIONS, Prev: Top, Up: Top 1 COMMON TASKS ************** Here are some quick examples of how to do some basic tasks with hledger. For more details, see the reference section below, the hledger_journal(5) manual, or the more extensive docs at https://hledger.org. * Menu: * Getting help:: * Constructing command lines:: * Starting a journal file:: * Setting opening balances:: * Recording transactions:: * Reconciling:: * Reporting:: * Migrating to a new file::  File: hledger.info, Node: Getting help, Next: Constructing command lines, Up: COMMON TASKS 1.1 Getting help ================ $ hledger # show available commands $ hledger --help # show common options $ hledger CMD --help # show common and command options, and command help $ hledger help # show available manuals/topics $ hledger help hledger # show hledger manual as info/man/text (auto-chosen) $ hledger help journal --man # show the journal manual as a man page $ hledger help --help # show more detailed help for the help command Find more docs, chat, mail list, reddit, issue tracker: https://hledger.org#help-feedback  File: hledger.info, Node: Constructing command lines, Next: Starting a journal file, Prev: Getting help, Up: COMMON TASKS 1.2 Constructing command lines ============================== hledger has an extensive and powerful command line interface. We strive to keep it simple and ergonomic, but you may run into one of the confusing real world details described in OPTIONS, below. If that happens, here are some tips that may help: * command-specific options must go after the command (it's fine to put all options there) ('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 is being parsed, add '--debug=2'.  File: hledger.info, Node: Starting a journal file, Next: Setting opening balances, Prev: Constructing command lines, Up: COMMON TASKS 1.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. 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 2020.journal $ echo "export LEDGER_FILE=$HOME/finance/2020.journal" >> ~/.bashrc $ source ~/.bashrc $ hledger stats Main file : /Users/simon/finance/2020.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 opening balances, Next: Recording transactions, Prev: Starting a journal file, Up: COMMON TASKS 1.4 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: 2020-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/2020.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 [2020-02-07]: 2020-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): . 2020-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 [2020-01-01]: . If you're using version control, this could be a good time to commit the journal. Eg: $ git commit -m 'initial balances' 2020.journal  File: hledger.info, Node: Recording transactions, Next: Reconciling, Prev: Setting opening balances, Up: COMMON TASKS 1.5 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: 2020/1/10 * gift received assets:cash $20 income:gifts 2020.1.12 * farmers market expenses:food $13 assets:cash 2020-01-15 paycheck income:salary assets:bank:checking $1000  File: hledger.info, Node: Reconciling, Next: Reporting, Prev: Recording transactions, Up: COMMON TASKS 1.6 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: 2020-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 '2020-01-15' and 'paycheck' If you're using version control, this can be another good time to commit: $ git commit -m 'txns' 2020.journal  File: hledger.info, Node: Reporting, Next: Migrating to a new file, Prev: Reconciling, Up: COMMON TASKS 1.7 Reporting ============= Here are some basic reports. Show all transactions: $ hledger print 2020-01-01 * opening balances assets:bank:checking $1000 assets:bank:savings $2000 assets:cash $100 liabilities:creditcard $-50 equity:opening/closing balances $-3050 2020-01-10 * gift received assets:cash $20 income:gifts 2020-01-12 * farmers market expenses:food $13 assets:cash 2020-01-15 * paycheck income:salary assets:bank:checking $1000 2020-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 --flat -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 --flat -2 Balance Sheet 2020-01-16 || 2020-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 2020-01-01-2020-01-16 || 2020-01-01-2020-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 2020-01-01 opening balances assets:cash $100 $100 2020-01-10 gift received assets:cash $20 $120 2020-01-12 farmers market assets:cash $-13 $107 2020-01-16 adjust cash assets:cash $-2 $105 Show weekly posting counts as a bar chart: $ hledger activity -W 2019-12-30 ***** 2020-01-06 **** 2020-01-13 ****  File: hledger.info, Node: Migrating to a new file, Prev: Reporting, Up: COMMON TASKS 1.8 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: OPTIONS, Next: COMMANDS, Prev: COMMON TASKS, Up: Top 2 OPTIONS ********* * Menu: * General options:: * Command options:: * Command arguments:: * Queries:: * Special characters in arguments and queries:: * Unicode characters:: * Input files:: * Output destination:: * Output format:: * Regular expressions:: * Smart dates:: * Report start & end date:: * Report intervals:: * Period expressions:: * Depth limiting:: * Pivoting:: * Valuation::  File: hledger.info, Node: General options, Next: Command options, Up: OPTIONS 2.1 General options =================== To see general usage help, including general options which are supported by most hledger commands, run 'hledger -h'. General help options: '-h --help' show general usage (or after COMMAND, command usage) '--version' show 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 '--anon' anonymize accounts and payees '--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) General reporting options: '-b --begin=DATE' include postings/txns on or after this date '-e --end=DATE' include postings/txns before this date '-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) '-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-value' with -V/-X/-value, also infer market prices from transactions '--auto' apply automated posting rules to modify transactions. '--forecast' generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. '--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. 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 options, Next: Command arguments, Prev: General options, Up: OPTIONS 2.2 Command options =================== To see options for a particular command, including command-specific options, run: 'hledger COMMAND -h'. Command-specific options must be written after the command name, eg: 'hledger print -x'. Additionally, if the command is an addon, you may need to put its options after a double-hyphen, eg: 'hledger ui -- --watch'. Or, you can run the addon executable directly: 'hledger-ui --watch'.  File: hledger.info, Node: Command arguments, Next: Queries, Prev: Command options, Up: OPTIONS 2.3 Command arguments ===================== Most hledger commands accept arguments after the command name, which are often a query, filtering the data in some way. You can save a set of command line options/arguments in a file, and then reuse them by writing '@FILENAME' as a command line argument. Eg: 'hledger bal @foo.args'. (To prevent this, eg if you have an argument that begins with a literal '@', precede it with '--', eg: 'hledger bal -- @ARG'). Inside the argument file, each line should contain just one option or argument. Avoid the use of spaces, except inside quotes (or you'll see a confusing error). Between a flag and its argument, use = (or nothing). Bad: assets depth:2 -X USD Good: assets depth:2 -X=USD For special characters (see below), use one less level of quoting than you would at the command prompt. Bad: -X"$" Good: -X$ See also: Save frequently used options.  File: hledger.info, Node: Queries, Next: Special characters in arguments and queries, Prev: Command arguments, Up: OPTIONS 2.4 Queries =========== One of hledger's strengths is being able to quickly report on precise subsets of your data. Most commands accept an optional query expression, written as arguments after the command name, to filter the data by date, account name or other criteria. The syntax is similar to a web search: one or more space-separated search terms, quotes to enclose whitespace, prefixes to match specific fields, a not: prefix to negate the match. We do not yet support arbitrary boolean combinations of search terms; instead most commands show transactions/postings/accounts which match (or negatively 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 instead shows 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. The following kinds of search terms can be used. Remember these can also be prefixed with *'not:'*, eg to exclude a particular subaccount. *'REGEX', 'acct:REGEX'* match account names by this regular expression. (With no prefix, 'acct:' is assumed.) same as above *'amt:N, amt:N, amt:>=N'* match postings with a single-commodity amount that is equal to, less than, or greater than N. (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 characters which are regex-significant, like the dollar sign ('$'), you need to prepend '\'. And when using the command line you need to add one more level of quoting to hide it from the shell, so eg do: 'hledger print cur:'\$'' or 'hledger print cur:\\$'. *'desc:REGEX'* match transaction descriptions. *'date:PERIODEXPR'* match dates within the specified period. PERIODEXPR is a period expression (with no report interval). Examples: 'date:2016', 'date:thismonth', 'date:2000/2/1-2/15', 'date:lastweek-'. If the '--date2' command line flag is present, this matches secondary dates instead. *'date2:PERIODEXPR'* match secondary dates within the specified period. *'depth:N'* match (or display, depending on command) accounts at or above this depth *'note:REGEX'* match transaction notes (part of description right of '|', or whole description when there's no '|') *'payee:REGEX'* match transaction payee/payer names (part of description left of '|', or whole description when there's no '|') *'real:, real:0'* match real or virtual postings respectively *'status:, status:!, status:*'* match unmarked, pending, or cleared transactions respectively *'tag:REGEX[=REGEX]'* match by tag name, and optionally also by tag value. Note a tag: query is considered to match a transaction if it matches any of the postings. Also remember that postings inherit the tags of their parent transaction. The following special search term is used automatically in hledger-web, only: *'inacct:ACCTNAME'* tells hledger-web to show the transaction register for this account. Can be filtered further with 'acct' etc. Some of these can also be expressed as command-line options (eg 'depth:2' is equivalent to '--depth 2'). Generally you can mix options and query arguments, and the resulting query will be their intersection (perhaps excluding the '-p/--period' option).  File: hledger.info, Node: Special characters in arguments and queries, Next: Unicode characters, Prev: Queries, Up: OPTIONS 2.5 Special characters in arguments and queries =============================================== In shell command lines, option and argument values which contain "problematic" characters, ie spaces, and also characters significant to your shell such as '<', '>', '(', ')', '|' and '$', should be escaped by enclosing them in quotes or by writing backslashes before the characters. Eg: 'hledger register -p 'last year' "accounts receivable (receivable|payable)" amt:\>100'. * Menu: * More escaping:: * Even more escaping:: * Less escaping::  File: hledger.info, Node: More escaping, Next: Even more escaping, Up: Special characters in arguments and queries 2.5.1 More escaping ------------------- Characters significant both to the shell and in regular expressions may need one extra level of escaping. These include parentheses, the pipe symbol and the dollar sign. Eg, to match the dollar symbol, bash users should do: 'hledger balance cur:'\$'' or: 'hledger balance cur:\\$'  File: hledger.info, Node: Even more escaping, Next: Less escaping, Prev: More escaping, Up: Special characters in arguments and queries 2.5.2 Even more escaping ------------------------ When hledger runs an addon executable (eg you type 'hledger ui', hledger runs 'hledger-ui'), it de-escapes command-line options and arguments once, so you might need to _triple_-escape. Eg in bash, running the ui command and matching the dollar sign, it's: 'hledger ui cur:'\\$'' or: 'hledger ui cur:\\\\$' If you asked why _four_ slashes above, this may help: unescaped: '$' escaped: '\$' double-escaped: '\\$' triple-escaped: '\\\\$' (The number of backslashes in fish shell is left as an exercise for the reader.) You can always avoid the extra escaping for addons by running the addon directly: 'hledger-ui cur:\\$'  File: hledger.info, Node: Less escaping, Prev: Even more escaping, Up: Special characters in arguments and queries 2.5.3 Less escaping ------------------- Inside an argument file, or in the search field of hledger-ui or hledger-web, or at a GHCI prompt, you need one less level of escaping than at the command line. And backslashes may work better than quotes. Eg: 'ghci> :main balance cur:\$'  File: hledger.info, Node: Unicode characters, Next: Input files, Prev: Special characters in arguments and queries, Up: OPTIONS 2.6 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: Input files, Next: Output destination, Prev: Unicode characters, Up: OPTIONS 2.7 Input files =============== hledger reads transactions from a data file (and the add command writes to it). By default this file is '$HOME/.hledger.journal' (or on Windows, something like 'C:/Users/USER/.hledger.journal'). You can override this with the '$LEDGER_FILE' environment variable: $ setenv LEDGER_FILE ~/finance/2016.journal $ hledger stats or with the '-f/--file' option: $ hledger -f /some/file stats The file name '-' (hyphen) means standard input: $ cat some.journal | hledger -f- 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 Ledger '.journal' '.j' journals, for transactions '.hledger' '.ledger' 'timeclock'timeclock files, for precise time '.timeclock' logging 'timedot'timedot files, for approximate time '.timedot' logging 'csv' comma/semicolon/tab/other-separated '.csv' '.ssv' '.tsv' values, for data import 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. When you can't ensure the right file extension, not to worry: you can force a specific reader/format by prefixing the file path with the format and a colon. Eg to read a .dat file as csv: $ hledger -f csv:/some/csv-file.dat stats $ echo 'i 2009/13/1 08:00:00' | hledger print -ftimeclock:- You can specify multiple '-f' options, to read multiple files as one big journal. There are some limitations with this: * directives in one file will not affect the other files * balance assertions will not see any account balances from previous files If you need either of those things, you can * use a single parent file which includes the others * or concatenate the files into one before reading, eg: 'cat a.journal b.journal | hledger -f- CMD'.  File: hledger.info, Node: Output destination, Next: Output format, Prev: Input files, Up: OPTIONS 2.8 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: Regular expressions, Prev: Output destination, Up: OPTIONS 2.9 Output format ================= Some commands (print, register, the balance commands) offer a choice of output format. In addition to the usual plain text format ('txt'), there are CSV ('csv'), HTML ('html'), JSON ('json') and SQL ('sql'). This is controlled by the '-O/--output-format' option: $ hledger print -O csv or, by a file extension specified with '-o/--output-file': $ hledger balancesheet -o foo.html # write HTML to foo.html The '-O' option can be used to override the file extension if needed: $ hledger balancesheet -o foo.txt -O html # write HTML to foo.txt Some notes about JSON output: * This feature is marked experimental, and not yet much used; you should expect our JSON to evolve. Real-world feedback is welcome. * Our JSON is rather large and verbose, as it is quite 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) Notes about SQL output: * SQL output is also marked experimental, and much like JSON could use real-world feedback. * SQL output is expected to work with sqlite, MySQL and PostgreSQL * 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: Regular expressions, Next: Smart dates, Prev: Output format, Up: OPTIONS 2.10 Regular expressions ======================== hledger uses regular expressions in a number of places: * query terms, on the command line and in the hledger-web search form: 'REGEX', 'desc:REGEX', 'cur:REGEX', 'tag:...=REGEX' * CSV rules conditional blocks: 'if REGEX ...' * account alias directives and options: 'alias /REGEX/ = REPLACEMENT', '--alias /REGEX/=REPLACEMENT' 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. they do not support backreferences; if you write '\1', it will match the digit '1'. Except when doing text replacement, eg in account aliases, where backreferences can be used in the replacement string to reference capturing groups in the search regexp. 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: Smart dates, Next: Report start & end date, Prev: Regular expressions, Up: OPTIONS 2.11 Smart dates ================ hledger's user interfaces accept a flexible "smart date" syntax (unlike dates in the journal file). Smart dates allow some english words, can be relative to today's date, and can have less-significant date parts omitted (defaulting to 1). 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' '20181201' 8 digit YYYYMMDD with valid year month and day '201812' 6 digit YYYYMM with valid year and month 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  File: hledger.info, Node: Report start & end date, Next: Report intervals, Prev: Smart dates, Up: OPTIONS 2.12 Report start & end date ============================ Most hledger reports show the full span of time represented by the journal data, by default. So, the effective report start and end dates will be the earliest and latest transaction or posting dates found in the journal. 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. Some notes: * As in Ledger, end dates are exclusive, so you need to write the date _after_ the last day you want to include. * 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. 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: Report intervals, Next: Period expressions, Prev: Report start & end date, Up: OPTIONS 2.13 Report intervals ===================== A report interval can be specified so that commands like register, balance and activity will divide their reports into multiple subperiods. The basic intervals can be selected with one of '-D/--daily', '-W/--weekly', '-M/--monthly', '-Q/--quarterly', or '-Y/--yearly'. More complex intervals may be specified with a period expression. Report intervals can not be specified with a query.  File: hledger.info, Node: Period expressions, Next: Depth limiting, Prev: Report intervals, Up: OPTIONS 2.14 Period expressions ======================= The '-p/--period' option accepts period expressions, a shorthand way of expressing a start date, end date, and/or report interval all at once. Here's a basic period expression specifying the first quarter of 2009. Note, hledger always treats start dates as inclusive and end dates as exclusive: '-p "from 2009/1/1 to 2009/4/1"' Keywords like "from" and "to" are optional, and so are the spaces, as long as you don't run two dates together. "to" can also be written as ".." or "-". These 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, the above can also be written as: '-p "1/1 4/1"' '-p "january-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 in your journal: '-p "from 2009/1/1"' everything after january 1, 2009 '-p "from 2009/1"' the same '-p "from 2009"' the same '-p "to 2009"' everything before january 1, 2009 A single date with no "from" or "to" defines both the start and end date like so: '-p "2009"' the year 2009; equivalent to “2009/1/1 to 2010/1/1” '-p "2009/1"' the month of jan; equivalent to “2009/1/1 to 2009/2/1” '-p "2009/1/1"' just that day; equivalent to “2009/1/1 to 2009/1/2” Or you can specify a single quarter like so: '-p "2009Q1"' first quarter of 2009, equivalent to “2009/1/1 to 2009/4/1” '-p "q4"' fourth quarter of the current year The argument of '-p' can also begin with, or be, a report interval expression. The basic report intervals are 'daily', 'weekly', 'monthly', 'quarterly', or 'yearly', which have the same effect as the '-D','-W','-M','-Q', or '-Y' flags. Between report interval and start/end dates (if any), the word 'in' is optional. Examples: '-p "weekly from 2009/1/1 to 2009/4/1"' '-p "monthly in 2008"' '-p "quarterly"' Note that 'weekly', 'monthly', 'quarterly' and 'yearly' intervals will always start on the first day on week, month, quarter or year accordingly, and will end on the last day of same period, even if associated period expression specifies different explicit start and end date. For example: '-p "weekly from starts on 2008/12/29, closest preceding 2009/1/1 to 2009/4/1"' Monday '-p "monthly in starts on 2018/11/01 2008/11/25"' '-p "quarterly from starts on 2009/04/01, ends on 2009/06/30, 2009-05-05 to which are first and last days of Q2 2009 2009-06-01"' '-p "yearly from starts on 2009/01/01, first day of 2009 2009-12-29"' The following more complex report intervals are also supported: 'biweekly', 'fortnightly', 'bimonthly', 'every day|week|month|quarter|year', 'every N days|weeks|months|quarters|years'. All of these will start on the first day of the requested period and end on the last one, as described above. Examples: '-p "bimonthly from periods will have boundaries on 2008/01/01, 2008"' 2008/03/01, ... '-p "every 2 weeks"' starts on closest preceding Monday '-p "every 5 month from periods will have boundaries on 2009/03/01, 2009/03"' 2009/08/01, ... If you want intervals that start on arbitrary day of your choosing and span a week, month or year, you need to use any of the following: 'every Nth day of week', 'every ', 'every Nth day [of month]', 'every Nth weekday [of month]', 'every MM/DD [of year]', 'every Nth MMM [of year]', 'every MMM Nth [of year]'. Examples: '-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 period boundaries will be on second Monday of Monday"' each month '-p "every 11/05"' yearly periods with boundaries on 5th of Nov '-p "every 5th Nov"' same '-p "every Nov 5th"' same Show historical balances at end of 15th each month (N is exclusive end date): 'hledger balance -H -p "every 16th day"' Group postings from start of wednesday to end of next tuesday (N is start date and exclusive end date): 'hledger register checking -p "every 3rd day of week"'  File: hledger.info, Node: Depth limiting, Next: Pivoting, Prev: Period expressions, Up: OPTIONS 2.15 Depth limiting =================== With the '--depth N' option (short form: '-N'), commands like account, balance and register will show only the uppermost accounts in the account tree, down to level N. Use this when you want a summary with less detail. This flag has the same effect as a 'depth:' query argument (so '-2', '--depth=2' or 'depth:2' are equivalent).  File: hledger.info, Node: Pivoting, Next: Valuation, Prev: Depth limiting, Up: OPTIONS 2.16 Pivoting ============= Normally hledger sums amounts, and organizes them in a hierarchy, based on account name. The '--pivot FIELD' option causes it to sum and organize hierarchy based on the value of some other field instead. FIELD can be: 'code', 'description', 'payee', 'note', or the full name (case insensitive) of any tag. As with account names, values containing 'colon:separated:parts' will be displayed hierarchically in reports. '--pivot' is a general option affecting all reports; you can think of hledger transforming the journal before any other processing, replacing every posting's account name with the value of the specified field on that posting, inheriting it from the transaction or using a blank value if it's not present. An example: 2016/02/16 Member Fee Payment assets:bank account 2 EUR income:member fees -2 EUR ; member: John Doe Normal balance report showing account names: $ hledger balance 2 EUR assets:bank account -2 EUR income:member fees -------------------- 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, described below): $ 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  File: hledger.info, Node: Valuation, Prev: Pivoting, Up: OPTIONS 2.17 Valuation ============== Instead of reporting amounts in their original commodity, hledger can convert them to cost/sale amount (using the conversion rate recorded in the transaction), or to market value (using some market price on a certain date). This is controlled by the '--value=TYPE[,COMMODITY]' option, but we also provide the simpler '-B'/'-V'/'-X' flags, and usually one of those is all you need. * Menu: * -B Cost:: * -V Value:: * -X Value in specified commodity:: * Valuation date:: * Market prices:: * --infer-value market prices from transactions:: * Valuation commodity:: * Simple valuation examples:: * --value Flexible valuation:: * More valuation examples:: * Effect of valuation on reports::  File: hledger.info, Node: -B Cost, Next: -V Value, Up: Valuation 2.17.1 -B: Cost --------------- The '-B/--cost' flag converts amounts to their cost or sale amount at transaction time, if they have a transaction price specified.  File: hledger.info, Node: -V Value, Next: -X Value in specified commodity, Prev: -B Cost, Up: Valuation 2.17.2 -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: Valuation 2.17.3 -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: Market prices, Prev: -X Value in specified commodity, Up: Valuation 2.17.4 Valuation date --------------------- Since market prices can change from day to day, market value reports have a valuation date (or more than one), which determines which market prices will be used. For single period reports, if an explicit report end date is specified, that will be used as the valuation date; otherwise the valuation date is "today". For multiperiod reports, each column/period is valued on the last day of the period.  File: hledger.info, Node: Market prices, Next: --infer-value market prices from transactions, Prev: Valuation date, Up: Valuation 2.17.5 Market prices -------------------- _(experimental)_ 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 (if the '--infer-value' flag is used) inferred from transaction prices. 2. A _reverse market price_: the inverse of a declared or inferred market price from B to A. 3. A _chained market price_: a synthetic price formed by combining the shortest chain of market prices (any of the above types) leading from A to B. Amounts for which no applicable market price can be found, are not converted.  File: hledger.info, Node: --infer-value market prices from transactions, Next: Valuation commodity, Prev: Market prices, Up: Valuation 2.17.6 -infer-value: market prices from transactions ---------------------------------------------------- _(experimental)_ 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 transaction prices as additional market prices (as Ledger does) ? We could produce value reports without needing P directives at all. Adding the '--infer-value' flag to '-V', '-X' or '--value' enables this. So for example, 'hledger bs -V --infer-value' will get market prices both from P directives and from transactions. 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 Valuation section carefully, and try adding '--debug' or '--debug=2' to troubleshoot. '--infer-value' 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.) * but not, currently, from "more correct" multicommodity transactions (no '@', multiple commodities, balanced).  File: hledger.info, Node: Valuation commodity, Next: Simple valuation examples, Prev: --infer-value market prices from transactions, Up: Valuation 2.17.7 Valuation commodity -------------------------- _(experimental)_ *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-value' 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-value' flag, transaction prices 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: Valuation 2.17.8 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: Valuation 2.17.9 -value: Flexible valuation --------------------------------- '-B', '-V' and '-X' are special cases of the more general '--value' option: --value=TYPE[,COMM] TYPE is cost, then, end, now or YYYY-MM-DD. COMM is an optional commodity symbol. Shows amounts converted to: - cost commodity using transaction prices (then optionally to COMM using market prices at period end(s)) - 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=cost' Convert amounts to cost, using the prices recorded in transactions. '--value=then' Convert amounts to their value in the default valuation commodity, using market prices on each posting's date. This is currently supported only by the print and register commands. '--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: Effect of valuation on reports, Prev: --value Flexible valuation, Up: Valuation 2.17.10 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 --value=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 You may need to explicitly set a commodity's display style, when reverse prices are used. Eg this output might be surprising: P 2000-01-01 A 2B 2000-01-01 a 1B b $ hledger print -x -X A 2000-01-01 a 0 b 0 Explanation: because there's no amount or commodity directive specifying a display style for A, 0.5A gets the default style, which shows no decimal digits. Because the displayed amount looks like zero, the commodity symbol and minus sign are not displayed either. Adding a commodity directive sets a more useful display style for A: P 2000-01-01 A 2B commodity 0.00A 2000-01-01 a 1B b $ hledger print -X A 2000-01-01 a 0.50A b -0.50A  File: hledger.info, Node: Effect of valuation on reports, Prev: More valuation examples, Up: Valuation 2.17.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 '--value=cost' '--value=now' ------------------------------------------------------------------------------- *print* posting cost value at value at value at value at amounts report end posting date report or DATE/today or today journal end balance unchanged unchanged unchanged unchanged unchanged assertions / assignments *register* starting cost value at not value at value at balance day before supported day before DATE/today (with -H) report or report or journal journal start start posting cost value at value at value at value at amounts report end posting date report or DATE/today (no report or today journal end interval) summary summarised value at sum of value at value at posting cost period postings in period ends DATE/today amounts ends interval, (with valued at report interval interval) start running sum/average sum/average sum/average sum/average sum/average total/averageof of of displayed of of displayed displayed values displayed displayed values values values values *balance (bs, bse, cf, is..)* balances sums of value at not value at value at (no report costs report end supported report or DATE/today interval) or today journal end of sums of sums of of sums of of postings postings postings balances sums of value at not value at value at (with costs period supported period ends DATE/today report ends of of sums of of sums interval) sums of postings of postings postings starting sums of sums of not sums of sums of balances costs of postings supported postings postings (with postings before before before report before report report report interval report start start start and -H) start budget like like not like like amounts balances balances supported balances balances with -budget grand sum of sum of not sum of sum of total (no displayed displayed supported displayed displayed report values values values values interval) row sums/averagessums/averagesnot sums/averages sums/averages totals/averagesof of supported of of (with displayed displayed displayed displayed report values values values values interval) column sums of sums of not sums of sums of totals displayed displayed supported displayed displayed values values values values grand sum/average sum/average not sum/average sum/average total/averageof column of column supported of column of totals totals totals column totals *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: COMMANDS, Next: ENVIRONMENT, Prev: OPTIONS, Up: Top 3 COMMANDS ********** hledger provides a number of subcommands; 'hledger' with no arguments shows a list. If you install additional 'hledger-*' packages, or if you put programs or scripts named 'hledger-NAME' in your PATH, these will also be listed as subcommands. Run a subcommand by writing its name as first argument (eg 'hledger incomestatement'). You can also write one of the standard short aliases displayed in parentheses in the command list ('hledger b'), or any any unambiguous prefix of a command name ('hledger inc'). Here are all the builtin commands in alphabetical order. See also 'hledger' for a more organised command list, and 'hledger CMD -h' for detailed command help. * Menu: * accounts:: * activity:: * add:: * aregister:: * balance:: * balancesheet:: * balancesheetequity:: * cashflow:: * check-dates:: * check-dupes:: * close:: * codes:: * commodities:: * descriptions:: * diff:: * files:: * help:: * import:: * incomestatement:: * notes:: * payees:: * prices:: * print:: * print-unique:: * register:: * register-match:: * rewrite:: * roi:: * stats:: * tags:: * test:: * Add-on commands::  File: hledger.info, Node: accounts, Next: activity, Up: COMMANDS 3.1 accounts ============ accounts, a Show account names. This command lists account names, either declared with account directives (-declared), posted to (-used), or both (the default). With query arguments, only matched account names and account names referenced by matched postings are shown. 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'. Examples: $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts  File: hledger.info, Node: activity, Next: add, Prev: accounts, Up: COMMANDS 3.2 activity ============ 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: COMMANDS 3.3 add ======= 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 journal file (if there are multiple '-f FILE' options, the first file is used.) Existing transactions are not changed. This is the only hledger command that writes to the journal file. 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, 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 the tutorial for a detailed explanation): $ 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: COMMANDS 3.4 aregister ============= aregister, areg Show transactions affecting a particular account, and the account's running balance. 'aregister' shows the transactions affecting a particular account (and its subaccounts), from the point of view of that account. Each line shows: * the transaction's (or posting's, see below) date * the names of the other account(s) involved * the net change to this account's balance * the account's historical running balance (including balance from transactions before the report start date). With 'aregister', each line represents a whole transaction - as in hledger-ui, hledger-web, and your bank statement. By contrast, the 'register' command shows individual postings, across all accounts. You might prefer 'aregister' for reconciling with real-world asset/liability accounts, and 'register' for reviewing detailed revenues/expenses. An account must be specified as the first argument, which should be the full account name or an account pattern (regular expression). aregister will show transactions in this account (the first one matched) and any of its subaccounts. Any additional arguments form a query which will filter the transactions shown. Transactions making a net change of zero are not shown by default; add the '-E/--empty' flag to show them. * Menu: * aregister and custom posting dates:: * Output format::  File: hledger.info, Node: aregister and custom posting dates, Next: , Up: aregister 3.4.1 aregister and custom posting dates ---------------------------------------- Transactions whose date is outside the report period can still be shown, if they have a posting to this account dated inside the report period. (And in this case it's the posting date that is shown.) This ensures that 'aregister' can show an accurate historical running balance, matching the one shown by 'register -H' with the same arguments. To filter strictly by transaction date instead, add the '--txn-dates' flag. If you use this flag and some of your postings have custom dates, it's probably best to assume the running balance is wrong. 3.4.2 Output format ------------------- This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', and 'json'. Examples: Show all transactions and historical running balance in the first account whose name contains "checking": $ hledger areg checking Show transactions and historical running balance in all asset accounts during july: $ hledger areg assets date:jul  File: hledger.info, Node: balance, Next: balancesheet, Prev: aregister, Up: COMMANDS 3.5 balance =========== balance, bal, b Show accounts and their balances. The balance command is hledger's most versatile command. Note, despite the name, it is not always used for showing real-world account balances; the more accounting-aware balancesheet and incomestatement may be more convenient for that. By default, it displays all accounts, and each account's change in balance during the entire period of the journal. Balance changes are calculated by adding up the postings in each account. You can limit the postings matched, by a query, to see fewer accounts, changes over a different time period, changes from only cleared transactions, etc. If you include an account's complete history of postings in the report, the balance change is equivalent to the account's current ending balance. For a real-world account, typically you won't have all transactions in the journal; instead you'll have all transactions after a certain date, and an "opening balances" transaction setting the correct starting balance on that date. Then the balance command will show real-world account balances. In some cases the -H/-historical flag is used to ensure this (more below). The balance command can produce several styles of report: * Menu: * Classic balance report:: * Customising the classic balance report:: * Colour support:: * Flat mode:: * Depth limited balance reports:: * Percentages:: * Multicolumn balance report:: * Budget report:: * Output format::  File: hledger.info, Node: Classic balance report, Next: Customising the classic balance report, Up: balance 3.5.1 Classic balance report ---------------------------- This is the original balance report, as found in Ledger. It usually looks like this: $ hledger balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 By default, accounts are displayed hierarchically, with subaccounts indented below their parent. At each level of the tree, accounts are sorted by account code if any, then by account name. Or with '-S/--sort-amount', by their balance amount, largest first. "Boring" accounts, which contain a single interesting subaccount and no balance of their own, are elided into the following line for more compact output. (Eg above, the "liabilities" account.) Use '--no-elide' to prevent this. Account balances are "inclusive" - they include the balances of any subaccounts. Accounts which have zero balance (and no non-zero subaccounts) are omitted. Use '-E/--empty' to show them. A final total is displayed by default; use '-N/--no-total' to suppress it, eg: $ hledger balance -p 2008/6 expenses --no-total $2 expenses $1 food $1 supplies  File: hledger.info, Node: Customising the classic balance report, Next: Colour support, Prev: Classic balance report, Up: balance 3.5.2 Customising the classic balance report -------------------------------------------- You can customise the layout of classic balance reports with '--format FMT': $ hledger 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 (plus a newline) 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: Colour support, Next: Flat mode, Prev: Customising the classic balance report, Up: balance 3.5.3 Colour support -------------------- In terminal output, when colour is enabled, the balance command shows negative amounts in red.  File: hledger.info, Node: Flat mode, Next: Depth limited balance reports, Prev: Colour support, Up: balance 3.5.4 Flat mode --------------- To see a flat list instead of the default hierarchical display, use '--flat'. In this mode, accounts (unless depth-clipped) show their full names and "exclusive" balance, excluding any subaccount balances. In this mode, you can also use '--drop N' to omit the first few account name components. $ hledger balance -p 2008/6 expenses -N --flat --drop 1 $1 food $1 supplies  File: hledger.info, Node: Depth limited balance reports, Next: Percentages, Prev: Flat mode, Up: balance 3.5.5 Depth limited balance reports ----------------------------------- With '--depth N' or 'depth:N' or just '-N', balance reports show accounts only to the specified numeric depth. This is very useful to summarise a complex set of accounts and get an overview. $ hledger balance -N -1 $-1 assets $2 expenses $-2 income $1 liabilities Flat-mode balance reports, which normally show exclusive balances, show inclusive balances at the depth limit.  File: hledger.info, Node: Percentages, Next: Multicolumn balance report, Prev: Depth limited balance reports, Up: balance 3.5.6 Percentages ----------------- With '-%' or '--percent', balance reports show each account's value expressed as a percentage of the column's total. This is useful to get an overview of the relative sizes of account balances. For example to obtain an overview of expenses: $ hledger balance expenses -% 100.0 % expenses 50.0 % food 50.0 % supplies -------------------- 100.0 % Note that '--tree' does not have an effect on '-%'. The percentages are always relative to the total sum of each column, they are never relative to the parent account. Since the percentages are relative to the columns sum, it is usually not useful to calculate percentages if the signs of the amounts are mixed. Although the results are technically correct, they are most likely useless. Especially in a balance report that sums up to zero (eg 'hledger balance -B') all percentage values will be zero. This flag does not work if the report contains any mixed commodity accounts. If there are mixed commodity accounts in the report be sure to use '-V' or '-B' to coerce the report into using a single commodity.  File: hledger.info, Node: Multicolumn balance report, Next: Budget report, Prev: Percentages, Up: balance 3.5.7 Multicolumn balance report -------------------------------- Multicolumn or tabular balance reports are a very useful hledger feature, and usually the preferred style. They share many of the above features, but they show the report as a table, with columns representing time periods. This mode is activated by providing a reporting interval. There are three types of multicolumn balance report, showing different information: 1. By default: each column shows the sum of postings in that period, ie the account's change of balance in that period. This is useful eg for a monthly income statement: $ hledger balance --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 2. With '--cumulative': each column shows the ending balance for that period, accumulating the changes across periods, starting from 0 at the report start date: $ hledger balance --quarterly income expenses -E --cumulative Ending balances (cumulative) in 2008: || 2008/03/31 2008/06/30 2008/09/30 2008/12/31 ===================++================================================= expenses:food || 0 $1 $1 $1 expenses:supplies || 0 $1 $1 $1 income:gifts || 0 $-1 $-1 $-1 income:salary || $-1 $-1 $-1 $-1 -------------------++------------------------------------------------- || $-1 0 0 0 3. With '--historical/-H': each column shows the actual historical ending balance for that period, accumulating the changes across periods, starting from the actual balance at the report start date. This is useful eg for a multi-period balance sheet, and when you are showing only the data after a certain start date: $ hledger balance ^assets ^liabilities --quarterly --historical --begin 2008/4/1 Ending balances (historical) in 2008/04/01-2008/12/31: || 2008/06/30 2008/09/30 2008/12/31 ======================++===================================== assets:bank:checking || $1 $1 0 assets:bank:saving || $1 $1 $1 assets:cash || $-2 $-2 $-2 liabilities:debts || 0 0 $1 ----------------------++------------------------------------- || 0 0 0 Note that '--cumulative' or '--historical/-H' disable '--row-total/-T', since summing end balances generally does not make sense. Multicolumn balance reports display accounts in flat mode by default; to see the hierarchy, use '--tree'. With a reporting interval (like '--quarterly' above), the report start/end dates will be adjusted if necessary so that they encompass the displayed report periods. This is so that the first and last periods will be "full" and comparable to the others. The '-E/--empty' flag does two things in multicolumn balance reports: first, the report will show all columns within the specified report period (without -E, leading and trailing columns with all zeroes are not shown). Second, all accounts which existed at the report start date will be considered, not just the ones with activity during the report period (use -E to include low-activity accounts which would otherwise would be omitted). The '-T/--row-total' flag adds an additional column showing the total for each row. The '-A/--average' flag adds a column showing the average value in each row. Here's an example of all three: $ hledger balance -Q income expenses --tree -ETA Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 Total Average ============++=================================================== expenses || 0 $2 0 0 $2 $1 food || 0 $1 0 0 $1 0 supplies || 0 $1 0 0 $1 0 income || $-1 $-1 0 0 $-2 $-1 gifts || 0 $-1 0 0 $-1 0 salary || $-1 0 0 0 $-1 0 ------------++--------------------------------------------------- || $-1 $1 0 0 0 0 (Average is rounded to the dollar here since all journal amounts are) The '--transpose' flag can be used to exchange the rows and columns of a multicolumn report. When showing multicommodity amounts, multicolumn balance reports will elide any amounts which have more than two commodities, since otherwise columns could get very wide. The '--no-elide' flag disables this. Hiding totals with the '-N/--no-total' flag can also help reduce the width of multicommodity reports. When the report is still too wide, a good workaround is to pipe it into 'less -RS' (-R for colour, -S to chop long lines). Eg: 'hledger bal -D --color=yes | less -RS'.  File: hledger.info, Node: Budget report, Next: , Prev: Multicolumn balance report, Up: balance 3.5.8 Budget report ------------------- With '--budget', extra columns are displayed showing budget goals for each account and period, if any. Budget goals are defined by periodic transactions. This is very useful for comparing planned and actual income, expenses, time usage, etc. -budget is most often combined with a report interval. For example, you can take average monthly expenses in the common expense categories to construct a minimal monthly budget: ;; Budget ~ monthly income $2000 expenses:food $400 expenses:bus $50 expenses:movies $30 assets:bank:checking ;; Two months worth of expenses 2017-11-01 income $1950 expenses:food $396 expenses:bus $49 expenses:movies $30 expenses:supplies $20 assets:bank:checking 2017-12-01 income $2100 expenses:food $412 expenses:bus $53 expenses:gifts $100 assets:bank:checking You can now see a monthly budget report: $ hledger balance -M --budget Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] This is different from a normal balance report in several ways: * Only accounts with budget goals during the report period are shown, by default. * In each column, in square brackets after the actual amount, budget goal amounts are shown, and the actual/goal percentage. (Note: budget goals should be in the same commodity as the actual amount.) * All parent accounts are always shown, even in flat mode. Eg assets, assets:bank, and expenses above. * Amounts always include all subaccounts, budgeted or unbudgeted, even in flat mode. This means that the numbers displayed will not always add up! Eg above, the 'expenses' actual amount includes the gifts and supplies transactions, but the 'expenses:gifts' and 'expenses:supplies' accounts are not shown, as they have no budget amounts declared. This can be confusing. When you need to make things clearer, use the '-E/--empty' flag, which will reveal all accounts including unbudgeted ones, giving the full picture. Eg: $ hledger balance -M --budget --empty Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:gifts || 0 $100 expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] expenses:supplies || $20 0 income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] You can roll over unspent budgets to next period with '--cumulative': $ hledger balance -M --budget --cumulative Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank:checking || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] expenses || $495 [ 103% of $480] $1060 [ 110% of $960] expenses:bus || $49 [ 98% of $50] $102 [ 102% of $100] expenses:food || $396 [ 99% of $400] $808 [ 101% of $800] expenses:movies || $30 [ 100% of $30] $30 [ 50% of $60] income || $1950 [ 98% of $2000] $4050 [ 101% of $4000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] For more examples, see Budgeting and Forecasting. * Menu: * Nested budgets::  File: hledger.info, Node: Nested budgets, Up: Budget report 3.5.8.1 Nested budgets ...................... You can add budgets to any account in your account hierarchy. If you have budgets on both parent account and some of its children, then budget(s) of the child account(s) would be added to the budget of their parent, much like account balances behave. In the most simple case this means that once you add a budget to any account, all its parents would have budget as well. To illustrate this, consider the following budget: ~ monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities With this, monthly budget for electronics is defined to be $100 and budget for personal expenses is an additional $1000, which implicitly means that budget for both 'expenses:personal' and 'expenses' is $1100. Transactions in 'expenses:personal:electronics' will be counted both towards its $100 budget and $1100 of 'expenses:personal' , and transactions in any other subaccount of 'expenses:personal' would be counted towards only towards the budget of 'expenses:personal'. For example, let's consider these transactions: ~ monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities 2019/01/01 Google home hub expenses:personal:electronics $90.00 liabilities $-90.00 2019/01/02 Phone screen protector expenses:personal:electronics:upgrades $10.00 liabilities 2019/01/02 Weekly train ticket expenses:personal:train tickets $153.00 liabilities 2019/01/03 Flowers expenses:personal $30.00 liabilities As you can see, we have transactions in 'expenses:personal:electronics:upgrades' and 'expenses:personal:train tickets', and since both of these accounts are without explicitly defined budget, these transactions would be counted towards budgets of 'expenses:personal:electronics' and 'expenses:personal' accordingly: $ hledger balance --budget -M Budget performance in 2019/01: || Jan ===============================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] liabilities || $-283.00 [ 26% of $-1100.00] -------------------------------++------------------------------- || 0 [ 0] And with '--empty', we can get a better picture of budget allocation and consumption: $ hledger balance --budget -M --empty Budget performance in 2019/01: || Jan ========================================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] expenses:personal:electronics:upgrades || $10.00 expenses:personal:train tickets || $153.00 liabilities || $-283.00 [ 26% of $-1100.00] ----------------------------------------++------------------------------- || 0 [ 0] 3.5.9 Output format ------------------- This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', (multicolumn non-budget reports only) 'html', and (experimental) 'json'.  File: hledger.info, Node: balancesheet, Next: balancesheetequity, Prev: balance, Up: COMMANDS 3.6 balancesheet ================ 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. The asset and liability accounts shown are those accounts declared with the 'Asset' or 'Cash' or 'Liability' type, or otherwise all accounts under a top-level 'asset' or 'liability' account (case insensitive, plurals allowed). Example: $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 With a reporting interval, multiple columns will be shown, one for each report period. As with multicolumn balance reports, you can alter the report mode with '--change'/'--cumulative'/'--historical'. Normally balancesheet shows historical ending balances, which is what you need for a balance sheet; note this means it ignores report begin dates (and '-T/--row-total', since summing end balances generally does not make sense). Instead of absolute values percentages can be displayed with '-%'. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'html', and (experimental) 'json'.  File: hledger.info, Node: balancesheetequity, Next: cashflow, Prev: balancesheet, Up: COMMANDS 3.7 balancesheetequity ====================== 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. The asset, liability and equity accounts shown are those accounts declared with the 'Asset', 'Cash', 'Liability' or 'Equity' type, or otherwise all accounts under a top-level 'asset', 'liability' or 'equity' account (case insensitive, plurals allowed). 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 also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'html', and (experimental) 'json'.  File: hledger.info, Node: cashflow, Next: check-dates, Prev: balancesheetequity, Up: COMMANDS 3.8 cashflow ============ cashflow, cf This command displays a cashflow statement, showing the inflows and outflows affecting "cash" (ie, liquid) assets. Amounts are shown with normal positive sign, as in conventional financial statements. The "cash" accounts shown are those accounts declared with the 'Cash' type, or otherwise all accounts under a top-level 'asset' account (case insensitive, plural allowed) which do not have 'fixed', 'investment', 'receivable' or 'A/R' in their name. Example: $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 With a reporting interval, multiple columns will be shown, one for each report period. Normally cashflow shows changes in assets per period, though as with multicolumn balance reports you can alter the report mode with '--change'/'--cumulative'/'--historical'. Instead of absolute values percentages can be displayed with '-%'. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'html', and (experimental) 'json'.  File: hledger.info, Node: check-dates, Next: check-dupes, Prev: cashflow, Up: COMMANDS 3.9 check-dates =============== check-dates Check that transactions are sorted by increasing date. With -date2, checks secondary dates instead. With -strict, dates must also be unique. With a query, only matched transactions' dates are checked. Reads the default journal file, or another specified with -f.  File: hledger.info, Node: check-dupes, Next: close, Prev: check-dates, Up: COMMANDS 3.10 check-dupes ================ check-dupes Reports account names having the same leaf but different prefixes. In other words, two or more leaves that are categorized differently. Reads the default journal file, or another specified as an argument. An example: http://stefanorodighiero.net/software/hledger-dupes.html  File: hledger.info, Node: close, Next: codes, Prev: check-dupes, Up: COMMANDS 3.11 close ========== close, equity Prints a "closing balances" transaction and an "opening balances" transaction that bring account balances to and from zero, respectively. These can be added to your journal file(s), eg to bring asset/liability balances forward into a new journal file, or to close out revenues/expenses to retained earnings at the end of a period. You can print just one of these transactions by using the '--close' or '--open' flag. You can customise their descriptions with the '--close-desc' and '--open-desc' options. One amountless posting to "equity:opening/closing balances" is added to balance the transactions, by default. You can customise this account name with '--close-acct' and '--open-acct'; if you specify only one of these, it will be used for both. With '--x/--explicit', the equity posting's amount will be shown. And if it involves multiple commodities, a posting for each commodity will be shown, as with the print command. With '--interleaved', the equity postings are shown next to the postings they balance, which makes troubleshooting easier. By default, transaction prices in the journal are ignored when generating the closing/opening transactions. With '--show-costs', this cost information is preserved ('balance -B' reports will be unchanged after the transition). Separate postings are generated for each cost in each commodity. Note this can generate very large journal entries, if you have many foreign currency or investment transactions. * Menu: * close usage::  File: hledger.info, Node: close usage, Up: close 3.11.1 close usage ------------------ If you split your journal files by time (eg yearly), you will typically run this command at the end of the year, and save the closing transaction as last entry of the old file, and the opening transaction as the first entry of the new file. This makes the files self contained, so that correct balances are reported no matter which of them are loaded. Ie, if you load just one file, the balances are initialised correctly; or if you load several files, the redundant closing/opening transactions cancel each other out. (They will show up in print or register reports; you can exclude them with a query like 'not:desc:'(opening|closing) balances''.) If you're running a business, you might also use this command to "close the books" at the end of an accounting period, transferring income statement account balances to retained earnings. (You may want to change the equity account name to something like "equity:retained earnings".) By default, the closing transaction is dated yesterday, the balances are calculated as of end of yesterday, and the opening transaction is dated today. To close on some other date, use: 'hledger close -e OPENINGDATE'. Eg, to close/open on the 2018/2019 boundary, use '-e 2019'. You can also use -p or 'date:PERIOD' (any starting date is ignored). Both transactions will include balance assertions for the closed/reopened accounts. You probably shouldn't use status or realness filters (like -C or -R or 'status:') with this command, or the generated balance assertions will depend on these flags. Likewise, if you run this command with -auto, the balance assertions will probably always require -auto. Examples: Carrying asset/liability balances into a new file for 2019: $ hledger close -f 2018.journal -e 2019 assets liabilities --open # (copy/paste the output to the start of your 2019 journal file) $ hledger close -f 2018.journal -e 2019 assets liabilities --close # (copy/paste the output to the end of your 2018 journal file) Now: $ hledger bs -f 2019.journal # one file - balances are correct $ hledger bs -f 2018.journal -f 2019.journal # two files - balances still correct $ hledger bs -f 2018.journal not:desc:closing # to see year-end balances, must exclude closing txn Transactions spanning the closing date can complicate matters, breaking balance assertions: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 assets:bank:checking -5 ; [2019/1/2] Here's one way to resolve that: ; in 2018.journal: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 liabilities:pending ; in 2019.journal: 2019/1/2 clearance of last year's pending transactions liabilities:pending 5 = 0 assets:checking  File: hledger.info, Node: codes, Next: commodities, Prev: close, Up: COMMANDS 3.12 codes ========== 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: 1/1 (123) (a) 1 1/1 () (a) 1 1/1 (a) 1 1/1 (126) (a) 1 $ hledger codes 123 124 126 $ hledger codes -E 123 124 126  File: hledger.info, Node: commodities, Next: descriptions, Prev: codes, Up: COMMANDS 3.13 commodities ================ commodities List all commodity/currency symbols used or declared in the journal.  File: hledger.info, Node: descriptions, Next: diff, Prev: commodities, Up: COMMANDS 3.14 descriptions ================= 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: COMMANDS 3.15 diff ========= 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: COMMANDS 3.16 files ========== 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: COMMANDS 3.17 help ========= help Show any of the hledger manuals. The 'help' command displays any of the main hledger manuals, in one of several ways. Run it with no argument to list the manuals, or provide a full or partial manual name to select one. hledger manuals are available in several formats. hledger help will use the first of these display methods that it finds: info, man, $PAGER, less, stdout (or when non-interactive, just stdout). You can force a particular viewer with the '--info', '--man', '--pager', '--cat' flags. Examples: $ hledger help Please choose a manual by typing "hledger help MANUAL" (a substring is ok). Manuals: hledger hledger-ui hledger-web journal csv timeclock timedot $ hledger help h --man hledger(1) hledger User Manuals hledger(1) NAME hledger - a command-line accounting tool SYNOPSIS hledger [-f FILE] COMMAND [OPTIONS] [ARGS] hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS] hledger DESCRIPTION hledger is a cross-platform program for tracking money, time, or any ...  File: hledger.info, Node: import, Next: incomestatement, Prev: help, Up: COMMANDS 3.18 import =========== import Read new transactions added to each FILE since last run, and add them to the main journal file. Or with -dry-run, just print the transactions that would be added. Or with -catchup, just mark all of the FILEs' transactions as imported, without actually importing any. The input files are specified as arguments - no need to write -f before each one. So eg to add new transactions from all CSV files to the main journal, it's just: 'hledger import *.csv' New transactions are detected in the same way as print -new: by assuming transactions are always added to the input files in increasing date order, and by saving '.latest.FILE' state files. The -dry-run output is in journal format, so you can filter it, eg to see only uncategorised transactions: $ hledger import --dry ... | hledger -f- print unknown --ignore-assertions * Menu: * Importing balance assignments::  File: hledger.info, Node: Importing balance assignments, Up: import 3.18.1 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: incomestatement, Next: notes, Prev: import, Up: COMMANDS 3.19 incomestatement ==================== 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. The revenue and expense accounts shown are those accounts declared with the 'Revenue' or 'Expense' type, or otherwise all accounts under a top-level 'revenue' or 'income' or 'expense' account (case insensitive, plurals allowed). Example: $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 With a reporting interval, multiple columns will be shown, one for each report period. Normally incomestatement shows revenues/expenses per period, though as with multicolumn balance reports you can alter the report mode with '--change'/'--cumulative'/'--historical'. Instead of absolute values percentages can be displayed with '-%'. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', 'html', and (experimental) 'json'.  File: hledger.info, Node: notes, Next: payees, Prev: incomestatement, Up: COMMANDS 3.20 notes ========== 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: COMMANDS 3.21 payees =========== payees List the unique payee/payer names that appear in transactions. This command lists the unique payee/payer names that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). Example: $ hledger payees Store Name Gas Station Person A  File: hledger.info, Node: prices, Next: print, Prev: payees, Up: COMMANDS 3.22 prices =========== prices Print market price directives from the journal. With -costs, also print synthetic market prices based on transaction prices. With -inverted-costs, also print inverse prices based on transaction prices. Prices (and postings providing prices) can be filtered by a query. Price amounts are always displayed with their full precision.  File: hledger.info, Node: print, Next: print-unique, Prev: prices, Up: COMMANDS 3.23 print ========== print, txns, p Show transaction journal entries, sorted by date. The print command displays full journal entries (transactions) from the journal file in date order, tidily formatted. With -date2, transactions are sorted by secondary date instead. print's output is always a valid hledger journal. It preserves all transaction information, but it does not preserve directives or inter-transaction comments $ hledger print 2008/01/01 income assets:bank:checking $1 income:salary $-1 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 2008/12/31 * pay off liabilities:debts $1 assets:bank:checking $-1 Normally, the journal entry's explicit or implicit amount style is preserved. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, when a transaction price is implied but not written, it will not appear in the output. You can use the '-x'/'--explicit' flag to make all amounts and transaction prices explicit, which 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'. Note, '-x'/'--explicit' will cause postings with a multi-commodity amount (these can arise when a multi-commodity transaction has an implicit amount) to be split into multiple single-commodity postings, keeping the output parseable. With '-B'/'--cost', amounts with transaction prices are converted to cost using that price. This can be used for troubleshooting. With '-m'/'--match' and a STR argument, print will show at most one transaction: the one one whose description is most similar to STR, and is most recent. STR should contain at least two characters. If there is no similar-enough match, no transaction will be shown. With '--new', for each FILE being read, hledger reads (and writes) a special state file ('.latest.FILE' in the same directory), containing the latest transaction date(s) that were seen last time FILE was read. When this file is found, only transactions with newer dates (and new transactions on the latest date) are printed. This is useful for ignoring already-seen entries in import data, such as downloaded CSV files. Eg: $ hledger -f bank1.csv print --new (shows transactions added since last print --new on this file) This assumes that transactions added to FILE always have same or increasing dates, and that transactions on the same day do not get reordered. See also the import command. This command also supports the output destination and output format options The output formats supported are 'txt', 'csv', and (experimental) 'json' and 'sql'. 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: print-unique, Next: register, Prev: print, Up: COMMANDS 3.24 print-unique ================= print-unique Print transactions which do not reuse an already-seen description. Example: $ cat unique.journal 1/1 test (acct:one) 1 2/2 test (acct:two) 2 $ LEDGER_FILE=unique.journal hledger print-unique (-f option not supported) 2015/01/01 test (acct:one) 1  File: hledger.info, Node: register, Next: register-match, Prev: print-unique, Up: COMMANDS 3.25 register ============= register, reg, r 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. 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. * Menu: * Custom register output::  File: hledger.info, Node: Custom register output, Up: register 3.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', and (experimental) 'json'.  File: hledger.info, Node: register-match, Next: rewrite, Prev: register, Up: COMMANDS 3.26 register-match =================== register-match Print the one posting whose transaction description is closest to DESC, in the style of the register command. If there are multiple equally good matches, it shows the most recent. Query options (options, not arguments) can be used to restrict the search space. Helps ledger-autosync detect already-seen transactions when importing.  File: hledger.info, Node: rewrite, Next: roi, Prev: register-match, Up: COMMANDS 3.27 rewrite ============ 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::  File: hledger.info, Node: Re-write rules in a file, Up: rewrite 3.27.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. * Menu: * Diff output format:: * rewrite vs print --auto::  File: hledger.info, Node: Diff output format, Next: rewrite vs print --auto, Up: Re-write rules in a file 3.27.1.1 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: Re-write rules in a file 3.27.1.2 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: COMMANDS 3.28 roi ======== roi Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. This command assumes that you have account(s) that hold nothing but your investments and whenever you record current appraisal/valuation of these investments you offset unrealized profit and loss into account(s) that, again, hold nothing but unrealized profit and loss. Any transactions affecting balance of investment account(s) and not originating from unrealized profit and loss account(s) are assumed to be your investments or withdrawals. At a minimum, you need to supply a query (which could be just an account name) to select your investments with '--inv', and another query to identify your profit and loss transactions with '--pnl'. It will compute and display the internalized rate of return (IRR) and time-weighted rate of return (TWR) for your investments for the time period requested. Both rates of return are annualized before display, regardless of the length of reporting interval.  File: hledger.info, Node: stats, Next: tags, Prev: roi, Up: COMMANDS 3.29 stats ========== stats Show some journal 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. Example: $ hledger stats Main journal file : /src/hledger/examples/sample.journal Included journal files : Transactions span : 2008-01-01 to 2009-01-01 (366 days) Last transaction : 2008-12-31 (2333 days ago) 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 : 12 ($) This command also supports output destination and output format selection.  File: hledger.info, Node: tags, Next: test, Prev: stats, Up: COMMANDS 3.30 tags ========= tags List the unique tag names used in the journal. With a TAGREGEX argument, only tag names matching the regular expression (case insensitive) are shown. With QUERY arguments, only transactions matching the query are considered. With the -values flag, the tags' unique values are listed instead. With -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.  File: hledger.info, Node: test, Next: Add-on commands, Prev: tags, Up: COMMANDS 3.31 test ========= 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: Add-on commands, Prev: test, Up: COMMANDS 3.32 Add-on commands ==================== hledger also searches for external add-on commands, and will include these in the commands list. These are programs or scripts in your PATH whose name starts with 'hledger-' and ends with a recognised file extension (currently: no extension, 'bat','com','exe', 'hs','lhs','pl','py','rb','rkt','sh'). Add-ons can be invoked like any hledger command, but there are a few things to be aware of. Eg if the 'hledger-web' add-on is installed, * 'hledger -h web' shows hledger's help, while 'hledger web -h' shows hledger-web's help. * Flags specific to the add-on must have a preceding '--' to hide them from hledger. So 'hledger web --serve --port 9000' will be rejected; you must use 'hledger web -- --serve --port 9000'. * You can always run add-ons directly if preferred: 'hledger-web --serve --port 9000'. Add-ons are a relatively easy way to add local features or experiment with new ideas. They can be written in any language, but haskell scripts have a big advantage: they can use the same hledger (and haskell) library functions that built-in commands do, for command-line options, journal parsing, reporting, etc. Two important add-ons are the hledger-ui and hledger-web user interfaces. These are maintained and released along with hledger: * Menu: * ui:: * web:: * iadd:: * interest::  File: hledger.info, Node: ui, Next: web, Up: Add-on commands 3.32.1 ui --------- hledger-ui provides an efficient terminal interface.  File: hledger.info, Node: web, Next: iadd, Prev: ui, Up: Add-on commands 3.32.2 web ---------- hledger-web provides a simple web interface. Third party add-ons, maintained separately from hledger, include:  File: hledger.info, Node: iadd, Next: interest, Prev: web, Up: Add-on commands 3.32.3 iadd ----------- hledger-iadd is a more interactive, terminal UI replacement for the add command.  File: hledger.info, Node: interest, Prev: iadd, Up: Add-on commands 3.32.4 interest --------------- hledger-interest generates interest transactions for an account according to various schemes. A few more experimental or old add-ons can be found in hledger's bin/ directory. These are typically prototypes and not guaranteed to work.  File: hledger.info, Node: ENVIRONMENT, Next: FILES, Prev: COMMANDS, Up: Top 4 ENVIRONMENT ************* *LEDGER_FILE* The journal file path when not specified with '-f'. Default: '~/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal'). A typical value is '~/DIR/YYYY.journal', where DIR is a version-controlled finance directory and YYYY is the current year. Or '~/DIR/current.journal', where current.journal is a symbolic link to YYYY.journal. On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a '~/.MacOSX/environment.plist' file containing { "LEDGER_FILE" : "~/finance/current.journal" } To see the effect you may need to 'killall Dock', or reboot. *COLUMNS* The screen width used by the register command. Default: the full terminal width. *NO_COLOR* If this variable exists with any value, hledger will not use ANSI color codes in terminal output. This overrides the -color/-colour option.  File: hledger.info, Node: FILES, Next: LIMITATIONS, Prev: ENVIRONMENT, Up: Top 5 FILES ******* Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with '-f', or '$LEDGER_FILE', or '$HOME/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal').  File: hledger.info, Node: LIMITATIONS, Next: TROUBLESHOOTING, Prev: FILES, Up: Top 6 LIMITATIONS ************* The need to precede addon command options with '--' when invoked from hledger is awkward. When input data contains non-ascii characters, a suitable system locale must be configured (or there will be an unhelpful error). Eg on POSIX, set LANG to something other than C. In a Microsoft Windows CMD window, non-ascii characters and colours are not supported. On Windows, non-ascii characters may not display correctly when running a hledger built in CMD in MSYS/CYGWIN, or vice-versa. In a Cygwin/MSYS/Mintty window, the tab key is not supported in hledger add. Not all of Ledger's journal file syntax is supported. See file format differences. On large data files, hledger is slower and uses more memory than Ledger.  File: hledger.info, Node: TROUBLESHOOTING, Prev: LIMITATIONS, Up: Top 7 TROUBLESHOOTING ***************** Here are some issues you might encounter when you run hledger (and remember you can also seek help from the IRC channel, mail list or bug tracker): *Successfully installed, but "No command 'hledger' found"* stack and cabal install binaries into a special directory, which should be added to your PATH environment variable. Eg on unix-like systems, that is ~/.local/bin and ~/.cabal/bin respectively. *I set a custom LEDGER_FILE, but hledger is still using the default file* 'LEDGER_FILE' should be a real environment variable, not just a shell variable. The command 'env | grep LEDGER_FILE' should show it. You may need to use 'export'. Here's an explanation. *Getting 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 to have a UTF-8-aware locale configured in the environment, otherwise they will fail with these kinds of errors when they encounter non-ascii characters. To fix it, set the LANG environment variable to some locale which supports UTF-8. The locale you choose must be installed on your system. Here's an example of setting LANG temporarily, on Ubuntu GNU/Linux: $ file my.journal my.journal: UTF-8 Unicode text # the file is UTF8-encoded $ echo $LANG C # LANG is set to the default locale, which does not support UTF8 $ locale -a # which locales are installed ? C en_US.utf8 # here's a UTF8-aware one we can use POSIX $ LANG=en_US.utf8 hledger -f my.journal print # ensure it is used for this command If available, 'C.UTF-8' will also work. If your preferred locale isn't listed by 'locale -a', you might need to install it. Eg on Ubuntu/Debian: $ apt-get install language-pack-fr $ locale -a C en_US.utf8 fr_BE.utf8 fr_CA.utf8 fr_CH.utf8 fr_FR.utf8 fr_LU.utf8 POSIX $ LANG=fr_FR.utf8 hledger -f my.journal print Here's how you could set it permanently, if you use a bash shell: $ echo "export LANG=en_US.utf8" >>~/.bash_profile $ bash --login Exact spelling and capitalisation may be important. Note the difference on MacOS ('UTF-8', not 'utf8'). Some platforms (eg ubuntu) allow variant spellings, but others (eg macos) require it to be exact: $ locale -a | grep -iE en_us.*utf en_US.UTF-8 $ LANG=en_US.UTF-8 hledger -f my.journal print  Tag Table: Node: Top68 Node: COMMON TASKS2321 Ref: #common-tasks2433 Node: Getting help2840 Ref: #getting-help2972 Node: Constructing command lines3525 Ref: #constructing-command-lines3717 Node: Starting a journal file4414 Ref: #starting-a-journal-file4612 Node: Setting opening balances5800 Ref: #setting-opening-balances5996 Node: Recording transactions9137 Ref: #recording-transactions9317 Node: Reconciling9873 Ref: #reconciling10016 Node: Reporting12273 Ref: #reporting12413 Node: Migrating to a new file16412 Ref: #migrating-to-a-new-file16560 Node: OPTIONS16859 Ref: #options16966 Node: General options17336 Ref: #general-options17461 Node: Command options20767 Ref: #command-options20918 Node: Command arguments21316 Ref: #command-arguments21463 Node: Queries22343 Ref: #queries22498 Node: Special characters in arguments and queries26460 Ref: #special-characters-in-arguments-and-queries26688 Node: More escaping27139 Ref: #more-escaping27301 Node: Even more escaping27597 Ref: #even-more-escaping27791 Node: Less escaping28462 Ref: #less-escaping28624 Node: Unicode characters28869 Ref: #unicode-characters29051 Node: Input files30463 Ref: #input-files30606 Node: Output destination32905 Ref: #output-destination33057 Node: Output format33482 Ref: #output-format33632 Node: Regular expressions35799 Ref: #regular-expressions35956 Node: Smart dates37692 Ref: #smart-dates37843 Node: Report start & end date39204 Ref: #report-start-end-date39376 Node: Report intervals40873 Ref: #report-intervals41038 Node: Period expressions41428 Ref: #period-expressions41588 Node: Depth limiting45920 Ref: #depth-limiting46064 Node: Pivoting46396 Ref: #pivoting46519 Node: Valuation48195 Ref: #valuation48297 Node: -B Cost48986 Ref: #b-cost49090 Node: -V Value49223 Ref: #v-value49369 Node: -X Value in specified commodity49564 Ref: #x-value-in-specified-commodity49763 Node: Valuation date49912 Ref: #valuation-date50080 Node: Market prices50490 Ref: #market-prices50670 Node: --infer-value market prices from transactions51447 Ref: #infer-value-market-prices-from-transactions51696 Node: Valuation commodity52978 Ref: #valuation-commodity53187 Node: Simple valuation examples54413 Ref: #simple-valuation-examples54615 Node: --value Flexible valuation55274 Ref: #value-flexible-valuation55482 Node: More valuation examples57429 Ref: #more-valuation-examples57638 Node: Effect of valuation on reports59643 Ref: #effect-of-valuation-on-reports59831 Node: COMMANDS65352 Ref: #commands65460 Node: accounts66568 Ref: #accounts66666 Node: activity67365 Ref: #activity67475 Node: add67858 Ref: #add67959 Node: aregister70752 Ref: #aregister70864 Node: aregister and custom posting dates72237 Ref: #aregister-and-custom-posting-dates72410 Ref: #output-format-173003 Node: balance73408 Ref: #balance73525 Node: Classic balance report74983 Ref: #classic-balance-report75156 Node: Customising the classic balance report76540 Ref: #customising-the-classic-balance-report76768 Node: Colour support78844 Ref: #colour-support79011 Node: Flat mode79107 Ref: #flat-mode79255 Node: Depth limited balance reports79668 Ref: #depth-limited-balance-reports79853 Node: Percentages80309 Ref: #percentages80475 Node: Multicolumn balance report81612 Ref: #multicolumn-balance-report81792 Node: Budget report87389 Ref: #budget-report87532 Node: Nested budgets92798 Ref: #nested-budgets92910 Ref: #output-format-296391 Node: balancesheet96588 Ref: #balancesheet96724 Node: balancesheetequity98236 Ref: #balancesheetequity98385 Node: cashflow99461 Ref: #cashflow99589 Node: check-dates100805 Ref: #check-dates100932 Node: check-dupes101211 Ref: #check-dupes101337 Node: close101630 Ref: #close101738 Node: close usage103260 Ref: #close-usage103353 Node: codes106166 Ref: #codes106274 Node: commodities106986 Ref: #commodities107113 Node: descriptions107195 Ref: #descriptions107323 Node: diff107627 Ref: #diff107733 Node: files108780 Ref: #files108880 Node: help109027 Ref: #help109127 Node: import110208 Ref: #import110322 Node: Importing balance assignments111215 Ref: #importing-balance-assignments111363 Node: incomestatement112012 Ref: #incomestatement112145 Node: notes113490 Ref: #notes113603 Node: payees113971 Ref: #payees114077 Node: prices114497 Ref: #prices114603 Node: print114944 Ref: #print115054 Node: print-unique119850 Ref: #print-unique119976 Node: register120261 Ref: #register120388 Node: Custom register output124837 Ref: #custom-register-output124966 Node: register-match126303 Ref: #register-match126437 Node: rewrite126788 Ref: #rewrite126903 Node: Re-write rules in a file128758 Ref: #re-write-rules-in-a-file128892 Node: Diff output format130102 Ref: #diff-output-format130271 Node: rewrite vs print --auto131363 Ref: #rewrite-vs.-print---auto131542 Node: roi132098 Ref: #roi132196 Node: stats133208 Ref: #stats133307 Node: tags134095 Ref: #tags134193 Node: test134712 Ref: #test134820 Node: Add-on commands135567 Ref: #add-on-commands135684 Node: ui137027 Ref: #ui137115 Node: web137169 Ref: #web137272 Node: iadd137388 Ref: #iadd137499 Node: interest137581 Ref: #interest137688 Node: ENVIRONMENT137928 Ref: #environment138040 Node: FILES139025 Ref: #files-1139128 Node: LIMITATIONS139341 Ref: #limitations139460 Node: TROUBLESHOOTING140202 Ref: #troubleshooting140315  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.19.1/embeddedfiles/hledger-ui.10000644000000000000000000004534713725533425016314 0ustar0000000000000000 .TH "hledger-ui" "1" "September 2020" "hledger-ui 1.18.99" "hledger User Manuals" .SH NAME .PP hledger-ui - terminal interface for the hledger accounting tool .SH SYNOPSIS .PP \f[C]hledger-ui [OPTIONS] [QUERYARGS]\f[R] .PD 0 .P .PD \f[C]hledger ui -- [OPTIONS] [QUERYARGS]\f[R] .SH DESCRIPTION .PP hledger is a reliable, 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). .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 data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]-f\f[R], or \f[C]$LEDGER_FILE\f[R], or \f[C]$HOME/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). For more about this see hledger(1), hledger_journal(5) etc. .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 .PP Note: if invoking hledger-ui as a hledger subcommand, write \f[C]--\f[R] before options as shown above. .PP Any QUERYARGS are interpreted as a hledger search query which filters the data. .TP \f[B]\f[CB]--watch\f[B]\f[R] watch for data and date changes and reload automatically .TP \f[B]\f[CB]--theme=default|terminal|greenterm\f[B]\f[R] use this custom display theme .TP \f[B]\f[CB]--register=ACCTREGEX\f[B]\f[R] start in the (first) matched account\[aq]s register screen .TP \f[B]\f[CB]--change\f[B]\f[R] show period balances (changes) at startup instead of historical balances .TP \f[B]\f[CB]-l --flat\f[B]\f[R] show accounts as a flat list (default) .TP \f[B]\f[CB]-t --tree\f[B]\f[R] show accounts as a tree .PP hledger input options: .TP \f[B]\f[CB]-f FILE --file=FILE\f[B]\f[R] use a different input file. For stdin, use - (default: \f[C]$LEDGER_FILE\f[R] or \f[C]$HOME/.hledger.journal\f[R]) .TP \f[B]\f[CB]--rules-file=RULESFILE\f[B]\f[R] Conversion rules file to use when reading CSV (default: FILE.rules) .TP \f[B]\f[CB]--separator=CHAR\f[B]\f[R] Field separator to expect when reading CSV (default: \[aq],\[aq]) .TP \f[B]\f[CB]--alias=OLD=NEW\f[B]\f[R] rename accounts named OLD to NEW .TP \f[B]\f[CB]--anon\f[B]\f[R] anonymize accounts and payees .TP \f[B]\f[CB]--pivot FIELDNAME\f[B]\f[R] use some other field or tag for the account name .TP \f[B]\f[CB]-I --ignore-assertions\f[B]\f[R] disable balance assertion checks (note: does not disable balance assignments) .PP hledger reporting options: .TP \f[B]\f[CB]-b --begin=DATE\f[B]\f[R] include postings/txns on or after this date .TP \f[B]\f[CB]-e --end=DATE\f[B]\f[R] include postings/txns before this date .TP \f[B]\f[CB]-D --daily\f[B]\f[R] multiperiod/multicolumn report by day .TP \f[B]\f[CB]-W --weekly\f[B]\f[R] multiperiod/multicolumn report by week .TP \f[B]\f[CB]-M --monthly\f[B]\f[R] multiperiod/multicolumn report by month .TP \f[B]\f[CB]-Q --quarterly\f[B]\f[R] multiperiod/multicolumn report by quarter .TP \f[B]\f[CB]-Y --yearly\f[B]\f[R] multiperiod/multicolumn report by year .TP \f[B]\f[CB]-p --period=PERIODEXP\f[B]\f[R] set start date, end date, and/or reporting interval all at once using period expressions syntax .TP \f[B]\f[CB]--date2\f[B]\f[R] match the secondary date instead (see command help for other effects) .TP \f[B]\f[CB]-U --unmarked\f[B]\f[R] include only unmarked postings/txns (can combine with -P or -C) .TP \f[B]\f[CB]-P --pending\f[B]\f[R] include only pending postings/txns .TP \f[B]\f[CB]-C --cleared\f[B]\f[R] include only cleared postings/txns .TP \f[B]\f[CB]-R --real\f[B]\f[R] include only non-virtual postings .TP \f[B]\f[CB]-NUM --depth=NUM\f[B]\f[R] hide/aggregate accounts or postings more than NUM levels deep .TP \f[B]\f[CB]-E --empty\f[B]\f[R] show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) .TP \f[B]\f[CB]-B --cost\f[B]\f[R] convert amounts to their cost/selling amount at transaction time .TP \f[B]\f[CB]-V --market\f[B]\f[R] convert amounts to their market value in default valuation commodities .TP \f[B]\f[CB]-X --exchange=COMM\f[B]\f[R] convert amounts to their market value in commodity COMM .TP \f[B]\f[CB]--value\f[B]\f[R] convert amounts to cost or market value, more flexibly than -B/-V/-X .TP \f[B]\f[CB]--infer-value\f[B]\f[R] with -V/-X/--value, also infer market prices from transactions .TP \f[B]\f[CB]--auto\f[B]\f[R] apply automated posting rules to modify transactions. .TP \f[B]\f[CB]--forecast\f[B]\f[R] generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. .TP \f[B]\f[CB]--color=WHEN (or --colour=WHEN)\f[B]\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. .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. .PP hledger help options: .TP \f[B]\f[CB]-h --help\f[B]\f[R] show general usage (or after COMMAND, command usage) .TP \f[B]\f[CB]--version\f[B]\f[R] show version .TP \f[B]\f[CB]--debug[=N]\f[B]\f[R] show debug output (levels 1-9, default: 1) .PP a \[at]file argument will be expanded to the contents of file, which should contain one command line option/argument per line. (to prevent this, insert a \f[C]--\f[R] argument before.) .SH keys .PP \f[C]?\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[C]?\f[R] again (or \f[C]escape\f[R], or \f[C]left\f[R], or \f[C]q\f[R]) to close it. the following keys work on most screens: .PP the cursor keys navigate: \f[C]right\f[R] (or \f[C]enter\f[R]) goes deeper, \f[C]left\f[R] returns to the previous screen, \f[C]up\f[R]/\f[C]down\f[R]/\f[C]page up\f[R]/\f[C]page down\f[R]/\f[C]home\f[R]/\f[C]end\f[R] move up and down through lists. Emacs-style (\f[C]ctrl-p\f[R]/\f[C]ctrl-n\f[R]/\f[C]ctrl-f\f[R]/\f[C]ctrl-b\f[R]) movement keys are also supported (but not vi-style keys, since hledger-1.19, sorry!). 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[C]shift-down/up\f[R] steps downward and upward through these standard report period durations: year, quarter, month, week, day. then, \f[C]shift-left/right\f[R] moves to the previous/next period. \f[C]T\f[R] sets the report period to today. with the \f[C]--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[C]/\f[R] and a \f[C]date:\f[R] query. .PP \f[C]/\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[C]enter\f[R] to set it, or \f[C]escape\f[R]to cancel. there are also keys for quickly adjusting some common filters like account depth and transaction status (see below). \f[C]backspace\f[R] or \f[C]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[C]f\f[R] toggles forecast mode, in which future/forecasted transactions are shown. \f[I](experimental)\f[R] .PP \f[C]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[C]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[C]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[C]i\f[R] toggles balance assertion checking. disabling balance assertions temporarily can be useful for troubleshooting. .PP \f[C]a\f[R] runs command-line hledger\[aq]s add command, and reloads the updated file. this allows some basic data entry. .PP \f[C]a\f[R] is like \f[C]a\f[R], but runs the hledger-iadd tool, which provides a terminal interface. this key will be available if \f[C]hledger-iadd\f[R] is installed in $path. .PP \f[C]e\f[R] runs $hledger_ui_editor, or $editor, or a default (\f[C]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[C]b\f[R] toggles cost mode, showing amounts in their transaction price\[aq]s commodity (like toggling the \f[C]-b/--cost\f[R] flag). .PP \f[C]v\f[R] toggles value mode, showing amounts\[aq] current market value in their default valuation commodity (like toggling the \f[C]-v/--market\f[R] flag). note, \[dq]current market value\[dq] means the value on the report end date if specified, otherwise today. to see the value on another date, you can temporarily set that as the report end date. eg: to see a transaction as it was valued on july 30, go to the accounts or register screen, press \f[C]/\f[R], and add \f[C]date:-7/30\f[R] to the query. .PP at most one of cost or value mode can be active at once. .PP there\[aq]s not yet any visual reminder when cost or value mode is active; for now pressing \f[C]b\f[R] \f[C]b\f[R] \f[C]v\f[R] should reliably reset to normal mode. .PP with --watch active, if you save an edit to the journal file while viewing the transaction screen in cost or value mode, the \f[C]b\f[R]/\f[C]v\f[R] keys will stop working. to work around, press g to force a manual reload, or exit the transaction screen. .PP \f[C]q\f[R] quits the application. .PP additional screen-specific keys are described below. .SH screens .SS accounts screen .PP this is normally the first screen displayed. it lists accounts and their balances, like hledger\[aq]s balance command. by default, it shows all accounts and their latest ending balances (including the balances of subaccounts). if you specify a query on the command line, it shows just the matched accounts and the balances from matched transactions. .PP Account names are shown as a flat list by default; press \f[C]t\f[R] to toggle tree mode. In list mode, account balances are exclusive of subaccounts, except where subaccounts are hidden by a depth limit (see below). In tree mode, all account balances are inclusive of subaccounts. .PP To see less detail, press a number key, \f[C]1\f[R] to \f[C]9\f[R], to set a depth limit. Or use \f[C]-\f[R] to decrease and \f[C]+\f[R]/\f[C]=\f[R] to increase the depth limit. \f[C]0\f[R] shows even less detail, collapsing all accounts to a single total. To remove the depth limit, set it higher than the maximum account depth, or press \f[C]ESCAPE\f[R]. .PP \f[C]H\f[R] toggles between showing historical balances or period balances. Historical balances (the default) are ending balances at the end of the report period, taking into account all transactions before that date (filtered by the filter query if any), including transactions before the start of the report period. In other words, historical balances are what you would see on a bank statement for that account (unless disturbed by a filter query). Period balances ignore transactions before the report start date, so they show the change in balance during the report period. They are more useful eg when viewing a time log. .PP \f[C]U\f[R] toggles filtering by unmarked status, including or excluding unmarked postings in the balances. Similarly, \f[C]P\f[R] toggles pending postings, and \f[C]C\f[R] toggles cleared postings. (By default, balances include all postings; if you activate one or two status filters, only those postings are included; and if you activate all three, the filter is removed.) .PP \f[C]R\f[R] toggles real mode, in which virtual postings are ignored. .PP \f[C]Z\f[R] toggles nonzero mode, in which only accounts with nonzero balances are shown (hledger-ui shows zero items by default, unlike command-line hledger). .PP Press \f[C]right\f[R] or \f[C]enter\f[R] to view an account\[aq]s transactions register. .SS Register screen .PP This screen shows the transactions affecting a particular account, like a check register. 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 historical total or period total for the current account, after the transaction. This can be toggled with \f[C]H\f[R]. Similar to the accounts screen, the historical total is affected by transactions (filtered by the filter query) before the report start date, while the period total is not. If the historical total is not disturbed by a filter query, it will be the running historical balance you would see on a bank register for the current account. .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[C]t\f[R] here also. .PP \f[C]U\f[R] toggles filtering by unmarked status, showing or hiding unmarked transactions. Similarly, \f[C]P\f[R] toggles pending transactions, and \f[C]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[C]R\f[R] toggles real mode, in which virtual postings are ignored. .PP \f[C]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[C]right\f[R] (or \f[C]enter\f[R]) to view the selected transaction in detail. .SS Transaction screen .PP 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[C]up\f[R] and \f[C]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). .SS Error screen .PP 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 ENVIRONMENT .PP \f[B]COLUMNS\f[R] The screen width to use. Default: the full terminal width. .PP \f[B]LEDGER_FILE\f[R] The journal file path when not specified with \f[C]-f\f[R]. Default: \f[C]\[ti]/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). .PP A typical value is \f[C]\[ti]/DIR/YYYY.journal\f[R], where DIR is a version-controlled finance directory and YYYY is the current year. Or \f[C]\[ti]/DIR/current.journal\f[R], where current.journal is a symbolic link to YYYY.journal. .PP On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a \f[C]\[ti]/.MacOSX/environment.plist\f[R] file containing .IP .nf \f[C] { \[dq]LEDGER_FILE\[dq] : \[dq]\[ti]/finance/current.journal\[dq] } \f[R] .fi .PP To see the effect you may need to \f[C]killall Dock\f[R], or reboot. .SH FILES .PP Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]-f\f[R], or \f[C]$LEDGER_FILE\f[R], or \f[C]$HOME/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). .SH BUGS .PP The need to precede options with \f[C]--\f[R] when invoked from hledger is awkward. .PP \f[C]-f-\f[R] doesn\[aq]t work (hledger-ui can\[aq]t read from stdin). .PP \f[C]-V\f[R] affects only the accounts screen. .PP When you press \f[C]g\f[R], the current and all previous screens are regenerated, which may cause a noticeable pause with large files. Also there is no visual indication that this is in progress. .PP \f[C]--watch\f[R] is not yet fully robust. It works well for normal usage, but many file changes in a short time (eg saving the file thousands of times with an editor macro) can cause problems at least on OSX. Symptoms include: unresponsive UI, periodic resetting of the cursor position, momentary display of parse errors, high CPU usage eventually subsiding, and possibly a small but persistent build-up of CPU usage until the program is restarted. .PP Also, if you are viewing files mounted from another machine, \f[C]--watch\f[R] requires that both machine clocks are roughly in step. .SH "REPORTING BUGS" Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) .SH AUTHORS Simon Michael and contributors .SH COPYRIGHT Copyright (C) 2007-2019 Simon Michael. .br Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5), ledger(1) http://hledger.org hledger-1.19.1/embeddedfiles/hledger-ui.txt0000644000000000000000000004664713725533425016777 0ustar0000000000000000 hledger-ui(1) hledger User Manuals hledger-ui(1) NAME hledger-ui - terminal interface for the hledger accounting tool SYNOPSIS hledger-ui [OPTIONS] [QUERYARGS] hledger ui -- [OPTIONS] [QUERYARGS] DESCRIPTION hledger is a reliable, 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). 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 data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with -f, or $LEDGER_FILE, or $HOME/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.journal). For more about this see hledger(1), hledger_journal(5) etc. 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 Note: if invoking hledger-ui as a hledger subcommand, write -- before options as shown above. Any QUERYARGS are interpreted as a hledger search query which filters the data. --watch watch for data and date changes and reload automatically --theme=default|terminal|greenterm use this custom display theme --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 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 --anon anonymize accounts and payees --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) hledger reporting options: -b --begin=DATE include postings/txns on or after this date -e --end=DATE include postings/txns before this date -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) -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-value with -V/-X/--value, also infer market prices from transactions --auto apply automated posting rules to modify transactions. --forecast generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. --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. 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. hledger help options: -h --help show general usage (or after COMMAND, command usage) --version show version --debug[=N] show debug output (levels 1-9, default: 1) a @file argument will be expanded to the contents of file, which should contain one command line option/argument per line. (to prevent this, insert a -- argument before.) keys ? 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/page up/page down/home/end move up and down through lists. Emacs-style (ctrl-p/ctrl-n/ctrl-f/ctrl-b) movement keys are also supported (but not vi-style keys, since hledger-1.19, sorry!). 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 --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. / 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. (experimental) 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 in their transaction price's com- modity (like toggling the -b/--cost flag). v toggles value mode, showing amounts' current market value in their default valuation commodity (like toggling the -v/--market flag). note, "current market value" means the value on the report end date if specified, otherwise today. to see the value on another date, you can temporarily set that as the report end date. eg: to see a transaction as it was valued on july 30, go to the accounts or register screen, press /, and add date:-7/30 to the query. at most one of cost or value mode can be active at once. there's not yet any visual reminder when cost or value mode is active; for now pressing b b v should reliably reset to normal mode. with --watch active, if you save an edit to the journal file while viewing the transaction screen in cost or value mode, the b/v keys will stop working. to work around, press g to force a manual reload, or exit the transaction screen. q quits the application. additional screen-specific keys are described below. screens accounts screen this is normally the first screen displayed. it lists accounts and their balances, like hledger's balance command. by default, it shows all accounts and their latest ending balances (including the balances of subaccounts). if you specify a query on the command line, it shows just the matched accounts and the balances from matched transactions. Account names are shown as a flat list by default; press t to toggle tree mode. In list mode, account balances are exclusive of subac- counts, except where subaccounts are hidden by a depth limit (see be- low). In tree mode, all account balances are inclusive of subaccounts. To see less detail, press a number key, 1 to 9, to set a depth limit. Or use - to decrease and +/= to increase the depth limit. 0 shows even less detail, collapsing all accounts to a single total. To remove the depth limit, set it higher than the maximum account depth, or press ES- CAPE. H toggles between showing historical balances or period balances. His- torical balances (the default) are ending balances at the end of the report period, taking into account all transactions before that date (filtered by the filter query if any), including transactions before the start of the report period. In other words, historical balances are what you would see on a bank statement for that account (unless disturbed by a filter query). Period balances ignore transactions be- fore the report start date, so they show the change in balance during the report period. They are more useful eg when viewing a time log. U toggles filtering by unmarked status, including or excluding unmarked postings in the balances. Similarly, P toggles pending postings, and C toggles cleared postings. (By default, balances include all postings; if you activate one or two status filters, only those postings are in- cluded; 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 accounts with nonzero balances are shown (hledger-ui shows zero items by default, unlike command-line hledger). Press right or enter to view an account's transactions register. Register screen This screen shows the transactions affecting a particular account, like a check register. 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 historical total or period total for the current account, after the transaction. This can be toggled with H. Similar to the accounts screen, the historical total is affected by transactions (filtered by the filter query) before the report start date, while the period total is not. If the historical total is not disturbed by a filter query, it will be the running historical balance you would see on a bank register for the current account. 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 (or enter) to view the selected transaction in detail. Transaction screen 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). Error screen 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.) ENVIRONMENT COLUMNS The screen width to use. Default: the full terminal width. LEDGER_FILE The journal file path when not specified with -f. Default: ~/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.jour- nal). A typical value is ~/DIR/YYYY.journal, where DIR is a version-con- trolled finance directory and YYYY is the current year. Or ~/DIR/cur- rent.journal, where current.journal is a symbolic link to YYYY.journal. On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a ~/.MacOSX/en- vironment.plist file containing { "LEDGER_FILE" : "~/finance/current.journal" } To see the effect you may need to killall Dock, or reboot. FILES Reads data from one or more files in hledger journal, timeclock, time- dot, or CSV format specified with -f, or $LEDGER_FILE, or $HOME/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.journal). BUGS The need to precede options with -- when invoked from hledger is awk- ward. -f- doesn't work (hledger-ui can't read from stdin). -V affects only the accounts screen. When you press g, the current and all previous screens are regenerated, which may cause a noticeable pause with large files. Also there is no visual indication that this is in progress. --watch is not yet fully robust. It works well for normal usage, but many file changes in a short time (eg saving the file thousands of times with an editor macro) can cause problems at least on OSX. Symp- toms include: unresponsive UI, periodic resetting of the cursor posi- tion, momentary display of parse errors, high CPU usage eventually sub- siding, and possibly a small but persistent build-up of CPU usage until the program is restarted. Also, if you are viewing files mounted from another machine, --watch requires that both machine clocks are roughly in step. REPORTING BUGS Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) AUTHORS Simon Michael and contributors COPYRIGHT Copyright (C) 2007-2019 Simon Michael. Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), hledger-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_time- dot(5), ledger(1) http://hledger.org hledger-ui 1.18.99 September 2020 hledger-ui(1) hledger-1.19.1/embeddedfiles/hledger-ui.info0000644000000000000000000004463713725533425017110 0ustar0000000000000000This is hledger-ui.info, produced by makeinfo version 6.7 from stdin.  File: hledger-ui.info, Node: Top, Next: OPTIONS, Up: (dir) hledger-ui(1) hledger-ui 1.18.99 ******************************** hledger-ui - terminal interface for the hledger accounting tool 'hledger-ui [OPTIONS] [QUERYARGS]' 'hledger ui -- [OPTIONS] [QUERYARGS]' hledger is a reliable, 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). 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 data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with '-f', or '$LEDGER_FILE', or '$HOME/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal'). For more about this see hledger(1), hledger_journal(5) etc. 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:: * keys:: * screens:: * ENVIRONMENT:: * FILES:: * BUGS::  File: hledger-ui.info, Node: OPTIONS, Next: keys, Prev: Top, Up: Top 1 OPTIONS ********* Note: if invoking hledger-ui as a hledger subcommand, write '--' before options as shown above. Any QUERYARGS are interpreted as a hledger search query which filters the data. '--watch' watch for data and date changes and reload automatically '--theme=default|terminal|greenterm' use this custom display theme '--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 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 '--anon' anonymize accounts and payees '--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) hledger reporting options: '-b --begin=DATE' include postings/txns on or after this date '-e --end=DATE' include postings/txns before this date '-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) '-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-value' with -V/-X/-value, also infer market prices from transactions '--auto' apply automated posting rules to modify transactions. '--forecast' generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. '--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. 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. hledger help options: '-h --help' show general usage (or after COMMAND, command usage) '--version' show version '--debug[=N]' show debug output (levels 1-9, default: 1) a @file argument will be expanded to the contents of file, which should contain one command line option/argument per line. (to prevent this, insert a '--' argument before.)  File: hledger-ui.info, Node: keys, Next: screens, Prev: OPTIONS, Up: Top 2 keys ****** '?' 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'/'page up'/'page down'/'home'/'end' move up and down through lists. Emacs-style ('ctrl-p'/'ctrl-n'/'ctrl-f'/'ctrl-b') movement keys are also supported (but not vi-style keys, since hledger-1.19, sorry!). 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 '--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. '/' 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. _(experimental)_ '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 in their transaction price's commodity (like toggling the '-b/--cost' flag). 'v' toggles value mode, showing amounts' current market value in their default valuation commodity (like toggling the '-v/--market' flag). note, "current market value" means the value on the report end date if specified, otherwise today. to see the value on another date, you can temporarily set that as the report end date. eg: to see a transaction as it was valued on july 30, go to the accounts or register screen, press '/', and add 'date:-7/30' to the query. at most one of cost or value mode can be active at once. there's not yet any visual reminder when cost or value mode is active; for now pressing 'b' 'b' 'v' should reliably reset to normal mode. with -watch active, if you save an edit to the journal file while viewing the transaction screen in cost or value mode, the 'b'/'v' keys will stop working. to work around, press g to force a manual reload, or exit the transaction screen. 'q' quits the application. additional screen-specific keys are described below.  File: hledger-ui.info, Node: screens, Next: ENVIRONMENT, Prev: keys, Up: Top 3 screens ********* * Menu: * accounts screen:: * Register screen:: * Transaction screen:: * Error screen::  File: hledger-ui.info, Node: accounts screen, Next: Register screen, Up: screens 3.1 accounts screen =================== this is normally the first screen displayed. it lists accounts and their balances, like hledger's balance command. by default, it shows all accounts and their latest ending balances (including the balances of subaccounts). if you specify a query on the command line, it shows just the matched accounts and the balances from matched transactions. Account names are shown as a flat list by default; press 't' to toggle tree mode. In list mode, account balances are exclusive of subaccounts, except where subaccounts are hidden by a depth limit (see below). In tree mode, all account balances are inclusive of subaccounts. To see less detail, press a number key, '1' to '9', to set a depth limit. Or use '-' to decrease and '+'/'=' to increase the depth limit. '0' shows even less detail, collapsing all accounts to a single total. To remove the depth limit, set it higher than the maximum account depth, or press 'ESCAPE'. 'H' toggles between showing historical balances or period balances. Historical balances (the default) are ending balances at the end of the report period, taking into account all transactions before that date (filtered by the filter query if any), including transactions before the start of the report period. In other words, historical balances are what you would see on a bank statement for that account (unless disturbed by a filter query). Period balances ignore transactions before the report start date, so they show the change in balance during the report period. They are more useful eg when viewing a time log. 'U' toggles filtering by unmarked status, including or excluding unmarked postings in the balances. Similarly, 'P' toggles pending postings, and 'C' toggles cleared postings. (By default, balances include all postings; if you activate one or two status filters, only those postings are included; 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 accounts with nonzero balances are shown (hledger-ui shows zero items by default, unlike command-line hledger). Press 'right' or 'enter' to view an account's transactions register.  File: hledger-ui.info, Node: Register screen, Next: Transaction screen, Prev: accounts screen, Up: screens 3.2 Register screen =================== This screen shows the transactions affecting a particular account, like a check register. 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 historical total or period total for the current account, after the transaction. This can be toggled with 'H'. Similar to the accounts screen, the historical total is affected by transactions (filtered by the filter query) before the report start date, while the period total is not. If the historical total is not disturbed by a filter query, it will be the running historical balance you would see on a bank register for the current account. 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' (or 'enter') to view the selected transaction in detail.  File: hledger-ui.info, Node: Transaction screen, Next: Error screen, Prev: Register screen, Up: screens 3.3 Transaction screen ====================== 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).  File: hledger-ui.info, Node: Error screen, Prev: Transaction screen, Up: screens 3.4 Error screen ================ 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: ENVIRONMENT, Next: FILES, Prev: screens, Up: Top 4 ENVIRONMENT ************* *COLUMNS* The screen width to use. Default: the full terminal width. *LEDGER_FILE* The journal file path when not specified with '-f'. Default: '~/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal'). A typical value is '~/DIR/YYYY.journal', where DIR is a version-controlled finance directory and YYYY is the current year. Or '~/DIR/current.journal', where current.journal is a symbolic link to YYYY.journal. On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a '~/.MacOSX/environment.plist' file containing { "LEDGER_FILE" : "~/finance/current.journal" } To see the effect you may need to 'killall Dock', or reboot.  File: hledger-ui.info, Node: FILES, Next: BUGS, Prev: ENVIRONMENT, Up: Top 5 FILES ******* Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with '-f', or '$LEDGER_FILE', or '$HOME/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal').  File: hledger-ui.info, Node: BUGS, Prev: FILES, Up: Top 6 BUGS ****** The need to precede options with '--' when invoked from hledger is awkward. '-f-' doesn't work (hledger-ui can't read from stdin). '-V' affects only the accounts screen. When you press 'g', the current and all previous screens are regenerated, which may cause a noticeable pause with large files. Also there is no visual indication that this is in progress. '--watch' is not yet fully robust. It works well for normal usage, but many file changes in a short time (eg saving the file thousands of times with an editor macro) can cause problems at least on OSX. Symptoms include: unresponsive UI, periodic resetting of the cursor position, momentary display of parse errors, high CPU usage eventually subsiding, and possibly a small but persistent build-up of CPU usage until the program is restarted. Also, if you are viewing files mounted from another machine, '--watch' requires that both machine clocks are roughly in step.  Tag Table: Node: Top71 Node: OPTIONS1476 Ref: #options1573 Node: keys5545 Ref: #keys5640 Node: screens9972 Ref: #screens10077 Node: accounts screen10167 Ref: #accounts-screen10295 Node: Register screen12510 Ref: #register-screen12665 Node: Transaction screen14662 Ref: #transaction-screen14820 Node: Error screen15690 Ref: #error-screen15812 Node: ENVIRONMENT16056 Ref: #environment16170 Node: FILES16977 Ref: #files17076 Node: BUGS17289 Ref: #bugs17366  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.19.1/embeddedfiles/hledger-web.10000644000000000000000000005011513725533425016441 0ustar0000000000000000 .TH "hledger-web" "1" "September 2020" "hledger-web 1.18.99" "hledger User Manuals" .SH NAME .PP hledger-web - web interface for the hledger accounting tool .SH SYNOPSIS .PP \f[C]hledger-web [OPTIONS]\f[R] .PD 0 .P .PD \f[C]hledger web -- [OPTIONS]\f[R] .SH DESCRIPTION .PP hledger is a reliable, 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). .PP hledger-web is hledger\[aq]s web interface. It starts a simple web application for browsing and adding transactions, and optionally opens it in a web browser window if possible. It provides a more user-friendly UI than the hledger CLI or hledger-ui interface, 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 ledger 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 data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]-f\f[R], or \f[C]$LEDGER_FILE\f[R], or \f[C]$HOME/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). For more about this see hledger(1), hledger_journal(5) etc. .SH OPTIONS .PP Command-line options and arguments may be used to set an initial filter on the data. These filter options are not shown in the web UI, but it will be applied in addition to any search query entered there. .PP Note: if invoking hledger-web as a hledger subcommand, write \f[C]--\f[R] before options, as shown in the synopsis above. .TP \f[B]\f[CB]--serve\f[B]\f[R] serve and log requests, don\[aq]t browse or auto-exit .TP \f[B]\f[CB]--serve-api\f[B]\f[R] like --serve, but serve only the JSON web API, without the server-side web UI .TP \f[B]\f[CB]--host=IPADDR\f[B]\f[R] listen on this IP address (default: 127.0.0.1) .TP \f[B]\f[CB]--port=PORT\f[B]\f[R] listen on this TCP port (default: 5000) .TP \f[B]\f[CB]--socket=SOCKETFILE\f[B]\f[R] use a unix domain socket file to listen for requests instead of a TCP socket. Implies \f[C]--serve\f[R]. It can only be used if the operating system can provide this type of socket. .TP \f[B]\f[CB]--base-url=URL\f[B]\f[R] set the base url (default: http://IPADDR:PORT). You would change this when sharing over the network, or integrating within a larger website. .TP \f[B]\f[CB]--file-url=URL\f[B]\f[R] set the static files url (default: BASEURL/static). hledger-web normally serves static files itself, but if you wanted to serve them from another server for efficiency, you would set the url with this. .TP \f[B]\f[CB]--capabilities=CAP[,CAP..]\f[B]\f[R] enable the view, add, and/or manage capabilities (default: view,add) .TP \f[B]\f[CB]--capabilities-header=HTTPHEADER\f[B]\f[R] read capabilities to enable from a HTTP header, like X-Sandstorm-Permissions (default: disabled) .PP hledger input options: .TP \f[B]\f[CB]-f FILE --file=FILE\f[B]\f[R] use a different input file. For stdin, use - (default: \f[C]$LEDGER_FILE\f[R] or \f[C]$HOME/.hledger.journal\f[R]) .TP \f[B]\f[CB]--rules-file=RULESFILE\f[B]\f[R] Conversion rules file to use when reading CSV (default: FILE.rules) .TP \f[B]\f[CB]--separator=CHAR\f[B]\f[R] Field separator to expect when reading CSV (default: \[aq],\[aq]) .TP \f[B]\f[CB]--alias=OLD=NEW\f[B]\f[R] rename accounts named OLD to NEW .TP \f[B]\f[CB]--anon\f[B]\f[R] anonymize accounts and payees .TP \f[B]\f[CB]--pivot FIELDNAME\f[B]\f[R] use some other field or tag for the account name .TP \f[B]\f[CB]-I --ignore-assertions\f[B]\f[R] disable balance assertion checks (note: does not disable balance assignments) .PP hledger reporting options: .TP \f[B]\f[CB]-b --begin=DATE\f[B]\f[R] include postings/txns on or after this date .TP \f[B]\f[CB]-e --end=DATE\f[B]\f[R] include postings/txns before this date .TP \f[B]\f[CB]-D --daily\f[B]\f[R] multiperiod/multicolumn report by day .TP \f[B]\f[CB]-W --weekly\f[B]\f[R] multiperiod/multicolumn report by week .TP \f[B]\f[CB]-M --monthly\f[B]\f[R] multiperiod/multicolumn report by month .TP \f[B]\f[CB]-Q --quarterly\f[B]\f[R] multiperiod/multicolumn report by quarter .TP \f[B]\f[CB]-Y --yearly\f[B]\f[R] multiperiod/multicolumn report by year .TP \f[B]\f[CB]-p --period=PERIODEXP\f[B]\f[R] set start date, end date, and/or reporting interval all at once using period expressions syntax .TP \f[B]\f[CB]--date2\f[B]\f[R] match the secondary date instead (see command help for other effects) .TP \f[B]\f[CB]-U --unmarked\f[B]\f[R] include only unmarked postings/txns (can combine with -P or -C) .TP \f[B]\f[CB]-P --pending\f[B]\f[R] include only pending postings/txns .TP \f[B]\f[CB]-C --cleared\f[B]\f[R] include only cleared postings/txns .TP \f[B]\f[CB]-R --real\f[B]\f[R] include only non-virtual postings .TP \f[B]\f[CB]-NUM --depth=NUM\f[B]\f[R] hide/aggregate accounts or postings more than NUM levels deep .TP \f[B]\f[CB]-E --empty\f[B]\f[R] show items with zero amount, normally hidden (and vice-versa in hledger-ui/hledger-web) .TP \f[B]\f[CB]-B --cost\f[B]\f[R] convert amounts to their cost/selling amount at transaction time .TP \f[B]\f[CB]-V --market\f[B]\f[R] convert amounts to their market value in default valuation commodities .TP \f[B]\f[CB]-X --exchange=COMM\f[B]\f[R] convert amounts to their market value in commodity COMM .TP \f[B]\f[CB]--value\f[B]\f[R] convert amounts to cost or market value, more flexibly than -B/-V/-X .TP \f[B]\f[CB]--infer-value\f[B]\f[R] with -V/-X/--value, also infer market prices from transactions .TP \f[B]\f[CB]--auto\f[B]\f[R] apply automated posting rules to modify transactions. .TP \f[B]\f[CB]--forecast\f[B]\f[R] generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. .TP \f[B]\f[CB]--color=WHEN (or --colour=WHEN)\f[B]\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. .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. .PP hledger help options: .TP \f[B]\f[CB]-h --help\f[B]\f[R] show general usage (or after COMMAND, command usage) .TP \f[B]\f[CB]--version\f[B]\f[R] show version .TP \f[B]\f[CB]--debug[=N]\f[B]\f[R] show debug output (levels 1-9, default: 1) .PP A \[at]FILE argument will be expanded to the contents of FILE, which should contain one command line option/argument per line. (To prevent this, insert a \f[C]--\f[R] argument before.) .PP By default, hledger-web starts the web app in \[dq]transient mode\[dq] and also opens it in your default web browser if possible. In this mode the web app will keep running for as long as you have it open in a browser window, and will exit after two minutes of inactivity (no requests and no browser windows viewing it). With \f[C]--serve\f[R], it just runs the web app without exiting, and logs requests to the console. With \f[C]--serve-api\f[R], only the JSON web api (see below) is served, with the usual HTML server-side web UI disabled. .PP By default the server listens on IP address 127.0.0.1, accessible only to local requests. You can use \f[C]--host\f[R] to change this, eg \f[C]--host 0.0.0.0\f[R] to listen on all configured addresses. .PP Similarly, use \f[C]--port\f[R] to set a TCP port other than 5000, eg if you are running multiple hledger-web instances. .PP Both of these options are ignored when \f[C]--socket\f[R] is used. In this case, it creates an \f[C]AF_UNIX\f[R] socket file at the supplied path and uses that for communication. This is an alternative way of running multiple hledger-web instances behind a reverse proxy that handles authentication for different users. The path can be derived in a predictable way, eg by using the username within the path. As an example, \f[C]nginx\f[R] as reverse proxy can use the variable \f[C]$remote_user\f[R] to derive a path from the username used in a HTTP basic authentication. The following \f[C]proxy_pass\f[R] directive allows access to all \f[C]hledger-web\f[R] instances that created a socket in \f[C]/tmp/hledger/\f[R]: .IP .nf \f[C] proxy_pass http://unix:/tmp/hledger/${remote_user}.socket; \f[R] .fi .PP You can use \f[C]--base-url\f[R] to change the protocol, hostname, port and path that appear in hyperlinks, useful eg for integrating hledger-web within a larger website. The default is \f[C]http://HOST:PORT/\f[R] using the server\[aq]s configured host address and TCP port (or \f[C]http://HOST\f[R] if PORT is 80). .PP With \f[C]--file-url\f[R] you can set a different base url for static files, eg for better caching or cookie-less serving on high performance websites. .SH PERMISSIONS .PP 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[C]--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[C]--capabilities=CAP[,CAP..]\f[R] flag when you start it, enabling one or more of the following capabilities. The default value is \f[C]view,add\f[R]: .RS 2 .IP \[bu] 2 \f[C]view\f[R] - allows viewing the journal file and all included files .IP \[bu] 2 \f[C]add\f[R] - allows adding new transactions to the main journal file .IP \[bu] 2 \f[C]manage\f[R] - allows editing, uploading or downloading the main or included files .RE .IP \[bu] 2 using the \f[C]--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 .PP If you enable the \f[C]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 .PP 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 .PP 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[C]--serve-api\f[R] flag. Eg: .IP .nf \f[C] $ hledger-web -f examples/sample.journal --serve-api \&... \f[R] .fi .PP You can get JSON data from these routes: .IP .nf \f[C] /accountnames /transactions /prices /commodities /accounts /accounttransactions/ACCOUNTNAME \f[R] .fi .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 .nf \f[C] $ 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] ] \f[R] .fi .PP Or all transactions: .IP .nf \f[C] $ 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, \&... \f[R] .fi .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 manual. .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[C]/accounttransactions\f[R] it\[aq]s getAccounttransactionsR, returning a \[dq]\f[C]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[C]/add\f[R], if hledger-web was started with the \f[C]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[C]/transactions\f[R] or \f[C]/accounttransactions\f[R], or you can export it with hledger-lib, eg like so: .IP .nf \f[C] \&.../hledger$ stack ghci hledger-lib >>> writeJsonFile \[dq]txn.json\[dq] (head $ jtxns samplejournal) >>> :q \f[R] .fi .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 .nf \f[C] { \[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] } \f[R] .fi .PP And here\[aq]s how to test adding it with curl. This should add a new entry to your journal: .IP .nf \f[C] $ curl http://127.0.0.1:5000/add -X PUT -H \[aq]Content-Type: application/json\[aq] --data-binary \[at]txn.json \f[R] .fi .SH ENVIRONMENT .PP \f[B]LEDGER_FILE\f[R] The journal file path when not specified with \f[C]-f\f[R]. Default: \f[C]\[ti]/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). .PP A typical value is \f[C]\[ti]/DIR/YYYY.journal\f[R], where DIR is a version-controlled finance directory and YYYY is the current year. Or \f[C]\[ti]/DIR/current.journal\f[R], where current.journal is a symbolic link to YYYY.journal. .PP On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a \f[C]\[ti]/.MacOSX/environment.plist\f[R] file containing .IP .nf \f[C] { \[dq]LEDGER_FILE\[dq] : \[dq]\[ti]/finance/current.journal\[dq] } \f[R] .fi .PP To see the effect you may need to \f[C]killall Dock\f[R], or reboot. .SH FILES .PP Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]-f\f[R], or \f[C]$LEDGER_FILE\f[R], or \f[C]$HOME/.hledger.journal\f[R] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[R]). .SH BUGS .PP The need to precede options with \f[C]--\f[R] when invoked from hledger is awkward. .PP \f[C]-f-\f[R] doesn\[aq]t work (hledger-web can\[aq]t read from stdin). .PP Query arguments and some hledger options are ignored. .PP Does not work in text-mode browsers. .PP Does not work well on small screens. .SH "REPORTING BUGS" Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) .SH AUTHORS Simon Michael and contributors .SH COPYRIGHT Copyright (C) 2007-2019 Simon Michael. .br Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5), ledger(1) http://hledger.org hledger-1.19.1/embeddedfiles/hledger-web.txt0000644000000000000000000005315413725533425017126 0ustar0000000000000000 hledger-web(1) hledger User Manuals hledger-web(1) NAME hledger-web - web interface for the hledger accounting tool SYNOPSIS hledger-web [OPTIONS] hledger web -- [OPTIONS] DESCRIPTION hledger is a reliable, 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). hledger-web is hledger's web interface. It starts a simple web appli- cation for browsing and adding transactions, and optionally opens it in a web browser window if possible. It provides a more user-friendly UI than the hledger CLI or hledger-ui interface, showing more at once (ac- counts, the current account register, balance charts) and allowing his- tory-aware data entry, interactive searching, and bookmarking. hledger-web also lets you share a ledger 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 data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with -f, or $LEDGER_FILE, or $HOME/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.journal). For more about this see hledger(1), hledger_journal(5) etc. OPTIONS Command-line options and arguments may be used to set an initial filter on the data. These filter options are not shown in the web UI, but it will be applied in addition to any search query entered there. Note: if invoking hledger-web as a hledger subcommand, write -- before options, as shown in the synopsis above. --serve serve and log requests, don't browse or auto-exit --serve-api like --serve, but serve only the JSON web API, without the server-side web UI --host=IPADDR listen on this IP address (default: 127.0.0.1) --port=PORT listen on this TCP port (default: 5000) --socket=SOCKETFILE use a unix domain socket file to listen for requests instead of a TCP socket. Implies --serve. It can only be used if the op- erating system can provide this type of socket. --base-url=URL set the base url (default: http://IPADDR:PORT). You would change this when sharing over the network, or integrating within a larger website. --file-url=URL set the static files url (default: BASEURL/static). hledger-web normally serves static files itself, but if you wanted to serve them from another server for efficiency, you would set the url with this. --capabilities=CAP[,CAP..] enable the view, add, and/or manage capabilities (default: view,add) --capabilities-header=HTTPHEADER read capabilities to enable from a HTTP header, like X-Sand- storm-Permissions (default: disabled) hledger 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 --anon anonymize accounts and payees --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) hledger reporting options: -b --begin=DATE include postings/txns on or after this date -e --end=DATE include postings/txns before this date -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) -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-value with -V/-X/--value, also infer market prices from transactions --auto apply automated posting rules to modify transactions. --forecast generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. --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. 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. hledger help options: -h --help show general usage (or after COMMAND, command usage) --version show version --debug[=N] show debug output (levels 1-9, default: 1) A @FILE argument will be expanded to the contents of FILE, which should contain one command line option/argument per line. (To prevent this, insert a -- argument before.) By default, hledger-web starts the web app in "transient mode" and also opens it in your default web browser if possible. In this mode the web app will keep running for as long as you have it open in a browser win- dow, and will exit after two minutes of inactivity (no requests and no browser windows viewing it). With --serve, it just runs the web app without exiting, and logs requests to the console. With --serve-api, only the JSON web api (see below) is served, with the usual HTML server-side web UI disabled. By default the server listens on IP address 127.0.0.1, accessible only to local requests. You can use --host to change this, eg --host 0.0.0.0 to listen on all configured addresses. Similarly, use --port to set a TCP port other than 5000, eg if you are running multiple hledger-web instances. Both of these options are ignored when --socket is used. In this case, it creates an AF_UNIX socket file at the supplied path and uses that for communication. This is an alternative way of running multiple hledger-web instances behind a reverse proxy that handles authentica- tion for different users. The path can be derived in a predictable way, eg by using the username within the path. As an example, nginx as reverse proxy can use the variable $remote_user to derive a path from the username used in a HTTP basic authentication. The following proxy_pass directive allows access to all hledger-web instances that created a socket in /tmp/hledger/: proxy_pass http://unix:/tmp/hledger/${remote_user}.socket; You can use --base-url to change the protocol, hostname, port and path that appear in hyperlinks, useful eg for 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). With --file-url you can set a different base url for static files, eg for better caching or cookie-less serving on high performance websites. 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: /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 manual. 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 ENVIRONMENT LEDGER_FILE The journal file path when not specified with -f. Default: ~/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.jour- nal). A typical value is ~/DIR/YYYY.journal, where DIR is a version-con- trolled finance directory and YYYY is the current year. Or ~/DIR/cur- rent.journal, where current.journal is a symbolic link to YYYY.journal. On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a ~/.MacOSX/en- vironment.plist file containing { "LEDGER_FILE" : "~/finance/current.journal" } To see the effect you may need to killall Dock, or reboot. FILES Reads data from one or more files in hledger journal, timeclock, time- dot, or CSV format specified with -f, or $LEDGER_FILE, or $HOME/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.journal). BUGS The need to precede options with -- when invoked from hledger is awk- ward. -f- doesn't work (hledger-web can't read from stdin). Query arguments and some hledger options are ignored. Does not work in text-mode browsers. Does not work well on small screens. REPORTING BUGS Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) AUTHORS Simon Michael and contributors COPYRIGHT Copyright (C) 2007-2019 Simon Michael. Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), hledger-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_time- dot(5), ledger(1) http://hledger.org hledger-web 1.18.99 September 2020 hledger-web(1) hledger-1.19.1/embeddedfiles/hledger-web.info0000644000000000000000000004544313725533425017244 0ustar0000000000000000This is hledger-web.info, produced by makeinfo version 6.7 from stdin.  File: hledger-web.info, Node: Top, Next: OPTIONS, Up: (dir) hledger-web(1) hledger-web 1.18.99 ********************************** hledger-web - web interface for the hledger accounting tool 'hledger-web [OPTIONS]' 'hledger web -- [OPTIONS]' hledger is a reliable, 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). hledger-web is hledger's web interface. It starts a simple web application for browsing and adding transactions, and optionally opens it in a web browser window if possible. It provides a more user-friendly UI than the hledger CLI or hledger-ui interface, 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 ledger 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 data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with '-f', or '$LEDGER_FILE', or '$HOME/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal'). For more about this see hledger(1), hledger_journal(5) etc. * Menu: * OPTIONS:: * PERMISSIONS:: * EDITING UPLOADING DOWNLOADING:: * RELOADING:: * JSON API:: * ENVIRONMENT:: * FILES:: * BUGS::  File: hledger-web.info, Node: OPTIONS, Next: PERMISSIONS, Prev: Top, Up: Top 1 OPTIONS ********* Command-line options and arguments may be used to set an initial filter on the data. These filter options are not shown in the web UI, but it will be applied in addition to any search query entered there. Note: if invoking hledger-web as a hledger subcommand, write '--' before options, as shown in the synopsis above. '--serve' serve and log requests, don't browse or auto-exit '--serve-api' like -serve, but serve only the JSON web API, without the server-side web UI '--host=IPADDR' listen on this IP address (default: 127.0.0.1) '--port=PORT' listen on this TCP port (default: 5000) '--socket=SOCKETFILE' use a unix domain socket file to listen for requests instead of a TCP socket. Implies '--serve'. It can only be used if the operating system can provide this type of socket. '--base-url=URL' set the base url (default: http://IPADDR:PORT). You would change this when sharing over the network, or integrating within a larger website. '--file-url=URL' set the static files url (default: BASEURL/static). hledger-web normally serves static files itself, but if you wanted to serve them from another server for efficiency, you would set the url with this. '--capabilities=CAP[,CAP..]' enable the view, add, and/or manage capabilities (default: view,add) '--capabilities-header=HTTPHEADER' read capabilities to enable from a HTTP header, like X-Sandstorm-Permissions (default: disabled) hledger 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 '--anon' anonymize accounts and payees '--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) hledger reporting options: '-b --begin=DATE' include postings/txns on or after this date '-e --end=DATE' include postings/txns before this date '-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) '-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-value' with -V/-X/-value, also infer market prices from transactions '--auto' apply automated posting rules to modify transactions. '--forecast' generate future transactions from periodic transaction rules, for the next 6 months or till report end date. In hledger-ui, also make ordinary future transactions visible. '--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. 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. hledger help options: '-h --help' show general usage (or after COMMAND, command usage) '--version' show version '--debug[=N]' show debug output (levels 1-9, default: 1) A @FILE argument will be expanded to the contents of FILE, which should contain one command line option/argument per line. (To prevent this, insert a '--' argument before.) By default, hledger-web starts the web app in "transient mode" and also opens it in your default web browser if possible. In this mode the web app will keep running for as long as you have it open in a browser window, and will exit after two minutes of inactivity (no requests and no browser windows viewing it). With '--serve', it just runs the web app without exiting, and logs requests to the console. With '--serve-api', only the JSON web api (see below) is served, with the usual HTML server-side web UI disabled. By default the server listens on IP address 127.0.0.1, accessible only to local requests. You can use '--host' to change this, eg '--host 0.0.0.0' to listen on all configured addresses. Similarly, use '--port' to set a TCP port other than 5000, eg if you are running multiple hledger-web instances. Both of these options are ignored when '--socket' is used. In this case, it creates an 'AF_UNIX' socket file at the supplied path and uses that for communication. This is an alternative way of running multiple hledger-web instances behind a reverse proxy that handles authentication for different users. The path can be derived in a predictable way, eg by using the username within the path. As an example, 'nginx' as reverse proxy can use the variable '$remote_user' to derive a path from the username used in a HTTP basic authentication. The following 'proxy_pass' directive allows access to all 'hledger-web' instances that created a socket in '/tmp/hledger/': proxy_pass http://unix:/tmp/hledger/${remote_user}.socket; You can use '--base-url' to change the protocol, hostname, port and path that appear in hyperlinks, useful eg for 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). With '--file-url' you can set a different base url for static files, eg for better caching or cookie-less serving on high performance websites.  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: ENVIRONMENT, 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: /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 manual. 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: ENVIRONMENT, Next: FILES, Prev: JSON API, Up: Top 6 ENVIRONMENT ************* *LEDGER_FILE* The journal file path when not specified with '-f'. Default: '~/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal'). A typical value is '~/DIR/YYYY.journal', where DIR is a version-controlled finance directory and YYYY is the current year. Or '~/DIR/current.journal', where current.journal is a symbolic link to YYYY.journal. On Mac computers, you can set this and other environment variables in a more thorough way that also affects applications started from the GUI (say, an Emacs dock icon). Eg on MacOS Catalina I have a '~/.MacOSX/environment.plist' file containing { "LEDGER_FILE" : "~/finance/current.journal" } To see the effect you may need to 'killall Dock', or reboot.  File: hledger-web.info, Node: FILES, Next: BUGS, Prev: ENVIRONMENT, Up: Top 7 FILES ******* Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with '-f', or '$LEDGER_FILE', or '$HOME/.hledger.journal' (on windows, perhaps 'C:/Users/USER/.hledger.journal').  File: hledger-web.info, Node: BUGS, Prev: FILES, Up: Top 8 BUGS ****** The need to precede options with '--' when invoked from hledger is awkward. '-f-' doesn't work (hledger-web can't read from stdin). Query arguments and some hledger options are ignored. Does not work in text-mode browsers. Does not work well on small screens.  Tag Table: Node: Top72 Node: OPTIONS1752 Ref: #options1857 Node: PERMISSIONS8737 Ref: #permissions8876 Node: EDITING UPLOADING DOWNLOADING10088 Ref: #editing-uploading-downloading10269 Node: RELOADING11103 Ref: #reloading11237 Node: JSON API11670 Ref: #json-api11784 Node: ENVIRONMENT17265 Ref: #environment17381 Node: FILES18114 Ref: #files18214 Node: BUGS18427 Ref: #bugs18505  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.19.1/embeddedfiles/hledger_journal.50000644000000000000000000016622413725533425017435 0ustar0000000000000000.\"t .TH "hledger_journal" "5" "September 2020" "hledger 1.18.99" "hledger User Manuals" .SH NAME .PP Journal - hledger\[aq]s default file format, representing a General Journal .SH DESCRIPTION .PP 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[C].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 a compatible subset, mostly, of ledger\[aq]s journal format, so hledger can work with compatible ledger journal files as well. It\[aq]s safe, and encouraged, to run both hledger and ledger on the same journal file, eg to validate the results you\[aq]re getting. .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. .SH FILE FORMAT .PP Here\[aq]s a description of each part of the file format (and hledger\[aq]s data model). These are mostly in the order you\[aq]ll use them, but in some cases related concepts have been grouped together for easy reference, or linked before they are introduced, so feel free to skip over anything that looks unnecessary right now. .SS Transactions .PP 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[C]!\f[R], or \f[C]*\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 .nf \f[C] 2008/01/01 income assets:bank:checking $1 income:salary $-1 \f[R] .fi .SS Dates .SS Simple dates .PP Dates in the journal file use \f[I]simple dates\f[R] format: \f[C]YYYY-MM-DD\f[R] or \f[C]YYYY/MM/DD\f[R] or \f[C]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 default year directive, or the current date when the command is run. Some examples: \f[C]2010-01-31\f[R], \f[C]2010/01/31\f[R], \f[C]2010.1.31\f[R], \f[C]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 Secondary dates .PP Real-life transactions sometimes involve more than one date - eg the date you write a cheque, and the date it clears in your bank. When you want to model this, for more accurate daily balances, you can specify individual posting dates. .PP Or, you can use the older \f[I]secondary date\f[R] feature (Ledger calls it auxiliary date or effective date). Note: we support this for compatibility, but I usually recommend avoiding this feature; posting dates are almost always clearer and simpler. .PP 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[C]--date2\f[R] flag (or \f[C]--aux-date\f[R] or \f[C]--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], as shown here: .IP .nf \f[C] 2010/2/23=2/19 movie ticket expenses:cinema $10 assets:checking \f[R] .fi .IP .nf \f[C] $ hledger register checking 2010-02-23 movie ticket assets:checking $-10 $-10 \f[R] .fi .IP .nf \f[C] $ hledger register checking --date2 2010-02-19 movie ticket assets:checking $-10 $-10 \f[R] .fi .SS Posting dates .PP You can give individual postings a different date from their parent transaction, by adding a posting comment containing a tag (see below) like \f[C]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 .nf \f[C] 2015/5/30 expenses:food $10 ; food purchased on saturday 5/30 assets:checking ; bank cleared it on monday, date:6/1 \f[R] .fi .IP .nf \f[C] $ hledger -f t.j register food 2015-05-30 expenses:food $10 $10 \f[R] .fi .IP .nf \f[C] $ hledger -f t.j register checking 2015-06-01 assets:checking $-10 $-10 \f[R] .fi .PP DATE should be a simple date; if the year is not specified it will use the year of the transaction\[aq]s date. You can set the secondary date similarly, with \f[C]date2:DATE2\f[R]. The \f[C]date:\f[R] or \f[C]date2:\f[R] tags must have a valid simple date value if they are present, eg a \f[C]date:\f[R] tag with no value is not allowed. .PP Ledger\[aq]s earlier, more compact bracketed date syntax is also supported: \f[C][DATE]\f[R], \f[C][DATE=DATE2]\f[R] or \f[C][=DATE2]\f[R]. hledger will attempt to parse any square-bracketed sequence of the \f[C]0123456789/-.=\f[R] characters in this way. With this syntax, DATE infers its year from the transaction and DATE2 infers its year from DATE. .SS Status .PP 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[C]!\f[R] T}@T{ pending T} T{ \f[C]*\f[R] T}@T{ cleared T} .TE .PP When reporting, you can filter by status with the \f[C]-U/--unmarked\f[R], \f[C]-P/--pending\f[R], and \f[C]-C/--cleared\f[R] flags; or the \f[C]status:\f[R], \f[C]status:!\f[R], and \f[C]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[C]-PC\f[R] to see the current balance at your bank, \f[C]-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 Description .PP 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 .PP You can optionally include a \f[C]|\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[C]|\f[R]) and an additional note field on the right (after the first \f[C]|\f[R]). This may be worthwhile if you need to do more precise querying and pivoting by payee or by note. .SS Comments .PP Lines in the journal beginning with a semicolon (\f[C];\f[R]) or hash (\f[C]#\f[R]) or star (\f[C]*\f[R]) are comments, and will be ignored. (Star comments cause org-mode nodes to be ignored, allowing emacs users to fold and navigate their journals with org-mode or orgstruct-mode.) .PP You can attach comments to a transaction by writing them after the description and/or indented on the following lines (before the postings). Similarly, you can attach comments to an individual posting by writing them after the amount and/or indented on the following lines. Transaction and posting comments must begin with a semicolon (\f[C];\f[R]). .PP Some examples: .IP .nf \f[C] # a file comment ; another file comment * also a file comment, useful in org/orgstruct mode comment A multiline file comment, which continues until a line containing just \[dq]end comment\[dq] (or end of file). end comment 2012/5/14 something ; a transaction comment ; the transaction comment, continued posting1 1 ; a comment for posting 1 posting2 ; a comment for posting 2 ; another comment line for posting 2 ; a file comment (because not indented) \f[R] .fi .PP You can also comment larger regions of a file using \f[C]comment\f[R] and \f[C]end comment\f[R] directives. .SS Tags .PP Tags are a way to add extra labels or labelled data to postings and transactions, which you can then search or pivot on. .PP A simple tag is a word (which may contain hyphens) followed by a full colon, written inside a transaction or posting comment line: .IP .nf \f[C] 2017/1/16 bought groceries ; sometag: \f[R] .fi .PP Tags can have a value, which is the text after the colon, up to the next comma or end of line, with leading/trailing whitespace removed: .IP .nf \f[C] expenses:food $10 ; a-posting-tag: the tag value \f[R] .fi .PP Note this means hledger\[aq]s tag values can not contain commas or newlines. Ending at commas means you can write multiple short tags on one line, comma separated: .IP .nf \f[C] assets:checking ; a comment containing tag1:, tag2: some value ... \f[R] .fi .PP Here, .IP \[bu] 2 \[dq]\f[C]a comment containing\f[R]\[dq] is just comment text, not a tag .IP \[bu] 2 \[dq]\f[C]tag1\f[R]\[dq] is a tag with no value .IP \[bu] 2 \[dq]\f[C]tag2\f[R]\[dq] is another tag, whose value is \[dq]\f[C]some value ...\f[R]\[dq] .PP Tags in a transaction comment affect the transaction and all of its postings, while tags in a posting comment affect only that posting. For example, the following transaction has three tags (\f[C]A\f[R], \f[C]TAG2\f[R], \f[C]third-tag\f[R]) and the posting has four (those plus \f[C]posting-tag\f[R]): .IP .nf \f[C] 1/1 a transaction ; A:, TAG2: ; third-tag: a third transaction tag, <- with a value (a) $1 ; posting-tag: \f[R] .fi .PP Tags are like Ledger\[aq]s metadata feature, except hledger\[aq]s tag values are simple strings. .SS Postings .PP 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[C]!\f[R], or \f[C]*\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 Virtual postings .PP A posting with a parenthesised account name is called a \f[I]virtual posting\f[R] or \f[I]unbalanced posting\f[R], which means it is exempt from the usual rule that a transaction\[aq]s postings must balance add up to zero. .PP This is not part of double entry accounting, so you might choose to avoid this feature. Or you can use it sparingly for certain special cases where it can be convenient. Eg, you could set opening balances without using a balancing equity account: .IP .nf \f[C] 1/1 opening balances (assets:checking) $1000 (assets:savings) $2000 \f[R] .fi .PP A posting with a bracketed account name is called a \f[I]balanced virtual posting\f[R]. The balanced virtual postings in a transaction must add up to zero (separately from other postings). Eg: .IP .nf \f[C] 1/1 buy food with cash, update budget envelope subaccounts, & something else assets:cash $-10 ; <- these balance expenses:food $7 ; <- expenses:food $3 ; <- [assets:checking:budget:food] $-10 ; <- and these balance [assets:checking:available] $10 ; <- (something:else) $5 ; <- not required to balance \f[R] .fi .PP Ordinary non-parenthesised, non-bracketed postings are called \f[I]real postings\f[R]. You can exclude virtual postings from reports with the \f[C]-R/--real\f[R] flag or \f[C]real:1\f[R] query. .SS Account names .PP Account names typically have several parts separated by a full colon, from which hledger derives a hierarchical chart of accounts. They can be anything you like, but in finance there are traditionally five top-level accounts: \f[C]assets\f[R], \f[C]liabilities\f[R], \f[C]income\f[R], \f[C]expenses\f[R], and \f[C]equity\f[R]. .PP Account names may contain single spaces, eg: \f[C]assets:accounts receivable\f[R]. Because of this, they must always be followed by \f[B]two or more spaces\f[R] (or newline). .PP Account names can be aliased. .SS Amounts .PP 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 .nf \f[C] 1 \f[R] .fi .PP \&..and usually a currency or commodity name (the \[dq]commodity\[dq]). This is a symbol, word, or phrase, to the left or right of the quantity, with or without a separating space: .IP .nf \f[C] $1 4000 AAPL \f[R] .fi .PP If the commodity name contains spaces, numbers, or punctuation, it must be enclosed in double quotes: .IP .nf \f[C] 3 \[dq]no. 42 green apples\[dq] \f[R] .fi .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 .nf \f[C] -$1 $-1 \f[R] .fi .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 .nf \f[C] + $1 $- 1 \f[R] .fi .PP Scientific E notation is allowed: .IP .nf \f[C] 1E-6 EUR 1E3 \f[R] .fi .PP A decimal mark can be written as a period or a comma: .IP .nf \f[C] 1.23 1,23456780000009 \f[R] .fi .SS Digit group marks .PP In the integer part of the quantity (left of the decimal mark), groups of digits can optionally be separated by a \[dq]digit group mark\[dq] - a space, comma, or period (different from the decimal mark): .IP .nf \f[C] $1,000,000.00 EUR 2.000.000,00 INR 9,99,99,999.00 1 000 000.9455 \f[R] .fi .PP Note, a number containing a single group mark and no decimal mark is ambiguous. Are these group marks or decimal marks ? .IP .nf \f[C] 1,000 1.000 \f[R] .fi .PP hledger will treat them both as decimal marks by default (cf #793). If you use digit group marks, to prevent confusion and undetected typos we recommend you write commodity directives at the top of the file to explicitly declare the decimal mark (and optionally a digit group mark). Note, these formats (\[dq]amount styles\[dq]) are specific to each commodity, so if your data uses multiple formats, hledger can handle it: .IP .nf \f[C] commodity $1,000.00 commodity EUR 1.000,00 commodity INR 9,99,99,999.00 commodity 1 000 000.9455 \f[R] .fi .SS Amount display style .PP For each commodity, hledger chooses a consistent format to use when displaying amounts. (Except price amounts, which are always displayed as written). The display style is chosen as follows: .IP \[bu] 2 If there is a commodity directive (or default commodity directive) for the commodity, that format is used (see examples above). .IP \[bu] 2 Otherwise the format of the first posting amount in that commodity seen in the journal is used. But the number of decimal places (\[dq]precision\[dq]) will be the maximum from all posting amounts in that commodity. .IP \[bu] 2 Or if there are no such amounts in the journal, a default format is used (like \f[C]$1000.00\f[R]). .PP Transaction prices don\[aq]t affect the amount display style directly, but occasionally they can do so indirectly (eg when an posting\[aq]s amount is inferred using a transaction price). If you find this causing problems, use a commodity directive to fix the display style. .PP In summary: amounts will be displayed much as they appear in your journal, with the max observed number of decimal places. If you want to see fewer decimal places in reports, use a commodity directive to override that. .PP hledger uses banker\[aq]s rounding: it rounds to the nearest even number, eg 0.5 displayed with zero decimal places is \[dq]0\[dq]). (Note, prior to hledger 1.17.1 this could vary if hledger happened to be built with an old version of Decimal (<0.5.1); since 1.17.1 it\[aq]s guaranteed.) .SS Transaction prices .PP Within a transaction, you can note an amount\[aq]s price in another commodity. This can be used to document the cost (in a purchase) or selling price (in a sale). For example, transaction prices are useful to record purchases of a foreign currency. Note transaction prices are fixed at the time of the transaction, and do not change over time. See also market prices, which represent prevailing exchange rates on a certain date. .PP There are several ways to record a transaction price: .IP "1." 3 Write the price per unit, as \f[C]\[at] UNITPRICE\f[R] after the amount: .RS 4 .IP .nf \f[C] 2009/1/1 assets:euros \[Eu]100 \[at] $1.35 ; one hundred euros purchased at $1.35 each assets:dollars ; balancing amount is -$135.00 \f[R] .fi .RE .IP "2." 3 Write the total price, as \f[C]\[at]\[at] TOTALPRICE\f[R] after the amount: .RS 4 .IP .nf \f[C] 2009/1/1 assets:euros \[Eu]100 \[at]\[at] $135 ; one hundred euros purchased at $135 for the lot assets:dollars \f[R] .fi .RE .IP "3." 3 Specify amounts for all postings, using exactly two commodities, and let hledger infer the price that balances the transaction: .RS 4 .IP .nf \f[C] 2009/1/1 assets:euros \[Eu]100 ; one hundred euros purchased assets:dollars $-135 ; for $135 \f[R] .fi .RE .IP "4." 3 Like 1, but the \f[C]\[at]\f[R] is parenthesised, i.e. \f[C](\[at])\f[R]; this is for compatibility with Ledger journals (Virtual posting costs), and is equivalent to 1 in hledger. .IP "5." 3 Like 2, but as in 4 the \f[C]\[at]\[at]\f[R] is parenthesised, i.e. \f[C](\[at]\[at])\f[R]; in hledger, this is equivalent to 2. .PP Use the \f[C]-B/--cost\f[R] flag to convert amounts to their transaction price\[aq]s commodity, if any. (mnemonic: \[dq]B\[dq] is from \[dq]cost Basis\[dq], as in Ledger). Eg here is how -B affects the balance report for the example above: .IP .nf \f[C] $ hledger bal -N --flat $-135 assets:dollars \[Eu]100 assets:euros $ hledger bal -N --flat -B $-135 assets:dollars $135 assets:euros # <- the euros\[aq] cost \f[R] .fi .PP Note -B is sensitive to the order of postings when a transaction price is inferred: the inferred price will be in the commodity of the last amount. So if example 3\[aq]s postings are reversed, while the transaction is equivalent, -B shows something different: .IP .nf \f[C] 2009/1/1 assets:dollars $-135 ; 135 dollars sold assets:euros \[Eu]100 ; for 100 euros \f[R] .fi .IP .nf \f[C] $ hledger bal -N --flat -B \[Eu]-100 assets:dollars # <- the dollars\[aq] selling price \[Eu]100 assets:euros \f[R] .fi .SS Lot prices and lot dates .PP Ledger allows another kind of price, lot price (four variants: \f[C]{UNITPRICE}\f[R], \f[C]{{TOTALPRICE}}\f[R], \f[C]{=FIXEDUNITPRICE}\f[R], \f[C]{{=FIXEDTOTALPRICE}}\f[R]), and/or a lot date (\f[C][DATE]\f[R]) to be specified. These are normally used to select a lot when selling investments. hledger will parse these, for compatibility with Ledger journals, but currently ignores them. A transaction price, lot price and/or lot date may appear in any order, after the posting amount and before the balance assertion if any. .SS Balance assertions .PP hledger supports Ledger-style balance assertions in journal files. These look like, for example, \f[C]= 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 .nf \f[C] 2013/1/1 a $1 =$1 b =$-1 2013/1/2 a $1 =$2 b $-1 =$-2 \f[R] .fi .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[C]-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, below). .SS Assertions and ordering .PP 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 included files .PP With included files, things are a little more complicated. Including preserves the ordering of postings and assertions. If you have multiple postings to an account on the same day, split across different files, and you also want to assert the account\[aq]s balance on the same day, you\[aq]ll have to put the assertion in the right file. .SS Assertions and multiple -f options .PP Balance assertions don\[aq]t work well across files specified with multiple -f options. Use include or concatenate the files instead. .SS Assertions and commodities .PP 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[C]== EXPECTEDBALANCE\f[R]). This asserts that there are no other unasserted commodities in the account (or, that their balance is 0). .IP .nf \f[C] 2013/1/1 a $1 a 1\[Eu] b $-1 c -1\[Eu] 2013/1/2 ; These assertions succeed a 0 = $1 a 0 = 1\[Eu] b 0 == $-1 c 0 == -1\[Eu] 2013/1/3 ; This assertion fails as \[aq]a\[aq] also contains 1\[Eu] a 0 == $1 \f[R] .fi .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 .nf \f[C] 2013/1/1 a:usd $1 a:euro 1\[Eu] b 2013/1/2 a 0 == 0 a:usd 0 == $1 a:euro 0 == 1\[Eu] \f[R] .fi .SS Assertions and prices .PP Balance assertions ignore transaction prices, and should normally be written without one: .IP .nf \f[C] 2019/1/1 (a) $1 \[at] \[Eu]1 = $1 \f[R] .fi .PP We do allow prices to be written there, however, and print shows them, even though 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 prices), and because balance \f[I]assignments\f[R] do use them (see below). .SS Assertions and subaccounts .PP The balance assertions above (\f[C]=\f[R] and \f[C]==\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[C]=*\f[R] or \f[C]==*\f[R], eg: .IP .nf \f[C] 2019/1/1 equity:opening balances checking:a 5 checking:b 5 checking 1 ==* 11 \f[R] .fi .SS Assertions and virtual postings .PP Balance assertions are checked against all postings, both real and virtual. They are not affected by the \f[C]--real/-R\f[R] flag or \f[C]real:\f[R] query. .SS Assertions and precision .PP 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 Balance assignments .PP 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 .nf \f[C] ; 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 \f[R] .fi .PP or when adjusting a balance to reality: .IP .nf \f[C] ; no cash left; update balance, record any untracked spending as a generic expense 2016/1/15 assets:cash = $0 expenses:misc \f[R] .fi .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). Note that using balance assignments makes your journal a little less explicit; to know the exact amount posted, you have to run hledger or do the calculations yourself, instead of just reading it. .SS Balance assignments and prices .PP A transaction price in a balance assignment will cause the calculated amount to have that price attached: .IP .nf \f[C] 2019/1/1 (a) = $1 \[at] \[Eu]2 \f[R] .fi .IP .nf \f[C] $ hledger print --explicit 2019-01-01 (a) $1 \[at] \[Eu]2 = $1 \[at] \[Eu]2 \f[R] .fi .SS Directives .PP A directive is a line in the journal beginning with a special keyword, that influences how the journal is processed. hledger\[aq]s directives are based on a subset of Ledger\[aq]s, but there are many differences (and also some differences between hledger versions). .PP Directives\[aq] behaviour and interactions can get a little bit complex, so here is a table summarising the directives and their effects, with links to more detailed docs. .PP .TS tab(@); lw(7.8n) lw(8.6n) lw(7.0n) lw(27.8n) lw(18.8n). T{ directive T}@T{ end directive T}@T{ subdirectives T}@T{ purpose T}@T{ can affect (as of 2018/06) T} _ T{ \f[C]account\f[R] T}@T{ T}@T{ any text T}@T{ document account names, declare account types & display order T}@T{ all entries in all files, before or after T} T{ \f[C]alias\f[R] T}@T{ \f[C]end aliases\f[R] T}@T{ T}@T{ rewrite account names T}@T{ following inline/included entries until end of current file or end directive T} T{ \f[C]apply account\f[R] T}@T{ \f[C]end apply account\f[R] T}@T{ T}@T{ prepend a common parent to account names T}@T{ following inline/included entries until end of current file or end directive T} T{ \f[C]comment\f[R] T}@T{ \f[C]end comment\f[R] T}@T{ T}@T{ ignore part of journal T}@T{ following inline/included entries until end of current file or end directive T} T{ \f[C]commodity\f[R] T}@T{ T}@T{ \f[C]format\f[R] T}@T{ declare a commodity and its number notation & display style T}@T{ number notation: following entries in that commodity in all files; display style: amounts of that commodity in reports T} T{ \f[C]D\f[R] T}@T{ T}@T{ T}@T{ declare a commodity to be used for commodityless amounts, and its number notation & display style T}@T{ default commodity: following commodityless entries until end of current file; number notation: following entries in that commodity until end of current file; display style: amounts of that commodity in reports T} T{ \f[C]include\f[R] T}@T{ T}@T{ T}@T{ include entries/directives from another file T}@T{ what the included directives affect T} T{ \f[C]P\f[R] T}@T{ T}@T{ T}@T{ declare a market price for a commodity T}@T{ amounts of that commodity in reports, when -V is used T} T{ \f[C]Y\f[R] T}@T{ T}@T{ T}@T{ declare a year for yearless dates T}@T{ following inline/included entries until end of current file T} T{ \f[C]=\f[R] T}@T{ T}@T{ T}@T{ declare an auto posting rule, adding postings to other transactions T}@T{ all entries in parent/current/child files (but not sibling files, see #1212) T} .TE .PP And some definitions: .PP .TS tab(@); lw(6.0n) lw(64.0n). T{ subdirective T}@T{ optional indented directive line immediately following a parent directive T} T{ number notation T}@T{ how to interpret numbers when parsing journal entries (the identity of the decimal separator character). (Currently each commodity can have its own notation, even in the same file.) T} T{ display style T}@T{ how to display amounts of a commodity in reports (symbol side and spacing, digit groups, decimal separator, decimal places) T} T{ directive scope T}@T{ which entries and (when there are multiple files) which files are affected by a directive T} .TE .PP As you can see, directives vary in which journal entries and files they affect, and whether they are focussed on input (parsing) or output (reports). Some directives have multiple effects. .SS Directives and multiple files .PP If you use multiple \f[C]-f\f[R]/\f[C]--file\f[R] options, or the \f[C]include\f[R] directive, hledger will process multiple input files. But note that directives which affect input (see above) typically last only until the end of the file in which they occur. .PP This may seem inconvenient, but it\[aq]s intentional; it makes reports stable and deterministic, independent of the order of input. Otherwise you could see different numbers if you happened to write -f options in a different order, or if you moved includes around while cleaning up your files. .PP It can be surprising though; for example, it means that \f[C]alias\f[R] directives do not affect parent or sibling files (see below). .SS Comment blocks .PP A line containing just \f[C]comment\f[R] starts a commented region of the file, and a line containing just \f[C]end comment\f[R] (or the end of the current file) ends it. See also comments. .SS Including other files .PP You can pull in the content of additional files by writing an include directive, like this: .IP .nf \f[C] include FILEPATH \f[R] .fi .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[C]include \[ti]/main.journal\f[R]. .PP The path may contain glob patterns to match multiple files, eg: \f[C]include *.journal\f[R]. .PP There is limited support for recursive wildcards: \f[C]**/\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[C]include */**/*.journal\f[R]. .PP The path may also be prefixed to force a specific file format, overriding the file extension (as described in hledger.1 -> Input files): \f[C]include timedot:\[ti]/notes/2020*.md\f[R]. .SS Default year .PP You can set a default year to be used for subsequent dates which don\[aq]t specify a year. This is a line beginning with \f[C]Y\f[R] followed by the year. Eg: .IP .nf \f[C] Y2009 ; set default year to 2009 12/15 ; equivalent to 2009/12/15 expenses 1 assets Y2010 ; 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 \f[R] .fi .SS Declaring commodities .PP The \f[C]commodity\f[R] directive has several functions: .IP "1." 3 It declares commodities which may be used in the journal. This is currently not enforced, but can serve as documentation. .IP "2." 3 It declares what decimal mark character (period or comma) to expect when parsing input - useful to disambiguate international number formats in your data. (Without this, hledger will parse both \f[C]1,000\f[R] and \f[C]1.000\f[R] as 1). .IP "3." 3 It declares the amount display style to use in output - decimal and digit group marks, number of decimal places, symbol placement etc. .PP You are likely to run into one of the problems solved by commodity directives, sooner or later, so it\[aq]s a good idea to just always use them to declare your commodities. .PP A commodity directive is just the word \f[C]commodity\f[R] followed by an amount. It may be written on a single line, like this: .IP .nf \f[C] ; commodity EXAMPLEAMOUNT ; display AAAA amounts with the symbol on the right, space-separated, ; using period as decimal point, with four decimal places, and ; separating thousands with comma. commodity 1,000.0000 AAAA \f[R] .fi .PP or on multiple lines, using the \[dq]format\[dq] subdirective. (In this case the commodity symbol appears twice and should be the same in both places.): .IP .nf \f[C] ; commodity SYMBOL ; format EXAMPLEAMOUNT ; 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 \f[R] .fi .PP The quantity of the amount does not matter; only the format is significant. The number must include a decimal mark: either a period or a comma, followed by 0 or more decimal digits. .PP Note hledger normally uses banker\[aq]s rounding, so 0.5 displayed with zero decimal digits is \[dq]0\[dq]. (More at Amount display style.) .SS Default commodity .PP The \f[C]D\f[R] directive sets a default commodity, to be used for amounts without a commodity symbol (ie, plain numbers). This commodity will be applied to all subsequent commodity-less amounts, or until the next \f[C]D\f[R] directive. (Note, this is different from Ledger\[aq]s \f[C]D\f[R].) .PP For compatibility/historical reasons, \f[C]D\f[R] also acts like a \f[C]commodity\f[R] directive, setting the commodity\[aq]s display style (for output) and decimal mark (for parsing input). As with \f[C]commodity\f[R], the amount must always be written with a decimal mark (period or comma). If both directives are used, \f[C]commodity\f[R]\[aq]s style takes precedence. .PP The syntax is \f[C]D AMOUNT\f[R]. Eg: .IP .nf \f[C] ; 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 \f[R] .fi .SS Declaring market prices .PP The \f[C]P\f[R] directive declares a market price, which is an exchange rate between two commodities on a certain date. (In Ledger, they are called \[dq]historical prices\[dq].) These are often obtained from a stock exchange, cryptocurrency exchange, or the foreign exchange market. .PP Here is the format: .IP .nf \f[C] P DATE COMMODITYA COMMODITYBAMOUNT \f[R] .fi .IP \[bu] 2 DATE is a simple date .IP \[bu] 2 COMMODITYA is the symbol of the commodity being priced .IP \[bu] 2 COMMODITYBAMOUNT is an amount (symbol and quantity) in a second commodity, giving the price in commodity B of one unit of commodity A. .PP These two market price directives say that one euro was worth 1.35 US dollars during 2009, and $1.40 from 2010 onward: .IP .nf \f[C] P 2009/1/1 \[Eu] $1.35 P 2010/1/1 \[Eu] $1.40 \f[R] .fi .PP The \f[C]-V\f[R], \f[C]-X\f[R] and \f[C]--value\f[R] flags use these market prices to show amount values in another commodity. See Valuation. .SS Declaring accounts .PP \f[C]account\f[R] directives can be used to pre-declare accounts. Though not required, they can provide several benefits: .IP \[bu] 2 They can document your intended chart of accounts, providing a reference. .IP \[bu] 2 They can store extra information about accounts (account numbers, notes, etc.) .IP \[bu] 2 They can help hledger know your accounts\[aq] types (asset, liability, equity, revenue, expense), useful for reports like balancesheet and incomestatement. .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 the add command, hledger-iadd, hledger-web, ledger-mode etc. .PP The simplest form is just the word \f[C]account\f[R] followed by a hledger-style account name, eg: .IP .nf \f[C] account assets:bank:checking \f[R] .fi .SS Account comments .PP Comments, beginning with a semicolon, can be added: .IP \[bu] 2 on the same line, \f[B]after two or more spaces\f[R] (because ; is allowed in account names) .IP \[bu] 2 on the next lines, indented .PP An example of both: .IP .nf \f[C] account assets:bank:checking ; same-line comment, note 2+ spaces before ; ; next-line comment ; another with tag, acctno:12345 (not used yet) \f[R] .fi .PP Same-line comments are not supported by Ledger, or hledger <1.13. .SS Account subdirectives .PP We also allow (and ignore) Ledger-style indented subdirectives, just for compatibility.: .IP .nf \f[C] account assets:bank:checking format blah blah ; <- subdirective, ignored \f[R] .fi .PP Here is the full syntax of account directives: .IP .nf \f[C] account ACCTNAME [ACCTTYPE] [;COMMENT] [;COMMENTS] [LEDGER-STYLE SUBDIRECTIVES, IGNORED] \f[R] .fi .SS Account types .PP hledger recognises five main types of account, corresponding to the account classes in the accounting equation: .PP \f[C]Asset\f[R], \f[C]Liability\f[R], \f[C]Equity\f[R], \f[C]Revenue\f[R], \f[C]Expense\f[R]. .PP These account types are important for controlling which accounts appear in the balancesheet, balancesheetequity, incomestatement reports (and probably for other things in future). .PP Additionally, we recognise the \f[C]Cash\f[R] type, which is also an \f[C]Asset\f[R], and which causes accounts to appear in the cashflow report. (\[dq]Cash\[dq] here means liquid assets, eg bank balances but typically not investments or receivables.) .SS Declaring account types .PP Generally, to make these reports work you should declare your top-level accounts and their types, using account directives with \f[C]type:\f[R] tags. .PP The tag\[aq]s value should be one of: \f[C]Asset\f[R], \f[C]Liability\f[R], \f[C]Equity\f[R], \f[C]Revenue\f[R], \f[C]Expense\f[R], \f[C]Cash\f[R], \f[C]A\f[R], \f[C]L\f[R], \f[C]E\f[R], \f[C]R\f[R], \f[C]X\f[R], \f[C]C\f[R] (all case insensitive). The type is inherited by all subaccounts except where they override it. Here\[aq]s a complete example: .IP .nf \f[C] account assets ; type: Asset account assets:bank ; type: Cash account assets:cash ; type: Cash account liabilities ; type: Liability account equity ; type: Equity account revenues ; type: Revenue account expenses ; type: Expense \f[R] .fi .SS Auto-detected account types .PP If you happen to use common english top-level account names, you may not need to declare account types, as they will be detected automatically using the following rules: .PP .TS tab(@); l l. T{ If name matches regular expression: T}@T{ account type is: T} _ T{ \f[C]\[ha]assets?(:|$)\f[R] T}@T{ \f[C]Asset\f[R] T} T{ \f[C]\[ha](debts?|liabilit(y|ies))(:|$)\f[R] T}@T{ \f[C]Liability\f[R] T} T{ \f[C]\[ha]equity(:|$)\f[R] T}@T{ \f[C]Equity\f[R] T} T{ \f[C]\[ha](income|revenue)s?(:|$)\f[R] T}@T{ \f[C]Revenue\f[R] T} T{ \f[C]\[ha]expenses?(:|$)\f[R] T}@T{ \f[C]Expense\f[R] T} .TE .PP .TS tab(@); lw(56.9n) lw(13.1n). T{ If account type is \f[C]Asset\f[R] and name does not contain regular expression: T}@T{ account type is: T} _ T{ \f[C](investment|receivable|:A/R|:fixed)\f[R] T}@T{ \f[C]Cash\f[R] T} .TE .PP Even so, explicit declarations may be a good idea, for clarity and predictability. .SS Interference from auto-detected account types .PP If you assign any account type, it\[aq]s a good idea to assign all of them, to prevent any confusion from mixing declared and auto-detected types. Although it\[aq]s unlikely to happen in real life, here\[aq]s an example: with the following journal, \f[C]balancesheetequity\f[R] shows \[dq]liabilities\[dq] in both Liabilities and Equity sections. Declaring another account as \f[C]type:Liability\f[R] would fix it: .IP .nf \f[C] account liabilities ; type:Equity 2020-01-01 assets 1 liabilities 1 equity -2 \f[R] .fi .SS Old account type syntax .PP In some hledger journals you might instead see this old syntax (the letters ALERX, separated from the account name by two or more spaces); this is deprecated and may be removed soon: .IP .nf \f[C] account assets A account liabilities L account equity E account revenues R account expenses X \f[R] .fi .SS Account display order .PP Account directives also set the order in which accounts are displayed, eg in reports, the hledger-ui accounts screen, and the hledger-web sidebar. By default accounts are listed in alphabetical order. But if you have these account directives in the journal: .IP .nf \f[C] account assets account liabilities account equity account revenues account expenses \f[R] .fi .PP you\[aq]ll see those accounts displayed in declaration order, not alphabetically: .IP .nf \f[C] $ hledger accounts -1 assets liabilities equity revenues expenses \f[R] .fi .PP Undeclared accounts, if any, are displayed last, in alphabetical order. .PP Note that 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 .nf \f[C] account other:zoo \f[R] .fi .PP would influence the position of \f[C]zoo\f[R] among \f[C]other\f[R]\[aq]s subaccounts, but not the position of \f[C]other\f[R] among the top-level accounts. This means: .IP \[bu] 2 you will sometimes declare parent accounts (eg \f[C]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[C]x:y\f[R] in between \f[C]a:b\f[R] and \f[C]a:c\f[R]). .SS Rewriting accounts .PP 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 or combining two accounts into one .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 See also Rewrite account names. .SS Basic aliases .PP To set an account alias, use the \f[C]alias\f[R] directive in your journal file. This affects all subsequent journal entries in the current file or its included files. The spaces around the = are optional: .IP .nf \f[C] alias OLD = NEW \f[R] .fi .PP Or, you can use the \f[C]--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 .nf \f[C] 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] \f[R] .fi .SS Regex aliases .PP There is also a more powerful variant that uses a regular expression, indicated by the forward slashes: .IP .nf \f[C] alias /REGEX/ = REPLACEMENT \f[R] .fi .PP or \f[C]--alias \[aq]/REGEX/=REPLACEMENT\[aq]\f[R]. .PP REGEX is a case-insensitive regular expression. Anywhere it matches inside an account name, the matched part will be replaced by REPLACEMENT. If REGEX contains parenthesised match groups, these can be referenced by the usual numeric backreferences in REPLACEMENT. Eg: .IP .nf \f[C] 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] \f[R] .fi .PP Also note that 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 .PP 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[C]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[C]--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[C]--debug=6\f[R] to the command line will show which aliases are being applied when. .SS Aliases and multiple files .PP As explained at Directives and multiple files, \f[C]alias\f[R] directives do not affect parent or sibling files. Eg in this command, .IP .nf \f[C] hledger -f a.aliases -f b.journal \f[R] .fi .PP account aliases defined in a.aliases will not affect b.journal. Including the aliases doesn\[aq]t work either: .IP .nf \f[C] include a.aliases 2020-01-01 ; not affected by a.aliases foo 1 bar \f[R] .fi .PP This means that account aliases should usually be declared at the start of your top-most file, like this: .IP .nf \f[C] alias foo=Foo alias bar=Bar 2020-01-01 ; affected by aliases above foo 1 bar include c.journal ; also affected \f[R] .fi .SS \f[C]end aliases\f[R] .PP You can clear (forget) all currently defined aliases with the \f[C]end aliases\f[R] directive: .IP .nf \f[C] end aliases \f[R] .fi .SS Default parent account .PP You can specify a parent account which will be prepended to all accounts within a section of the journal. Use the \f[C]apply account\f[R] and \f[C]end apply account\f[R] directives like so: .IP .nf \f[C] apply account home 2010/1/1 food $10 cash end apply account \f[R] .fi .PP which is equivalent to: .IP .nf \f[C] 2010/01/01 home:food $10 home:cash $-10 \f[R] .fi .PP If \f[C]end apply account\f[R] is omitted, the effect lasts to the end of the file. Included files are also affected, eg: .IP .nf \f[C] apply account business include biz.journal end apply account apply account personal include personal.journal \f[R] .fi .PP Prior to hledger 1.0, legacy \f[C]account\f[R] and \f[C]end\f[R] spellings were also supported. .PP A default parent account also affects account directives. It does not affect account names being entered via hledger add or hledger-web. If account aliases are present, they are applied after the default parent account. .SS Periodic transactions .PP Periodic transaction rules describe transactions that recur. They allow hledger to generate temporary future transactions to help with forecasting, so you don\[aq]t have to write out each one in the journal, and it\[aq]s easy to try out different forecasts. Secondly, they are also used to define the budgets shown in budget reports. .PP Periodic transactions can be a little tricky, so before you use them, read this whole section - or at least these 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[C]hledger print --forecast tag:generated\f[R] or \f[C]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[C]weekly from DATE\f[R], DATE must be a monday. \f[C]\[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[C]\[ti] every 10th day of month from 2020/01\f[R], which is equivalent to \f[C]\[ti] every 10th day of month from 2020/01/01\f[R], will be adjusted to start on 2019/12/10. .SS Periodic rule syntax .PP A periodic transaction rule looks like a normal journal entry, with the date replaced by a tilde (\f[C]\[ti]\f[R]) followed by a period expression (mnemonic: \f[C]\[ti]\f[R] looks like a recurring sine wave.): .IP .nf \f[C] \[ti] monthly expenses:rent $2000 assets:bank:checking \f[R] .fi .PP There is an additional constraint on the period expression: the start date must fall on a natural boundary of the interval. Eg \f[C]monthly from 2018/1/1\f[R] is valid, but \f[C]monthly from 2018/1/15\f[R] is not. .PP Partial or relative dates (M/D, D, tomorrow, last week) in the period expression can work (useful or not). They will be relative to today\[aq]s date, unless a Y default year directive is in effect, in which case they will be relative to Y/1/1. .SS Two spaces between period expression and description! .PP 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 .nf \f[C] ; 2 or more spaces needed here, so the period is not understood as \[dq]every 2 months in 2020\[dq] ; || ; vv \[ti] every 2 months in 2020, we will review assets:bank:checking $1500 income:acme inc \f[R] .fi .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 Forecasting with periodic transactions .PP The \f[C]--forecast\f[R] flag activates any periodic transaction rules in the journal. They will generate temporary recurring transactions, which are not saved in the journal, but will appear in all reports (eg print). This can be useful for estimating balances into the future, or experimenting with different scenarios. Or, it can be used as a data entry aid: describe recurring transactions, and every so often copy the output of \f[C]print --forecast\f[R] into the journal. .PP These transactions will have an extra tag indicating which periodic rule generated them: \f[C]generated-transaction:\[ti] PERIODICEXPR\f[R]. And a similar, hidden tag (beginning with an underscore) which, because it\[aq]s never displayed by print, can be used to match transactions generated \[dq]just now\[dq]: \f[C]_generated-transaction:\[ti] PERIODICEXPR\f[R]. .PP Periodic transactions are generated within some forecast period. By default, this .IP \[bu] 2 begins on the later of .RS 2 .IP \[bu] 2 the report start date if specified with -b/-p/date: .IP \[bu] 2 the day after the latest normal (non-periodic) transaction in the journal, or today if there are no normal transactions. .RE .IP \[bu] 2 ends on the report end date if specified with -e/-p/date:, or 6 months (180 days) from today. .PP This means that periodic transactions will begin only after the latest recorded transaction. And a recorded transaction dated in the future can prevent generation of periodic transactions. (You can avoid that by writing the future transaction as a one-time periodic rule instead - put tilde before the date, eg \f[C]\[ti] YYYY-MM-DD ...\f[R]). .PP Or, you can set your own arbitrary \[dq]forecast period\[dq], which can overlap recorded transactions, and need not be in the future, by providing an option argument, like \f[C]--forecast=PERIODEXPR\f[R]. Note the equals sign is required, a space won\[aq]t work. PERIODEXPR is a period expression, which can specify the start date, end date, or both, like in a \f[C]date:\f[R] query. (See also hledger.1 -> Report start & end date). Some examples: \f[C]--forecast=202001-202004\f[R], \f[C]--forecast=jan-\f[R], \f[C]--forecast=2020\f[R]. .SS Budgeting with periodic transactions .PP With the \f[C]--budget\f[R] flag, currently supported by the balance command, each periodic transaction rule declares recurring budget goals for the specified accounts. Eg the first example above declares a goal of spending $2000 on rent (and also, a goal of depositing $2000 into checking) every month. Goals and actual performance can then be compared in budget reports. .PP For more details, see: balance: Budget report and Budgeting and Forecasting. .PP .SS Auto postings .PP \[dq]Automated postings\[dq] or \[dq]auto postings\[dq] are extra postings which get added automatically to transactions which match certain queries, defined by \[dq]auto posting rules\[dq], when you use the \f[C]--auto\f[R] flag. .PP An auto posting rule looks a bit like a transaction: .IP .nf \f[C] = QUERY ACCOUNT AMOUNT ... ACCOUNT [AMOUNT] \f[R] .fi .PP except the first line is an equals sign (mnemonic: \f[C]=\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[C]$2\f[R]. This will be used as-is. .IP \[bu] 2 a number, eg \f[C]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[C]*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[C]*$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 .nf \f[C] = expenses:groceries \[aq]expenses:dining out\[aq] (budget:funds:dining out) *-1 \f[R] .fi .PP Some examples: .IP .nf \f[C] ; 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 \f[R] .fi .IP .nf \f[C] $ 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 \f[R] .fi .SS Auto postings and multiple files .PP 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[C]-f\f[R]/\f[C]--file\f[R] are used - see #1212). .SS Auto postings and dates .PP 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 .PP 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. .SS Auto posting tags .PP Automated postings will have some extra tags: .IP \[bu] 2 \f[C]generated-posting:= QUERY\f[R] - shows this was generated by an auto posting rule, and the query .IP \[bu] 2 \f[C]_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[C]modified:\f[R] - this transaction was modified .IP \[bu] 2 \f[C]_modified:\f[R] - a hidden tag not appearing in the comment; this transaction was modified \[dq]just now\[dq]. .SH "REPORTING BUGS" Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) .SH AUTHORS Simon Michael and contributors .SH COPYRIGHT Copyright (C) 2007-2019 Simon Michael. .br Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5), ledger(1) http://hledger.org hledger-1.19.1/embeddedfiles/hledger_journal.txt0000644000000000000000000020506013725533425020100 0ustar0000000000000000 hledger_journal(5) hledger User Manuals hledger_journal(5) NAME Journal - hledger's default file format, representing a General Journal DESCRIPTION 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 a compatible subset, mostly, of ledger's journal format, so hledger can work with compatible ledger journal files as well. It's safe, and encouraged, to run both hledger and ledger on the same journal file, eg to validate the results you're get- ting. 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. FILE FORMAT Here's a description of each part of the file format (and hledger's data model). These are mostly in the order you'll use them, but in some cases related concepts have been grouped together for easy refer- ence, or linked before they are introduced, so feel free to skip over anything that looks unnecessary right now. 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 default year 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.) Secondary dates Real-life transactions sometimes involve more than one date - eg the date you write a cheque, and the date it clears in your bank. When you want to model this, for more accurate daily balances, you can specify individual posting dates. Or, you can use the older secondary date feature (Ledger calls it aux- iliary date or effective date). Note: we support this for compatibil- ity, but I usually recommend avoiding this feature; posting dates are almost always clearer and simpler. 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", as shown here: 2010/2/23=2/19 movie ticket expenses:cinema $10 assets:checking $ hledger register checking 2010-02-23 movie ticket assets:checking $-10 $-10 $ hledger register checking --date2 2010-02-19 movie ticket assets:checking $-10 $-10 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. You can set the secondary date similarly, with date2:DATE2. The date: or date2: tags must have a valid simple date value if they are present, eg a date: tag with no value is not allowed. Ledger's earlier, more compact bracketed date syntax is also supported: [DATE], [DATE=DATE2] or [=DATE2]. 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. 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. 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. Comments Lines in the journal beginning with a semicolon (;) or hash (#) or star (*) are comments, and will be ignored. (Star comments cause org-mode nodes to be ignored, allowing emacs users to fold and navigate their journals with org-mode or orgstruct-mode.) You can attach comments to a transaction by writing them after the de- scription and/or indented on the following lines (before the postings). Similarly, you can attach comments to an individual posting by writing them after the amount and/or indented on the following lines. Transac- tion and posting comments must begin with a semicolon (;). Some examples: # a file comment ; another file comment * also a file comment, useful in org/orgstruct mode comment A multiline file comment, which continues until a line containing just "end comment" (or end of file). end comment 2012/5/14 something ; a transaction comment ; the transaction comment, continued posting1 1 ; a comment for posting 1 posting2 ; a comment for posting 2 ; another comment line for posting 2 ; a file comment (because not indented) You can also comment larger regions of a file using comment and end comment directives. Tags Tags are a way to add extra labels or labelled data to postings and transactions, which you can then search or pivot on. A simple tag is a word (which may contain hyphens) followed by a full colon, written inside a transaction or posting comment line: 2017/1/16 bought groceries ; sometag: Tags can have a value, which is the text after the colon, up to the next comma or end of line, with leading/trailing whitespace removed: expenses:food $10 ; a-posting-tag: the tag value Note this means hledger's tag values can not contain commas or new- lines. Ending at commas means you can write multiple short tags on one line, comma separated: assets:checking ; a comment containing tag1:, tag2: some value ... Here, o "a comment containing" is just comment text, not a tag o "tag1" is a tag with no value o "tag2" is another tag, whose value is "some value ..." Tags in a transaction comment affect the transaction and all of its postings, while tags in a posting comment affect only that posting. For example, the following transaction has three tags (A, TAG2, third- tag) and the posting has four (those plus posting-tag): 1/1 a transaction ; A:, TAG2: ; third-tag: a third transaction tag, <- with a value (a) $1 ; posting-tag: Tags are like Ledger's metadata feature, except hledger's tag values are simple strings. 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 spa- ces. But if you accidentally leave only one space (or tab) before the amount, the amount will be considered part of the account name. Virtual postings A posting with a parenthesised account name is called a virtual posting or unbalanced posting, which means it is exempt from the usual rule that a transaction's postings must balance add up to zero. This is not part of double entry accounting, so you might choose to avoid this feature. Or you can use it sparingly for certain special cases where it can be convenient. Eg, you could set opening balances without using a balancing equity account: 1/1 opening balances (assets:checking) $1000 (assets:savings) $2000 A posting with a bracketed account name is called a balanced virtual posting. The balanced virtual postings in a transaction must add up to zero (separately from other postings). Eg: 1/1 buy food with cash, update budget envelope subaccounts, & something else assets:cash $-10 ; <- these balance expenses:food $7 ; <- expenses:food $3 ; <- [assets:checking:budget:food] $-10 ; <- and these balance [assets:checking:available] $10 ; <- (something:else) $5 ; <- not required to balance Ordinary non-parenthesised, non-bracketed postings are called real postings. You can exclude virtual postings from reports with the -R/--real flag or real:1 query. Account names Account names typically have several parts separated by a full colon, from which hledger derives a hierarchical chart of accounts. They can be anything you like, but in finance there are traditionally five top- level accounts: assets, liabilities, income, expenses, and equity. Account names may contain single spaces, eg: assets:accounts receiv- able. Because of this, they must always be followed by two or more spaces (or newline). Account names can be aliased. 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 or commodity name (the "commodity"). This is a symbol, word, or phrase, to the left or right of the quantity, with or without a separating space: $1 4000 AAPL If the commodity name contains spaces, numbers, or punctuation, it must be enclosed in double quotes: 3 "no. 42 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 A decimal mark can be written as a period or a comma: 1.23 1,23456780000009 Digit group marks 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 Note, a number containing a single group mark and no decimal mark is ambiguous. Are these group marks or decimal marks ? 1,000 1.000 hledger will treat them both as decimal marks by default (cf #793). If you use digit group marks, to prevent confusion and undetected typos we recommend you write commodity directives at the top of the file to ex- plicitly declare the decimal mark (and optionally a digit group mark). Note, these formats ("amount styles") are specific to each commodity, so if your data uses multiple formats, hledger can handle it: commodity $1,000.00 commodity EUR 1.000,00 commodity INR 9,99,99,999.00 commodity 1 000 000.9455 Amount display style For each commodity, hledger chooses a consistent format to use when displaying amounts. (Except price amounts, which are always displayed as written). The display style is chosen as follows: o If there is a commodity directive (or default commodity directive) for the commodity, that format is used (see examples above). o Otherwise the format of the first posting amount in that commodity seen in the journal is used. But the number of decimal places ("pre- cision") will be the maximum from all posting amounts in that commod- ity. o Or if there are no such amounts in the journal, a default format is used (like $1000.00). Transaction prices don't affect the amount display style directly, but occasionally they can do so indirectly (eg when an posting's amount is inferred using a transaction price). If you find this causing prob- lems, use a commodity directive to fix the display style. In summary: amounts will be displayed much as they appear in your jour- nal, with the max observed number of decimal places. If you want to see fewer decimal places in reports, use a commodity directive to over- ride that. hledger uses banker's rounding: it rounds to the nearest even number, eg 0.5 displayed with zero decimal places is "0"). (Note, prior to hledger 1.17.1 this could vary if hledger happened to be built with an old version of Decimal (<0.5.1); since 1.17.1 it's guaranteed.) Transaction prices Within a transaction, you can note an amount's price in another commod- ity. This can be used to document the cost (in a purchase) or selling price (in a sale). For example, transaction prices are useful to record purchases of a foreign currency. Note transaction prices are fixed at the time of the transaction, and do not change over time. See also market prices, which represent prevailing exchange rates on a cer- tain date. There are several ways to record a transaction price: 1. Write the price per unit, as @ UNITPRICE after the amount: 2009/1/1 assets:euros EUR100 @ $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 EUR100 @@ $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: 2009/1/1 assets:euros EUR100 ; one hundred euros purchased assets:dollars $-135 ; for $135 4. Like 1, but the @ is parenthesised, i.e. (@); this is for compati- bility with Ledger journals (Virtual posting costs), and is equiva- lent to 1 in hledger. 5. Like 2, but as in 4 the @@ is parenthesised, i.e. (@@); in hledger, this is equivalent to 2. Use the -B/--cost flag to convert amounts to their transaction price's commodity, if any. (mnemonic: "B" is from "cost Basis", as in Ledger). Eg here is how -B affects the balance report for the example above: $ hledger bal -N --flat $-135 assets:dollars EUR100 assets:euros $ hledger bal -N --flat -B $-135 assets:dollars $135 assets:euros # <- the euros' cost Note -B is sensitive to the order of postings when a transaction price is inferred: the inferred price will be in the commodity of the last amount. So if example 3's postings are reversed, while the transaction is equivalent, -B shows something different: 2009/1/1 assets:dollars $-135 ; 135 dollars sold assets:euros EUR100 ; for 100 euros $ hledger bal -N --flat -B EUR-100 assets:dollars # <- the dollars' selling price EUR100 assets:euros Lot prices and lot dates Ledger allows another kind of price, lot price (four variants: {UNIT- PRICE}, {{TOTALPRICE}}, {=FIXEDUNITPRICE}, {{=FIXEDTOTALPRICE}}), and/or a lot date ([DATE]) to be specified. These are normally used to select a lot when selling investments. hledger will parse these, for compatibility with Ledger journals, but currently ignores them. A transaction price, lot price and/or lot date may appear in any order, after the posting amount and before the balance assertion if any. 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, 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 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. Assertions and included files With included files, things are a little more complicated. Including preserves the ordering of postings and assertions. If you have multi- ple postings to an account on the same day, split across different files, and you also want to assert the account's balance on the same day, you'll have to put the assertion in the right file. Assertions and multiple -f options Balance assertions don't work well across files specified with multiple -f options. Use include or concatenate the files instead. 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 unasserted commodities in the account (or, that their balance is 0). 2013/1/1 a $1 a 1EUR b $-1 c -1EUR 2013/1/2 ; These assertions succeed a 0 = $1 a 0 = 1EUR b 0 == $-1 c 0 == -1EUR 2013/1/3 ; This assertion fails as 'a' also contains 1EUR 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 1EUR b 2013/1/2 a 0 == 0 a:usd 0 == $1 a:euro 0 == 1EUR Assertions and prices Balance assertions ignore transaction prices, and should normally be written without one: 2019/1/1 (a) $1 @ EUR1 = $1 We do allow prices to be written there, however, and print shows them, even though 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 prices), and because balance assign- ments do use them (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 are checked against all postings, both real and vir- tual. They are not affected by the --real/-R flag or real: query. 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. 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). Note that using balance assignments makes your journal a little less explicit; to know the exact amount posted, you have to run hledger or do the calculations yourself, instead of just reading it. Balance assignments and prices A transaction price in a balance assignment will cause the calculated amount to have that price attached: 2019/1/1 (a) = $1 @ EUR2 $ hledger print --explicit 2019-01-01 (a) $1 @ EUR2 = $1 @ EUR2 Directives A directive is a line in the journal beginning with a special keyword, that influences how the journal is processed. hledger's directives are based on a subset of Ledger's, but there are many differences (and also some differences between hledger versions). Directives' behaviour and interactions can get a little bit complex, so here is a table summarising the directives and their effects, with links to more detailed docs. direc- end di- subdi- purpose can affect (as of tive rective rec- 2018/06) tives ------------------------------------------------------------------------------------ account any document account names, de- all entries in all text clare account types & dis- files, before or play order after alias end rewrite account names following in- aliases line/included en- tries until end of current file or end directive apply end apply prepend a common parent to following in- account account account names line/included en- tries until end of current file or end directive comment end com- ignore part of journal following in- ment line/included en- tries until end of current file or end directive commod- format declare a commodity and its number notation: ity number notation & display following entries style in that commodity in all files; dis- play style: amounts of that commodity in reports D declare a commodity to be default commodity: used for commodityless following commod- amounts, and its number no- ityless entries un- tation & display style til end of current file; number nota- tion: following en- tries in that com- modity until end of current file; dis- play style: amounts of that commodity in reports include include entries/directives what the included from another file directives affect P declare a market price for a amounts of that commodity commodity in re- ports, when -V is used Y declare a year for yearless following in- dates line/included en- tries until end of current file = declare an auto posting all entries in par- rule, adding postings to ent/current/child other transactions files (but not sib- ling files, see #1212) And some definitions: subdi- optional indented directive line immediately following a parent rec- directive tive number how to interpret numbers when parsing journal entries (the iden- nota- tity of the decimal separator character). (Currently each com- tion modity can have its own notation, even in the same file.) dis- how to display amounts of a commodity in reports (symbol side play and spacing, digit groups, decimal separator, decimal places) style direc- which entries and (when there are multiple files) which files tive are affected by a directive scope As you can see, directives vary in which journal entries and files they affect, and whether they are focussed on input (parsing) or output (re- ports). Some directives have multiple effects. Directives and multiple files If you use multiple -f/--file options, or the include directive, hledger will process multiple input files. But note that directives which affect input (see above) typically last only until the end of the file in which they occur. This may seem inconvenient, but it's intentional; it makes reports sta- ble and deterministic, independent of the order of input. Otherwise you could see different numbers if you happened to write -f options in a different order, or if you moved includes around while cleaning up your files. It can be surprising though; for example, it means that alias direc- tives do not affect parent or sibling files (see below). Comment blocks A line containing just comment starts a commented region of the file, and a line containing just end comment (or the end of the current file) ends it. See also comments. Including other files 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 hledger.1 -> Input files): in- clude timedot:~/notes/2020*.md. Default year You can set a default year to be used for subsequent dates which don't specify a year. This is a line beginning with Y followed by the year. Eg: Y2009 ; set default year to 2009 12/15 ; equivalent to 2009/12/15 expenses 1 assets Y2010 ; 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 Declaring commodities The commodity directive has several functions: 1. It declares commodities which may be used in the journal. This is currently not enforced, but can serve as documentation. 2. It declares what decimal mark character (period or comma) to expect when parsing input - useful to disambiguate international number formats in your data. (Without this, hledger will parse both 1,000 and 1.000 as 1). 3. It declares the amount display style to use in output - decimal and digit group marks, number of decimal places, symbol placement etc. You are likely to run into one of the problems solved by commodity di- rectives, sooner or later, so it's a good idea to just always use them to declare your commodities. A commodity directive is just the word commodity followed by an amount. It may be written on a single line, like this: ; commodity EXAMPLEAMOUNT ; display AAAA amounts with the symbol on the right, space-separated, ; using period as decimal point, with four decimal places, and ; separating thousands with comma. commodity 1,000.0000 AAAA or on multiple lines, using the "format" subdirective. (In this case the commodity symbol appears twice and should be the same in both places.): ; commodity SYMBOL ; format EXAMPLEAMOUNT ; 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 The quantity of the amount does not matter; only the format is signifi- cant. The number must include a decimal mark: either a period or a comma, followed by 0 or more decimal digits. Note hledger normally uses banker's rounding, so 0.5 displayed with zero decimal digits is "0". (More at Amount display style.) Default commodity The D directive sets a default commodity, to be used for amounts with- out a commodity symbol (ie, plain numbers). This commodity will be ap- plied to all subsequent commodity-less amounts, or until the next D di- rective. (Note, this is different from Ledger's D.) For compatibility/historical reasons, D also acts like a commodity di- rective, setting the commodity's display style (for output) and decimal mark (for parsing input). As with commodity, the amount must always be written with a decimal mark (period or comma). If both directives are used, commodity's style takes precedence. The syntax is D AMOUNT. 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 Declaring market prices The P directive declares a market price, which is an exchange rate be- tween two commodities on a certain date. (In Ledger, they are called "historical prices".) These are often obtained from a stock exchange, cryptocurrency exchange, or the foreign exchange market. Here is the format: P DATE COMMODITYA COMMODITYBAMOUNT o DATE is a simple date o COMMODITYA is the symbol of the commodity being priced o COMMODITYBAMOUNT is an amount (symbol and quantity) in a second com- modity, giving the price in commodity B of one unit of commodity A. These two market price directives say that one euro was worth 1.35 US dollars during 2009, and $1.40 from 2010 onward: P 2009/1/1 EUR $1.35 P 2010/1/1 EUR $1.40 The -V, -X and --value flags use these market prices to show amount values in another commodity. See Valuation. Declaring accounts account directives can be used to pre-declare accounts. Though not re- quired, they can provide several benefits: o They can document your intended chart of accounts, providing a refer- ence. o They can store extra information about accounts (account numbers, notes, etc.) o They can help hledger know your accounts' types (asset, liability, equity, revenue, expense), useful for reports like balancesheet and incomestatement. 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 the add command, hledger- iadd, hledger-web, ledger-mode etc. The simplest form is just the word account followed by a hledger-style account name, eg: account assets:bank:checking Account comments Comments, beginning with a semicolon, can be added: o on the same line, after two or more spaces (because ; is allowed in account names) o on the next lines, indented An example of both: account assets:bank:checking ; same-line comment, note 2+ spaces before ; ; next-line comment ; another with tag, acctno:12345 (not used yet) Same-line comments are not supported by Ledger, or hledger <1.13. Account subdirectives We also allow (and ignore) Ledger-style indented subdirectives, just for compatibility.: account assets:bank:checking format blah blah ; <- subdirective, ignored Here is the full syntax of account directives: account ACCTNAME [ACCTTYPE] [;COMMENT] [;COMMENTS] [LEDGER-STYLE SUBDIRECTIVES, IGNORED] Account types hledger recognises five main types of account, corresponding to the ac- count classes in the accounting equation: Asset, Liability, Equity, Revenue, Expense. These account types are important for controlling which accounts appear in the balancesheet, balancesheetequity, incomestatement reports (and probably for other things in future). Additionally, we recognise the Cash type, which is also an Asset, and which causes accounts to appear in the cashflow report. ("Cash" here means liquid assets, eg bank balances but typically not investments or receivables.) Declaring account types Generally, to make these reports work you should declare your top-level accounts and their types, using account directives with type: tags. The tag's value should be one of: Asset, Liability, Equity, Revenue, Expense, Cash, A, L, E, R, X, C (all case insensitive). The type is inherited by all subaccounts except where they override it. Here's a complete example: account assets ; type: Asset account assets:bank ; type: Cash account assets:cash ; type: Cash account liabilities ; type: Liability account equity ; type: Equity account revenues ; type: Revenue account expenses ; type: Expense Auto-detected account types If you happen to use common english top-level account names, you may not need to declare account types, as they will be detected automati- cally using the following rules: If name matches regular account type is: expression: ---------------------------------------------- ^assets?(:|$) Asset ^(debts?|lia- Liability bilit(y|ies))(:|$) ^equity(:|$) Equity ^(income|revenue)s?(:|$) Revenue ^expenses?(:|$) Expense If account type is Asset and name does not contain regu- account type lar expression: is: -------------------------------------------------------------------------- (investment|receivable|:A/R|:fixed) Cash Even so, explicit declarations may be a good idea, for clarity and pre- dictability. Interference from auto-detected account types If you assign any account type, it's a good idea to assign all of them, to prevent any confusion from mixing declared and auto-detected types. Although it's unlikely to happen in real life, here's an example: with the following journal, balancesheetequity shows "liabilities" in both Liabilities and Equity sections. Declaring another account as type:Li- ability would fix it: account liabilities ; type:Equity 2020-01-01 assets 1 liabilities 1 equity -2 Old account type syntax In some hledger journals you might instead see this old syntax (the letters ALERX, separated from the account name by two or more spaces); this is deprecated and may be removed soon: account assets A account liabilities L account equity E account revenues R account expenses X Account display order Account directives also set the order in which accounts are displayed, eg in reports, the hledger-ui accounts screen, and the hledger-web sidebar. By default accounts are listed in alphabetical order. But if you have these account directives in the journal: account assets account liabilities account equity account revenues account expenses you'll see those accounts displayed in declaration order, not alphabet- ically: $ hledger accounts -1 assets liabilities equity revenues expenses Undeclared accounts, if any, are displayed last, in alphabetical order. Note that 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). Rewriting accounts 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 or combining two accounts into one 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. 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. 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 the forward slashes: alias /REGEX/ = REPLACEMENT or --alias '/REGEX/=REPLACEMENT'. REGEX is a case-insensitive regular expression. Anywhere it matches inside an account name, the matched part will be replaced by REPLACE- MENT. If REGEX contains parenthesised match groups, these can be ref- erenced by the usual numeric backreferences in REPLACEMENT. Eg: alias /^(.+):bank:([^:]+):(.*)/ = \1:\2 \3 ; rewrites "assets:bank:wells fargo:checking" to "assets:wells fargo checking" Also note that REPLACEMENT continues to the end of line (or on command line, to end of option argument), so it can contain trailing white- space. 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 2020-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 2020-01-01 ; affected by aliases above foo 1 bar include c.journal ; also affected end aliases You can clear (forget) all currently defined aliases with the end aliases directive: end aliases Default parent account You can specify a parent account which will be prepended to all ac- counts within a section of the journal. Use the apply account and end apply account directives like so: apply account home 2010/1/1 food $10 cash end apply account which is equivalent to: 2010/01/01 home:food $10 home:cash $-10 If end apply account is omitted, the effect lasts to the end of the file. Included files are also affected, eg: apply account business include biz.journal end apply account apply account personal include personal.journal Prior to hledger 1.0, legacy account and end spellings were also sup- ported. A default parent account also affects account directives. It does not affect account names being entered via hledger add or hledger-web. If account aliases are present, they are applied after the default parent account. Periodic transactions Periodic transaction rules describe transactions that recur. They al- low hledger to generate temporary future transactions to help with forecasting, so you don't have to write out each one in the journal, and it's easy to try out different forecasts. Secondly, they are also used to define the budgets shown in budget reports. Periodic transactions can be a little tricky, so before you use them, read this whole section - or at least these 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 2020/01, which is equivalent to ~ every 10th day of month from 2020/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.): ~ monthly expenses:rent $2000 assets:bank:checking There is an additional constraint on the period expression: the start date must fall on a natural boundary of the interval. Eg monthly from 2018/1/1 is valid, but monthly from 2018/1/15 is not. Partial or relative dates (M/D, D, tomorrow, last week) in the period expression can work (useful or not). They will be relative to today's date, unless a Y default year directive is in effect, in which case they will be relative to Y/1/1. 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 2020" ; || ; vv ~ every 2 months in 2020, 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. Forecasting with periodic transactions The --forecast flag activates any periodic transaction rules in the journal. They will generate temporary recurring transactions, which are not saved in the journal, but will appear in all reports (eg print). This can be useful for estimating balances into the future, or experimenting with different scenarios. Or, it can be used as a data entry aid: describe recurring transactions, and every so often copy the output of print --forecast into the journal. These transactions will have an extra tag indicating which periodic rule generated them: generated-transaction:~ PERIODICEXPR. And a simi- lar, hidden tag (beginning with an underscore) which, because it's never displayed by print, can be used to match transactions generated "just now": _generated-transaction:~ PERIODICEXPR. Periodic transactions are generated within some forecast period. By default, this o begins on the later of o the report start date if specified with -b/-p/date: o the day after the latest normal (non-periodic) transaction in the journal, or today if there are no normal transactions. o ends on the report end date if specified with -e/-p/date:, or 6 months (180 days) from today. This means that periodic transactions will begin only after the latest recorded transaction. And a recorded transaction dated in the future can prevent generation of periodic transactions. (You can avoid that by writing the future transaction as a one-time periodic rule instead - put tilde before the date, eg ~ YYYY-MM-DD ...). Or, you can set your own arbitrary "forecast period", which can overlap recorded transactions, and need not be in the future, by providing an option argument, like --forecast=PERIODEXPR. Note the equals sign is required, a space won't work. PERIODEXPR is a period expression, which can specify the start date, end date, or both, like in a date: query. (See also hledger.1 -> Report start & end date). Some examples: --forecast=202001-202004, --forecast=jan-, --forecast=2020. Budgeting with periodic transactions With the --budget flag, currently supported by the balance command, each periodic transaction rule declares recurring budget goals for the specified accounts. Eg the first example above declares a goal of spending $2000 on rent (and also, a goal of depositing $2000 into checking) every month. Goals and actual performance can then be com- pared in budget reports. For more details, see: balance: Budget report and Budgeting and Fore- casting. Auto postings "Automated postings" or "auto postings" are extra postings which get added automatically to transactions which match certain queries, de- fined by "auto posting rules", when you use the --auto flag. 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. 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". REPORTING BUGS Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) AUTHORS Simon Michael and contributors COPYRIGHT Copyright (C) 2007-2019 Simon Michael. Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), hledger-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_time- dot(5), ledger(1) http://hledger.org hledger 1.18.99 September 2020 hledger_journal(5) hledger-1.19.1/embeddedfiles/hledger_journal.info0000644000000000000000000021617613725533425020226 0ustar0000000000000000This is hledger_journal.info, produced by makeinfo version 6.7 from stdin.  File: hledger_journal.info, Node: Top, Up: (dir) hledger_journal(5) hledger 1.18.99 ********************************** Journal - hledger's default file format, representing a General Journal 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 a compatible subset, mostly, of ledger's journal format, so hledger can work with compatible ledger journal files as well. It's safe, and encouraged, to run both hledger and ledger on the same journal file, eg to validate the results you're getting. 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). These are mostly in the order you'll use them, but in some cases related concepts have been grouped together for easy reference, or linked before they are introduced, so feel free to skip over anything that looks unnecessary right now. * Menu: * Transactions::  File: hledger_journal.info, Node: Transactions, Up: Top 1 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 * Menu: * Dates:: * Status:: * Description:: * Comments:: * Tags:: * Postings:: * Account names:: * Amounts:: * Transaction prices:: * Lot prices and lot dates:: * Balance assertions:: * Balance assignments:: * Directives:: * Periodic transactions:: * Auto postings::  File: hledger_journal.info, Node: Dates, Next: Status, Up: Transactions 1.1 Dates ========= * Menu: * Simple dates:: * Secondary dates:: * Posting dates::  File: hledger_journal.info, Node: Simple dates, Next: Secondary dates, Up: Dates 1.1.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 default year 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_journal.info, Node: Secondary dates, Next: Posting dates, Prev: Simple dates, Up: Dates 1.1.2 Secondary dates --------------------- Real-life transactions sometimes involve more than one date - eg the date you write a cheque, and the date it clears in your bank. When you want to model this, for more accurate daily balances, you can specify individual posting dates. Or, you can use the older _secondary date_ feature (Ledger calls it auxiliary date or effective date). Note: we support this for compatibility, but I usually recommend avoiding this feature; posting dates are almost always clearer and simpler. 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", as shown here: 2010/2/23=2/19 movie ticket expenses:cinema $10 assets:checking $ hledger register checking 2010-02-23 movie ticket assets:checking $-10 $-10 $ hledger register checking --date2 2010-02-19 movie ticket assets:checking $-10 $-10  File: hledger_journal.info, Node: Posting dates, Prev: Secondary dates, Up: Dates 1.1.3 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. You can set the secondary date similarly, with 'date2:DATE2'. The 'date:' or 'date2:' tags must have a valid simple date value if they are present, eg a 'date:' tag with no value is not allowed. Ledger's earlier, more compact bracketed date syntax is also supported: '[DATE]', '[DATE=DATE2]' or '[=DATE2]'. 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.  File: hledger_journal.info, Node: Status, Next: Description, Prev: Dates, Up: Transactions 1.2 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_journal.info, Node: Description, Next: Comments, Prev: Status, Up: Transactions 1.3 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_journal.info, Node: Payee and note, Up: Description 1.3.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_journal.info, Node: Comments, Next: Tags, Prev: Description, Up: Transactions 1.4 Comments ============ Lines in the journal beginning with a semicolon (';') or hash ('#') or star ('*') are comments, and will be ignored. (Star comments cause org-mode nodes to be ignored, allowing emacs users to fold and navigate their journals with org-mode or orgstruct-mode.) You can attach comments to a transaction by writing them after the description and/or indented on the following lines (before the postings). Similarly, you can attach comments to an individual posting by writing them after the amount and/or indented on the following lines. Transaction and posting comments must begin with a semicolon (';'). Some examples: # a file comment ; another file comment * also a file comment, useful in org/orgstruct mode comment A multiline file comment, which continues until a line containing just "end comment" (or end of file). end comment 2012/5/14 something ; a transaction comment ; the transaction comment, continued posting1 1 ; a comment for posting 1 posting2 ; a comment for posting 2 ; another comment line for posting 2 ; a file comment (because not indented) You can also comment larger regions of a file using 'comment' and 'end comment' directives.  File: hledger_journal.info, Node: Tags, Next: Postings, Prev: Comments, Up: Transactions 1.5 Tags ======== Tags are a way to add extra labels or labelled data to postings and transactions, which you can then search or pivot on. A simple tag is a word (which may contain hyphens) followed by a full colon, written inside a transaction or posting comment line: 2017/1/16 bought groceries ; sometag: Tags can have a value, which is the text after the colon, up to the next comma or end of line, with leading/trailing whitespace removed: expenses:food $10 ; a-posting-tag: the tag value Note this means hledger's tag values can not contain commas or newlines. Ending at commas means you can write multiple short tags on one line, comma separated: assets:checking ; a comment containing tag1:, tag2: some value ... Here, * "'a comment containing'" is just comment text, not a tag * "'tag1'" is a tag with no value * "'tag2'" is another tag, whose value is "'some value ...'" Tags in a transaction comment affect the transaction and all of its postings, while tags in a posting comment affect only that posting. For example, the following transaction has three tags ('A', 'TAG2', 'third-tag') and the posting has four (those plus 'posting-tag'): 1/1 a transaction ; A:, TAG2: ; third-tag: a third transaction tag, <- with a value (a) $1 ; posting-tag: Tags are like Ledger's metadata feature, except hledger's tag values are simple strings.  File: hledger_journal.info, Node: Postings, Next: Account names, Prev: Tags, Up: Transactions 1.6 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. * Menu: * Virtual postings::  File: hledger_journal.info, Node: Virtual postings, Up: Postings 1.6.1 Virtual postings ---------------------- A posting with a parenthesised account name is called a _virtual posting_ or _unbalanced posting_, which means it is exempt from the usual rule that a transaction's postings must balance add up to zero. This is not part of double entry accounting, so you might choose to avoid this feature. Or you can use it sparingly for certain special cases where it can be convenient. Eg, you could set opening balances without using a balancing equity account: 1/1 opening balances (assets:checking) $1000 (assets:savings) $2000 A posting with a bracketed account name is called a _balanced virtual posting_. The balanced virtual postings in a transaction must add up to zero (separately from other postings). Eg: 1/1 buy food with cash, update budget envelope subaccounts, & something else assets:cash $-10 ; <- these balance expenses:food $7 ; <- expenses:food $3 ; <- [assets:checking:budget:food] $-10 ; <- and these balance [assets:checking:available] $10 ; <- (something:else) $5 ; <- not required to balance Ordinary non-parenthesised, non-bracketed postings are called _real postings_. You can exclude virtual postings from reports with the '-R/--real' flag or 'real:1' query.  File: hledger_journal.info, Node: Account names, Next: Amounts, Prev: Postings, Up: Transactions 1.7 Account names ================= Account names typically have several parts separated by a full colon, from which hledger derives a hierarchical chart of accounts. They can be anything you like, but in finance there are traditionally five top-level accounts: 'assets', 'liabilities', 'income', 'expenses', and 'equity'. Account names may contain single spaces, eg: 'assets:accounts receivable'. Because of this, they must always be followed by *two or more spaces* (or newline). Account names can be aliased.  File: hledger_journal.info, Node: Amounts, Next: Transaction prices, Prev: Account names, Up: Transactions 1.8 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 or commodity name (the "commodity"). This is a symbol, word, or phrase, to the left or right of the quantity, with or without a separating space: $1 4000 AAPL If the commodity name contains spaces, numbers, or punctuation, it must be enclosed in double quotes: 3 "no. 42 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 A decimal mark can be written as a period or a comma: 1.23 1,23456780000009 * Menu: * Digit group marks:: * Amount display style::  File: hledger_journal.info, Node: Digit group marks, Next: Amount display style, Up: Amounts 1.8.1 Digit group marks ----------------------- 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 Note, a number containing a single group mark and no decimal mark is ambiguous. Are these group marks or decimal marks ? 1,000 1.000 hledger will treat them both as decimal marks by default (cf #793). If you use digit group marks, to prevent confusion and undetected typos we recommend you write commodity directives at the top of the file to explicitly declare the decimal mark (and optionally a digit group mark). Note, these formats ("amount styles") are specific to each commodity, so if your data uses multiple formats, hledger can handle it: commodity $1,000.00 commodity EUR 1.000,00 commodity INR 9,99,99,999.00 commodity 1 000 000.9455  File: hledger_journal.info, Node: Amount display style, Prev: Digit group marks, Up: Amounts 1.8.2 Amount display style -------------------------- For each commodity, hledger chooses a consistent format to use when displaying amounts. (Except price amounts, which are always displayed as written). The display style is chosen as follows: * If there is a commodity directive (or default commodity directive) for the commodity, that format is used (see examples above). * Otherwise the format of the first posting amount in that commodity seen in the journal is used. But the number of decimal places ("precision") will be the maximum from all posting amounts in that commodity. * Or if there are no such amounts in the journal, a default format is used (like '$1000.00'). Transaction prices don't affect the amount display style directly, but occasionally they can do so indirectly (eg when an posting's amount is inferred using a transaction price). If you find this causing problems, use a commodity directive to fix the display style. In summary: amounts will be displayed much as they appear in your journal, with the max observed number of decimal places. If you want to see fewer decimal places in reports, use a commodity directive to override that. hledger uses banker's rounding: it rounds to the nearest even number, eg 0.5 displayed with zero decimal places is "0"). (Note, prior to hledger 1.17.1 this could vary if hledger happened to be built with an old version of Decimal (<0.5.1); since 1.17.1 it's guaranteed.)  File: hledger_journal.info, Node: Transaction prices, Next: Lot prices and lot dates, Prev: Amounts, Up: Transactions 1.9 Transaction prices ====================== Within a transaction, you can note an amount's price in another commodity. This can be used to document the cost (in a purchase) or selling price (in a sale). For example, transaction prices are useful to record purchases of a foreign currency. Note transaction prices are fixed at the time of the transaction, and do not change over time. See also market prices, which represent prevailing exchange rates on a certain date. There are several ways to record a transaction price: 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: 2009/1/1 assets:euros €100 ; one hundred euros purchased assets:dollars $-135 ; for $135 4. Like 1, but the '@' is parenthesised, i.e. '(@)'; this is for compatibility with Ledger journals (Virtual posting costs), and is equivalent to 1 in hledger. 5. Like 2, but as in 4 the '@@' is parenthesised, i.e. '(@@)'; in hledger, this is equivalent to 2. Use the '-B/--cost' flag to convert amounts to their transaction price's commodity, if any. (mnemonic: "B" is from "cost Basis", as in Ledger). Eg here is how -B affects the balance report for the example above: $ hledger bal -N --flat $-135 assets:dollars €100 assets:euros $ hledger bal -N --flat -B $-135 assets:dollars $135 assets:euros # <- the euros' cost Note -B is sensitive to the order of postings when a transaction price is inferred: the inferred price will be in the commodity of the last amount. So if example 3's postings are reversed, while the transaction is equivalent, -B shows something different: 2009/1/1 assets:dollars $-135 ; 135 dollars sold assets:euros €100 ; for 100 euros $ hledger bal -N --flat -B €-100 assets:dollars # <- the dollars' selling price €100 assets:euros  File: hledger_journal.info, Node: Lot prices and lot dates, Next: Balance assertions, Prev: Transaction prices, Up: Transactions 1.10 Lot prices and lot dates ============================= Ledger allows another kind of price, lot price (four variants: '{UNITPRICE}', '{{TOTALPRICE}}', '{=FIXEDUNITPRICE}', '{{=FIXEDTOTALPRICE}}'), and/or a lot date ('[DATE]') to be specified. These are normally used to select a lot when selling investments. hledger will parse these, for compatibility with Ledger journals, but currently ignores them. A transaction price, lot price and/or lot date may appear in any order, after the posting amount and before the balance assertion if any.  File: hledger_journal.info, Node: Balance assertions, Next: Balance assignments, Prev: Lot prices and lot dates, Up: Transactions 1.11 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, below). * Menu: * Assertions and ordering:: * Assertions and included files:: * Assertions and multiple -f options:: * Assertions and commodities:: * Assertions and prices:: * Assertions and subaccounts:: * Assertions and virtual postings:: * Assertions and precision::  File: hledger_journal.info, Node: Assertions and ordering, Next: Assertions and included files, Up: Balance assertions 1.11.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_journal.info, Node: Assertions and included files, Next: Assertions and multiple -f options, Prev: Assertions and ordering, Up: Balance assertions 1.11.2 Assertions and included files ------------------------------------ With included files, things are a little more complicated. Including preserves the ordering of postings and assertions. If you have multiple postings to an account on the same day, split across different files, and you also want to assert the account's balance on the same day, you'll have to put the assertion in the right file.  File: hledger_journal.info, Node: Assertions and multiple -f options, Next: Assertions and commodities, Prev: Assertions and included files, Up: Balance assertions 1.11.3 Assertions and multiple -f options ----------------------------------------- Balance assertions don't work well across files specified with multiple -f options. Use include or concatenate the files instead.  File: hledger_journal.info, Node: Assertions and commodities, Next: Assertions and prices, Prev: Assertions and multiple -f options, Up: Balance assertions 1.11.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 unasserted commodities in the account (or, 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_journal.info, Node: Assertions and prices, Next: Assertions and subaccounts, Prev: Assertions and commodities, Up: Balance assertions 1.11.5 Assertions and prices ---------------------------- Balance assertions ignore transaction prices, and should normally be written without one: 2019/1/1 (a) $1 @ €1 = $1 We do allow prices to be written there, however, and print shows them, even though 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 prices), and because balance _assignments_ do use them (see below).  File: hledger_journal.info, Node: Assertions and subaccounts, Next: Assertions and virtual postings, Prev: Assertions and prices, Up: Balance assertions 1.11.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_journal.info, Node: Assertions and virtual postings, Next: Assertions and precision, Prev: Assertions and subaccounts, Up: Balance assertions 1.11.7 Assertions and virtual postings -------------------------------------- Balance assertions are checked against all postings, both real and virtual. They are not affected by the '--real/-R' flag or 'real:' query.  File: hledger_journal.info, Node: Assertions and precision, Prev: Assertions and virtual postings, Up: Balance assertions 1.11.8 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_journal.info, Node: Balance assignments, Next: Directives, Prev: Balance assertions, Up: Transactions 1.12 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). Note that using balance assignments makes your journal a little less explicit; to know the exact amount posted, you have to run hledger or do the calculations yourself, instead of just reading it. * Menu: * Balance assignments and prices::  File: hledger_journal.info, Node: Balance assignments and prices, Up: Balance assignments 1.12.1 Balance assignments and prices ------------------------------------- A transaction price 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_journal.info, Node: Directives, Next: Periodic transactions, Prev: Balance assignments, Up: Transactions 1.13 Directives =============== A directive is a line in the journal beginning with a special keyword, that influences how the journal is processed. hledger's directives are based on a subset of Ledger's, but there are many differences (and also some differences between hledger versions). Directives' behaviour and interactions can get a little bit complex, so here is a table summarising the directives and their effects, with links to more detailed docs. directiveend subdirectivespurpose can affect (as of directive 2018/06) ----------------------------------------------------------------------------- 'account' any document account names, all entries in text declare account types & all files, before display order or after 'alias' 'end rewrite account names following aliases' inline/included entries until end of current file or end directive 'apply 'end prepend a common parent to following account' apply account names inline/included account' entries until end of current file or end directive 'comment''end ignore part of journal following comment' inline/included entries until end of current file or end directive 'commodity' 'format'declare a commodity and its number notation: number notation & display following entries style in that commodity in all files; display style: amounts of that commodity in reports 'D' declare a commodity to be default used for commodityless commodity: amounts, and its number following notation & display style commodityless entries until end of current file; number notation: following entries in that commodity until end of current file; display style: amounts of that commodity in reports 'include' include entries/directives what the included from another file directives affect 'P' declare a market price for amounts of that a commodity commodity in reports, when -V is used 'Y' declare a year for yearless following dates inline/included entries until end of current file '=' declare an auto posting all entries in rule, adding postings to parent/current/child other transactions files (but not sibling files, see #1212) And some definitions: subdirectiveoptional indented directive line immediately following a parent directive number how to interpret numbers when parsing journal entries (the notationidentity of the decimal separator character). (Currently each commodity can have its own notation, even in the same file.) displayhow to display amounts of a commodity in reports (symbol side style and spacing, digit groups, decimal separator, decimal places) directivewhich entries and (when there are multiple files) which files scope are affected by a directive As you can see, directives vary in which journal entries and files they affect, and whether they are focussed on input (parsing) or output (reports). Some directives have multiple effects. * Menu: * Directives and multiple files:: * Comment blocks:: * Including other files:: * Default year:: * Declaring commodities:: * Default commodity:: * Declaring market prices:: * Declaring accounts:: * Rewriting accounts:: * Default parent account::  File: hledger_journal.info, Node: Directives and multiple files, Next: Comment blocks, Up: Directives 1.13.1 Directives and multiple files ------------------------------------ If you use multiple '-f'/'--file' options, or the 'include' directive, hledger will process multiple input files. But note that directives which affect input (see above) typically last only until the end of the file in which they occur. This may seem inconvenient, but it's intentional; it makes reports stable and deterministic, independent of the order of input. Otherwise you could see different numbers if you happened to write -f options in a different order, or if you moved includes around while cleaning up your files. It can be surprising though; for example, it means that 'alias' directives do not affect parent or sibling files (see below).  File: hledger_journal.info, Node: Comment blocks, Next: Including other files, Prev: Directives and multiple files, Up: Directives 1.13.2 Comment blocks --------------------- A line containing just 'comment' starts a commented region of the file, and a line containing just 'end comment' (or the end of the current file) ends it. See also comments.  File: hledger_journal.info, Node: Including other files, Next: Default year, Prev: Comment blocks, Up: Directives 1.13.3 Including other files ---------------------------- 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 hledger.1 -> Input files): 'include timedot:~/notes/2020*.md'.  File: hledger_journal.info, Node: Default year, Next: Declaring commodities, Prev: Including other files, Up: Directives 1.13.4 Default year ------------------- You can set a default year to be used for subsequent dates which don't specify a year. This is a line beginning with 'Y' followed by the year. Eg: Y2009 ; set default year to 2009 12/15 ; equivalent to 2009/12/15 expenses 1 assets Y2010 ; 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  File: hledger_journal.info, Node: Declaring commodities, Next: Default commodity, Prev: Default year, Up: Directives 1.13.5 Declaring commodities ---------------------------- The 'commodity' directive has several functions: 1. It declares commodities which may be used in the journal. This is currently not enforced, but can serve as documentation. 2. It declares what decimal mark character (period or comma) to expect when parsing input - useful to disambiguate international number formats in your data. (Without this, hledger will parse both '1,000' and '1.000' as 1). 3. It declares the amount display style to use in output - decimal and digit group marks, number of decimal places, symbol placement etc. You are likely to run into one of the problems solved by commodity directives, sooner or later, so it's a good idea to just always use them to declare your commodities. A commodity directive is just the word 'commodity' followed by an amount. It may be written on a single line, like this: ; commodity EXAMPLEAMOUNT ; display AAAA amounts with the symbol on the right, space-separated, ; using period as decimal point, with four decimal places, and ; separating thousands with comma. commodity 1,000.0000 AAAA or on multiple lines, using the "format" subdirective. (In this case the commodity symbol appears twice and should be the same in both places.): ; commodity SYMBOL ; format EXAMPLEAMOUNT ; 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 The quantity of the amount does not matter; only the format is significant. The number must include a decimal mark: either a period or a comma, followed by 0 or more decimal digits. Note hledger normally uses banker's rounding, so 0.5 displayed with zero decimal digits is "0". (More at Amount display style.)  File: hledger_journal.info, Node: Default commodity, Next: Declaring market prices, Prev: Declaring commodities, Up: Directives 1.13.6 Default commodity ------------------------ The 'D' directive sets a default commodity, to be used for amounts without a commodity symbol (ie, plain numbers). This commodity will be applied to all subsequent commodity-less amounts, or until the next 'D' directive. (Note, this is different from Ledger's 'D'.) For compatibility/historical reasons, 'D' also acts like a 'commodity' directive, setting the commodity's display style (for output) and decimal mark (for parsing input). As with 'commodity', the amount must always be written with a decimal mark (period or comma). If both directives are used, 'commodity''s style takes precedence. The syntax is 'D AMOUNT'. 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  File: hledger_journal.info, Node: Declaring market prices, Next: Declaring accounts, Prev: Default commodity, Up: Directives 1.13.7 Declaring market prices ------------------------------ The 'P' directive declares a market price, which is an exchange rate between two commodities on a certain date. (In Ledger, they are called "historical prices".) These are often obtained from a stock exchange, cryptocurrency exchange, or the foreign exchange market. Here is the format: P DATE COMMODITYA COMMODITYBAMOUNT * DATE is a simple date * COMMODITYA is the symbol of the commodity being priced * COMMODITYBAMOUNT is an amount (symbol and quantity) in a second commodity, giving the price in commodity B of one unit of commodity A. These two market price directives say that one euro was worth 1.35 US dollars during 2009, and $1.40 from 2010 onward: P 2009/1/1 € $1.35 P 2010/1/1 € $1.40 The '-V', '-X' and '--value' flags use these market prices to show amount values in another commodity. See Valuation.  File: hledger_journal.info, Node: Declaring accounts, Next: Rewriting accounts, Prev: Declaring market prices, Up: Directives 1.13.8 Declaring accounts ------------------------- 'account' directives can be used to pre-declare accounts. Though not required, they can provide several benefits: * They can document your intended chart of accounts, providing a reference. * They can store extra information about accounts (account numbers, notes, etc.) * They can help hledger know your accounts' types (asset, liability, equity, revenue, expense), useful for reports like balancesheet and incomestatement. * They control account display order in reports, allowing non-alphabetic sorting (eg Revenues to appear above Expenses). * They help with account name completion in the add command, hledger-iadd, hledger-web, ledger-mode etc. The simplest form is just the word 'account' followed by a hledger-style account name, eg: account assets:bank:checking * Menu: * Account comments:: * Account subdirectives:: * Account types:: * Account display order::  File: hledger_journal.info, Node: Account comments, Next: Account subdirectives, Up: Declaring accounts 1.13.8.1 Account comments ......................... Comments, beginning with a semicolon, can be added: * on the same line, *after two or more spaces* (because ; is allowed in account names) * on the next lines, indented An example of both: account assets:bank:checking ; same-line comment, note 2+ spaces before ; ; next-line comment ; another with tag, acctno:12345 (not used yet) Same-line comments are not supported by Ledger, or hledger <1.13.  File: hledger_journal.info, Node: Account subdirectives, Next: Account types, Prev: Account comments, Up: Declaring accounts 1.13.8.2 Account subdirectives .............................. We also allow (and ignore) Ledger-style indented subdirectives, just for compatibility.: account assets:bank:checking format blah blah ; <- subdirective, ignored Here is the full syntax of account directives: account ACCTNAME [ACCTTYPE] [;COMMENT] [;COMMENTS] [LEDGER-STYLE SUBDIRECTIVES, IGNORED]  File: hledger_journal.info, Node: Account types, Next: Account display order, Prev: Account subdirectives, Up: Declaring accounts 1.13.8.3 Account types ...................... hledger recognises five main types of account, corresponding to the account classes in the accounting equation: 'Asset', 'Liability', 'Equity', 'Revenue', 'Expense'. These account types are important for controlling which accounts appear in the balancesheet, balancesheetequity, incomestatement reports (and probably for other things in future). Additionally, we recognise the 'Cash' type, which is also an 'Asset', and which causes accounts to appear in the cashflow report. ("Cash" here means liquid assets, eg bank balances but typically not investments or receivables.) Declaring account types Generally, to make these reports work you should declare your top-level accounts and their types, using account directives with 'type:' tags. The tag's value should be one of: 'Asset', 'Liability', 'Equity', 'Revenue', 'Expense', 'Cash', 'A', 'L', 'E', 'R', 'X', 'C' (all case insensitive). The type is inherited by all subaccounts except where they override it. Here's a complete example: account assets ; type: Asset account assets:bank ; type: Cash account assets:cash ; type: Cash account liabilities ; type: Liability account equity ; type: Equity account revenues ; type: Revenue account expenses ; type: Expense Auto-detected account types If you happen to use common english top-level account names, you may not need to declare account types, as they will be detected automatically using the following rules: If name matches regular account expression: type is: ------------------------------------------------- '^assets?(:|$)' 'Asset' '^(debts?|liabilit(y|ies))(:|$)' 'Liability' '^equity(:|$)' 'Equity' '^(income|revenue)s?(:|$)' 'Revenue' '^expenses?(:|$)' 'Expense' If account type is 'Asset' and name does not contain account type regular expression: is: -------------------------------------------------------------------------- '(investment|receivable|:A/R|:fixed)' 'Cash' Even so, explicit declarations may be a good idea, for clarity and predictability. Interference from auto-detected account types If you assign any account type, it's a good idea to assign all of them, to prevent any confusion from mixing declared and auto-detected types. Although it's unlikely to happen in real life, here's an example: with the following journal, 'balancesheetequity' shows "liabilities" in both Liabilities and Equity sections. Declaring another account as 'type:Liability' would fix it: account liabilities ; type:Equity 2020-01-01 assets 1 liabilities 1 equity -2 Old account type syntax In some hledger journals you might instead see this old syntax (the letters ALERX, separated from the account name by two or more spaces); this is deprecated and may be removed soon: account assets A account liabilities L account equity E account revenues R account expenses X  File: hledger_journal.info, Node: Account display order, Prev: Account types, Up: Declaring accounts 1.13.8.4 Account display order .............................. Account directives also set the order in which accounts are displayed, eg in reports, the hledger-ui accounts screen, and the hledger-web sidebar. By default accounts are listed in alphabetical order. But if you have these account directives in the journal: account assets account liabilities account equity account revenues account expenses you'll see those accounts displayed in declaration order, not alphabetically: $ hledger accounts -1 assets liabilities equity revenues expenses Undeclared accounts, if any, are displayed last, in alphabetical order. Note that 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_journal.info, Node: Rewriting accounts, Next: Default parent account, Prev: Declaring accounts, Up: Directives 1.13.9 Rewriting accounts ------------------------- 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 or combining two accounts into one * 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. See also Rewrite account names. * Menu: * Basic aliases:: * Regex aliases:: * Combining aliases:: * Aliases and multiple files:: * end aliases::  File: hledger_journal.info, Node: Basic aliases, Next: Regex aliases, Up: Rewriting accounts 1.13.9.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. 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_journal.info, Node: Regex aliases, Next: Combining aliases, Prev: Basic aliases, Up: Rewriting accounts 1.13.9.2 Regex aliases ...................... There is also a more powerful variant that uses a regular expression, indicated by the forward slashes: alias /REGEX/ = REPLACEMENT or '--alias '/REGEX/=REPLACEMENT''. REGEX is a case-insensitive regular expression. Anywhere it matches inside an account name, the matched part will be replaced by REPLACEMENT. If REGEX contains parenthesised match groups, these can be referenced by the usual numeric backreferences in REPLACEMENT. Eg: alias /^(.+):bank:([^:]+):(.*)/ = \1:\2 \3 ; rewrites "assets:bank:wells fargo:checking" to "assets:wells fargo checking" Also note that REPLACEMENT continues to the end of line (or on command line, to end of option argument), so it can contain trailing whitespace.  File: hledger_journal.info, Node: Combining aliases, Next: Aliases and multiple files, Prev: Regex aliases, Up: Rewriting accounts 1.13.9.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_journal.info, Node: Aliases and multiple files, Next: end aliases, Prev: Combining aliases, Up: Rewriting accounts 1.13.9.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 2020-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 2020-01-01 ; affected by aliases above foo 1 bar include c.journal ; also affected  File: hledger_journal.info, Node: end aliases, Prev: Aliases and multiple files, Up: Rewriting accounts 1.13.9.5 'end aliases' ...................... You can clear (forget) all currently defined aliases with the 'end aliases' directive: end aliases  File: hledger_journal.info, Node: Default parent account, Prev: Rewriting accounts, Up: Directives 1.13.10 Default parent account ------------------------------ You can specify a parent account which will be prepended to all accounts within a section of the journal. Use the 'apply account' and 'end apply account' directives like so: apply account home 2010/1/1 food $10 cash end apply account which is equivalent to: 2010/01/01 home:food $10 home:cash $-10 If 'end apply account' is omitted, the effect lasts to the end of the file. Included files are also affected, eg: apply account business include biz.journal end apply account apply account personal include personal.journal Prior to hledger 1.0, legacy 'account' and 'end' spellings were also supported. A default parent account also affects account directives. It does not affect account names being entered via hledger add or hledger-web. If account aliases are present, they are applied after the default parent account.  File: hledger_journal.info, Node: Periodic transactions, Next: Auto postings, Prev: Directives, Up: Transactions 1.14 Periodic transactions ========================== Periodic transaction rules describe transactions that recur. They allow hledger to generate temporary future transactions to help with forecasting, so you don't have to write out each one in the journal, and it's easy to try out different forecasts. Secondly, they are also used to define the budgets shown in budget reports. Periodic transactions can be a little tricky, so before you use them, read this whole section - or at least these 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 2020/01', which is equivalent to '~ every 10th day of month from 2020/01/01', will be adjusted to start on 2019/12/10. * Menu: * Periodic rule syntax:: * Two spaces between period expression and description!:: * Forecasting with periodic transactions:: * Budgeting with periodic transactions::  File: hledger_journal.info, Node: Periodic rule syntax, Next: Two spaces between period expression and description!, Up: Periodic transactions 1.14.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.): ~ monthly expenses:rent $2000 assets:bank:checking There is an additional constraint on the period expression: the start date must fall on a natural boundary of the interval. Eg 'monthly from 2018/1/1' is valid, but 'monthly from 2018/1/15' is not. Partial or relative dates (M/D, D, tomorrow, last week) in the period expression can work (useful or not). They will be relative to today's date, unless a Y default year directive is in effect, in which case they will be relative to Y/1/1.  File: hledger_journal.info, Node: Two spaces between period expression and description!, Next: Forecasting with periodic transactions, Prev: Periodic rule syntax, Up: Periodic transactions 1.14.2 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 2020" ; || ; vv ~ every 2 months in 2020, 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_journal.info, Node: Forecasting with periodic transactions, Next: Budgeting with periodic transactions, Prev: Two spaces between period expression and description!, Up: Periodic transactions 1.14.3 Forecasting with periodic transactions --------------------------------------------- The '--forecast' flag activates any periodic transaction rules in the journal. They will generate temporary recurring transactions, which are not saved in the journal, but will appear in all reports (eg print). This can be useful for estimating balances into the future, or experimenting with different scenarios. Or, it can be used as a data entry aid: describe recurring transactions, and every so often copy the output of 'print --forecast' into the journal. These transactions will have an extra tag indicating which periodic rule generated them: 'generated-transaction:~ PERIODICEXPR'. And a similar, hidden tag (beginning with an underscore) which, because it's never displayed by print, can be used to match transactions generated "just now": '_generated-transaction:~ PERIODICEXPR'. Periodic transactions are generated within some forecast period. By default, this * begins on 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, or today if there are no normal transactions. * ends on the report end date if specified with -e/-p/date:, or 6 months (180 days) from today. This means that periodic transactions will begin only after the latest recorded transaction. And a recorded transaction dated in the future can prevent generation of periodic transactions. (You can avoid that by writing the future transaction as a one-time periodic rule instead - put tilde before the date, eg '~ YYYY-MM-DD ...'). Or, you can set your own arbitrary "forecast period", which can overlap recorded transactions, and need not be in the future, by providing an option argument, like '--forecast=PERIODEXPR'. Note the equals sign is required, a space won't work. PERIODEXPR is a period expression, which can specify the start date, end date, or both, like in a 'date:' query. (See also hledger.1 -> Report start & end date). Some examples: '--forecast=202001-202004', '--forecast=jan-', '--forecast=2020'.  File: hledger_journal.info, Node: Budgeting with periodic transactions, Prev: Forecasting with periodic transactions, Up: Periodic transactions 1.14.4 Budgeting with periodic transactions ------------------------------------------- With the '--budget' flag, currently supported by the balance command, each periodic transaction rule declares recurring budget goals for the specified accounts. Eg the first example above declares a goal of spending $2000 on rent (and also, a goal of depositing $2000 into checking) every month. Goals and actual performance can then be compared in budget reports. For more details, see: balance: Budget report and Budgeting and Forecasting.  File: hledger_journal.info, Node: Auto postings, Prev: Periodic transactions, Up: Transactions 1.15 Auto postings ================== "Automated postings" or "auto postings" are extra postings which get added automatically to transactions which match certain queries, defined by "auto posting rules", when you use the '--auto' flag. 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:: * Auto postings and dates:: * Auto postings and transaction balancing / inferred amounts / balance assertions:: * Auto posting tags::  File: hledger_journal.info, Node: Auto postings and multiple files, Next: Auto postings and dates, Up: Auto postings 1.15.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).  File: hledger_journal.info, Node: Auto postings and dates, Next: Auto postings and transaction balancing / inferred amounts / balance assertions, Prev: Auto postings and multiple files, Up: Auto postings 1.15.2 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_journal.info, Node: Auto postings and transaction balancing / inferred amounts / balance assertions, Next: Auto posting tags, Prev: Auto postings and dates, Up: Auto postings 1.15.3 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.  File: hledger_journal.info, Node: Auto posting tags, Prev: Auto postings and transaction balancing / inferred amounts / balance assertions, Up: Auto postings 1.15.4 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".  Tag Table: Node: Top76 Node: Transactions1875 Ref: #transactions1967 Node: Dates3251 Ref: #dates3350 Node: Simple dates3415 Ref: #simple-dates3541 Node: Secondary dates4050 Ref: #secondary-dates4204 Node: Posting dates5540 Ref: #posting-dates5669 Node: Status7041 Ref: #status7162 Node: Description8870 Ref: #description9004 Node: Payee and note9324 Ref: #payee-and-note9438 Node: Comments9773 Ref: #comments9899 Node: Tags11093 Ref: #tags11208 Node: Postings12601 Ref: #postings12729 Node: Virtual postings13755 Ref: #virtual-postings13872 Node: Account names15177 Ref: #account-names15318 Node: Amounts15805 Ref: #amounts15944 Node: Digit group marks17052 Ref: #digit-group-marks17200 Node: Amount display style18138 Ref: #amount-display-style18292 Node: Transaction prices19729 Ref: #transaction-prices19901 Node: Lot prices and lot dates22332 Ref: #lot-prices-and-lot-dates22529 Node: Balance assertions23017 Ref: #balance-assertions23203 Node: Assertions and ordering24236 Ref: #assertions-and-ordering24424 Node: Assertions and included files25124 Ref: #assertions-and-included-files25367 Node: Assertions and multiple -f options25700 Ref: #assertions-and-multiple--f-options25956 Node: Assertions and commodities26088 Ref: #assertions-and-commodities26320 Node: Assertions and prices27477 Ref: #assertions-and-prices27691 Node: Assertions and subaccounts28131 Ref: #assertions-and-subaccounts28360 Node: Assertions and virtual postings28684 Ref: #assertions-and-virtual-postings28926 Node: Assertions and precision29068 Ref: #assertions-and-precision29261 Node: Balance assignments29528 Ref: #balance-assignments29702 Node: Balance assignments and prices30866 Ref: #balance-assignments-and-prices31038 Node: Directives31262 Ref: #directives31421 Node: Directives and multiple files37112 Ref: #directives-and-multiple-files37295 Node: Comment blocks37959 Ref: #comment-blocks38142 Node: Including other files38318 Ref: #including-other-files38498 Node: Default year39422 Ref: #default-year39591 Node: Declaring commodities39998 Ref: #declaring-commodities40181 Node: Default commodity41987 Ref: #default-commodity42173 Node: Declaring market prices43062 Ref: #declaring-market-prices43257 Node: Declaring accounts44114 Ref: #declaring-accounts44300 Node: Account comments45225 Ref: #account-comments45388 Node: Account subdirectives45812 Ref: #account-subdirectives46007 Node: Account types46320 Ref: #account-types46504 Node: Account display order49550 Ref: #account-display-order49720 Node: Rewriting accounts50871 Ref: #rewriting-accounts51056 Node: Basic aliases51813 Ref: #basic-aliases51959 Node: Regex aliases52663 Ref: #regex-aliases52835 Node: Combining aliases53554 Ref: #combining-aliases53747 Node: Aliases and multiple files55023 Ref: #aliases-and-multiple-files55232 Node: end aliases55811 Ref: #end-aliases55968 Node: Default parent account56069 Ref: #default-parent-account56237 Node: Periodic transactions57121 Ref: #periodic-transactions57296 Node: Periodic rule syntax59168 Ref: #periodic-rule-syntax59374 Node: Two spaces between period expression and description!60078 Ref: #two-spaces-between-period-expression-and-description60397 Node: Forecasting with periodic transactions61081 Ref: #forecasting-with-periodic-transactions61386 Node: Budgeting with periodic transactions63441 Ref: #budgeting-with-periodic-transactions63680 Node: Auto postings64129 Ref: #auto-postings64269 Node: Auto postings and multiple files66448 Ref: #auto-postings-and-multiple-files66652 Node: Auto postings and dates66861 Ref: #auto-postings-and-dates67135 Node: Auto postings and transaction balancing / inferred amounts / balance assertions67310 Ref: #auto-postings-and-transaction-balancing-inferred-amounts-balance-assertions67661 Node: Auto posting tags68003 Ref: #auto-posting-tags68218  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.19.1/embeddedfiles/hledger_csv.50000644000000000000000000011441713725533425016553 0ustar0000000000000000.\"t .TH "hledger_csv" "5" "September 2020" "hledger 1.18.99" "hledger User Manuals" .SH NAME .PP CSV - how hledger reads CSV data, and the CSV rules file format .SH DESCRIPTION .PP hledger can read CSV files (Character Separated Value - usually comma, semicolon, or tab) containing dated records as if they were journal files, automatically converting each CSV record into a transaction. .PP (To learn about \f[I]writing\f[R] CSV, see CSV output.) .PP We describe each CSV file\[aq]s format with a corresponding \f[I]rules file\f[R]. By default this is named like the CSV file with a \f[C].rules\f[R] extension added. Eg when reading \f[C]FILE.csv\f[R], hledger also looks for \f[C]FILE.csv.rules\f[R] in the same directory as \f[C]FILE.csv\f[R]. You can specify a different rules file with the \f[C]--rules-file\f[R] option. If a rules file is not found, hledger will create a sample rules file, which you\[aq]ll need to adjust. .PP This file contains rules describing the CSV data (header line, fields layout, date format etc.), and how to construct hledger journal entries (transactions) from it. Often there will also be a list of conditional rules for categorising transactions based on their descriptions. Here\[aq]s an overview of the CSV rules; these are described more fully below, after the examples: .PP .TS tab(@); lw(30.1n) lw(39.9n). T{ \f[B]\f[CB]skip\f[B]\f[R] T}@T{ skip one or more header lines or matched CSV records T} T{ \f[B]\f[CB]fields\f[B]\f[R] T}@T{ name CSV fields, assign them to hledger fields T} T{ \f[B]field assignment\f[R] T}@T{ assign a value to one hledger field, with interpolation T} T{ \f[B]\f[CB]separator\f[B]\f[R] T}@T{ a custom field separator T} T{ \f[B]\f[CB]if\f[B] block\f[R] T}@T{ apply some rules to CSV records matched by patterns T} T{ \f[B]\f[CB]if\f[B] table\f[R] T}@T{ apply some rules to CSV records matched by patterns, alternate syntax T} T{ \f[B]\f[CB]end\f[B]\f[R] T}@T{ skip the remaining CSV records T} T{ \f[B]\f[CB]date-format\f[B]\f[R] T}@T{ describe the format of CSV dates T} T{ \f[B]\f[CB]newest-first\f[B]\f[R] T}@T{ disambiguate record order when there\[aq]s only one date T} T{ \f[B]\f[CB]include\f[B]\f[R] T}@T{ inline another CSV rules file T} T{ \f[B]\f[CB]balance-type\f[B]\f[R] T}@T{ choose which type of balance assignments to use T} .TE .PP Note, for best error messages when reading CSV files, use a \f[C].csv\f[R], \f[C].tsv\f[R] or \f[C].ssv\f[R] file extension or file prefix - see File Extension below. .PP There\[aq]s an introductory Convert CSV files tutorial on hledger.org. .SH EXAMPLES .PP Here are some sample hledger CSV rules files. See also the full collection at: .PD 0 .P .PD https://github.com/simonmichael/hledger/tree/master/examples/csv .SS Basic .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 .nf \f[C] Date, Description, Id, Amount 12/11/2019, Foo, 123, 10.23 \f[R] .fi .IP .nf \f[C] # basic.csv.rules skip 1 fields date, description, _, amount date-format %d/%m/%Y \f[R] .fi .IP .nf \f[C] $ hledger print -f basic.csv 2019-11-12 Foo expenses:unknown 10.23 income:unknown -10.23 \f[R] .fi .PP Default account names are chosen, since we didn\[aq]t set them. .SS Bank of Ireland .PP 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 .nf \f[C] Date,Details,Debit,Credit,Balance 07/12/2012,LODGMENT 529898,,10.0,131.21 07/12/2012,PAYMENT,5,,126 \f[R] .fi .IP .nf \f[C] # 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 \f[R] .fi .IP .nf \f[C] $ 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 \f[R] .fi .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 Amazon .PP 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 .nf \f[C] \[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] \f[R] .fi .IP .nf \f[C] # 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 \f[R] .fi .IP .nf \f[C] $ 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 \f[R] .fi .SS Paypal .PP Here\[aq]s a real-world rules file for (customised) Paypal CSV, with some Paypal-specific rules, and a second rules file included: .IP .nf \f[C] \[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] \f[R] .fi .IP .nf \f[C] # 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 \f[R] .fi .IP .nf \f[C] # 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 \f[R] .fi .IP .nf \f[C] $ 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: \f[R] .fi .SH CSV RULES .PP The following kinds of rule can appear in the rules file, in any order. Blank lines and lines beginning with \f[C]#\f[R] or \f[C];\f[R] are ignored. .SS \f[C]skip\f[R] .IP .nf \f[C] skip N \f[R] .fi .PP The word \[dq]skip\[dq] followed by a number (or no number, meaning 1) tells hledger to ignore this many non-empty lines preceding the CSV data. (Empty/blank lines are skipped automatically.) You\[aq]ll need this whenever your CSV data contains header lines. .PP It also has a second purpose: it can be used inside if blocks to ignore certain CSV records (described below). .SS \f[C]fields\f[R] .IP .nf \f[C] fields FIELDNAME1, FIELDNAME2, ... \f[R] .fi .PP A fields list (the word \[dq]fields\[dq] followed by comma-separated field names) is the quick way to assign CSV field values to hledger fields. It does two things: .IP "1." 3 it names the CSV fields. This is optional, but can be convenient later for interpolating them. .IP "2." 3 when you use a standard hledger field name, it assigns the CSV value to that part of the hledger 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 .nf \f[C] fields date, description, , amount, , , somefield, anotherfield \f[R] .fi .PP Field names may not contain whitespace. Fields you don\[aq]t care about can be left unnamed. Currently there must be least two items (there must be at least one comma). .PP Note, always use comma in the fields list, even if your CSV uses another separator character. .PP Here are the standard hledger field/pseudo-field names. For more about the transaction parts they refer to, see the manual for hledger\[aq]s journal format. .SS Transaction field names .PP \f[C]date\f[R], \f[C]date2\f[R], \f[C]status\f[R], \f[C]code\f[R], \f[C]description\f[R], \f[C]comment\f[R] can be used to form the transaction\[aq]s first line. .SS Posting field names .SS account .PP \f[C]accountN\f[R], where N is 1 to 99, causes a posting to be generated, with that account name. .PP Most often there are two postings, so you\[aq]ll want to set \f[C]account1\f[R] and \f[C]account2\f[R]. Typically \f[C]account1\f[R] is associated with the CSV file, and is set once with a top-level assignment, while \f[C]account2\f[R] is set based on each transaction\[aq]s description, and in conditional blocks. .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 .PP \f[C]amountN\f[R] sets posting N\[aq]s amount. If the CSV uses separate fields for inflows and outflows, you can use \f[C]amountN-in\f[R] and \f[C]amountN-out\f[R] instead. By assigning to \f[C]amount1\f[R], \f[C]amount2\f[R], ... etc. you can generate anywhere from 0 to 99 postings. .PP There is also an older, unnumbered form of these names, suitable for 2-posting transactions, which sets both posting 1\[aq]s and (negated) posting 2\[aq]s amount: \f[C]amount\f[R], or \f[C]amount-in\f[R] and \f[C]amount-out\f[R]. This is still supported because it keeps pre-hledger-1.17 csv rules files working, and because it can be more succinct, and because it converts posting 2\[aq]s amount to cost if there\[aq]s a transaction price, which can be useful. .PP If you have an existing rules file using the unnumbered form, you might want to use the numbered form in certain conditional blocks, without having to update and retest all the old rules. To facilitate this, posting 1 ignores \f[C]amount\f[R]/\f[C]amount-in\f[R]/\f[C]amount-out\f[R] if any of \f[C]amount1\f[R]/\f[C]amount1-in\f[R]/\f[C]amount1-out\f[R] are assigned, and posting 2 ignores them if any of \f[C]amount2\f[R]/\f[C]amount2-in\f[R]/\f[C]amount2-out\f[R] are assigned, avoiding conflicts. .SS currency .PP If the CSV has the currency symbol in a separate field (ie, not part of the amount field), you can use \f[C]currencyN\f[R] to prepend it to posting N\[aq]s amount. Or, \f[C]currency\f[R] with no number affects all postings. .SS balance .PP \f[C]balanceN\f[R] sets a balance assertion amount (or if the posting amount is left empty, a balance assignment) on posting N. .PP Also, for compatibility with hledger <1.17: \f[C]balance\f[R] with no number is equivalent to \f[C]balance1\f[R]. .PP You can adjust the type of assertion/assignment with the \f[C]balance-type\f[R] rule (see below). .SS comment .PP Finally, \f[C]commentN\f[R] sets a comment on the Nth posting. Comments can also contain tags, as usual. .PP See TIPS below for more about setting amounts and currency. .SS field assignment .IP .nf \f[C] HLEDGERFIELDNAME FIELDVALUE \f[R] .fi .PP Instead of or in addition to a fields list, you can use a \[dq]field assignment\[dq] rule to set the value of a single hledger field, by writing its name (any of the standard hledger field names above) followed by a text value. The value may contain interpolated CSV fields, referenced by their 1-based position in the CSV record (\f[C]%N\f[R]), or by the name they were given in the fields list (\f[C]%CSVFIELDNAME\f[R]). Some examples: .IP .nf \f[C] # 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 \f[R] .fi .PP Interpolation strips outer whitespace (so a CSV value like \f[C]\[dq] 1 \[dq]\f[R] becomes \f[C]1\f[R] when interpolated) (#1051). See TIPS below for more about referencing other fields. .SS \f[C]separator\f[R] .PP You can use the \f[C]separator\f[R] rule to read other kinds of character-separated data. The argument is any single separator character, or the words \f[C]tab\f[R] or \f[C]space\f[R] (case insensitive). Eg, for comma-separated values (CSV): .IP .nf \f[C] separator , \f[R] .fi .PP or for semicolon-separated values (SSV): .IP .nf \f[C] separator ; \f[R] .fi .PP or for tab-separated values (TSV): .IP .nf \f[C] separator TAB \f[R] .fi .PP If the input file has a \f[C].csv\f[R], \f[C].ssv\f[R] or \f[C].tsv\f[R] file extension (or a \f[C]csv:\f[R], \f[C]ssv:\f[R], \f[C]tsv:\f[R] prefix), the appropriate separator will be inferred automatically, and you won\[aq]t need this rule. .SS \f[C]if\f[R] block .IP .nf \f[C] if MATCHER RULE if MATCHER MATCHER MATCHER RULE RULE \f[R] .fi .PP Conditional blocks (\[dq]if blocks\[dq]) are a block of rules that are applied only to CSV records which match certain patterns. They are often used for customising account names based on transaction descriptions. .SS Matching the whole record .PP Each MATCHER can be a record matcher, which looks like this: .IP .nf \f[C] REGEX \f[R] .fi .PP REGEX is a case-insensitive regular expression which tries to match anywhere within the CSV record. It is a POSIX ERE (extended regular expression) that also supports GNU word boundaries (\f[C]\[rs]b\f[R], \f[C]\[rs]B\f[R], \f[C]\[rs]<\f[R], \f[C]\[rs]>\f[R]), and nothing else. If you have trouble, be sure to check our https://hledger.org/hledger.html#regular-expressions doc. .PP Important note: the record that is matched is not the original record, but a synthetic one, with any enclosing double quotes (but not enclosing whitespace) removed, and always comma-separated (which means that a field containing a comma will appear like two fields). Eg, if the original record is \f[C]2020-01-01; \[dq]Acme, Inc.\[dq]; 1,000\f[R], the REGEX will actually see \f[C]2020-01-01,Acme, Inc., 1,000\f[R]). .SS Matching individual fields .PP Or, MATCHER can be a field matcher, like this: .IP .nf \f[C] %CSVFIELD REGEX \f[R] .fi .PP which matches just the content of a particular CSV field. CSVFIELD is a percent sign followed by the field\[aq]s name or column number, like \f[C]%date\f[R] or \f[C]%1\f[R]. .SS Combining matchers .PP A single matcher can be written on the same line as the \[dq]if\[dq]; or multiple matchers can be written on the following lines, non-indented. Multiple matchers are OR\[aq]d (any one of them can match), unless one begins with an \f[C]&\f[R] symbol, in which case it is AND\[aq]ed with the previous matcher. .IP .nf \f[C] if MATCHER & MATCHER RULE \f[R] .fi .SS Rules applied on successful match .PP After the patterns there should be one or more rules to apply, all indented by at least one space. Three kinds of rule are allowed in conditional blocks: .IP \[bu] 2 field assignments (to set a hledger field) .IP \[bu] 2 skip (to skip the matched CSV record) .IP \[bu] 2 end (to skip all remaining CSV records). .PP Examples: .IP .nf \f[C] # if the CSV record contains \[dq]groceries\[dq], set account2 to \[dq]expenses:groceries\[dq] if groceries account2 expenses:groceries \f[R] .fi .IP .nf \f[C] # if the CSV record contains any of these patterns, set account2 and comment as shown if monthly service fee atm transaction fee banking thru software account2 expenses:business:banking comment XXX deductible ? check it \f[R] .fi .SS \f[C]if\f[R] table .IP .nf \f[C] if,CSVFIELDNAME1,CSVFIELDNAME2,...,CSVFIELDNAMEn MATCHER1,VALUE11,VALUE12,...,VALUE1n MATCHER2,VALUE21,VALUE22,...,VALUE2n MATCHER3,VALUE31,VALUE32,...,VALUE3n \f[R] .fi .PP Conditional tables (\[dq]if tables\[dq]) are a different syntax to specify field assignments that will be applied only to CSV records which match certain patterns. .PP MATCHER could be either field or record matcher, as described above. When MATCHER matches, values from that row would be assigned to the CSV fields named on the \f[C]if\f[R] line, in the same order. .PP Therefore \f[C]if\f[R] table is exactly equivalent to a sequence of of \f[C]if\f[R] blocks: .IP .nf \f[C] if MATCHER1 CSVFIELDNAME1 VALUE11 CSVFIELDNAME2 VALUE12 ... CSVFIELDNAMEn VALUE1n if MATCHER2 CSVFIELDNAME1 VALUE21 CSVFIELDNAME2 VALUE22 ... CSVFIELDNAMEn VALUE2n if MATCHER3 CSVFIELDNAME1 VALUE31 CSVFIELDNAME2 VALUE32 ... CSVFIELDNAMEn VALUE3n \f[R] .fi .PP Each line starting with MATCHER should contain enough (possibly empty) values for all the listed fields. .PP Rules would be checked and applied in the order they are listed in the table and, like with \f[C]if\f[R] blocks, later rules (in the same or another table) or \f[C]if\f[R] blocks could override the effect of any rule. .PP Instead of \[aq],\[aq] you can use a variety of other non-alphanumeric characters as a separator. First character after \f[C]if\f[R] is taken to be the separator for the rest of the table. It is the responsibility of the user to ensure that separator does not occur inside MATCHERs and values - there is no way to escape separator. .PP Example: .IP .nf \f[C] if,account2,comment atm transaction fee,expenses:business:banking,deductible? check it %description groceries,expenses:groceries, 2020/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call-out \f[R] .fi .SS \f[C]end\f[R] .PP This rule can be used inside if blocks (only), to make hledger stop reading this CSV file and move on to the next input file, or to command execution. Eg: .IP .nf \f[C] # ignore everything following the first empty record if ,,,, end \f[R] .fi .SS \f[C]date-format\f[R] .IP .nf \f[C] date-format DATEFMT \f[R] .fi .PP This is a helper for the \f[C]date\f[R] (and \f[C]date2\f[R]) fields. If your CSV dates are not formatted like \f[C]YYYY-MM-DD\f[R], \f[C]YYYY/MM/DD\f[R] or \f[C]YYYY.MM.DD\f[R], you\[aq]ll need to add a date-format rule describing them with a strptime date parsing pattern, which must parse the CSV date value completely. Some examples: .IP .nf \f[C] # MM/DD/YY date-format %m/%d/%y \f[R] .fi .IP .nf \f[C] # D/M/YYYY # The - makes leading zeros optional. date-format %-d/%-m/%Y \f[R] .fi .IP .nf \f[C] # YYYY-Mmm-DD date-format %Y-%h-%d \f[R] .fi .IP .nf \f[C] # 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 \f[R] .fi .PP For the supported strptime syntax, see: .PD 0 .P .PD https://hackage.haskell.org/package/time/docs/Data-Time-Format.html#v:formatTime .SS \f[C]newest-first\f[R] .PP hledger always sorts the generated transactions by date. Transactions on the same date should appear in the same order as their CSV records, as hledger can usually auto-detect whether the CSV\[aq]s normal order is oldest first or newest first. But if all of the following are true: .IP \[bu] 2 the CSV might sometimes contain just one day of data (all records having the same date) .IP \[bu] 2 the CSV records are normally in reverse chronological order (newest at the top) .IP \[bu] 2 and you care about preserving the order of same-day transactions .PP then, you should add the \f[C]newest-first\f[R] rule as a hint. Eg: .IP .nf \f[C] # tell hledger explicitly that the CSV is normally newest first newest-first \f[R] .fi .SS \f[C]include\f[R] .IP .nf \f[C] include RULESFILE \f[R] .fi .PP This includes the contents of another CSV rules file at this point. \f[C]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 .nf \f[C] # someaccount.csv.rules ## someaccount-specific rules fields date,description,amount account1 assets:someaccount account2 expenses:misc ## common rules include categorisation.rules \f[R] .fi .SS \f[C]balance-type\f[R] .PP Balance assertions generated by assigning to balanceN are of the simple \f[C]=\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[C]balance-type\f[R] rule: .IP .nf \f[C] # balance assertions will consider all commodities and all subaccounts balance-type ==* \f[R] .fi .PP Here are the balance assertion types for quick reference: .IP .nf \f[C] = single commodity, exclude subaccounts =* single commodity, include subaccounts == multi commodity, exclude subaccounts ==* multi commodity, include subaccounts \f[R] .fi .SH TIPS .SS Rapid feedback .PP It\[aq]s a good idea to get rapid feedback while creating/troubleshooting CSV rules. Here\[aq]s a good way, using entr from http://eradman.com/entrproject : .IP .nf \f[C] $ ls foo.csv* | entr bash -c \[aq]echo ----; hledger -f foo.csv print desc:SOMEDESC\[aq] \f[R] .fi .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 .PP hledger accepts CSV conforming to RFC 4180. When CSV values are enclosed in quotes, note: .IP \[bu] 2 they must be double quotes (not single quotes) .IP \[bu] 2 spaces outside the quotes are not allowed .SS File Extension .PP To help hledger identify the format and show the right error messages, CSV/SSV/TSV files should normally be named with a \f[C].csv\f[R], \f[C].ssv\f[R] or \f[C].tsv\f[R] filename extension. Or, the file path should be prefixed with \f[C]csv:\f[R], \f[C]ssv:\f[R] or \f[C]tsv:\f[R]. Eg: .IP .nf \f[C] $ hledger -f foo.ssv print \f[R] .fi .PP or: .IP .nf \f[C] $ cat foo | hledger -f ssv:- foo \f[R] .fi .PP You can override the file extension with a separator rule if needed. See also: Input files in the hledger manual. .SS Reading multiple CSV files .PP If you use multiple \f[C]-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[C]--rules-file\f[R] option, that rules file will be used for all the CSV files. .SS Valid transactions .PP 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 .nf \f[C] $ hledger -f file.csv print | hledger -f- print \f[R] .fi .SS Deduplicating, importing .PP 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[C].latest.FILE.csv\f[R] file.) This is the easiest way to import CSV data. Eg: .IP .nf \f[C] # download the latest CSV files, then run this command. # Note, no -f flags needed here. $ hledger import *.csv [--dry] \f[R] .fi .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 -> sidebar -> real world setups .IP \[bu] 2 https://plaintextaccounting.org -> data import/conversion .SS Setting amounts .PP A posting amount can be set in one of these ways: .IP \[bu] 2 by assigning (with a fields list or field assignment) to \f[C]amountN\f[R] (posting N\[aq]s amount) or \f[C]amount\f[R] (posting 1\[aq]s amount) .IP \[bu] 2 by assigning to \f[C]amountN-in\f[R] and \f[C]amountN-out\f[R] (or \f[C]amount-in\f[R] and \f[C]amount-out\f[R]). For each CSV record, whichever of these has a non-zero value will be used, with appropriate sign. If both contain a non-zero value, this may not work. .IP \[bu] 2 by assigning to \f[C]balanceN\f[R] (or \f[C]balance\f[R]) instead of the above, setting the amount indirectly via a balance assignment. If you do this the default account name may be wrong, so you should set that explicitly. .PP There is some special handling for an amount\[aq]s sign: .IP \[bu] 2 If an amount value is parenthesised, it will be de-parenthesised and sign-flipped. .IP \[bu] 2 If an amount value begins with a double minus sign, those cancel out and are removed. .IP \[bu] 2 If an amount value begins with a plus sign, that will be removed .SS Setting currency/commodity .PP If the currency/commodity symbol is included in the CSV\[aq]s amount field(s), you don\[aq]t have to do anything special. .PP If the currency is provided as a separate CSV field, you can either: .IP \[bu] 2 assign that to \f[C]currency\f[R], which adds it to all posting amounts. The symbol will prepended to the amount quantity (on the left side). If you write a trailing space after the symbol, there will be a space between symbol and amount (an exception to the usual whitespace stripping). .IP \[bu] 2 or assign it to \f[C]currencyN\f[R] which adds it to posting N\[aq]s amount only. .IP \[bu] 2 or for more control, construct the amount from symbol and quantity using field assignment, eg: .RS 2 .IP .nf \f[C] fields date,description,currency,quantity # add currency symbol on the right: amount %quantity %currency \f[R] .fi .RE .SS Referencing other fields .PP 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 .nf \f[C] # 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 \f[R] .fi .PP Here, since there\[aq]s no CSV amount1 field, %amount1 will produce a literal \[dq]amount1\[dq]: .IP .nf \f[C] fields date,description,csvamount amount1 %csvamount USD # Can\[aq]t interpolate amount1 here comment %amount1 \f[R] .fi .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 .nf \f[C] comment A comment B if something comment C \f[R] .fi .SS How CSV rules are evaluated .PP Here\[aq]s how to think of CSV rules being evaluated (if you really need to). First, .IP \[bu] 2 \f[C]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[C]skip\f[R] (at top level) .IP \[bu] 2 \f[C]date-format\f[R] .IP \[bu] 2 \f[C]newest-first\f[R] .IP \[bu] 2 \f[C]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[C]if\f[R] blocks. If any of them contain a \f[C]end\f[R] rule, skip all remaining CSV records. Otherwise if any of them contain a \f[C]skip\f[R] rule, skip that many CSV records. If there are multiple matched \f[C]skip\f[R] rules, the first one wins. .IP \[bu] 2 collect all field assignments at top level and in matched \f[C]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 %CSVFIELDNAME references), or a default .IP \[bu] 2 generate a synthetic hledger transaction 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. .SH "REPORTING BUGS" Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) .SH AUTHORS Simon Michael and contributors .SH COPYRIGHT Copyright (C) 2007-2019 Simon Michael. .br Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5), ledger(1) http://hledger.org hledger-1.19.1/embeddedfiles/hledger_csv.txt0000644000000000000000000012017513725533425017224 0ustar0000000000000000 hledger_csv(5) hledger User Manuals hledger_csv(5) NAME CSV - how hledger reads CSV data, and the CSV rules file format DESCRIPTION hledger can read CSV files (Character Separated Value - usually comma, semicolon, or tab) containing dated records as if they were journal files, automatically converting each CSV record into a transaction. (To learn about writing CSV, see CSV output.) We describe each CSV file's format with a corresponding rules file. By default this is named like the CSV file with a .rules extension added. Eg when reading FILE.csv, hledger also looks for FILE.csv.rules in the same directory as FILE.csv. You can specify a different rules file with the --rules-file option. If a rules file is not found, hledger will create a sample rules file, which you'll need to adjust. This file contains rules describing the CSV data (header line, fields layout, date format etc.), and how to construct hledger journal entries (transactions) from it. Often there will also be a list of conditional rules for categorising transactions based on their descriptions. Here's an overview of the CSV rules; these are described more fully be- low, after the examples: skip skip one or more header lines or matched CSV records fields name CSV fields, assign them to hledger fields field assignment assign a value to one hledger field, with interpolation separator a custom field separator if block apply some rules to CSV records matched by patterns if table apply some rules to CSV records matched by patterns, alternate syntax end skip the remaining CSV records date-format describe the format of CSV dates newest-first disambiguate record order when there's only one date include inline another CSV rules file balance-type choose which type of balance assignments to use Note, for best error messages when reading CSV files, use a .csv, .tsv or .ssv file extension or file prefix - see File Extension below. There's an introductory Convert CSV files tutorial on hledger.org. EXAMPLES Here are some sample hledger CSV rules files. See also the full col- lection at: https://github.com/simonmichael/hledger/tree/master/examples/csv Basic 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 Default account names are chosen, since we didn't set them. 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. 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: CSV RULES The following kinds of rule can appear in the rules file, in any order. Blank lines and lines beginning with # or ; are ignored. skip skip N The word "skip" followed by a number (or no number, meaning 1) tells hledger to ignore this many non-empty lines preceding the CSV data. (Empty/blank lines are skipped automatically.) You'll need this when- ever your CSV data contains header lines. It also has a second purpose: it can be used inside if blocks to ignore certain CSV records (described below). fields fields FIELDNAME1, FIELDNAME2, ... A fields list (the word "fields" followed by comma-separated field names) is the quick way to assign CSV field values to hledger fields. It does two things: 1. it names the CSV fields. This is optional, but can be convenient later for interpolating them. 2. when you use a standard hledger field name, it assigns the CSV value to that part of the hledger 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 Field names may not contain whitespace. Fields you don't care about can be left unnamed. Currently there must be least two items (there must be at least one comma). Note, always use comma in the fields list, even if your CSV uses an- other separator character. Here are the standard hledger field/pseudo-field names. For more about the transaction parts they refer to, see the manual for hledger's jour- nal format. Transaction field names date, date2, status, code, description, comment can be used to form the transaction's first line. Posting field names account accountN, where N is 1 to 99, causes a posting to be generated, with that account name. 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, and in conditional blocks. 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 amountN sets posting N's amount. If the CSV uses separate fields for inflows and outflows, you can use amountN-in and amountN-out instead. By assigning to amount1, amount2, ... etc. you can generate anywhere from 0 to 99 postings. There is also an older, unnumbered form of these names, suitable for 2-posting transactions, which sets both posting 1's and (negated) post- ing 2's amount: amount, or amount-in and amount-out. This is still supported because it keeps pre-hledger-1.17 csv rules files working, and because it can be more succinct, and because it converts posting 2's amount to cost if there's a transaction price, which can be useful. If you have an existing rules file using the unnumbered form, you might want to use the numbered form in certain conditional blocks, without having to update and retest all the old rules. To facilitate this, posting 1 ignores amount/amount-in/amount-out if any of amount1/amount1-in/amount1-out are assigned, and posting 2 ignores them if any of amount2/amount2-in/amount2-out are assigned, avoiding con- flicts. currency If the CSV has the currency symbol in a separate field (ie, not part of the amount field), you can use currencyN to prepend it to posting N's amount. Or, currency with no number affects all postings. balance balanceN sets a balance assertion amount (or if the posting amount is left empty, a balance assignment) on posting N. Also, for compatibility with hledger <1.17: balance with no number is equivalent to balance1. You can adjust the type of assertion/assignment with the balance-type rule (see below). comment Finally, commentN sets a comment on the Nth posting. Comments can also contain tags, as usual. See TIPS below for more about setting amounts and currency. field assignment HLEDGERFIELDNAME FIELDVALUE Instead of or in addition to a fields list, you can use a "field as- signment" rule to set the value of a single hledger field, by writing its name (any of the standard hledger field names above) followed by a text value. The value may contain interpolated CSV fields, referenced by their 1-based position in the CSV record (%N), or by the name they were given in the fields list (%CSVFIELDNAME). 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 Interpolation strips outer whitespace (so a CSV value like " 1 " be- comes 1 when interpolated) (#1051). See TIPS below for more about ref- erencing other fields. 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. if block if MATCHER RULE if MATCHER MATCHER MATCHER RULE RULE Conditional blocks ("if blocks") are a block of rules that are applied only to CSV records which match certain patterns. They are often used for customising account names based on transaction descriptions. Matching the whole record Each MATCHER can be a record matcher, which looks like this: REGEX REGEX is a case-insensitive regular expression which tries to match anywhere within the CSV record. It is a POSIX ERE (extended regular expression) that also supports GNU word boundaries (\b, \B, \<, \>), and nothing else. If you have trouble, be sure to check our https://hledger.org/hledger.html#regular-expressions doc. Important note: the record that is matched is not the original record, but a synthetic one, with any enclosing double quotes (but not enclos- ing whitespace) removed, and always comma-separated (which means that a field containing a comma will appear like two fields). Eg, if the original record is 2020-01-01; "Acme, Inc."; 1,000, the REGEX will ac- tually see 2020-01-01,Acme, Inc., 1,000). Matching individual fields Or, MATCHER can be a field matcher, like this: %CSVFIELD REGEX which matches just the content of a particular CSV field. CSVFIELD is a percent sign followed by the field's name or column number, like %date or %1. Combining matchers A single matcher can be written on the same line as the "if"; or multi- ple matchers can be written on the following lines, non-indented. Mul- tiple matchers are OR'd (any one of them can match), unless one begins with an & symbol, in which case it is AND'ed with the previous matcher. if MATCHER & MATCHER RULE Rules applied on successful match After the patterns there should be one or more rules to apply, all in- dented by at least one space. Three kinds of rule are allowed in con- ditional blocks: o field assignments (to set a hledger field) o skip (to skip the matched CSV record) o end (to skip all remaining CSV records). Examples: # if the CSV record contains "groceries", set account2 to "expenses:groceries" if groceries account2 expenses:groceries # if the CSV record contains any of these patterns, set account2 and comment as shown if monthly service fee atm transaction fee banking thru software account2 expenses:business:banking comment XXX deductible ? check it if table if,CSVFIELDNAME1,CSVFIELDNAME2,...,CSVFIELDNAMEn MATCHER1,VALUE11,VALUE12,...,VALUE1n MATCHER2,VALUE21,VALUE22,...,VALUE2n MATCHER3,VALUE31,VALUE32,...,VALUE3n Conditional tables ("if tables") are a different syntax to specify field assignments that will be applied only to CSV records which match certain patterns. MATCHER could be either field or record matcher, as described above. When MATCHER matches, values from that row would be assigned to the CSV fields named on the if line, in the same order. Therefore if table is exactly equivalent to a sequence of of if blocks: if MATCHER1 CSVFIELDNAME1 VALUE11 CSVFIELDNAME2 VALUE12 ... CSVFIELDNAMEn VALUE1n if MATCHER2 CSVFIELDNAME1 VALUE21 CSVFIELDNAME2 VALUE22 ... CSVFIELDNAMEn VALUE2n if MATCHER3 CSVFIELDNAME1 VALUE31 CSVFIELDNAME2 VALUE32 ... CSVFIELDNAMEn VALUE3n Each line starting with MATCHER should contain enough (possibly empty) values for all the listed fields. Rules would be checked and applied in the order they are listed in the table and, like with if blocks, later rules (in the same or another ta- ble) or if blocks could override the effect of any rule. Instead of ',' you can use a variety of other non-alphanumeric charac- ters as a separator. First character after if is taken to be the sepa- rator for the rest of the table. It is the responsibility of the user to ensure that separator does not occur inside MATCHERs and values - there is no way to escape separator. Example: if,account2,comment atm transaction fee,expenses:business:banking,deductible? check it %description groceries,expenses:groceries, 2020/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call-out end This rule can be used inside if blocks (only), to make hledger stop reading this CSV file and move on to the next input file, or to command execution. Eg: # ignore everything following the first empty record if ,,,, end 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 date parsing pattern, which 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 For the supported strptime syntax, see: https://hackage.haskell.org/package/time/docs/Data-Time-For- mat.html#v:formatTime newest-first hledger always sorts the generated transactions by date. Transactions on the same date should appear in the same order as their CSV records, as hledger can usually auto-detect whether the CSV's normal order is oldest first or newest first. But if all of the following are true: o the CSV might sometimes contain just one day of data (all records having the same date) o the CSV records are normally in reverse chronological order (newest at the top) o and you care about preserving the order of same-day transactions then, you should add the newest-first rule as a hint. Eg: # tell hledger explicitly that the CSV is normally newest first newest-first 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 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 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 http://eradman.com/entr- project : $ 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 hledger accepts CSV conforming to RFC 4180. When CSV values are en- closed in quotes, note: o they must be double quotes (not single quotes) o spaces outside the quotes are not allowed File Extension To help hledger identify the format and show the right error messages, CSV/SSV/TSV files should normally be named with a .csv, .ssv or .tsv filename extension. Or, the file path should be prefixed with csv:, ssv: or tsv:. Eg: $ hledger -f foo.ssv print or: $ cat foo | hledger -f ssv:- foo You can override the file extension with a separator rule if needed. See also: Input files in the hledger manual. 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. 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 -> sidebar -> real world setups o https://plaintextaccounting.org -> data import/conversion Setting amounts A posting amount can be set in one of these ways: o by assigning (with a fields list or field assignment) to amountN (posting N's amount) or amount (posting 1's amount) o by assigning to amountN-in and amountN-out (or amount-in and amount- out). For each CSV record, whichever of these has a non-zero value will be used, with appropriate sign. If both contain a non-zero value, this may not work. o by assigning to balanceN (or balance) instead of the above, setting the amount indirectly via a balance assignment. If you do this the default account name may be wrong, so you should set that explicitly. There is some special handling for an amount's sign: o If an amount value is parenthesised, it will be de-parenthesised and sign-flipped. o If an amount value begins with a double minus sign, those cancel out and are removed. o If an amount value begins with a plus sign, that will be removed Setting currency/commodity If the currency/commodity symbol is included in the CSV's amount field(s), you don't have to do anything special. If the currency is provided as a separate CSV field, you can either: o assign that to currency, which adds it to all posting amounts. The symbol will prepended to the amount quantity (on the left side). If you write a trailing space after the symbol, there will be a space between symbol and amount (an exception to the usual whitespace stripping). o or assign it to currencyN which adds it to posting N's amount only. o or for more control, construct the amount from symbol and quantity using field assignment, eg: fields date,description,currency,quantity # add currency symbol on the right: amount %quantity %currency 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 %CSVFIELDNAME references), or a de- fault o generate a synthetic hledger transaction 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. REPORTING BUGS Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) AUTHORS Simon Michael and contributors COPYRIGHT Copyright (C) 2007-2019 Simon Michael. Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), hledger-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_time- dot(5), ledger(1) http://hledger.org hledger 1.18.99 September 2020 hledger_csv(5) hledger-1.19.1/embeddedfiles/hledger_csv.info0000644000000000000000000012165313725533425017342 0ustar0000000000000000This is hledger_csv.info, produced by makeinfo version 6.7 from stdin.  File: hledger_csv.info, Node: Top, Next: EXAMPLES, Up: (dir) hledger_csv(5) hledger 1.18.99 ****************************** CSV - how hledger reads CSV data, and the CSV rules file format hledger can read CSV files (Character Separated Value - usually comma, semicolon, or tab) containing dated records as if they were journal files, automatically converting each CSV record into a transaction. (To learn about _writing_ CSV, see CSV output.) We describe each CSV file's format with a corresponding _rules file_. By default this is named like the CSV file with a '.rules' extension added. Eg when reading 'FILE.csv', hledger also looks for 'FILE.csv.rules' in the same directory as 'FILE.csv'. You can specify a different rules file with the '--rules-file' option. If a rules file is not found, hledger will create a sample rules file, which you'll need to adjust. This file contains rules describing the CSV data (header line, fields layout, date format etc.), and how to construct hledger journal entries (transactions) from it. Often there will also be a list of conditional rules for categorising transactions based on their descriptions. Here's an overview of the CSV rules; these are described more fully below, after the examples: *'skip'* skip one or more header lines or matched CSV records *'fields'* name CSV fields, assign them to hledger fields *field assignment* assign a value to one hledger field, with interpolation *'separator'* a custom field separator *'if' block* apply some rules to CSV records matched by patterns *'if' table* apply some rules to CSV records matched by patterns, alternate syntax *'end'* skip the remaining CSV records *'date-format'* describe the format of CSV dates *'newest-first'* disambiguate record order when there's only one date *'include'* inline another CSV rules file *'balance-type'* choose which type of balance assignments to use Note, for best error messages when reading CSV files, use a '.csv', '.tsv' or '.ssv' file extension or file prefix - see File Extension below. There's an introductory Convert CSV files tutorial on hledger.org. * Menu: * EXAMPLES:: * CSV RULES:: * TIPS::  File: hledger_csv.info, Node: EXAMPLES, Next: CSV RULES, Prev: Top, Up: Top 1 EXAMPLES ********** Here are some sample hledger CSV rules files. See also the full collection at: https://github.com/simonmichael/hledger/tree/master/examples/csv * Menu: * Basic:: * Bank of Ireland:: * Amazon:: * Paypal::  File: hledger_csv.info, Node: Basic, Next: Bank of Ireland, Up: EXAMPLES 1.1 Basic ========= 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 Default account names are chosen, since we didn't set them.  File: hledger_csv.info, Node: Bank of Ireland, Next: Amazon, Prev: Basic, Up: EXAMPLES 1.2 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_csv.info, Node: Amazon, Next: Paypal, Prev: Bank of Ireland, Up: EXAMPLES 1.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_csv.info, Node: Paypal, Prev: Amazon, Up: EXAMPLES 1.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_csv.info, Node: CSV RULES, Next: TIPS, Prev: EXAMPLES, Up: Top 2 CSV RULES *********** The following kinds of rule can appear in the rules file, in any order. Blank lines and lines beginning with '#' or ';' are ignored. * Menu: * skip:: * fields:: * field assignment:: * separator:: * if block:: * if table:: * end:: * date-format:: * newest-first:: * include:: * balance-type::  File: hledger_csv.info, Node: skip, Next: fields, Up: CSV RULES 2.1 'skip' ========== skip N The word "skip" followed by a number (or no number, meaning 1) tells hledger to ignore this many non-empty lines preceding the CSV data. (Empty/blank lines are skipped automatically.) You'll need this whenever your CSV data contains header lines. It also has a second purpose: it can be used inside if blocks to ignore certain CSV records (described below).  File: hledger_csv.info, Node: fields, Next: field assignment, Prev: skip, Up: CSV RULES 2.2 'fields' ============ fields FIELDNAME1, FIELDNAME2, ... A fields list (the word "fields" followed by comma-separated field names) is the quick way to assign CSV field values to hledger fields. It does two things: 1. it names the CSV fields. This is optional, but can be convenient later for interpolating them. 2. when you use a standard hledger field name, it assigns the CSV value to that part of the hledger 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 Field names may not contain whitespace. Fields you don't care about can be left unnamed. Currently there must be least two items (there must be at least one comma). Note, always use comma in the fields list, even if your CSV uses another separator character. Here are the standard hledger field/pseudo-field names. For more about the transaction parts they refer to, see the manual for hledger's journal format. * Menu: * Transaction field names:: * Posting field names::  File: hledger_csv.info, Node: Transaction field names, Next: Posting field names, Up: fields 2.2.1 Transaction field names ----------------------------- 'date', 'date2', 'status', 'code', 'description', 'comment' can be used to form the transaction's first line.  File: hledger_csv.info, Node: Posting field names, Prev: Transaction field names, Up: fields 2.2.2 Posting field names ------------------------- * Menu: * account:: * amount:: * currency:: * balance:: * comment::  File: hledger_csv.info, Node: account, Next: amount, Up: Posting field names 2.2.2.1 account ............... 'accountN', where N is 1 to 99, causes a posting to be generated, with that account name. 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, and in conditional blocks. 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_csv.info, Node: amount, Next: currency, Prev: account, Up: Posting field names 2.2.2.2 amount .............. 'amountN' sets posting N's amount. If the CSV uses separate fields for inflows and outflows, you can use 'amountN-in' and 'amountN-out' instead. By assigning to 'amount1', 'amount2', ... etc. you can generate anywhere from 0 to 99 postings. There is also an older, unnumbered form of these names, suitable for 2-posting transactions, which sets both posting 1's and (negated) posting 2's amount: 'amount', or 'amount-in' and 'amount-out'. This is still supported because it keeps pre-hledger-1.17 csv rules files working, and because it can be more succinct, and because it converts posting 2's amount to cost if there's a transaction price, which can be useful. If you have an existing rules file using the unnumbered form, you might want to use the numbered form in certain conditional blocks, without having to update and retest all the old rules. To facilitate this, posting 1 ignores 'amount'/'amount-in'/'amount-out' if any of 'amount1'/'amount1-in'/'amount1-out' are assigned, and posting 2 ignores them if any of 'amount2'/'amount2-in'/'amount2-out' are assigned, avoiding conflicts.  File: hledger_csv.info, Node: currency, Next: balance, Prev: amount, Up: Posting field names 2.2.2.3 currency ................ If the CSV has the currency symbol in a separate field (ie, not part of the amount field), you can use 'currencyN' to prepend it to posting N's amount. Or, 'currency' with no number affects all postings.  File: hledger_csv.info, Node: balance, Next: comment, Prev: currency, Up: Posting field names 2.2.2.4 balance ............... 'balanceN' sets a balance assertion amount (or if the posting amount is left empty, a balance assignment) on posting N. Also, for compatibility with hledger <1.17: 'balance' with no number is equivalent to 'balance1'. You can adjust the type of assertion/assignment with the 'balance-type' rule (see below).  File: hledger_csv.info, Node: comment, Prev: balance, Up: Posting field names 2.2.2.5 comment ............... Finally, 'commentN' sets a comment on the Nth posting. Comments can also contain tags, as usual. See TIPS below for more about setting amounts and currency.  File: hledger_csv.info, Node: field assignment, Next: separator, Prev: fields, Up: CSV RULES 2.3 field assignment ==================== HLEDGERFIELDNAME FIELDVALUE Instead of or in addition to a fields list, you can use a "field assignment" rule to set the value of a single hledger field, by writing its name (any of the standard hledger field names above) followed by a text value. The value may contain interpolated CSV fields, referenced by their 1-based position in the CSV record ('%N'), or by the name they were given in the fields list ('%CSVFIELDNAME'). 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 Interpolation strips outer whitespace (so a CSV value like '" 1 "' becomes '1' when interpolated) (#1051). See TIPS below for more about referencing other fields.  File: hledger_csv.info, Node: separator, Next: if block, Prev: field assignment, Up: CSV RULES 2.4 '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_csv.info, Node: if block, Next: if table, Prev: separator, Up: CSV RULES 2.5 'if' block ============== if MATCHER RULE if MATCHER MATCHER MATCHER RULE RULE Conditional blocks ("if blocks") are a block of rules that are applied only to CSV records which match certain patterns. They are often used for customising account names based on transaction descriptions. * Menu: * Matching the whole record:: * Matching individual fields:: * Combining matchers:: * Rules applied on successful match::  File: hledger_csv.info, Node: Matching the whole record, Next: Matching individual fields, Up: if block 2.5.1 Matching the whole record ------------------------------- Each MATCHER can be a record matcher, which looks like this: REGEX REGEX is a case-insensitive regular expression which tries to match anywhere within the CSV record. It is a POSIX ERE (extended regular expression) that also supports GNU word boundaries ('\b', '\B', '\<', '\>'), and nothing else. If you have trouble, be sure to check our https://hledger.org/hledger.html#regular-expressions doc. Important note: the record that is matched is not the original record, but a synthetic one, with any enclosing double quotes (but not enclosing whitespace) removed, and always comma-separated (which means that a field containing a comma will appear like two fields). Eg, if the original record is '2020-01-01; "Acme, Inc."; 1,000', the REGEX will actually see '2020-01-01,Acme, Inc., 1,000').  File: hledger_csv.info, Node: Matching individual fields, Next: Combining matchers, Prev: Matching the whole record, Up: if block 2.5.2 Matching individual fields -------------------------------- Or, MATCHER can be a field matcher, like this: %CSVFIELD REGEX which matches just the content of a particular CSV field. CSVFIELD is a percent sign followed by the field's name or column number, like '%date' or '%1'.  File: hledger_csv.info, Node: Combining matchers, Next: Rules applied on successful match, Prev: Matching individual fields, Up: if block 2.5.3 Combining matchers ------------------------ A single matcher can be written on the same line as the "if"; or multiple matchers can be written on the following lines, non-indented. Multiple matchers are OR'd (any one of them can match), unless one begins with an '&' symbol, in which case it is AND'ed with the previous matcher. if MATCHER & MATCHER RULE  File: hledger_csv.info, Node: Rules applied on successful match, Prev: Combining matchers, Up: if block 2.5.4 Rules applied on successful match --------------------------------------- After the patterns there should be one or more rules to apply, all indented by at least one space. Three kinds of rule are allowed in conditional blocks: * field assignments (to set a hledger field) * skip (to skip the matched CSV record) * end (to skip all remaining CSV records). Examples: # if the CSV record contains "groceries", set account2 to "expenses:groceries" if groceries account2 expenses:groceries # if the CSV record contains any of these patterns, set account2 and comment as shown if monthly service fee atm transaction fee banking thru software account2 expenses:business:banking comment XXX deductible ? check it  File: hledger_csv.info, Node: if table, Next: end, Prev: if block, Up: CSV RULES 2.6 'if' table ============== if,CSVFIELDNAME1,CSVFIELDNAME2,...,CSVFIELDNAMEn MATCHER1,VALUE11,VALUE12,...,VALUE1n MATCHER2,VALUE21,VALUE22,...,VALUE2n MATCHER3,VALUE31,VALUE32,...,VALUE3n Conditional tables ("if tables") are a different syntax to specify field assignments that will be applied only to CSV records which match certain patterns. MATCHER could be either field or record matcher, as described above. When MATCHER matches, values from that row would be assigned to the CSV fields named on the 'if' line, in the same order. Therefore 'if' table is exactly equivalent to a sequence of of 'if' blocks: if MATCHER1 CSVFIELDNAME1 VALUE11 CSVFIELDNAME2 VALUE12 ... CSVFIELDNAMEn VALUE1n if MATCHER2 CSVFIELDNAME1 VALUE21 CSVFIELDNAME2 VALUE22 ... CSVFIELDNAMEn VALUE2n if MATCHER3 CSVFIELDNAME1 VALUE31 CSVFIELDNAME2 VALUE32 ... CSVFIELDNAMEn VALUE3n Each line starting with MATCHER should contain enough (possibly empty) values for all the listed fields. Rules would be checked and applied in the order they are listed in the table and, like with 'if' blocks, later rules (in the same or another table) or 'if' blocks could override the effect of any rule. Instead of ',' you can use a variety of other non-alphanumeric characters as a separator. First character after 'if' is taken to be the separator for the rest of the table. It is the responsibility of the user to ensure that separator does not occur inside MATCHERs and values - there is no way to escape separator. Example: if,account2,comment atm transaction fee,expenses:business:banking,deductible? check it %description groceries,expenses:groceries, 2020/01/12.*Plumbing LLC,expenses:house:upkeep,emergency plumbing call-out  File: hledger_csv.info, Node: end, Next: date-format, Prev: if table, Up: CSV RULES 2.7 'end' ========= This rule can be used inside if blocks (only), to make hledger stop reading this CSV file and move on to the next input file, or to command execution. Eg: # ignore everything following the first empty record if ,,,, end  File: hledger_csv.info, Node: date-format, Next: newest-first, Prev: end, Up: CSV RULES 2.8 '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 date parsing pattern, which 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 For the supported strptime syntax, see: https://hackage.haskell.org/package/time/docs/Data-Time-Format.html#v:formatTime  File: hledger_csv.info, Node: newest-first, Next: include, Prev: date-format, Up: CSV RULES 2.9 'newest-first' ================== hledger always sorts the generated transactions by date. Transactions on the same date should appear in the same order as their CSV records, as hledger can usually auto-detect whether the CSV's normal order is oldest first or newest first. But if all of the following are true: * the CSV might sometimes contain just one day of data (all records having the same date) * the CSV records are normally in reverse chronological order (newest at the top) * and you care about preserving the order of same-day transactions then, you should add the 'newest-first' rule as a hint. Eg: # tell hledger explicitly that the CSV is normally newest first newest-first  File: hledger_csv.info, Node: include, Next: balance-type, Prev: newest-first, Up: CSV RULES 2.10 '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_csv.info, Node: balance-type, Prev: include, Up: CSV RULES 2.11 '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_csv.info, Node: TIPS, Prev: CSV RULES, Up: Top 3 TIPS ****** * Menu: * Rapid feedback:: * Valid CSV:: * File Extension:: * Reading multiple CSV files:: * Valid transactions:: * Deduplicating importing:: * Setting amounts:: * Setting currency/commodity:: * Referencing other fields:: * How CSV rules are evaluated::  File: hledger_csv.info, Node: Rapid feedback, Next: Valid CSV, Up: TIPS 3.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 http://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_csv.info, Node: Valid CSV, Next: File Extension, Prev: Rapid feedback, Up: TIPS 3.2 Valid CSV ============= hledger accepts CSV conforming to RFC 4180. When CSV values are enclosed in quotes, note: * they must be double quotes (not single quotes) * spaces outside the quotes are not allowed  File: hledger_csv.info, Node: File Extension, Next: Reading multiple CSV files, Prev: Valid CSV, Up: TIPS 3.3 File Extension ================== To help hledger identify the format and show the right error messages, CSV/SSV/TSV files should normally be named with a '.csv', '.ssv' or '.tsv' filename extension. Or, the file path should be prefixed with 'csv:', 'ssv:' or 'tsv:'. Eg: $ hledger -f foo.ssv print or: $ cat foo | hledger -f ssv:- foo You can override the file extension with a separator rule if needed. See also: Input files in the hledger manual.  File: hledger_csv.info, Node: Reading multiple CSV files, Next: Valid transactions, Prev: File Extension, Up: TIPS 3.4 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_csv.info, Node: Valid transactions, Next: Deduplicating importing, Prev: Reading multiple CSV files, Up: TIPS 3.5 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_csv.info, Node: Deduplicating importing, Next: Setting amounts, Prev: Valid transactions, Up: TIPS 3.6 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 -> sidebar -> real world setups * https://plaintextaccounting.org -> data import/conversion  File: hledger_csv.info, Node: Setting amounts, Next: Setting currency/commodity, Prev: Deduplicating importing, Up: TIPS 3.7 Setting amounts =================== A posting amount can be set in one of these ways: * by assigning (with a fields list or field assignment) to 'amountN' (posting N's amount) or 'amount' (posting 1's amount) * by assigning to 'amountN-in' and 'amountN-out' (or 'amount-in' and 'amount-out'). For each CSV record, whichever of these has a non-zero value will be used, with appropriate sign. If both contain a non-zero value, this may not work. * by assigning to 'balanceN' (or 'balance') instead of the above, setting the amount indirectly via a balance assignment. If you do this the default account name may be wrong, so you should set that explicitly. There is some special handling for an amount's sign: * If an amount value is parenthesised, it will be de-parenthesised and sign-flipped. * If an amount value begins with a double minus sign, those cancel out and are removed. * If an amount value begins with a plus sign, that will be removed  File: hledger_csv.info, Node: Setting currency/commodity, Next: Referencing other fields, Prev: Setting amounts, Up: TIPS 3.8 Setting currency/commodity ============================== If the currency/commodity symbol is included in the CSV's amount field(s), you don't have to do anything special. If the currency is provided as a separate CSV field, you can either: * assign that to 'currency', which adds it to all posting amounts. The symbol will prepended to the amount quantity (on the left side). If you write a trailing space after the symbol, there will be a space between symbol and amount (an exception to the usual whitespace stripping). * or assign it to 'currencyN' which adds it to posting N's amount only. * or for more control, construct the amount from symbol and quantity using field assignment, eg: fields date,description,currency,quantity # add currency symbol on the right: amount %quantity %currency  File: hledger_csv.info, Node: Referencing other fields, Next: How CSV rules are evaluated, Prev: Setting currency/commodity, Up: TIPS 3.9 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_csv.info, Node: How CSV rules are evaluated, Prev: Referencing other fields, Up: TIPS 3.10 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 %CSVFIELDNAME references), or a default * generate a synthetic hledger transaction 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.  Tag Table: Node: Top72 Node: EXAMPLES2677 Ref: #examples2783 Node: Basic2991 Ref: #basic3091 Node: Bank of Ireland3633 Ref: #bank-of-ireland3768 Node: Amazon5230 Ref: #amazon5348 Node: Paypal7067 Ref: #paypal7161 Node: CSV RULES14805 Ref: #csv-rules14914 Node: skip15209 Ref: #skip15302 Node: fields15677 Ref: #fields15799 Node: Transaction field names16964 Ref: #transaction-field-names17124 Node: Posting field names17235 Ref: #posting-field-names17387 Node: account17457 Ref: #account17573 Node: amount18110 Ref: #amount18241 Node: currency19348 Ref: #currency19483 Node: balance19689 Ref: #balance19823 Node: comment20140 Ref: #comment20257 Node: field assignment20420 Ref: #field-assignment20563 Node: separator21381 Ref: #separator21516 Node: if block22056 Ref: #if-block22181 Node: Matching the whole record22582 Ref: #matching-the-whole-record22757 Node: Matching individual fields23561 Ref: #matching-individual-fields23765 Node: Combining matchers23989 Ref: #combining-matchers24185 Node: Rules applied on successful match24498 Ref: #rules-applied-on-successful-match24689 Node: if table25343 Ref: #if-table25462 Node: end27200 Ref: #end27312 Node: date-format27536 Ref: #date-format27668 Node: newest-first28417 Ref: #newest-first28555 Node: include29238 Ref: #include29369 Node: balance-type29813 Ref: #balance-type29933 Node: TIPS30633 Ref: #tips30715 Node: Rapid feedback30971 Ref: #rapid-feedback31088 Node: Valid CSV31548 Ref: #valid-csv31678 Node: File Extension31870 Ref: #file-extension32022 Node: Reading multiple CSV files32451 Ref: #reading-multiple-csv-files32636 Node: Valid transactions32877 Ref: #valid-transactions33055 Node: Deduplicating importing33683 Ref: #deduplicating-importing33862 Node: Setting amounts34895 Ref: #setting-amounts35064 Node: Setting currency/commodity36051 Ref: #setting-currencycommodity36243 Node: Referencing other fields37046 Ref: #referencing-other-fields37246 Node: How CSV rules are evaluated38143 Ref: #how-csv-rules-are-evaluated38316  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.19.1/embeddedfiles/hledger_timeclock.50000644000000000000000000000535313725533425017730 0ustar0000000000000000 .TH "hledger_timeclock" "5" "September 2020" "hledger 1.18.99" "hledger User Manuals" .SH NAME .PP Timeclock - the time logging format of timeclock.el, as read by hledger .SH DESCRIPTION .PP hledger can read timeclock files. 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). .IP .nf \f[C] i 2015/03/30 09:00:00 some:account name optional description after two spaces o 2015/03/30 09:20:00 i 2015/03/31 22:21:45 another account o 2015/04/01 02:00:34 \f[R] .fi .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[C]hledger print\f[R] generates these journal entries: .IP .nf \f[C] $ hledger -f t.timeclock print 2015-03-30 * optional description after two spaces (some:account name) 0.33h 2015-03-31 * 22:21-23:59 (another account) 1.64h 2015-04-01 * 00:00-02:00 (another account) 2.01h \f[R] .fi .PP Here is a sample.timeclock to download and some queries to try: .IP .nf \f[C] $ 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 \f[R] .fi .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[C]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[C]ti\f[R] and \f[C]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. .SH "REPORTING BUGS" Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) .SH AUTHORS Simon Michael and contributors .SH COPYRIGHT Copyright (C) 2007-2019 Simon Michael. .br Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5), ledger(1) http://hledger.org hledger-1.19.1/embeddedfiles/hledger_timeclock.txt0000644000000000000000000000601313725533425020375 0ustar0000000000000000 hledger_timeclock(5) hledger User Manuals hledger_timeclock(5) NAME Timeclock - the time logging format of timeclock.el, as read by hledger DESCRIPTION hledger can read timeclock files. 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). i 2015/03/30 09:00:00 some:account name optional description after two spaces 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 two spaces (some:account name) 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 timeclock- 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. REPORTING BUGS Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) AUTHORS Simon Michael and contributors COPYRIGHT Copyright (C) 2007-2019 Simon Michael. Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), hledger-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_time- dot(5), ledger(1) http://hledger.org hledger 1.18.99 September 2020 hledger_timeclock(5) hledger-1.19.1/embeddedfiles/hledger_timeclock.info0000644000000000000000000000445613725533425020522 0ustar0000000000000000This is hledger_timeclock.info, produced by makeinfo version 6.7 from stdin.  File: hledger_timeclock.info, Node: Top, Up: (dir) hledger_timeclock(5) hledger 1.18.99 ************************************ Timeclock - the time logging format of timeclock.el, as read by hledger hledger can read timeclock files. 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). i 2015/03/30 09:00:00 some:account name optional description after two spaces 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 two spaces (some:account name) 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.  Tag Table: Node: Top78  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.19.1/embeddedfiles/hledger_timedot.50000644000000000000000000001176213725533425017424 0ustar0000000000000000 .TH "hledger_timedot" "5" "September 2020" "hledger 1.18.99" "hledger User Manuals" .SH NAME .PP Timedot - hledger\[aq]s human-friendly time logging format .SH DESCRIPTION .PP Timedot is a plain text format for logging dated, categorised quantities (of time, usually), supported by hledger. It is convenient for approximate and retroactive time logging, eg when the real-time clock-in/out required with a timeclock file is too precise or too interruptive. It can be formatted like a bar chart, making clear at a glance where time was spent. .PP Though called \[dq]timedot\[dq], this format is read by hledger as commodityless quantities, so it could be used to represent dated quantities other than time. In the docs below we\[aq]ll assume it\[aq]s time. .PP A timedot file contains a series of day entries. A day entry begins with a non-indented hledger-style simple date (Y-M-D, Y/M/D, Y.M.D..) Any additional text on the same line is used as a transaction description for this day. .PP This is followed by optionally-indented timelog items for that day, one per line. Each timelog item is a note, usually a hledger:style:account:name representing a time category, followed by two or more spaces, and a quantity. Each timelog item generates a hledger transaction. .PP Quantities can be written as: .IP \[bu] 2 dots: a sequence of dots (.) representing quarter hours. Spaces may optionally be used for grouping. Eg: .... \&.. .IP \[bu] 2 an integral or decimal number, representing hours. Eg: 1.5 .IP \[bu] 2 an integral or decimal number immediately followed by a unit symbol \f[C]s\f[R], \f[C]m\f[R], \f[C]h\f[R], \f[C]d\f[R], \f[C]w\f[R], \f[C]mo\f[R], or \f[C]y\f[R], representing seconds, minutes, hours, days weeks, months or years respectively. Eg: 90m. The following equivalencies are assumed, currently: 1m = 60s, 1h = 60m, 1d = 24h, 1w = 7d, 1mo = 30d, 1y=365d. .PP There is some flexibility allowing notes and todo lists to be kept right in the time log, if needed: .IP \[bu] 2 Blank lines and lines beginning with \f[C]#\f[R] or \f[C];\f[R] are ignored. .IP \[bu] 2 Lines not ending with a double-space and quantity are parsed as items taking no time, which will not appear in balance reports by default. (Add -E to see them.) .IP \[bu] 2 Org mode headlines (lines beginning with one or more \f[C]*\f[R] followed by a space) can be used as date lines or timelog items (the stars are ignored). Also all org headlines before the first date line are ignored. This means org users can manage their timelog as an org outline (eg using org-mode/orgstruct-mode in Emacs), for organisation, faster navigation, controlling visibility etc. .PP Examples: .IP .nf \f[C] # 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 . \f[R] .fi .IP .nf \f[C] 2016/2/3 inc:client1 4 fos:hledger 3 biz:research 1 \f[R] .fi .IP .nf \f[C] * Time log ** 2020-01-01 *** adm:time . *** adm:finance . \f[R] .fi .IP .nf \f[C] * 2020 Work Diary ** Q1 *** 2020-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 \f[R] .fi .PP Reporting: .IP .nf \f[C] $ hledger -f t.timedot print date:2016/2/2 2016-02-02 * (inc:client1) 2.00 2016-02-02 * (biz:research) 0.25 \f[R] .fi .IP .nf \f[C] $ hledger -f t.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 \f[R] .fi .PP I prefer to use period for separating account components. We can make this work with an account alias: .IP .nf \f[C] 2016/2/4 fos.hledger.timedot 4 fos.ledger .. \f[R] .fi .IP .nf \f[C] $ hledger -f t.timedot --alias /\[rs]\[rs]./=: bal date:2016/2/4 4.50 fos 4.00 hledger:timedot 0.50 ledger -------------------- 4.50 \f[R] .fi .PP Here is a sample.timedot. .SH "REPORTING BUGS" Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) .SH AUTHORS Simon Michael and contributors .SH COPYRIGHT Copyright (C) 2007-2019 Simon Michael. .br Released under GNU GPL v3 or later. .SH SEE ALSO hledger(1), hledger\-ui(1), hledger\-web(1), hledger\-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_timedot(5), ledger(1) http://hledger.org hledger-1.19.1/embeddedfiles/hledger_timedot.txt0000644000000000000000000001366113725533425020077 0ustar0000000000000000 hledger_timedot(5) hledger User Manuals hledger_timedot(5) NAME Timedot - hledger's human-friendly time logging format DESCRIPTION Timedot is a plain text format for logging dated, categorised quanti- ties (of time, usually), supported by hledger. It is convenient for approximate and retroactive time logging, eg when the real-time clock- in/out required with a timeclock file is too precise or too interrup- tive. It can be formatted like a bar chart, making clear at a glance where time was spent. Though called "timedot", this format is read by hledger as commodity- less quantities, so it could be used to represent dated quantities other than time. In the docs below we'll assume it's time. A timedot file contains a series of day entries. A day entry begins with a non-indented hledger-style simple date (Y-M-D, Y/M/D, Y.M.D..) Any additional text on the same line is used as a transaction descrip- tion for this day. This is followed by optionally-indented timelog items for that day, one per line. Each timelog item is a note, usually a hledger:style:ac- count:name representing a time category, followed by two or more spa- ces, and a quantity. Each timelog item generates a hledger transac- tion. Quantities can be written as: o dots: a sequence of dots (.) representing quarter hours. Spaces may optionally be used for grouping. Eg: .... .. o an integral or decimal number, representing hours. Eg: 1.5 o an integral or decimal number immediately followed by a unit symbol s, m, h, d, w, mo, or y, representing seconds, minutes, hours, days weeks, months or years respectively. Eg: 90m. The following equiva- lencies are assumed, currently: 1m = 60s, 1h = 60m, 1d = 24h, 1w = 7d, 1mo = 30d, 1y=365d. There is some flexibility allowing notes and todo lists to be kept right in the time log, if needed: o Blank lines and lines beginning with # or ; are ignored. o Lines not ending with a double-space and quantity are parsed as items taking no time, which will not appear in balance reports by default. (Add -E to see them.) o Org mode headlines (lines beginning with one or more * followed by a space) can be used as date lines or timelog items (the stars are ig- nored). Also all org headlines before the first date line are ig- nored. This means org users can manage their timelog as an org out- line (eg using org-mode/orgstruct-mode in Emacs), for organisation, faster navigation, controlling visibility etc. Examples: # 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 . 2016/2/3 inc:client1 4 fos:hledger 3 biz:research 1 * Time log ** 2020-01-01 *** adm:time . *** adm:finance . * 2020 Work Diary ** Q1 *** 2020-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 Reporting: $ hledger -f t.timedot print date:2016/2/2 2016-02-02 * (inc:client1) 2.00 2016-02-02 * (biz:research) 0.25 $ hledger -f t.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 I prefer to use period for separating account components. We can make this work with an account alias: 2016/2/4 fos.hledger.timedot 4 fos.ledger .. $ hledger -f t.timedot --alias /\\./=: bal date:2016/2/4 4.50 fos 4.00 hledger:timedot 0.50 ledger -------------------- 4.50 Here is a sample.timedot. REPORTING BUGS Report bugs at http://bugs.hledger.org (or on the #hledger IRC channel or hledger mail list) AUTHORS Simon Michael and contributors COPYRIGHT Copyright (C) 2007-2019 Simon Michael. Released under GNU GPL v3 or later. SEE ALSO hledger(1), hledger-ui(1), hledger-web(1), hledger-api(1), hledger_csv(5), hledger_journal(5), hledger_timeclock(5), hledger_time- dot(5), ledger(1) http://hledger.org hledger 1.18.99 September 2020 hledger_timedot(5) hledger-1.19.1/embeddedfiles/hledger_timedot.info0000644000000000000000000001072013725533425020204 0ustar0000000000000000This is hledger_timedot.info, produced by makeinfo version 6.7 from stdin.  File: hledger_timedot.info, Node: Top, Up: (dir) hledger_timedot(5) hledger 1.18.99 ********************************** Timedot - hledger's human-friendly time logging format Timedot is a plain text format for logging dated, categorised quantities (of time, usually), supported by hledger. It is convenient for approximate and retroactive time logging, eg when the real-time clock-in/out required with a timeclock file is too precise or too interruptive. It can be formatted like a bar chart, making clear at a glance where time was spent. Though called "timedot", this format is read by hledger as commodityless quantities, so it could be used to represent dated quantities other than time. In the docs below we'll assume it's time. A timedot file contains a series of day entries. A day entry begins with a non-indented hledger-style simple date (Y-M-D, Y/M/D, Y.M.D..) Any additional text on the same line is used as a transaction description for this day. This is followed by optionally-indented timelog items for that day, one per line. Each timelog item is a note, usually a hledger:style:account:name representing a time category, followed by two or more spaces, and a quantity. Each timelog item generates a hledger transaction. Quantities can be written as: * dots: a sequence of dots (.) representing quarter hours. Spaces may optionally be used for grouping. Eg: .... .. * an integral or decimal number, representing hours. Eg: 1.5 * an integral or decimal number immediately followed by a unit symbol 's', 'm', 'h', 'd', 'w', 'mo', or 'y', representing seconds, minutes, hours, days weeks, months or years respectively. Eg: 90m. The following equivalencies are assumed, currently: 1m = 60s, 1h = 60m, 1d = 24h, 1w = 7d, 1mo = 30d, 1y=365d. There is some flexibility allowing notes and todo lists to be kept right in the time log, if needed: * Blank lines and lines beginning with '#' or ';' are ignored. * Lines not ending with a double-space and quantity are parsed as items taking no time, which will not appear in balance reports by default. (Add -E to see them.) * Org mode headlines (lines beginning with one or more '*' followed by a space) can be used as date lines or timelog items (the stars are ignored). Also all org headlines before the first date line are ignored. This means org users can manage their timelog as an org outline (eg using org-mode/orgstruct-mode in Emacs), for organisation, faster navigation, controlling visibility etc. Examples: # 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 . 2016/2/3 inc:client1 4 fos:hledger 3 biz:research 1 * Time log ** 2020-01-01 *** adm:time . *** adm:finance . * 2020 Work Diary ** Q1 *** 2020-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 Reporting: $ hledger -f t.timedot print date:2016/2/2 2016-02-02 * (inc:client1) 2.00 2016-02-02 * (biz:research) 0.25 $ hledger -f t.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 I prefer to use period for separating account components. We can make this work with an account alias: 2016/2/4 fos.hledger.timedot 4 fos.ledger .. $ hledger -f t.timedot --alias /\\./=: bal date:2016/2/4 4.50 fos 4.00 hledger:timedot 0.50 ledger -------------------- 4.50 Here is a sample.timedot.  Tag Table: Node: Top76  End Tag Table  Local Variables: coding: utf-8 End: hledger-1.19.1/Hledger/Cli/Commands/Accounts.txt0000644000000000000000000000125713725467057017572 0ustar0000000000000000accounts, a Show account names. _FLAGS This command lists account names, either declared with account directives (--declared), posted to (--used), or both (the default). With query arguments, only matched account names and account names referenced by matched postings are shown. 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. Examples: $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts hledger-1.19.1/Hledger/Cli/Commands/Activity.txt0000644000000000000000000000057713725467056017612 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.19.1/Hledger/Cli/Commands/Add.txt0000644000000000000000000000527413725467060016500 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 journal file (if there are multiple -f FILE options, the first file is used.) Existing transactions are not changed. This is the only hledger command that writes to the journal file. 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, 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 the tutorial for a detailed explanation): $ 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.19.1/Hledger/Cli/Commands/Aregister.txt0000644000000000000000000000432413725467056017735 0ustar0000000000000000aregister, areg Show transactions affecting a particular account, and the account's running balance. _FLAGS aregister shows the transactions affecting a particular account (and its subaccounts), from the point of view of that account. Each line shows: - the transaction's (or posting's, see below) date - the names of the other account(s) involved - the net change to this account's balance - the account's historical running balance (including balance from transactions before the report start date). With aregister, each line represents a whole transaction - as in hledger-ui, hledger-web, and your bank statement. By contrast, the register command shows individual postings, across all accounts. You might prefer aregister for reconciling with real-world asset/liability accounts, and register for reviewing detailed revenues/expenses. An account must be specified as the first argument, which should be the full account name or an account pattern (regular expression). aregister will show transactions in this account (the first one matched) and any of its subaccounts. Any additional arguments form a query which will filter the transactions shown. Transactions making a net change of zero are not shown by default; add the -E/--empty flag to show them. aregister and custom posting dates Transactions whose date is outside the report period can still be shown, if they have a posting to this account dated inside the report period. (And in this case it's the posting date that is shown.) This ensures that aregister can show an accurate historical running balance, matching the one shown by register -H with the same arguments. To filter strictly by transaction date instead, add the --txn-dates flag. If you use this flag and some of your postings have custom dates, it's probably best to assume the running balance is wrong. Output format This command also supports the output destination and output format options The output formats supported are txt, csv, and json. Examples: Show all transactions and historical running balance in the first account whose name contains "checking": $ hledger areg checking Show transactions and historical running balance in all asset accounts during july: $ hledger areg assets date:jul hledger-1.19.1/Hledger/Cli/Commands/Balance.txt0000644000000000000000000005114513725467061017334 0ustar0000000000000000balance, bal, b Show accounts and their balances. _FLAGS The balance command is hledger's most versatile command. Note, despite the name, it is not always used for showing real-world account balances; the more accounting-aware balancesheet and incomestatement may be more convenient for that. By default, it displays all accounts, and each account's change in balance during the entire period of the journal. Balance changes are calculated by adding up the postings in each account. You can limit the postings matched, by a query, to see fewer accounts, changes over a different time period, changes from only cleared transactions, etc. If you include an account's complete history of postings in the report, the balance change is equivalent to the account's current ending balance. For a real-world account, typically you won't have all transactions in the journal; instead you'll have all transactions after a certain date, and an "opening balances" transaction setting the correct starting balance on that date. Then the balance command will show real-world account balances. In some cases the -H/--historical flag is used to ensure this (more below). The balance command can produce several styles of report: Classic balance report This is the original balance report, as found in Ledger. It usually looks like this: $ hledger balance $-1 assets $1 bank:saving $-2 cash $2 expenses $1 food $1 supplies $-2 income $-1 gifts $-1 salary $1 liabilities:debts -------------------- 0 By default, accounts are displayed hierarchically, with subaccounts indented below their parent. At each level of the tree, accounts are sorted by account code if any, then by account name. Or with -S/--sort-amount, by their balance amount, largest first. "Boring" accounts, which contain a single interesting subaccount and no balance of their own, are elided into the following line for more compact output. (Eg above, the "liabilities" account.) Use --no-elide to prevent this. Account balances are "inclusive" - they include the balances of any subaccounts. Accounts which have zero balance (and no non-zero subaccounts) are omitted. Use -E/--empty to show them. A final total is displayed by default; use -N/--no-total to suppress it, eg: $ hledger balance -p 2008/6 expenses --no-total $2 expenses $1 food $1 supplies Customising the classic balance report You can customise the layout of classic balance reports with --format FMT: $ hledger 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 (plus a newline) 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 Colour support In terminal output, when colour is enabled, the balance command shows negative amounts in red. Flat mode To see a flat list instead of the default hierarchical display, use --flat. In this mode, accounts (unless depth-clipped) show their full names and "exclusive" balance, excluding any subaccount balances. In this mode, you can also use --drop N to omit the first few account name components. $ hledger balance -p 2008/6 expenses -N --flat --drop 1 $1 food $1 supplies Depth limited balance reports With --depth N or depth:N or just -N, balance reports show accounts only to the specified numeric depth. This is very useful to summarise a complex set of accounts and get an overview. $ hledger balance -N -1 $-1 assets $2 expenses $-2 income $1 liabilities Flat-mode balance reports, which normally show exclusive balances, show inclusive balances at the depth limit. Percentages With -% or --percent, balance reports show each account's value expressed as a percentage of the column's total. This is useful to get an overview of the relative sizes of account balances. For example to obtain an overview of expenses: $ hledger balance expenses -% 100.0 % expenses 50.0 % food 50.0 % supplies -------------------- 100.0 % Note that --tree does not have an effect on -%. The percentages are always relative to the total sum of each column, they are never relative to the parent account. Since the percentages are relative to the columns sum, it is usually not useful to calculate percentages if the signs of the amounts are mixed. Although the results are technically correct, they are most likely useless. Especially in a balance report that sums up to zero (eg hledger balance -B) all percentage values will be zero. This flag does not work if the report contains any mixed commodity accounts. If there are mixed commodity accounts in the report be sure to use -V or -B to coerce the report into using a single commodity. Multicolumn balance report Multicolumn or tabular balance reports are a very useful hledger feature, and usually the preferred style. They share many of the above features, but they show the report as a table, with columns representing time periods. This mode is activated by providing a reporting interval. There are three types of multicolumn balance report, showing different information: 1. By default: each column shows the sum of postings in that period, ie the account's change of balance in that period. This is useful eg for a monthly income statement: $ hledger balance --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 2. With --cumulative: each column shows the ending balance for that period, accumulating the changes across periods, starting from 0 at the report start date: $ hledger balance --quarterly income expenses -E --cumulative Ending balances (cumulative) in 2008: || 2008/03/31 2008/06/30 2008/09/30 2008/12/31 ===================++================================================= expenses:food || 0 $1 $1 $1 expenses:supplies || 0 $1 $1 $1 income:gifts || 0 $-1 $-1 $-1 income:salary || $-1 $-1 $-1 $-1 -------------------++------------------------------------------------- || $-1 0 0 0 3. With --historical/-H: each column shows the actual historical ending balance for that period, accumulating the changes across periods, starting from the actual balance at the report start date. This is useful eg for a multi-period balance sheet, and when you are showing only the data after a certain start date: $ hledger balance ^assets ^liabilities --quarterly --historical --begin 2008/4/1 Ending balances (historical) in 2008/04/01-2008/12/31: || 2008/06/30 2008/09/30 2008/12/31 ======================++===================================== assets:bank:checking || $1 $1 0 assets:bank:saving || $1 $1 $1 assets:cash || $-2 $-2 $-2 liabilities:debts || 0 0 $1 ----------------------++------------------------------------- || 0 0 0 Note that --cumulative or --historical/-H disable --row-total/-T, since summing end balances generally does not make sense. Multicolumn balance reports display accounts in flat mode by default; to see the hierarchy, use --tree. With a reporting interval (like --quarterly above), the report start/end dates will be adjusted if necessary so that they encompass the displayed report periods. This is so that the first and last periods will be "full" and comparable to the others. The -E/--empty flag does two things in multicolumn balance reports: first, the report will show all columns within the specified report period (without -E, leading and trailing columns with all zeroes are not shown). Second, all accounts which existed at the report start date will be considered, not just the ones with activity during the report period (use -E to include low-activity accounts which would otherwise would be omitted). The -T/--row-total flag adds an additional column showing the total for each row. The -A/--average flag adds a column showing the average value in each row. Here's an example of all three: $ hledger balance -Q income expenses --tree -ETA Balance changes in 2008: || 2008q1 2008q2 2008q3 2008q4 Total Average ============++=================================================== expenses || 0 $2 0 0 $2 $1 food || 0 $1 0 0 $1 0 supplies || 0 $1 0 0 $1 0 income || $-1 $-1 0 0 $-2 $-1 gifts || 0 $-1 0 0 $-1 0 salary || $-1 0 0 0 $-1 0 ------------++--------------------------------------------------- || $-1 $1 0 0 0 0 (Average is rounded to the dollar here since all journal amounts are) The --transpose flag can be used to exchange the rows and columns of a multicolumn report. When showing multicommodity amounts, multicolumn balance reports will elide any amounts which have more than two commodities, since otherwise columns could get very wide. The --no-elide flag disables this. Hiding totals with the -N/--no-total flag can also help reduce the width of multicommodity reports. When the report is still too wide, a good workaround is to pipe it into less -RS (-R for colour, -S to chop long lines). Eg: hledger bal -D --color=yes | less -RS. Budget report With --budget, extra columns are displayed showing budget goals for each account and period, if any. Budget goals are defined by periodic transactions. This is very useful for comparing planned and actual income, expenses, time usage, etc. --budget is most often combined with a report interval. For example, you can take average monthly expenses in the common expense categories to construct a minimal monthly budget: ;; Budget ~ monthly income $2000 expenses:food $400 expenses:bus $50 expenses:movies $30 assets:bank:checking ;; Two months worth of expenses 2017-11-01 income $1950 expenses:food $396 expenses:bus $49 expenses:movies $30 expenses:supplies $20 assets:bank:checking 2017-12-01 income $2100 expenses:food $412 expenses:bus $53 expenses:gifts $100 assets:bank:checking You can now see a monthly budget report: $ hledger balance -M --budget Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] This is different from a normal balance report in several ways: - Only accounts with budget goals during the report period are shown, by default. - In each column, in square brackets after the actual amount, budget goal amounts are shown, and the actual/goal percentage. (Note: budget goals should be in the same commodity as the actual amount.) - All parent accounts are always shown, even in flat mode. Eg assets, assets:bank, and expenses above. - Amounts always include all subaccounts, budgeted or unbudgeted, even in flat mode. This means that the numbers displayed will not always add up! Eg above, the expenses actual amount includes the gifts and supplies transactions, but the expenses:gifts and expenses:supplies accounts are not shown, as they have no budget amounts declared. This can be confusing. When you need to make things clearer, use the -E/--empty flag, which will reveal all accounts including unbudgeted ones, giving the full picture. Eg: $ hledger balance -M --budget --empty Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] assets:bank:checking || $-2445 [ 99% of $-2480] $-2665 [ 107% of $-2480] expenses || $495 [ 103% of $480] $565 [ 118% of $480] expenses:bus || $49 [ 98% of $50] $53 [ 106% of $50] expenses:food || $396 [ 99% of $400] $412 [ 103% of $400] expenses:gifts || 0 $100 expenses:movies || $30 [ 100% of $30] 0 [ 0% of $30] expenses:supplies || $20 0 income || $1950 [ 98% of $2000] $2100 [ 105% of $2000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] You can roll over unspent budgets to next period with --cumulative: $ hledger balance -M --budget --cumulative Budget performance in 2017/11/01-2017/12/31: || Nov Dec ======================++==================================================== assets || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] assets:bank:checking || $-2445 [ 99% of $-2480] $-5110 [ 103% of $-4960] expenses || $495 [ 103% of $480] $1060 [ 110% of $960] expenses:bus || $49 [ 98% of $50] $102 [ 102% of $100] expenses:food || $396 [ 99% of $400] $808 [ 101% of $800] expenses:movies || $30 [ 100% of $30] $30 [ 50% of $60] income || $1950 [ 98% of $2000] $4050 [ 101% of $4000] ----------------------++---------------------------------------------------- || 0 [ 0] 0 [ 0] For more examples, see Budgeting and Forecasting. Nested budgets You can add budgets to any account in your account hierarchy. If you have budgets on both parent account and some of its children, then budget(s) of the child account(s) would be added to the budget of their parent, much like account balances behave. In the most simple case this means that once you add a budget to any account, all its parents would have budget as well. To illustrate this, consider the following budget: ~ monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities With this, monthly budget for electronics is defined to be $100 and budget for personal expenses is an additional $1000, which implicitly means that budget for both expenses:personal and expenses is $1100. Transactions in expenses:personal:electronics will be counted both towards its $100 budget and $1100 of expenses:personal , and transactions in any other subaccount of expenses:personal would be counted towards only towards the budget of expenses:personal. For example, let's consider these transactions: ~ monthly from 2019/01 expenses:personal $1,000.00 expenses:personal:electronics $100.00 liabilities 2019/01/01 Google home hub expenses:personal:electronics $90.00 liabilities $-90.00 2019/01/02 Phone screen protector expenses:personal:electronics:upgrades $10.00 liabilities 2019/01/02 Weekly train ticket expenses:personal:train tickets $153.00 liabilities 2019/01/03 Flowers expenses:personal $30.00 liabilities As you can see, we have transactions in expenses:personal:electronics:upgrades and expenses:personal:train tickets, and since both of these accounts are without explicitly defined budget, these transactions would be counted towards budgets of expenses:personal:electronics and expenses:personal accordingly: $ hledger balance --budget -M Budget performance in 2019/01: || Jan ===============================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] liabilities || $-283.00 [ 26% of $-1100.00] -------------------------------++------------------------------- || 0 [ 0] And with --empty, we can get a better picture of budget allocation and consumption: $ hledger balance --budget -M --empty Budget performance in 2019/01: || Jan ========================================++=============================== expenses || $283.00 [ 26% of $1100.00] expenses:personal || $283.00 [ 26% of $1100.00] expenses:personal:electronics || $100.00 [ 100% of $100.00] expenses:personal:electronics:upgrades || $10.00 expenses:personal:train tickets || $153.00 liabilities || $-283.00 [ 26% of $-1100.00] ----------------------------------------++------------------------------- || 0 [ 0] Output format This command also supports the output destination and output format options The output formats supported are txt, csv, (multicolumn non-budget reports only) html, and (experimental) json. hledger-1.19.1/Hledger/Cli/Commands/Balancesheet.txt0000644000000000000000000000270213725467061020360 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 The asset and liability accounts shown are those accounts declared with the Asset or Cash or Liability type, or otherwise all accounts under a top-level asset or liability account (case insensitive, plurals allowed). Example: $ hledger balancesheet Balance Sheet Assets: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Liabilities: $1 liabilities:debts -------------------- $1 Total: -------------------- 0 With a reporting interval, multiple columns will be shown, one for each report period. As with multicolumn balance reports, you can alter the report mode with --change/--cumulative/--historical. Normally balancesheet shows historical ending balances, which is what you need for a balance sheet; note this means it ignores report begin dates (and -T/--row-total, since summing end balances generally does not make sense). Instead of absolute values percentages can be displayed with -%. This command also supports the output destination and output format options The output formats supported are txt, csv, html, and (experimental) json. hledger-1.19.1/Hledger/Cli/Commands/Balancesheetequity.txt0000644000000000000000000000203313725467061021616 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 The asset, liability and equity accounts shown are those accounts declared with the Asset, Cash, Liability or Equity type, or otherwise all accounts under a top-level asset, liability or equity account (case insensitive, plurals allowed). 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 also supports the output destination and output format options The output formats supported are txt, csv, html, and (experimental) json. hledger-1.19.1/Hledger/Cli/Commands/Cashflow.txt0000644000000000000000000000223413725467060017547 0ustar0000000000000000cashflow, cf This command displays a cashflow statement, showing the inflows and outflows affecting "cash" (ie, liquid) assets. Amounts are shown with normal positive sign, as in conventional financial statements. _FLAGS The "cash" accounts shown are those accounts declared with the Cash type, or otherwise all accounts under a top-level asset account (case insensitive, plural allowed) which do not have fixed, investment, receivable or A/R in their name. Example: $ hledger cashflow Cashflow Statement Cash flows: $-1 assets $1 bank:saving $-2 cash -------------------- $-1 Total: -------------------- $-1 With a reporting interval, multiple columns will be shown, one for each report period. Normally cashflow shows changes in assets per period, though as with multicolumn balance reports you can alter the report mode with --change/--cumulative/--historical. Instead of absolute values percentages can be displayed with -%. This command also supports the output destination and output format options The output formats supported are txt, csv, html, and (experimental) json. hledger-1.19.1/Hledger/Cli/Commands/Checkdates.txt0000644000000000000000000000043513725467057020046 0ustar0000000000000000check-dates Check that transactions are sorted by increasing date. With --date2, checks secondary dates instead. With --strict, dates must also be unique. With a query, only matched transactions' dates are checked. Reads the default journal file, or another specified with -f. _FLAGS hledger-1.19.1/Hledger/Cli/Commands/Checkdupes.txt0000644000000000000000000000044713725467056020070 0ustar0000000000000000check-dupes Reports account names having the same leaf but different prefixes. In other words, two or more leaves that are categorized differently. Reads the default journal file, or another specified as an argument. _FLAGS An example: http://stefanorodighiero.net/software/hledger-dupes.html hledger-1.19.1/Hledger/Cli/Commands/Close.txt0000644000000000000000000001023013725467057017047 0ustar0000000000000000close, equity Prints a "closing balances" transaction and an "opening balances" transaction that bring account balances to and from zero, respectively. These can be added to your journal file(s), eg to bring asset/liability balances forward into a new journal file, or to close out revenues/expenses to retained earnings at the end of a period. _FLAGS You can print just one of these transactions by using the --close or --open flag. You can customise their descriptions with the --close-desc and --open-desc options. One amountless posting to "equity:opening/closing balances" is added to balance the transactions, by default. You can customise this account name with --close-acct and --open-acct; if you specify only one of these, it will be used for both. With --x/--explicit, the equity posting's amount will be shown. And if it involves multiple commodities, a posting for each commodity will be shown, as with the print command. With --interleaved, the equity postings are shown next to the postings they balance, which makes troubleshooting easier. By default, transaction prices in the journal are ignored when generating the closing/opening transactions. With --show-costs, this cost information is preserved (balance -B reports will be unchanged after the transition). Separate postings are generated for each cost in each commodity. Note this can generate very large journal entries, if you have many foreign currency or investment transactions. close usage If you split your journal files by time (eg yearly), you will typically run this command at the end of the year, and save the closing transaction as last entry of the old file, and the opening transaction as the first entry of the new file. This makes the files self contained, so that correct balances are reported no matter which of them are loaded. Ie, if you load just one file, the balances are initialised correctly; or if you load several files, the redundant closing/opening transactions cancel each other out. (They will show up in print or register reports; you can exclude them with a query like not:desc:'(opening|closing) balances'.) If you're running a business, you might also use this command to "close the books" at the end of an accounting period, transferring income statement account balances to retained earnings. (You may want to change the equity account name to something like "equity:retained earnings".) By default, the closing transaction is dated yesterday, the balances are calculated as of end of yesterday, and the opening transaction is dated today. To close on some other date, use: hledger close -e OPENINGDATE. Eg, to close/open on the 2018/2019 boundary, use -e 2019. You can also use -p or date:PERIOD (any starting date is ignored). Both transactions will include balance assertions for the closed/reopened accounts. You probably shouldn't use status or realness filters (like -C or -R or status:) with this command, or the generated balance assertions will depend on these flags. Likewise, if you run this command with --auto, the balance assertions will probably always require --auto. Examples: Carrying asset/liability balances into a new file for 2019: $ hledger close -f 2018.journal -e 2019 assets liabilities --open # (copy/paste the output to the start of your 2019 journal file) $ hledger close -f 2018.journal -e 2019 assets liabilities --close # (copy/paste the output to the end of your 2018 journal file) Now: $ hledger bs -f 2019.journal # one file - balances are correct $ hledger bs -f 2018.journal -f 2019.journal # two files - balances still correct $ hledger bs -f 2018.journal not:desc:closing # to see year-end balances, must exclude closing txn Transactions spanning the closing date can complicate matters, breaking balance assertions: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 assets:bank:checking -5 ; [2019/1/2] Here's one way to resolve that: ; in 2018.journal: 2018/12/30 a purchase made in 2018, clearing the following year expenses:food 5 liabilities:pending ; in 2019.journal: 2019/1/2 clearance of last year's pending transactions liabilities:pending 5 = 0 assets:checking hledger-1.19.1/Hledger/Cli/Commands/Codes.txt0000644000000000000000000000127513725467056017047 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: 1/1 (123) (a) 1 1/1 () (a) 1 1/1 (a) 1 1/1 (126) (a) 1 $ hledger codes 123 124 126 $ hledger codes -E 123 124 126 hledger-1.19.1/Hledger/Cli/Commands/Commodities.txt0000644000000000000000000000013113725467062020251 0ustar0000000000000000commodities List all commodity/currency symbols used or declared in the journal. _FLAGS hledger-1.19.1/Hledger/Cli/Commands/Descriptions.txt0000644000000000000000000000046013725467061020447 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.19.1/Hledger/Cli/Commands/Diff.txt0000644000000000000000000000202313725467061016646 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.19.1/Hledger/Cli/Commands/Files.txt0000644000000000000000000000023113725467057017044 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.19.1/Hledger/Cli/Commands/Help.txt0000644000000000000000000000205213725467060016667 0ustar0000000000000000help Show any of the hledger manuals. _FLAGS The help command displays any of the main hledger manuals, in one of several ways. Run it with no argument to list the manuals, or provide a full or partial manual name to select one. hledger manuals are available in several formats. hledger help will use the first of these display methods that it finds: info, man, $PAGER, less, stdout (or when non-interactive, just stdout). You can force a particular viewer with the --info, --man, --pager, --cat flags. Examples: $ hledger help Please choose a manual by typing "hledger help MANUAL" (a substring is ok). Manuals: hledger hledger-ui hledger-web journal csv timeclock timedot $ hledger help h --man hledger(1) hledger User Manuals hledger(1) NAME hledger - a command-line accounting tool SYNOPSIS hledger [-f FILE] COMMAND [OPTIONS] [ARGS] hledger [-f FILE] ADDONCMD -- [OPTIONS] [ARGS] hledger DESCRIPTION hledger is a cross-platform program for tracking money, time, or any ... hledger-1.19.1/Hledger/Cli/Commands/Import.txt0000644000000000000000000000275413725467057017270 0ustar0000000000000000import Read new transactions added to each FILE since last run, and add them to the main journal file. Or with --dry-run, just print the transactions that would be added. Or with --catchup, just mark all of the FILEs' transactions as imported, without actually importing any. _FLAGS The input files are specified as arguments - no need to write -f before each one. So eg to add new transactions from all CSV files to the main journal, it's just: hledger import *.csv New transactions are detected in the same way as print --new: by assuming transactions are always added to the input files in increasing date order, and by saving .latest.FILE state files. The --dry-run output is in journal format, so you can filter it, eg to see only uncategorised transactions: $ hledger import --dry ... | hledger -f- print unknown --ignore-assertions 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.) hledger-1.19.1/Hledger/Cli/Commands/Incomestatement.txt0000644000000000000000000000243413725467056021147 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 The revenue and expense accounts shown are those accounts declared with the Revenue or Expense type, or otherwise all accounts under a top-level revenue or income or expense account (case insensitive, plurals allowed). Example: $ hledger incomestatement Income Statement Revenues: $-2 income $-1 gifts $-1 salary -------------------- $-2 Expenses: $2 expenses $1 food $1 supplies -------------------- $2 Total: -------------------- 0 With a reporting interval, multiple columns will be shown, one for each report period. Normally incomestatement shows revenues/expenses per period, though as with multicolumn balance reports you can alter the report mode with --change/--cumulative/--historical. Instead of absolute values percentages can be displayed with -%. This command also supports the output destination and output format options The output formats supported are txt, csv, html, and (experimental) json. hledger-1.19.1/Hledger/Cli/Commands/Notes.txt0000644000000000000000000000055713725467056017104 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.19.1/Hledger/Cli/Commands/Payees.txt0000644000000000000000000000064313725467060017231 0ustar0000000000000000payees List the unique payee/payer names that appear in transactions. _FLAGS This command lists the unique payee/payer names that appear in transactions, in alphabetic order. You can add a query to select a subset of transactions. The payee/payer is the part of the transaction description before a | character (or if there is no |, the whole description). Example: $ hledger payees Store Name Gas Station Person A hledger-1.19.1/Hledger/Cli/Commands/Prices.txt0000644000000000000000000000053413725467060017227 0ustar0000000000000000prices Print market price directives from the journal. With --costs, also print synthetic market prices based on transaction prices. With --inverted-costs, also print inverse prices based on transaction prices. Prices (and postings providing prices) can be filtered by a query. Price amounts are always displayed with their full precision. _FLAGS hledger-1.19.1/Hledger/Cli/Commands/Print.txt0000644000000000000000000001114713725467061017101 0ustar0000000000000000print, txns, p Show transaction journal entries, sorted by date. _FLAGS The print command displays full journal entries (transactions) from the journal file in date order, tidily formatted. With --date2, transactions are sorted by secondary date instead. print's output is always a valid hledger journal. It preserves all transaction information, but it does not preserve directives or inter-transaction comments $ hledger print 2008/01/01 income assets:bank:checking $1 income:salary $-1 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 2008/12/31 * pay off liabilities:debts $1 assets:bank:checking $-1 Normally, the journal entry's explicit or implicit amount style is preserved. For example, when an amount is omitted in the journal, it will not appear in the output. Similarly, when a transaction price is implied but not written, it will not appear in the output. You can use the -x/--explicit flag to make all amounts and transaction prices explicit, which 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. Note, -x/--explicit will cause postings with a multi-commodity amount (these can arise when a multi-commodity transaction has an implicit amount) to be split into multiple single-commodity postings, keeping the output parseable. With -B/--cost, amounts with transaction prices are converted to cost using that price. This can be used for troubleshooting. With -m/--match and a STR argument, print will show at most one transaction: the one one whose description is most similar to STR, and is most recent. STR should contain at least two characters. If there is no similar-enough match, no transaction will be shown. With --new, for each FILE being read, hledger reads (and writes) a special state file (.latest.FILE in the same directory), containing the latest transaction date(s) that were seen last time FILE was read. When this file is found, only transactions with newer dates (and new transactions on the latest date) are printed. This is useful for ignoring already-seen entries in import data, such as downloaded CSV files. Eg: $ hledger -f bank1.csv print --new (shows transactions added since last print --new on this file) This assumes that transactions added to FILE always have same or increasing dates, and that transactions on the same day do not get reordered. See also the import command. This command also supports the output destination and output format options The output formats supported are txt, csv, and (experimental) json and sql. 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.19.1/Hledger/Cli/Commands/Printunique.txt0000644000000000000000000000044113725467061020323 0ustar0000000000000000print-unique Print transactions which do not reuse an already-seen description. _FLAGS Example: $ cat unique.journal 1/1 test (acct:one) 1 2/2 test (acct:two) 2 $ LEDGER_FILE=unique.journal hledger print-unique (-f option not supported) 2015/01/01 test (acct:one) 1 hledger-1.19.1/Hledger/Cli/Commands/Register.txt0000644000000000000000000001306113725467057017573 0ustar0000000000000000register, reg, r 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. 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. 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, and (experimental) json. hledger-1.19.1/Hledger/Cli/Commands/Registermatch.txt0000644000000000000000000000054313725467057020611 0ustar0000000000000000register-match Print the one posting whose transaction description is closest to DESC, in the style of the register command. If there are multiple equally good matches, it shows the most recent. Query options (options, not arguments) can be used to restrict the search space. Helps ledger-autosync detect already-seen transactions when importing. _FLAGS hledger-1.19.1/Hledger/Cli/Commands/Rewrite.txt0000644000000000000000000001101013725467060017412 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.19.1/Hledger/Cli/Commands/Roi.txt0000644000000000000000000000175213725467057016544 0ustar0000000000000000roi Shows the time-weighted (TWR) and money-weighted (IRR) rate of return on your investments. _FLAGS This command assumes that you have account(s) that hold nothing but your investments and whenever you record current appraisal/valuation of these investments you offset unrealized profit and loss into account(s) that, again, hold nothing but unrealized profit and loss. Any transactions affecting balance of investment account(s) and not originating from unrealized profit and loss account(s) are assumed to be your investments or withdrawals. At a minimum, you need to supply a query (which could be just an account name) to select your investments with --inv, and another query to identify your profit and loss transactions with --pnl. It will compute and display the internalized rate of return (IRR) and time-weighted rate of return (TWR) for your investments for the time period requested. Both rates of return are annualized before display, regardless of the length of reporting interval. hledger-1.19.1/Hledger/Cli/Commands/Stats.txt0000644000000000000000000000142113725467062017076 0ustar0000000000000000stats Show some journal 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. Example: $ hledger stats Main journal file : /src/hledger/examples/sample.journal Included journal files : Transactions span : 2008-01-01 to 2009-01-01 (366 days) Last transaction : 2008-12-31 (2333 days ago) 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 : 12 ($) This command also supports output destination and output format selection. hledger-1.19.1/Hledger/Cli/Commands/Tags.txt0000644000000000000000000000100613725467057016701 0ustar0000000000000000tags List the unique tag names used in the journal. With a TAGREGEX argument, only tag names matching the regular expression (case insensitive) are shown. With QUERY arguments, only transactions matching the query are considered. With the --values flag, the tags' unique values are listed instead. With --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. _FLAGS hledger-1.19.1/Hledger/Cli/Commands/Test.txt0000644000000000000000000000134213725467056016724 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).