hledger-1.2/Hledger/0000755000000000000000000000000013035210046012520 5ustar0000000000000000hledger-1.2/Hledger/Cli/0000755000000000000000000000000013067573465013255 5ustar0000000000000000hledger-1.2/Text/0000755000000000000000000000000013035210046012072 5ustar0000000000000000hledger-1.2/Text/Tabular/0000755000000000000000000000000013066774455013513 5ustar0000000000000000hledger-1.2/app/0000755000000000000000000000000013035210046011726 5ustar0000000000000000hledger-1.2/bench/0000755000000000000000000000000013042200120012213 5ustar0000000000000000hledger-1.2/doc/0000755000000000000000000000000013067573420011730 5ustar0000000000000000hledger-1.2/doc/other/0000755000000000000000000000000013035210046013034 5ustar0000000000000000hledger-1.2/test/0000755000000000000000000000000013035210046012125 5ustar0000000000000000hledger-1.2/Hledger/Cli.hs0000644000000000000000000003416713035210046013576 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.Accounts, module Hledger.Cli.Add, module Hledger.Cli.Balance, module Hledger.Cli.Balancesheet, module Hledger.Cli.Cashflow, module Hledger.Cli.Help, module Hledger.Cli.Histogram, module Hledger.Cli.Incomestatement, module Hledger.Cli.Info, module Hledger.Cli.Man, module Hledger.Cli.Print, module Hledger.Cli.Register, module Hledger.Cli.Stats, module Hledger.Cli.CliOptions, module Hledger.Cli.DocFiles, module Hledger.Cli.Utils, module Hledger.Cli.Version, tests_Hledger_Cli, module Hledger, module System.Console.CmdArgs.Explicit ) where import Data.Monoid ((<>)) import Data.Text (Text) import qualified Data.Text as T import Data.Time.Calendar import System.Console.CmdArgs.Explicit hiding (Name) -- don't clash with hledger-ui import Test.HUnit import Hledger import Hledger.Cli.Accounts import Hledger.Cli.Add import Hledger.Cli.Balance import Hledger.Cli.Balancesheet import Hledger.Cli.Cashflow import Hledger.Cli.Histogram import Hledger.Cli.Help import Hledger.Cli.Incomestatement import Hledger.Cli.Info import Hledger.Cli.Man import Hledger.Cli.Print import Hledger.Cli.Register import Hledger.Cli.Stats import Hledger.Cli.CliOptions import Hledger.Cli.DocFiles import Hledger.Cli.Utils import Hledger.Cli.Version tests_Hledger_Cli :: Test tests_Hledger_Cli = TestList [ tests_Hledger -- ,tests_Hledger_Cli_Add ,tests_Hledger_Cli_Balance ,tests_Hledger_Cli_Balancesheet ,tests_Hledger_Cli_Cashflow -- ,tests_Hledger_Cli_Histogram ,tests_Hledger_Cli_Incomestatement ,tests_Hledger_Cli_CliOptions -- ,tests_Hledger_Cli_Print ,tests_Hledger_Cli_Register -- ,tests_Hledger_Cli_Stats ,"apply account directive" ~: let ignoresourcepos j = j{jtxns=map (\t -> t{tsourcepos=nullsourcepos}) (jtxns j)} in let sameParse str1 str2 = do j1 <- readJournal Nothing Nothing True Nothing str1 >>= either error' (return . ignoresourcepos) j2 <- readJournal Nothing Nothing True Nothing str2 >>= either error' (return . ignoresourcepos) j1 `is` j2{jlastreadtime=jlastreadtime j1, jfiles=jfiles j1} --, jparsestate=jparsestate j1} in TestList [ "apply account directive 1" ~: 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" ) ,"apply account directive should preserve \"virtual\" posting type" ~: do j <- readJournal Nothing Nothing True Nothing "apply account test\n2008/12/07 One\n (from) $-1\n (to) $1\n" >>= either error' return let p = head $ tpostings $ head $ jtxns j assertBool "" $ paccount p == "test:from" assertBool "" $ ptype p == VirtualPosting ] ,"account aliases" ~: do j <- readJournal Nothing Nothing True Nothing "!alias expenses = equity:draw:personal\n1/1\n (expenses:food) 1\n" >>= either error' return let p = head $ tpostings $ head $ jtxns j assertBool "" $ paccount p == "equity:draw:personal:food" ,"ledgerAccountNames" ~: ledgerAccountNames ledger7 `is` ["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"] -- ,"journalCanonicaliseAmounts" ~: -- "use the greatest precision" ~: -- (map asprecision $ journalAmountAndPriceCommodities $ journalCanonicaliseAmounts $ journalWithAmounts ["1","2.00"]) `is` [2,2] -- don't know what this should do -- ,"elideAccountName" ~: do -- (elideAccountName 50 "aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa" -- `is` "aa:aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa") -- (elideAccountName 20 "aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa:aaaaaaaaaaaaaaaaaaaa" -- `is` "aa:aa:aaaaaaaaaaaaaa") ,"default year" ~: do j <- readJournal Nothing Nothing True Nothing defaultyear_journal_txt >>= either error' return tdate (head $ jtxns j) `is` fromGregorian 2009 1 1 return () ,"show dollars" ~: showAmount (usd 1) ~?= "$1.00" ,"show hours" ~: showAmount (hrs 1) ~?= "1.00h" ] -- fixtures/test data -- date1 = parsedate "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=parsedate "2007/01/01", tdate2=Nothing, tstatus=Uncleared, tcode="*", tdescription="opening balance", tcomment="", ttags=[], tpostings= ["assets:cash" `post` usd 4.82 ,"equity:opening balances" `post` usd (-4.82) ], tpreceding_comment_lines="" } , txnTieKnot Transaction { tindex=0, tsourcepos=nullsourcepos, tdate=parsedate "2007/02/01", tdate2=Nothing, tstatus=Uncleared, tcode="*", tdescription="ayres suites", tcomment="", ttags=[], tpostings= ["expenses:vacation" `post` usd 179.92 ,"assets:checking" `post` usd (-179.92) ], tpreceding_comment_lines="" } , txnTieKnot Transaction { tindex=0, tsourcepos=nullsourcepos, tdate=parsedate "2007/01/02", tdate2=Nothing, tstatus=Uncleared, tcode="*", tdescription="auto transfer to savings", tcomment="", ttags=[], tpostings= ["assets:saving" `post` usd 200 ,"assets:checking" `post` usd (-200) ], tpreceding_comment_lines="" } , txnTieKnot Transaction { tindex=0, tsourcepos=nullsourcepos, tdate=parsedate "2007/01/03", tdate2=Nothing, tstatus=Uncleared, tcode="*", tdescription="poquito mas", tcomment="", ttags=[], tpostings= ["expenses:food:dining" `post` usd 4.82 ,"assets:cash" `post` usd (-4.82) ], tpreceding_comment_lines="" } , txnTieKnot Transaction { tindex=0, tsourcepos=nullsourcepos, tdate=parsedate "2007/01/03", tdate2=Nothing, tstatus=Uncleared, tcode="*", tdescription="verizon", tcomment="", ttags=[], tpostings= ["expenses:phone" `post` usd 95.11 ,"assets:checking" `post` usd (-95.11) ], tpreceding_comment_lines="" } , txnTieKnot Transaction { tindex=0, tsourcepos=nullsourcepos, tdate=parsedate "2007/01/03", tdate2=Nothing, tstatus=Uncleared, tcode="*", tdescription="discover", tcomment="", ttags=[], tpostings= ["liabilities:credit cards:discover" `post` usd 80 ,"assets:checking" `post` usd (-80) ], tpreceding_comment_lines="" } ] } ledger7 :: Ledger ledger7 = ledgerFromJournal Any journal7 hledger-1.2/Hledger/Cli/Main.hs0000644000000000000000000004414113066774457014504 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 Nothing Nothing True "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 Control.Monad import Data.Char (isDigit) import Data.String.Here import Data.List import Data.List.Split (splitOn) import Safe import System.Console.CmdArgs.Explicit as C import System.Environment import System.Exit import System.FilePath import System.Process import Text.Printf import Hledger (ensureJournalFileExists) import Hledger.Cli.Add import Hledger.Cli.Accounts import Hledger.Cli.Balance import Hledger.Cli.Balancesheet import Hledger.Cli.Cashflow import Hledger.Cli.DocFiles import Hledger.Cli.Help import Hledger.Cli.Histogram import Hledger.Cli.Incomestatement import Hledger.Cli.Info import Hledger.Cli.Man import Hledger.Cli.Print import Hledger.Cli.Register import Hledger.Cli.Stats import Hledger.Cli.CliOptions import Hledger.Cli.Tests import Hledger.Cli.Utils import Hledger.Cli.Version import Hledger.Data.Dates (getCurrentDay) import Hledger.Data.RawOptions (RawOpts) import Hledger.Reports.ReportOptions (period_, interval_, queryFromOpts) import Hledger.Utils -- | The overall cmdargs mode describing command-line options for hledger. mainmode addons = defMode { modeNames = [progname ++ " [CMD]"] ,modeArgs = ([], Just $ argsFlag "[ARGS]") ,modeHelp = unlines ["hledger's command line interface"] ,modeGroupModes = Group { -- subcommands in the unnamed group, shown first: groupUnnamed = [ ] -- subcommands in named groups: ,groupNamed = [ ] -- subcommands handled but not shown in the help: ,groupHidden = [ oldconvertmode ,accountsmode ,activitymode ,addmode ,balancemode ,balancesheetmode ,cashflowmode ,helpmode ,incomestatementmode ,infomode ,manmode ,printmode ,registermode ,statsmode ,testmode ] ++ map quickAddonCommandMode 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 = lines $ regexReplace "PROGNAME" progname [here|Examples: PROGNAME list commands PROGNAME CMD [--] [OPTS] [ARGS] run a command (use -- with addon commands) PROGNAME-CMD [OPTS] [ARGS] or run addon commands directly PROGNAME -h general usage PROGNAME CMD -h command usage PROGNAME --help PROGNAME manual PROGNAME --man PROGNAME manual as man page PROGNAME --info PROGNAME manual as info manual PROGNAME help list help topics PROGNAME help TOPIC TOPIC manual PROGNAME man TOPIC TOPIC manual as man page PROGNAME info TOPIC TOPIC manual as info manual |] } oldconvertmode = (defCommandMode ["convert"]) { modeValue = [("command","convert")] ,modeHelp = "convert is no longer needed, just use -f FILE.csv" ,modeArgs = ([], Just $ argsFlag "[CSVFILE]") ,modeGroupFlags = Group { groupUnnamed = [] ,groupHidden = helpflags ,groupNamed = [] } } builtinCommands :: [Mode RawOpts] builtinCommands = let gs = modeGroupModes $ mainmode [] in concatMap snd (groupNamed gs) ++ groupUnnamed gs ++ groupHidden gs builtinCommandNames :: [String] builtinCommandNames = concatMap modeNames builtinCommands -- | 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 args cmdargsopts = either usageError id $ process (mainmode addons) args' cmdargsopts' = decodeRawOpts cmdargsopts 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 -- -h ..., --version ... moveArgs (f:a:as) | isMovableNoArgFlag f = (moveArgs $ a:as) ++ [f] -- -f FILE ..., --alias ALIAS ... moveArgs (f:v:a:as) | isMovableReqArgFlag f, isValue v = (moveArgs $ a:as) ++ [f,v] -- -fFILE ..., --alias=ALIAS ... moveArgs (fv:a:as) | isMovableReqArgFlagAndValue fv = (moveArgs $ a:as) ++ [fv] -- -f(missing arg) moveArgs (f:a:as) | isMovableReqArgFlag f, not (isValue a) = (moveArgs $ a:as) ++ [f] -- anything else moveArgs as = as 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 -- | Template for the commands list. Includes an entry for known (or -- hypothetical) builtin and addon commands; these will be filtered -- based on the commands found at runtime. COUNT is replaced with the -- number of commands found. OTHERCMDS is replaced with an entry for -- each unknown addon command found. The command descriptions here -- should be synced with the commands' builtin help and the command -- list in the hledger manual. commandsListTemplate :: String commandsListTemplate = [here|Commands available (COUNT): Standard reports: accounts show chart of accounts balancesheet (bs) show a balance sheet cashflow (cf) show a cashflow statement incomestatement (is) show an income statement transactions (txns) show transactions in some account General reporting: activity show a bar chart of posting counts per interval balance (bal) show accounts and balances budget add automated postings/txns/bucket accts (experimental) chart generate simple balance pie charts (experimental) check check more powerful balance assertions check-dates check transactions are ordered by date check-dupes check for accounts with the same leaf name irr calculate internal rate of return of an investment prices show market price records print show transaction journal entries print-unique show only transactions with unique descriptions register (reg) show postings and running total register-match show best matching transaction for a description stats show some journal statistics Interfaces: add console ui for adding transactions api web api server iadd curses ui for adding transactions ui curses ui web web ui Misc: autosync download/deduplicate/convert OFX data equity generate transactions to zero & restore account balances interest generate interest transactions rewrite add automated postings to certain transactions test run some self tests OTHERCMDS Help: (see also -h, CMD -h, --help|---man|--info) help|man|info show any of the hledger manuals in text/man/info format |] knownCommands :: [String] knownCommands = sort $ commandsFromCommandsList commandsListTemplate -- | Extract the command names from a commands list like the above: -- the first word (or words separated by |) of lines beginning with a space. commandsFromCommandsList :: String -> [String] commandsFromCommandsList s = concatMap (splitOn "|") [w | ' ':l <- lines s, let w:_ = words l] -- | 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 commandsList where commandsFound = builtinCommandNames ++ addonsFound unknownCommandsFound = addonsFound \\ knownCommands adjustline (' ':l) | not $ w `elem` commandsFound = [] where w = takeWhile (not . (`elem` "| ")) l adjustline l = [l] commandsList1 = regexReplace "OTHERCMDS" (unlines [' ':w | w <- unknownCommandsFound]) $ unlines $ concatMap adjustline $ lines commandsListTemplate commandsList = regexReplace "COUNT" (show $ length $ commandsFromCommandsList commandsList1) commandsList1 -- | 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 let args' = moveFlagsAfterCommand 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 = tracePrettyAtIO 2 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 hasShortHelpFlag args = any (`elem` args) ["-h"] hasLongHelpFlag args = any (`elem` args) ["--help"] hasManFlag args = any (`elem` args) ["--man"] hasInfoFlag args = any (`elem` args) ["--info"] hasSomeHelpFlag args = hasShortHelpFlag args || hasLongHelpFlag args || hasManFlag args || hasInfoFlag args f `orShowHelp` mode | hasShortHelpFlag args = putStr $ showModeUsage mode | hasLongHelpFlag args = printHelpForTopic t | hasManFlag args = runManForTopic t | hasInfoFlag args = runInfoForTopic t | otherwise = f where t = topicForMode mode 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 runHledgerCommand -- high priority flags and situations. -h, then --help, then --info are highest priority. | hasShortHelpFlag argsbeforecmd = dbgIO "" "-h before command, showing general usage" >> printUsage | hasLongHelpFlag argsbeforecmd = dbgIO "" "--help before command, showing general manual" >> printHelpForTopic (topicForMode $ mainmode addons) | hasManFlag argsbeforecmd = dbgIO "" "--man before command, showing general manual with man" >> runManForTopic (topicForMode $ mainmode addons) | hasInfoFlag argsbeforecmd = dbgIO "" "--info before command, showing general manual with info" >> runInfoForTopic (topicForMode $ mainmode addons) | not (hasSomeHelpFlag argsaftercmd) && (hasVersion argsbeforecmd || (hasVersion argsaftercmd && isInternalCommand)) = putStrLn prognameandversion | not (hasSomeHelpFlag 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 -- internal commands | cmd == "activity" = withJournalDo opts histogram `orShowHelp` activitymode | cmd == "add" = (journalFilePathFromOpts opts >>= (ensureJournalFileExists . head) >> withJournalDo opts add) `orShowHelp` addmode | cmd == "accounts" = withJournalDo opts accounts `orShowHelp` accountsmode | cmd == "balance" = withJournalDo opts balance `orShowHelp` balancemode | cmd == "balancesheet" = withJournalDo opts balancesheet `orShowHelp` balancesheetmode | cmd == "cashflow" = withJournalDo opts cashflow `orShowHelp` cashflowmode | cmd == "incomestatement" = withJournalDo opts incomestatement `orShowHelp` incomestatementmode | cmd == "print" = withJournalDo opts print' `orShowHelp` printmode | cmd == "register" = withJournalDo opts register `orShowHelp` registermode | cmd == "stats" = withJournalDo opts stats `orShowHelp` statsmode | cmd == "test" = test' opts `orShowHelp` testmode | cmd == "help" = help' opts `orShowHelp` helpmode | cmd == "man" = man opts `orShowHelp` manmode | cmd == "info" = info' opts `orShowHelp` infomode -- an external command | 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 -- tests_runHledgerCommand = [ -- -- "runHledgerCommand" ~: do -- -- let opts = defreportopts{query_="expenses"} -- -- d <- getCurrentDay -- -- runHledgerCommand addons opts@CliOpts{command_=cmd} args -- ] hledger-1.2/Hledger/Cli/CliOptions.hs0000644000000000000000000007157613067077532015706 0ustar0000000000000000{-| Common cmdargs modes and flags, a command-line options type, and related utilities used by hledger commands. -} {-# LANGUAGE CPP, ScopedTypeVariables, DeriveDataTypeable, FlexibleContexts, TypeFamilies #-} module Hledger.Cli.CliOptions ( -- * cmdargs flags & modes helpflags, detailedversionflag, inputflags, reportflags, outputflags, generalflagsgroup1, generalflagsgroup2, generalflagsgroup3, defMode, defCommandMode, quickAddonCommandMode, hledgerCommandMode, argsFlag, showModeUsage, withAliases, -- * CLI options CliOpts(..), defcliopts, getHledgerCliOpts, decodeRawOpts, rawOptsToCliOpts, checkCliOpts, outputFormats, defaultOutputFormat, defaultBalanceLineFormat, -- possibly these should move into argsToCliOpts -- * CLI option accessors -- | These do the extra processing required for some options. aliasesFromOpts, journalFilePathFromOpts, rulesFilePathFromOpts, outputFileFromOpts, outputFormatFromOpts, defaultWidth, widthFromOpts, -- | For register: registerWidthsFromOpts, maybeAccountNameDrop, -- | For balance: lineFormatFromOpts, -- * Other utils hledgerAddons, topicForMode, -- * Tests tests_Hledger_Cli_CliOptions ) where import Prelude () import Prelude.Compat import qualified Control.Exception as C import Control.Monad (when) import Data.Default #if !MIN_VERSION_base(4,8,0) import Data.Functor.Compat ((<$>)) #endif import Data.Functor.Identity (Identity) import Data.List.Compat import Data.List.Split (splitOneOf) import Data.Ord import Data.Maybe -- import Data.Text (Text) import qualified Data.Text as T 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 Test.HUnit import Text.Megaparsec import Hledger import Hledger.Cli.DocFiles import Hledger.Cli.Version -- common cmdargs flags -- | Common help flags: --help, --debug, --version... helpflags :: [Flag RawOpts] helpflags = [ flagNone ["h"] (setboolopt "h") "show general usage (or after CMD, command usage)" ,flagNone ["help"] (setboolopt "help") "show this program's manual as plain text (or after an addon CMD, the add-on's manual)" ,flagNone ["man"] (setboolopt "man") "show this program's manual with man" ,flagNone ["info"] (setboolopt "info") "show this program's manual with info" -- ,flagNone ["browse-args"] (setboolopt "browse-args") "use a web UI to select options and build up a command line" ,flagReq ["debug"] (\s opts -> Right $ setopt "debug" s opts) "[N]" "show debug output (levels 1-9, default: 1)" ,flagNone ["version"] (setboolopt "version") "show version information" ] -- | A hidden flag, just for the hledger executable. detailedversionflag :: Flag RawOpts detailedversionflag = flagNone ["version+"] (setboolopt "version+") "show version information with extra detail" -- | Common input-related flags: --file, --rules-file, --alias... inputflags :: [Flag RawOpts] inputflags = [ flagReq ["file","f"] (\s opts -> Right $ setopt "file" s opts) "FILE" "use a different input file. For stdin, use - (default: $LEDGER_FILE or $HOME/.hledger.journal)" ,flagReq ["rules-file"] (\s opts -> Right $ setopt "rules-file" s opts) "RFILE" "CSV conversion rules file (default: FILE.rules)" ,flagReq ["alias"] (\s opts -> Right $ setopt "alias" s opts) "OLD=NEW" "rename accounts named OLD to NEW" ,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 = [ 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 (overrides the flags above)" ,flagNone ["date2"] (setboolopt "date2") "show, and make -b/-e/-p/date: match, secondary dates instead" ,flagNone ["cleared","C"] (setboolopt "cleared") "include only cleared postings/txns" ,flagNone ["pending"] (setboolopt "pending") "include only pending postings/txns" ,flagNone ["uncleared","U"] (setboolopt "uncleared") "include only uncleared (and pending) postings/txns" ,flagNone ["real","R"] (setboolopt "real") "include only non-virtual postings" ,flagReq ["depth"] (\s opts -> Right $ setopt "depth" s opts) "N" "hide accounts/postings deeper than N" ,flagNone ["empty","E"] (setboolopt "empty") "show items with zero amount, normally hidden" ,flagNone ["cost","B"] (setboolopt "cost") "convert amounts to their cost at transaction time (using the transaction price, if any)" ,flagNone ["value","V"] (setboolopt "value") "convert amounts to their market value on the report end date (using the most recent applicable market price, if any)" ] -- | Common output-related flags: --output-file, --output-format... outputflags = [ flagReq ["output-format","O"] (\s opts -> Right $ setopt "output-format" s opts) "FMT" "select the output format. Supported formats:\ntxt, csv." ,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 = [] -- 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 default flags are short and long help (-h and --help). -- The usage message shows [QUERY] as argument. defCommandMode :: [Name] -> Mode RawOpts defCommandMode names = defMode { modeNames=names ,modeGroupFlags = Group { groupNamed = [] ,groupUnnamed = [ flagNone ["h"] (setboolopt "h") "Show usage." -- ,flagNone ["help"] (setboolopt "help") "Show long help." ] ,groupHidden = [] -- flags not displayed in the usage } ,modeArgs = ([], Just $ argsFlag "[QUERY]") ,modeValue=[("command", headDef "" names)] } -- | A cmdargs mode representing the hledger add-on command with the given name. -- Like defCommandMode, but adds a appropriate short help message if the addon name -- is recognised, and includes hledger's common input/reporting/help flags as default. -- Just used by hledger for generating the commands list I think (or possibly for -- invoking the addons as well ?) quickAddonCommandMode :: Name -> Mode RawOpts quickAddonCommandMode name = (defCommandMode [name]) { modeHelp = fromMaybe "" $ lookup (stripAddonExtension name) standardAddonsHelp ,modeGroupFlags = Group { groupUnnamed = [] ,groupHidden = [] ,groupNamed = [generalflagsgroup1] } } -- | A template for a command's CLI help, influencing the content and layout -- of the usage text generated by a cmdargs mode. -- It is a multiline string structured like so: -- The first line defines the command name (first word) and aliases (any other words). -- From the second line up to a line containing just "FLAGS", or the end, is the preamble, -- displayed above the flags list generated by cmdargs. Short help goes here. -- Any lines after the FLAGS line are the postamble, displayed below the flags list. -- Long help/full manual goes here. type HelpTemplate = String -- | Parse a help template into command names, help preamble, and help postamble lines. parseHelpTemplate :: HelpTemplate -> Maybe ([Name], String, [String]) parseHelpTemplate t = case lines t of [] -> Nothing (l:ls) -> Just (names, preamble, postamblelines) where names = words l (preamblels, postamblels) = break (== "FLAGS") ls preamble = unlines $ reverse $ dropWhile null $ reverse preamblels postamblelines = dropWhile null $ drop 1 postamblels -- | Build a cmdarg mode suitable for a hledger add-on command, -- from a help template and flag/argument specifications. -- Reduces boilerplate a little, though the complicated cmdargs -- flag and argument specs are still required. -- See the addons in bin/ for examples of usage. hledgerCommandMode :: HelpTemplate -> [Flag RawOpts] -> [(Help, [Flag RawOpts])] -> [Flag RawOpts] -> ([Arg RawOpts], Maybe (Arg RawOpts)) -> Mode RawOpts hledgerCommandMode tmpl ungroupedflags groupedflags hiddenflags args = case parseHelpTemplate tmpl of Nothing -> error' $ "Could not parse help template:\n"++tmpl++"\n" Just (names, preamble, postamblelines) -> (defCommandMode names) { modeHelp = preamble ,modeHelpSuffix = postamblelines ,modeGroupFlags = Group { groupUnnamed = ungroupedflags ,groupNamed = groupedflags ,groupHidden = hiddenflags } ,modeArgs = args } -- | Built-in descriptions for some of the known addons. standardAddonsHelp :: [(String,String)] standardAddonsHelp = [ ("chart", "generate simple balance pie charts") ,("interest", "generate interest transaction entries") ,("irr", "calculate internal rate of return") ,("vty", "start the curses-style interface") ,("web", "start the web interface") ,("accounts", "list account names") ,("balance-csv", "output a balance report as CSV") ,("equity", "show a transaction entry zeroing all accounts") ,("print-unique", "print only transactions with unique descriptions") ,("register-csv", "output a register report as CSV") ,("rewrite", "add specified postings to matched transaction entries") ,("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") ] -- | 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, hledger-web or -- hledger-api manual. topicForMode :: Mode a -> Topic topicForMode m | n == "hledger-ui" = "ui" | n == "hledger-web" = "web" -- | n == "hledger-api" = lookupDocTxt "api" -- hledger-api uses docopt | 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] ,rules_file_ :: Maybe FilePath ,output_file_ :: Maybe FilePath ,output_format_ :: Maybe String ,alias_ :: [String] ,ignore_assertions_ :: Bool ,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) ,reportopts_ :: ReportOpts } deriving (Show, Data, Typeable) instance Default CliOpts where def = defcliopts defcliopts :: CliOpts defcliopts = CliOpts def def def def def def def def def def def defaultWidth def -- | Convert possibly encoded option values to regular unicode strings. decodeRawOpts :: RawOpts -> RawOpts decodeRawOpts = map (\(name',val) -> (name', fromSystemString val)) -- | Default width for hledger console output, when not otherwise specified. defaultWidth :: Int defaultWidth = 80 -- | 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 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_ = map (T.unpack . stripquotes . T.pack) $ listofstringopt "file" rawopts ,rules_file_ = maybestringopt "rules-file" rawopts ,output_file_ = maybestringopt "output-file" rawopts ,output_format_ = maybestringopt "output-format" rawopts ,alias_ = map (T.unpack . stripquotes . T.pack) $ listofstringopt "alias" rawopts ,debug_ = intopt "debug" rawopts ,ignore_assertions_ = boolopt "ignore-assertions" rawopts ,no_new_accounts_ = boolopt "no-new-accounts" rawopts -- add ,width_ = maybestringopt "width" rawopts ,available_width_ = availablewidth ,reportopts_ = ropts } -- | 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. -- -- 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 -> IO CliOpts getHledgerCliOpts mode' = do args' <- getArgs let rawopts = either usageError decodeRawOpts $ process mode' args' opts <- rawOptsToCliOpts rawopts debugArgs args' opts when ("help" `inRawOpts` rawopts_ opts) $ putStr longhelp >> exitSuccess when ("h" `inRawOpts` rawopts_ opts) $ putStr shorthelp >> exitSuccess return opts where longhelp = showModeUsage mode' shorthelp = unlines $ (reverse $ dropWhile null $ reverse $ takeWhile (not . ("flags:" `isInfixOf`)) $ lines longhelp) ++ ["" ," See --help for full detail, including common 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) -- CliOpts accessors -- | Get the account name aliases from options, if any. aliasesFromOpts :: CliOpts -> [AccountAlias] aliasesFromOpts = map (\a -> fromparse $ runParser accountaliasp ("--alias "++quoteIfNeeded a) $ T.pack a) . alias_ -- | 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" ] -- | 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) $ rules_file_ 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 Dec 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 Dec s m (Int, Maybe Int) registerwidthp = do totalwidth <- read `fmap` some digitChar descwidth <- optional (char ',' >> read `fmap` some digitChar) eof return (totalwidth, descwidth) -- | Drop leading components of accounts names as specified by --drop, but only in --flat mode. maybeAccountNameDrop :: ReportOpts -> AccountName -> AccountName maybeAccountNameDrop opts a | tree_ opts = a | otherwise = accountNameDrop (drop_ opts) a -- 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] | takeExtension f `elem` compiledExts = [f] | takeExtension g `elem` compiledExts = [g] dropRedundantSourceVersion fs = fs compiledExts = ["",".com",".exe"] -- | Get the sorted unique filenames of all hledger-* executables in -- the current user's PATH. Currently 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. Limitations: -- we do not currently check that the file is really a file (not eg a -- directory) or whether it has execute permission. hledgerExecutablesInPath :: IO [String] hledgerExecutablesInPath = do pathdirs <- splitOneOf "[:;]" `fmap` getEnvSafe "PATH" pathfiles <- concat `fmap` mapM getDirectoryContentsSafe pathdirs return $ nub $ sort $ filter isHledgerExeName pathfiles -- XXX should exclude directories and files without execute permission. -- These will do a stat for each hledger-*, probably ok. -- But they need paths, not just filenames -- hledgerexes <- filterM doesFileExist hledgernamed -- hledgerexes' <- filterM isExecutable hledgerexes -- return hledgerexes -- isExecutable f = getPermissions f >>= (return . executable) isHledgerExeName :: String -> Bool isHledgerExeName = isRight . parsewith hledgerexenamep . T.pack where hledgerexenamep = do _ <- string progname _ <- char '-' _ <- some (noneOf ".") optional (string "." >> choice' (map string 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) -- tests tests_Hledger_Cli_CliOptions :: Test tests_Hledger_Cli_CliOptions = TestList [ ] hledger-1.2/Hledger/Cli/DocFiles.hs0000644000000000000000000000724113035210046015257 0ustar0000000000000000{-# LANGUAGE TemplateHaskell, OverloadedStrings #-} {-| Embedded documentation files in various formats, and helpers for viewing them. |-} module Hledger.Cli.DocFiles ( Topic ,docFiles ,docTopics ,lookupDocNroff ,lookupDocTxt ,lookupDocInfo ,printHelpForTopic ,runManForTopic ,runInfoForTopic ) where import Prelude () import Prelude.Compat import Data.FileEmbed import Data.String import System.IO import System.IO.Temp import System.Process import Hledger.Utils (first3, second3, third3) type Topic = String docFiles :: IsString a => [(Topic, (a, a, a))] docFiles = [ ("cli", ($(makeRelativeToProject "doc/hledger.1" >>= embedStringFile) ,$(makeRelativeToProject "doc/hledger.1.txt" >>= embedStringFile) ,$(makeRelativeToProject "doc/hledger.1.info" >>= embedStringFile) )) ,("ui", ($(makeRelativeToProject "doc/other/hledger-ui.1" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger-ui.1.txt" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger-ui.1.info" >>= embedStringFile) )) ,("web", ($(makeRelativeToProject "doc/other/hledger-web.1" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger-web.1.txt" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger-web.1.info" >>= embedStringFile) )) ,("api", ($(makeRelativeToProject "doc/other/hledger-api.1" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger-api.1.txt" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger-api.1.info" >>= embedStringFile) )) ,("journal", ($(makeRelativeToProject "doc/other/hledger_journal.5" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger_journal.5.txt" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger_journal.5.info" >>= embedStringFile) )) ,("csv", ($(makeRelativeToProject "doc/other/hledger_csv.5" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger_csv.5.txt" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger_csv.5.info" >>= embedStringFile) )) ,("timeclock", ($(makeRelativeToProject "doc/other/hledger_timeclock.5" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger_timeclock.5.txt" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger_timeclock.5.info" >>= embedStringFile) )) ,("timedot", ($(makeRelativeToProject "doc/other/hledger_timedot.5" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger_timedot.5.txt" >>= embedStringFile) ,$(makeRelativeToProject "doc/other/hledger_timedot.5.info" >>= embedStringFile) )) ] docTopics :: [Topic] docTopics = map fst docFiles lookupDocTxt :: IsString a => Topic -> a lookupDocTxt name = maybe (fromString $ "No text manual found for topic: "++name) second3 $ lookup name docFiles lookupDocNroff :: IsString a => Topic -> a lookupDocNroff name = maybe (fromString $ "No man page found for topic: "++name) first3 $ lookup name docFiles lookupDocInfo :: IsString a => Topic -> a lookupDocInfo name = maybe (fromString $ "No info manual found for topic: "++name) third3 $ lookup name docFiles printHelpForTopic :: Topic -> IO () printHelpForTopic t = putStrLn $ lookupDocTxt t runManForTopic :: Topic -> IO () runManForTopic t = withSystemTempFile ("hledger-"++t++".nroff") $ \f h -> do 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 hPutStrLn h $ lookupDocInfo t hClose h callCommand $ "info " ++ f hledger-1.2/Hledger/Cli/Tests.hs0000644000000000000000000000375113035210046014673 0ustar0000000000000000-- {-# OPTIONS_GHC -F -pgmF htfpp #-} {-# LANGUAGE CPP #-} {- | A simple test runner for hledger's built-in unit tests. -} module Hledger.Cli.Tests ( testmode ,test' ) where import Control.Monad -- import Data.Text (Text) import qualified Data.Text as T import System.Exit import Test.HUnit import Hledger import Hledger.Cli #ifdef TESTS import Test.Framework import {-@ HTF_TESTS @-} Hledger.Read.JournalReader -- | Run HTF unit tests and exit with success or failure. test' :: CliOpts -> IO () test' _opts = htfMain htf_importedTests #else -- | Run HUnit unit tests and exit with success or failure. test' :: CliOpts -> IO () test' opts = do results <- runTests opts if errors results > 0 || failures results > 0 then exitFailure else exitWith ExitSuccess testmode = (defCommandMode ["test"]) { modeHelp = "run built-in self-tests" ,modeArgs = ([], Just $ argsFlag "[REGEXPS]") ,modeGroupFlags = Group { groupUnnamed = [] ,groupHidden = [] ,groupNamed = [generalflagsgroup3] } } -- | Run all or just the matched unit tests and return their HUnit result counts. runTests :: CliOpts -> IO Counts runTests = liftM (fst . flip (,) 0) . runTestTT . flatTests -- -- | Run all or just the matched unit tests until the first failure or -- -- error, returning the name of the problem test if any. -- runTestsTillFailure :: CliOpts -> IO (Maybe String) -- runTestsTillFailure _ = undefined -- do -- -- let ts = flatTests opts -- -- results = liftM (fst . flip (,) 0) $ runTestTT $ -- -- firstproblem = find (\counts -> ) -- | All or pattern-matched tests, as a flat list to show simple names. flatTests opts = TestList $ filter (matchesAccount (queryFromOpts nulldate $ reportopts_ opts) . T.pack . testName) $ flattenTests tests_Hledger_Cli -- -- | All or pattern-matched tests, in the original suites to show hierarchical names. -- hierarchicalTests opts = filterTests (matchesAccount (queryFromOpts nulldate $ reportopts_ opts) . testName) tests_Hledger_Cli #endif hledger-1.2/Hledger/Cli/Utils.hs0000644000000000000000000002434413066173044014704 0ustar0000000000000000{-# LANGUAGE ScopedTypeVariables, CPP #-} {-| Utilities for top-level modules and ghci. See also Hledger.Read and Hledger.Utils. -} module Hledger.Cli.Utils ( withJournalDo, writeOutput, journalReload, journalReloadIfChanged, journalFileIsNewer, journalSpecifiedFileIsNewer, fileModificationTime, openBrowserOn, writeFileWithBackup, writeFileWithBackupIfChanged, readFileStrictly, Test(TestList), ) where import Control.Exception as C import Control.Monad ((<=<)) import Data.Hashable (hash) import Data.List import Data.Maybe import Data.Text (Text) import qualified Data.Text as T import qualified Data.Text.IO as T import Data.Time (Day) import Data.Word import Numeric 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 Test.HUnit import Text.Printf import Text.Regex.TDFA ((=~)) -- kludge - adapt to whichever directory version is installed, or when -- cabal macros aren't available, assume the new directory #ifdef MIN_VERSION_directory #if MIN_VERSION_directory(1,2,0) #define directory_1_2 #endif #else #define directory_1_2 #endif #ifdef directory_1_2 import System.Time (ClockTime(TOD)) import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds) #endif import Hledger.Cli.CliOptions import Hledger.Data import Hledger.Read import Hledger.Reports import Hledger.Utils -- | Parse the user's specified journal file, maybe apply some transformations -- (aliases, pivot) and run a hledger command on it, or throw an error. withJournalDo :: CliOpts -> (CliOpts -> Journal -> IO ()) -> IO () 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. rulespath <- rulesFilePathFromOpts opts journalpaths <- journalFilePathFromOpts opts ej <- readJournalFiles Nothing rulespath (not $ ignore_assertions_ opts) journalpaths let f = cmd opts . pivotByOpts opts . anonymiseByOpts opts . journalApplyAliases (aliasesFromOpts opts) <=< journalApplyValue (reportopts_ opts) either error' f ej -- | 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 -> pivot $ T.pack tag Nothing -> id -- | Apply the pivot transformation by given tag on a journal. pivot :: Text -> Journal -> Journal pivot tag j = j{jtxns = map pivotTrans . jtxns $ j} where pivotTrans t = t{tpostings = map pivotPosting . tpostings $ t} pivotPosting p | Just (_ , value) <- tagTuple = p{paccount = value, porigin = Just $ originalPosting p} | _ <- tagTuple = p{paccount = T.pack "", porigin = Just $ originalPosting p} where tagTuple = find ((tag ==) . fst) . postingAllImplicitTags $ p -- | Apply the anonymisation transformation on a journal, if option is present anonymiseByOpts :: CliOpts -> Journal -> Journal anonymiseByOpts opts = case maybestringopt "anon" . rawopts_ $ opts of Just _ -> anonymise Nothing -> id -- | Apply the anonymisation transformation on a journal anonymise :: Journal -> Journal anonymise j = let pAnons p = p { paccount = T.intercalate (T.pack ":") . map anon . T.splitOn (T.pack ":") . paccount $ p , pcomment = T.empty , ptransaction = fmap tAnons . ptransaction $ p } tAnons txn = txn { tpostings = map pAnons . tpostings $ txn , tdescription = anon . tdescription $ txn , tcomment = T.empty } in j { jtxns = map tAnons . jtxns $ j } where anon = T.pack . flip showHex "" . (fromIntegral :: Int -> Word32) . hash journalApplyValue :: ReportOpts -> Journal -> IO Journal journalApplyValue ropts j = do mvaluedate <- reportEndDate j ropts let convert | value_ ropts , Just d <- mvaluedate = overJournalAmounts (amountValue j d) | otherwise = id return $ convert j -- | Write some output to stdout or to a file selected by --output-file. 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. -- readJournalWithOpts :: CliOpts -> String -> IO Journal -- readJournalWithOpts opts s = readJournal Nothing Nothing Nothing s >>= either error' return -- | Re-read the journal file(s) specified by options and maybe apply some -- transformations (aliases, pivot), or return an error string. -- Reads the full journal, without filtering. journalReload :: CliOpts -> IO (Either String Journal) journalReload opts = do rulespath <- rulesFilePathFromOpts opts journalpaths <- journalFilePathFromOpts opts ((pivotByOpts opts . journalApplyAliases (aliasesFromOpts opts)) <$>) <$> readJournalFiles Nothing rulespath (not $ ignore_assertions_ opts) journalpaths -- | 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 #ifdef directory_1_2 utc <- getModificationTime f let nom = utcTimeToPOSIXSeconds utc let clo = TOD (read $ takeWhile (`elem` "0123456789") $ show nom) 0 -- XXX read #else clo <- getModificationTime f #endif 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. writeFileWithBackupIfChanged :: FilePath -> T.Text -> IO Bool writeFileWithBackupIfChanged f t = do s <- readFile' 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 = readFile' 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 hledger-1.2/Hledger/Cli/Version.hs0000644000000000000000000000475513035210046015223 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" prettify _ = error' "VERSION has too many components, please fix" hledger-1.2/Hledger/Cli/Add.hs0000644000000000000000000005125113067025341014266 0ustar0000000000000000{-| A history-aware add command to help with data entry. |-} {-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-unused-do-bind #-} {-# LANGUAGE CPP, ScopedTypeVariables, DeriveDataTypeable, RecordWildCards, TypeOperators, FlexibleContexts, OverloadedStrings #-} module Hledger.Cli.Add where import Prelude () import Prelude.Compat import Control.Exception as E import Control.Monad import Control.Monad.Trans.Class import Control.Monad.State.Strict (evalState, evalStateT) import Control.Monad.Trans (liftIO) import Data.Char (toUpper, toLower) import 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.Typeable (Typeable) import Safe (headDef, headMay) 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.Text import Text.Printf import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Register (postingsReportAsText) addmode = (defCommandMode ["add"]) { modeHelp = "prompt for transactions and add them to the journal" ,modeHelpSuffix = ["Defaults come from previous similar transactions; use query patterns to restrict these."] ,modeGroupFlags = Group { groupUnnamed = [ flagNone ["no-new-accounts"] (\opts -> setboolopt "no-new-accounts" opts) "don't allow creating new accounts" ] ,groupHidden = [] ,groupNamed = [generalflagsgroup2] } } -- | 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,Typeable) defEntryState = EntryState { esOpts = defcliopts ,esArgs = [] ,esToday = nulldate ,esDefDate = nulldate ,esJournal = nulljournal ,esSimilarTransaction = Nothing ,esPostings = [] } data RestartTransactionException = RestartTransactionException deriving (Typeable,Show) instance Exception RestartTransactionException -- data ShowHelpException = ShowHelpException deriving (Typeable,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=map (T.unpack . stripquotes . T.pack) $ 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 restart the transaction." ,"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 mt <- runInputT (setComplete noCompletion defaultSettings) (run $ haskeline $ confirmedTransactionWizard es) case mt of Nothing -> fail "urk ?" 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) -- confirmedTransactionWizard :: (ArbitraryIO :<: b, OutputLn :<: b, Line :<: b) => EntryState -> Wizard b Transaction -- confirmedTransactionWizard :: EntryState -> Wizard Haskeline Transaction confirmedTransactionWizard es@EntryState{..} = do t <- transactionWizard es -- liftIO $ hPrintf stderr {- "Transaction entered:\n%s" -} (show t) output $ show t y <- let def = "y" in retryMsg "Please enter y or n." $ parser ((fmap ('y' ==)) . headMay . map toLower . strip) $ defaultTo' def $ nonEmpty $ maybeRestartTransaction $ line $ green $ printf "Save this transaction to the journal ?%s: " (showDefault def) if y then return t else throw RestartTransactionException transactionWizard es@EntryState{..} = do (date,code) <- dateAndCodeWizard es let es1@EntryState{esArgs=args1} = es{esArgs=drop 1 esArgs, esDefDate=date} (desc,comment) <- descriptionAndCommentWizard es1 let mbaset = similarTransaction es1 desc when (isJust mbaset) $ liftIO $ hPrintf stderr "Using this similar transaction for defaults:\n%s" (show $ fromJust mbaset) let es2 = es1{esArgs=drop 1 args1, esSimilarTransaction=mbaset} balancedPostingsWizard = do ps <- postingsWizard es2{esPostings=[]} let t = nulltransaction{tdate=date ,tstatus=Uncleared ,tcode=code ,tdescription=desc ,tcomment=comment ,tpostings=ps } case balanceTransaction Nothing t of -- imprecise balancing (?) Right t' -> return t' Left err -> liftIO (hPutStrLn stderr $ "\n" ++ (capitalize err) ++ "please re-enter.") >> balancedPostingsWizard balancedPostingsWizard -- 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 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 $ maybeRestartTransaction $ -- maybeShowHelp $ line $ green $ printf "Date%s: " (showDefault def) where parseSmartDateAndCode refdate s = either (const Nothing) (\(d,c) -> return (fixSmartDate refdate d, c)) edc where edc = runParser (dateandcodep <* eof) "" $ T.pack $ lowercase s dateandcodep :: Parser (SmartDate, Text) dateandcodep = do d <- smartdate c <- optional codep many spacenonewline eof return (d, T.pack $ fromMaybe "" c) -- defday = fixSmartDate today $ fromparse $ (parse smartdate "" . lowercase) defdate -- datestr = showDate $ fixSmartDate defday smtdate descriptionAndCommentWizard EntryState{..} = do let def = headDef "" esArgs s <- withCompletion (descriptionCompleter esJournal def) $ defaultTo' def $ nonEmpty $ maybeRestartTransaction $ line $ green $ printf "Description%s: " (showDefault def) let (desc,comment) = (T.pack $ strip a, T.pack $ strip $ dropWhile (==';') b) where (a,b) = break (==';') s return (desc, comment) postingsWizard es@EntryState{..} = do mp <- postingWizard es case mp of Nothing -> return esPostings Just p -> postingsWizard es{esArgs=drop 2 esArgs, esPostings=esPostings++[p]} postingWizard es@EntryState{..} = do acct <- accountWizard es if acct `elem` [".",""] then case (esPostings, postingsBalanced esPostings) of ([],_) -> liftIO (hPutStrLn stderr "Please enter some postings first.") >> postingWizard es (_,False) -> liftIO (hPutStrLn stderr "Please enter more postings to balance the transaction.") >> postingWizard es (_,True) -> return Nothing -- no more postings, end of transaction else do let es1 = es{esArgs=drop 1 esArgs} (amt,comment) <- amountAndCommentWizard es1 return $ Just nullposting{paccount=T.pack $ stripbrackets acct ,pamount=Mixed [amt] ,pcomment=comment ,ptype=accountNamePostingType $ T.pack acct } postingsBalanced :: [Posting] -> Bool postingsBalanced ps = isRight $ balanceTransaction Nothing nulltransaction{tpostings=ps} accountWizard EntryState{..} = do let pnum = length esPostings + 1 historicalp = maybe Nothing (Just . (!! (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 $ maybeRestartTransaction $ line $ green $ printf "Account %d%s%s: " pnum (endmsg::String) (showDefault def) where canfinish = not (null esPostings) && postingsBalanced esPostings parseAccountOrDotOrNull :: String -> Bool -> String -> Maybe String parseAccountOrDotOrNull _ _ "." = dbg1 $ Just "." -- . always signals end of txn parseAccountOrDotOrNull "" True "" = dbg1 $ Just "" -- when there's no default and txn is balanced, "" also signals end of txn parseAccountOrDotOrNull def@(_:_) _ "" = dbg1 $ Just def -- when there's a default, "" means use that parseAccountOrDotOrNull _ _ s = dbg1 $ fmap 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 && not (t `elem` journalAccountNames esJournal) = Nothing | otherwise = Just t dbg1 = id -- strace amountAndCommentWizard 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 (isZeroMixedAmount 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 $ maybeRestartTransaction $ line $ green $ printf "Amount %d%s: " pnum (showDefault def) where parseAmountAndComment s = either (const Nothing) Just $ runParser (evalStateT (amountandcommentp <* eof) nodefcommodityj) "" (T.pack s) nodefcommodityj = esJournal{jparsedefaultcommodity=Nothing} amountandcommentp :: JournalParser (Amount, Text) amountandcommentp = do a <- amountp lift (many spacenonewline) c <- T.pack <$> fromMaybe "" `fmap` optional (char ';' >> many anyChar) -- 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 maxprecisionwithpoint -- -- 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) maybeRestartTransaction = parser (\s -> if s=="<" then throw RestartTransactionException 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 $ journalAccountNamesUsed 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 $ showTransactionUnelided 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 (show 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. 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.2/Hledger/Cli/Accounts.hs0000644000000000000000000000461213035210046015345 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 OverloadedStrings #-} module Hledger.Cli.Accounts ( accountsmode ,accounts ,tests_Hledger_Cli_Accounts ) where import Data.List import Data.Monoid -- import Data.Text (Text) import qualified Data.Text as T import System.Console.CmdArgs.Explicit as C import Test.HUnit import Hledger import Prelude hiding (putStrLn) import Hledger.Utils.UTF8IOCompat (putStrLn) import Hledger.Cli.CliOptions -- | Command line options for this command. accountsmode = (defCommandMode $ ["accounts"] ++ aliases) { modeHelp = "show account names" `withAliases` aliases ,modeHelpSuffix = [ "This command lists the accounts referenced by matched postings (and in tree mode, their parents as well). The accounts can be depth-clipped (--depth N) or have their leading parts trimmed (--drop N)." ] ,modeGroupFlags = C.Group { groupUnnamed = [ flagNone ["tree"] (\opts -> setboolopt "tree" opts) "show short account names, as a tree" ,flagNone ["flat"] (\opts -> setboolopt "flat" opts) "show full account names, as a list (default)" ,flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "flat mode: omit N leading account name parts" ] ,groupHidden = [] ,groupNamed = [generalflagsgroup1] } } where aliases = [] -- | The accounts command. accounts :: CliOpts -> Journal -> IO () accounts CliOpts{reportopts_=ropts} j = do d <- getCurrentDay let q = queryFromOpts d ropts nodepthq = dbg1 "nodepthq" $ filterQuery (not . queryIsDepth) q depth = dbg1 "depth" $ queryDepth $ filterQuery queryIsDepth q ps = dbg1 "ps" $ journalPostings $ filterJournalPostings nodepthq j as = dbg1 "as" $ nub $ filter (not . T.null) $ map (clipAccountName depth) $ sort $ map paccount ps as' | tree_ ropts = expandAccountNames as | otherwise = as render a | tree_ ropts = T.replicate (2 * (accountNameLevel a - 1)) " " <> accountLeafName a | otherwise = maybeAccountNameDrop ropts a mapM_ (putStrLn . T.unpack . render) as' tests_Hledger_Cli_Accounts = TestList [] hledger-1.2/Hledger/Cli/Balance.hs0000644000000000000000000005267513067562322015143 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 correponding or prior postings, ie the account doesn't exist yet. Currently, empty cells show 0. -} {-# LANGUAGE OverloadedStrings #-} module Hledger.Cli.Balance ( balancemode ,balance ,balanceReportAsText ,balanceReportItemAsText ,multiBalanceReportAsText ,renderBalanceReportTable ,balanceReportAsTable ,tests_Hledger_Cli_Balance ) where import Data.List (intercalate) import Data.Maybe -- import Data.Monoid import qualified Data.Text as T import System.Console.CmdArgs.Explicit as C import Text.CSV import Test.HUnit import Text.Printf (printf) import Text.Tabular as T import Text.Tabular.AsciiWide import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Utils -- | Command line options for this command. balancemode = (defCommandMode $ ["balance"] ++ aliases) { -- also accept but don't show the common bal alias modeHelp = "show accounts and balances" `withAliases` aliases ,modeGroupFlags = C.Group { groupUnnamed = [ flagNone ["change"] (\opts -> setboolopt "change" opts) "show balance change in each period (default)" ,flagNone ["cumulative"] (\opts -> setboolopt "cumulative" opts) "show balance change accumulated across periods (in multicolumn reports)" ,flagNone ["historical","H"] (\opts -> setboolopt "historical" opts) "show historical ending balance in each period (includes postings before report start date)\n " ,flagNone ["tree"] (\opts -> setboolopt "tree" opts) "show accounts as a tree; amounts include subaccounts (default in simple reports)" ,flagNone ["flat"] (\opts -> setboolopt "flat" opts) "show accounts as a list; amounts exclude subaccounts except when account is depth-clipped (default in multicolumn reports)\n " ,flagNone ["average","A"] (\opts -> setboolopt "average" opts) "show a row average column (in multicolumn reports)" ,flagNone ["row-total","T"] (\opts -> setboolopt "row-total" opts) "show a row total column (in multicolumn reports)" ,flagNone ["no-total","N"] (\opts -> setboolopt "no-total" opts) "omit the final total row" ,flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "omit N leading account name parts (in flat mode)" ,flagNone ["no-elide"] (\opts -> setboolopt "no-elide" opts) "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"] (\opts -> setboolopt "pretty-tables" opts) "use unicode when displaying tables" ] ++ outputflags ,groupHidden = [] ,groupNamed = [generalflagsgroup1] } } where aliases = ["bal"] -- | The balance command, prints a balance report. balance :: CliOpts -> Journal -> IO () balance opts@CliOpts{reportopts_=ropts} j = do d <- getCurrentDay case lineFormatFromOpts ropts of Left err -> error' $ unlines [err] Right _ -> do let format = outputFormatFromOpts opts interval = interval_ ropts -- shenanigans: use single/multiBalanceReport when we must, -- ie when there's a report interval, or --historical or -- cumulative. -- Otherwise prefer the older balanceReport since it can elide boring parents. case interval of NoInterval -> do let report -- For --historical/--cumulative, we must use multiBalanceReport. -- (This forces --no-elide.) | balancetype_ ropts `elem` [HistoricalBalance, CumulativeChange] = let ropts' | flat_ ropts = ropts | otherwise = ropts{accountlistmode_=ALTree} in singleBalanceReport ropts' (queryFromOpts d ropts) j | otherwise = balanceReport ropts (queryFromOpts d ropts) j render = case format of "csv" -> \ropts r -> (++ "\n") $ printCSV $ balanceReportAsCsv ropts r _ -> balanceReportAsText writeOutput opts $ render ropts report _ -> do let report = multiBalanceReport ropts (queryFromOpts d ropts) j render = case format of "csv" -> \ropts r -> (++ "\n") $ printCSV $ multiBalanceReportAsCsv ropts r _ -> multiBalanceReportAsText writeOutput opts $ render ropts report -- single-column balance reports -- | Find the best commodity to convert to when asked to show the -- market value of this commodity on the given date. That is, the one -- in which it has most recently been market-priced, ie the commodity -- mentioned in the most recent applicable historical price directive -- before this date. -- defaultValuationCommodity :: Journal -> Day -> CommoditySymbol -> Maybe CommoditySymbol -- defaultValuationCommodity j d c = mpamount <$> commodityValue j d c -- | Render a single-column balance report as CSV. balanceReportAsCsv :: ReportOpts -> BalanceReport -> CSV balanceReportAsCsv opts (items, total) = ["account","balance"] : [[T.unpack a, showMixedAmountOneLineWithoutPrice b] | (a, _, _, b) <- items] ++ if no_total_ opts then [] else [["total", showMixedAmountOneLineWithoutPrice 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 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 _ -> [] tests_balanceReportAsText = [ "balanceReportAsText" ~: do -- "unicode in balance layout" ~: do j <- readJournal' "2009/01/01 * медвежья шкура\n расходы:покупки 100\n актив:наличные\n" let opts = defreportopts balanceReportAsText opts (balanceReport opts (queryFromOpts (parsedate "2008/11/26") opts) j) `is` unlines [" -100 актив:наличные" ," 100 расходы:покупки" ,"--------------------" ," 0" ] ] {- :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 fmt ( maybeAccountNameDrop opts accountName, depth, normaliseMixedAmountSquashPricesForDisplay amt ) -- | Render a balance report item using the given StringFormat, generating one or more lines of text. renderBalanceReportItem :: StringFormat -> (AccountName, Int, MixedAmount) -> [String] renderBalanceReportItem 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 (acctname, depth, total)) render = map (renderComponent (acctname, depth, total)) defaultTotalFieldWidth = 20 -- | Render one StringFormat component for a balance report item. renderComponent :: (AccountName, Int, MixedAmount) -> StringFormatComponent -> String renderComponent _ (FormatLiteral s) = s renderComponent (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 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 :: (AccountName, Int, MixedAmount) -> StringFormatComponent -> String renderComponent1 _ (FormatLiteral s) = s renderComponent1 (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) (showMixedAmountWithoutPrice total)) _ -> "" -- multi-column balance reports -- | Render a multi-column balance report as CSV. multiBalanceReportAsCsv :: ReportOpts -> MultiBalanceReport -> CSV multiBalanceReportAsCsv opts (MultiBalanceReport (colspans, items, (coltotals,tot,avg))) = ("account" : "short account" : "indent" : map showDateSpan colspans ++ (if row_total_ opts then ["total"] else []) ++ (if average_ opts then ["average"] else []) ) : [T.unpack a : T.unpack a' : show i : map showMixedAmountOneLineWithoutPrice (amts ++ (if row_total_ opts then [rowtot] else []) ++ (if average_ opts then [rowavg] else [])) | (a,a',i, amts, rowtot, rowavg) <- items] ++ if no_total_ opts then [] else [["totals", "", ""] ++ map showMixedAmountOneLineWithoutPrice ( coltotals ++ (if row_total_ opts then [tot] else []) ++ (if average_ opts then [avg] else []) )] -- | Render a multi-column balance report as plain text suitable for console output. multiBalanceReportAsText :: ReportOpts -> MultiBalanceReport -> String multiBalanceReportAsText opts r = printf "%s in %s:" typeStr (showDateSpan $ multiBalanceReportSpan r) ++ "\n" ++ renderBalanceReportTable opts tabl where tabl = balanceReportAsTable opts r typeStr :: String typeStr = case balancetype_ opts of PeriodChange -> "Balance changes" CumulativeChange -> "Ending balances (cumulative)" HistoricalBalance -> "Ending balances (historical)" -- | Given a table representing a multi-column balance report (for example, -- made using 'balanceReportAsTable'), render it in a format suitable for -- console output. renderBalanceReportTable :: ReportOpts -> Table String String MixedAmount -> String renderBalanceReportTable (ReportOpts { pretty_tables_ = pretty }) = unlines . trimborder . lines . render pretty id (" " ++) showMixedAmountOneLineWithoutPrice . align where trimborder = ("":) . (++[""]) . drop 1 . init . map (drop 1 . init) align (Table l t d) = Table l' t d where acctswidth = maximum' $ map strWidth (headerContents l) l' = padRightWide acctswidth <$> l -- | Build a 'Table' from a multi-column balance report. balanceReportAsTable :: ReportOpts -> MultiBalanceReport -> Table String String MixedAmount balanceReportAsTable opts (MultiBalanceReport (colspans, items, (coltotals,tot,avg))) = addtotalrow $ Table (T.Group NoLine $ map Header accts) (T.Group NoLine $ map Header colheadings) (map rowvals items) where mkDate = case balancetype_ opts of PeriodChange -> showDateSpan _ -> maybe "" (showDate . prevday) . spanEnd colheadings = map mkDate colspans ++ (if row_total_ opts then [" Total"] else []) ++ (if average_ opts then ["Average"] else []) accts = map renderacct items renderacct (a,a',i,_,_,_) | tree_ opts = replicate ((i-1)*2) ' ' ++ T.unpack a' | otherwise = T.unpack $ maybeAccountNameDrop opts a rowvals (_,_,_,as,rowtot,rowavg) = as ++ (if row_total_ opts then [rowtot] else []) ++ (if average_ opts then [rowavg] else []) addtotalrow | no_total_ opts = id | otherwise = (+----+ (row "" $ coltotals ++ (if row_total_ opts then [tot] else []) ++ (if average_ opts then [avg] else []) )) -- | Figure out the overall date span of a multicolumn balance report. multiBalanceReportSpan :: MultiBalanceReport -> DateSpan multiBalanceReportSpan (MultiBalanceReport ([], _, _)) = DateSpan Nothing Nothing multiBalanceReportSpan (MultiBalanceReport (colspans, _, _)) = DateSpan (spanStart $ head colspans) (spanEnd $ last colspans) tests_Hledger_Cli_Balance = TestList tests_balanceReportAsText hledger-1.2/Hledger/Cli/Balancesheet.hs0000644000000000000000000000237513067573465016176 0ustar0000000000000000{-# LANGUAGE QuasiQuotes, RecordWildCards, NoCPP #-} {-| The @balancesheet@ command prints a simple balance sheet. -} module Hledger.Cli.Balancesheet ( balancesheetmode ,balancesheet ,tests_Hledger_Cli_Balancesheet ) where import Data.String.Here import System.Console.CmdArgs.Explicit import Test.HUnit import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.BalanceView bsBV = BalanceView { bvmode = "balancesheet", bvaliases = ["bs"], bvhelp = [here|This command displays a simple balance sheet, showing historical ending balances of asset and liability accounts (ignoring any report begin date). It assumes that these accounts are under a top-level `asset` or `liability` account (plural forms also allowed). |], bvtitle = "Balance Sheet", bvqueries = [ ("Assets" , journalAssetAccountQuery), ("Liabilities", journalLiabilityAccountQuery) ], bvtype = HistoricalBalance } balancesheetmode :: Mode RawOpts balancesheetmode = balanceviewmode bsBV balancesheet :: CliOpts -> Journal -> IO () balancesheet = balanceviewReport bsBV tests_Hledger_Cli_Balancesheet :: Test tests_Hledger_Cli_Balancesheet = TestList [ ] hledger-1.2/Hledger/Cli/BalanceView.hs0000644000000000000000000002020213067565416015762 0ustar0000000000000000{-# LANGUAGE OverloadedStrings, RecordWildCards #-} {-| This module is used by the 'balancesheet', 'incomestatement', and 'cashflow' commands to print out acocunt balances based on a specific "view", which consists of a title and multiple named queries that are aggregated and totaled. -} module Hledger.Cli.BalanceView ( BalanceView(..) ,balanceviewmode ,balanceviewReport ) where import Control.Monad (unless) import Data.List (intercalate, foldl', isPrefixOf) import Data.Maybe (fromMaybe) import Data.Monoid (Sum(..), (<>)) import System.Console.CmdArgs.Explicit as C import Text.Tabular as T import Hledger import Hledger.Cli.Balance import Hledger.Cli.CliOptions -- | Describes a view for the balance, which can consist of multiple -- separate named queries that are aggregated and totaled. data BalanceView = BalanceView { bvmode :: String, -- ^ command line mode of the view bvaliases :: [String], -- ^ command line aliases bvhelp :: String, -- ^ command line help message bvtitle :: String, -- ^ title of the view bvqueries :: [(String, Journal -> Query)], -- ^ named queries that make up the view bvtype :: BalanceType -- ^ the type of balance this view shows. -- This overrides user input. } balanceviewmode :: BalanceView -> Mode RawOpts balanceviewmode BalanceView{..} = (defCommandMode $ bvmode : bvaliases) { modeHelp = bvhelp `withAliases` bvaliases ,modeGroupFlags = C.Group { groupUnnamed = [ flagNone ["change"] (\opts -> setboolopt "change" opts) ("show balance change in each period" ++ defType PeriodChange) ,flagNone ["cumulative"] (\opts -> setboolopt "cumulative" opts) ("show balance change accumulated across periods (in multicolumn reports)" ++ defType CumulativeChange ) ,flagNone ["historical","H"] (\opts -> setboolopt "historical" opts) ("show historical ending balance in each period (includes postings before report start date)" ++ defType HistoricalBalance ) ,flagNone ["flat"] (\opts -> setboolopt "flat" opts) "show accounts as a list" ,flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "flat mode: omit N leading account name parts" ,flagNone ["no-total","N"] (\opts -> setboolopt "no-total" opts) "omit the final total row" ,flagNone ["tree"] (\opts -> setboolopt "tree" opts) "show accounts as a tree; amounts include subaccounts (default in simple reports)" ,flagNone ["average","A"] (\opts -> setboolopt "average" opts) "show a row average column (in multicolumn reports)" ,flagNone ["row-total","T"] (\opts -> setboolopt "row-total" opts) "show a row total column (in multicolumn reports)" ,flagNone ["no-elide"] (\opts -> setboolopt "no-elide" opts) "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"] (\opts -> setboolopt "pretty-tables" opts) "use unicode when displaying tables" ] ,groupHidden = [] ,groupNamed = [generalflagsgroup1] } } where defType :: BalanceType -> String defType bt | bt == bvtype = " (default)" | otherwise = "" balanceviewQueryReport :: ReportOpts -> Query -> Journal -> String -> (Journal -> Query) -> ([String], Sum MixedAmount) balanceviewQueryReport ropts q0 j t q = ([view], Sum amt) where q' = And [q0, q j] rep@(_ , amt) -- For --historical/--cumulative, we must use multiBalanceReport. -- (This forces --no-elide.) -- See Balance.hs's implementation of 'balance' for more information | balancetype_ ropts `elem` [HistoricalBalance, CumulativeChange] = singleBalanceReport ropts q' j | otherwise = balanceReport ropts q' j view = intercalate "\n" [t <> ":", balanceReportAsText ropts rep] multiBalanceviewQueryReport :: ReportOpts -> Query -> Journal -> String -> (Journal -> Query) -> ([Table String String MixedAmount], [[MixedAmount]], Sum MixedAmount) multiBalanceviewQueryReport ropts q0 j t q = ([tabl], [coltotals], Sum tot) where singlesection = "Cash" `isPrefixOf` t -- TODO temp ropts' = ropts { no_total_ = singlesection && no_total_ ropts, empty_ = True } q' = And [q0, q j] MultiBalanceReport (dates, rows, (coltotals,tot,avg)) = multiBalanceReport ropts' q' j rows' | empty_ ropts = rows | otherwise = filter (not . emptyRow) rows where emptyRow (_,_,_,amts,_,_) = all isZeroMixedAmount amts r = MultiBalanceReport (dates, rows', (coltotals, tot, avg)) Table hLeft hTop dat = balanceReportAsTable ropts' r tabl = Table (T.Group SingleLine [Header t, hLeft]) hTop ([]:dat) -- | Prints out a balance report according to a given view balanceviewReport :: BalanceView -> CliOpts -> Journal -> IO () balanceviewReport BalanceView{..} CliOpts{command_=cmd, reportopts_=ropts, rawopts_=raw} j = do currDay <- getCurrentDay let q0 = queryFromOpts currDay ropts' let title = bvtitle ++ maybe "" (' ':) balanceclarification case interval_ ropts' of NoInterval -> do let (views, amt) = foldMap (uncurry (balanceviewQueryReport ropts' q0 j)) bvqueries mapM_ putStrLn (title : "" : views) unless (no_total_ ropts' || cmd=="cashflow") . mapM_ putStrLn $ -- TODO temp [ "Total:" , "--------------------" , padleft 20 $ showMixedAmountWithoutPrice (getSum amt) ] _ -> do let (tabls, amts, Sum totsum) = foldMap (uncurry (multiBalanceviewQueryReport ropts' q0 j)) bvqueries sumAmts = case amts of a1:as -> foldl' (zipWith (+)) a1 as [] -> [] totavg = totsum `divideMixedAmount` fromIntegral (length sumAmts) mergedTabl = case tabls of t1:ts -> foldl' merging t1 ts [] -> T.empty totTabl | no_total_ ropts' || length bvqueries == 1 = mergedTabl | otherwise = mergedTabl +====+ row "Total" (sumAmts ++ (if row_total_ ropts' then [totsum] else []) ++ (if average_ ropts' then [totavg] else []) ) putStrLn title putStrLn $ renderBalanceReportTable ropts totTabl where overwriteBalanceType = case reverse $ filter (`elem` ["change","cumulative","historical"]) $ map fst raw of "historical":_ -> Just HistoricalBalance "cumulative":_ -> Just CumulativeChange "change":_ -> Just PeriodChange _ -> Nothing balancetype = fromMaybe bvtype overwriteBalanceType -- we must clarify that the statements aren't actual income statements, -- etc. if the user overrides the balance type balanceclarification = flip fmap overwriteBalanceType $ \t -> case t of PeriodChange -> "(Balance Changes)" CumulativeChange -> "(Cumulative Ending Balances)" HistoricalBalance -> "(Historical Ending Balances)" ropts' = treeIfNotPeriod $ ropts { balancetype_ = balancetype } treeIfNotPeriod = case (balancetype, interval_ ropts) of -- For --historical/--cumulative, we must use multiBalanceReport. -- (This forces --no-elide.) -- These settings format the output in a way that we can convert to -- a normal balance report using singleBalanceReport. See -- Balance.hs for more information. (HistoricalBalance, NoInterval) -> \o -> o { accountlistmode_ = ALTree } (CumulativeChange , NoInterval) -> \o -> o { accountlistmode_ = ALTree } _ -> id merging (Table hLeft hTop dat) (Table hLeft' _ dat') = Table (T.Group DoubleLine [hLeft, hLeft']) hTop (dat ++ dat') hledger-1.2/Hledger/Cli/Cashflow.hs0000644000000000000000000000237613067573465015367 0ustar0000000000000000{-# LANGUAGE QuasiQuotes, RecordWildCards, NoCPP #-} {-| 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.Cashflow ( cashflowmode ,cashflow ,tests_Hledger_Cli_Cashflow ) where import Data.String.Here import System.Console.CmdArgs.Explicit import Test.HUnit import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.BalanceView cfBV = BalanceView { bvmode = "cashflow", bvaliases = ["cf"], bvhelp = [here|This command displays a simple cashflow statement, showing changes in "cash" accounts. It assumes that these accounts are under a top-level `asset` account and do not contain `receivable` or `A/R` in their name (plural forms also allowed). |], bvtitle = "Cashflow Statement", bvqueries = [("Cash flows", journalCashAccountQuery)], bvtype = PeriodChange } cashflowmode :: Mode RawOpts cashflowmode = balanceviewmode cfBV cashflow :: CliOpts -> Journal -> IO () cashflow = balanceviewReport cfBV tests_Hledger_Cli_Cashflow :: Test tests_Hledger_Cli_Cashflow = TestList [ ] hledger-1.2/Hledger/Cli/Help.hs0000644000000000000000000000150313035210046014452 0ustar0000000000000000{-| The help command. |-} module Hledger.Cli.Help ( helpmode ,help' ) where import Prelude () import Prelude.Compat import Data.List import System.Console.CmdArgs.Explicit import Hledger.Data.RawOptions import Hledger.Cli.CliOptions import Hledger.Cli.DocFiles helpmode = (defCommandMode $ ["help"] ++ aliases) { modeHelp = "show any of the hledger manuals" `withAliases` aliases ,modeGroupFlags = Group { groupUnnamed = [] ,groupHidden = [] ,groupNamed = [] } } where aliases = [] -- | Print detailed help on various topics. help' :: CliOpts -> IO () help' opts = do let args = listofstringopt "args" $ rawopts_ opts case args of [] -> putStrLn $ "Choose a topic, eg: hledger help cli\n" ++ intercalate ", " docTopics topic:_ -> printHelpForTopic topic hledger-1.2/Hledger/Cli/Histogram.hs0000644000000000000000000000351513035210046015524 0ustar0000000000000000{-| Print a histogram report. (The "activity" command). -} module Hledger.Cli.Histogram where import Data.List import Data.Maybe import Data.Ord import System.Console.CmdArgs.Explicit import Text.Printf import Hledger import Hledger.Cli.CliOptions import Prelude hiding (putStr) import Hledger.Utils.UTF8IOCompat (putStr) activitymode :: Mode RawOpts activitymode = (defCommandMode $ ["activity"] ++ aliases) { modeHelp = "show an ascii barchart of posting counts per interval (default: daily)" `withAliases` aliases ,modeHelpSuffix = [] ,modeGroupFlags = Group { groupUnnamed = [] ,groupHidden = [] ,groupNamed = [generalflagsgroup1] } } where aliases = [] barchar :: Char barchar = '*' -- | Print a histogram of some statistic per report interval, such as -- number of postings per day. histogram :: CliOpts -> Journal -> IO () histogram 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 = sortBy (comparing 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.2/Hledger/Cli/Incomestatement.hs0000644000000000000000000000243713067573465016756 0ustar0000000000000000{-# LANGUAGE QuasiQuotes, TemplateHaskell, OverloadedStrings, NoCPP #-} {-| The @incomestatement@ command prints a simple income statement (profit & loss) report. -} module Hledger.Cli.Incomestatement ( incomestatementmode ,incomestatement ,tests_Hledger_Cli_Incomestatement ) where import Data.String.Here import System.Console.CmdArgs.Explicit import Test.HUnit import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.BalanceView isBV = BalanceView { bvmode = "incomestatement", bvaliases = ["is"], bvhelp = [here|This command displays a simple income statement, showing revenues and expenses during a period. It assumes that these accounts are under a top-level `revenue` or `income` or `expense` account (plural forms also allowed). |], bvtitle = "Income Statement", bvqueries = [ ("Revenues", journalIncomeAccountQuery), ("Expenses", journalExpenseAccountQuery) ], bvtype = PeriodChange } incomestatementmode :: Mode RawOpts incomestatementmode = balanceviewmode isBV incomestatement :: CliOpts -> Journal -> IO () incomestatement = balanceviewReport isBV tests_Hledger_Cli_Incomestatement :: Test tests_Hledger_Cli_Incomestatement = TestList [ ] hledger-1.2/Hledger/Cli/Info.hs0000644000000000000000000000152013035210046014454 0ustar0000000000000000{-| The info command. |-} module Hledger.Cli.Info ( infomode ,info' ) where import Prelude () import Prelude.Compat import Data.List import System.Console.CmdArgs.Explicit import Hledger.Data.RawOptions import Hledger.Cli.CliOptions import Hledger.Cli.DocFiles infomode = (defCommandMode $ ["info"] ++ aliases) { modeHelp = "show any of the hledger manuals with info" `withAliases` aliases ,modeGroupFlags = Group { groupUnnamed = [] ,groupHidden = [] ,groupNamed = [] } } where aliases = [] -- | Try to use info to view the selected manual. info' :: CliOpts -> IO () info' opts = do let args = listofstringopt "args" $ rawopts_ opts case args of [] -> putStrLn $ "Choose a topic, eg: hledger info cli\n" ++ intercalate ", " docTopics topic:_ -> runInfoForTopic topic hledger-1.2/Hledger/Cli/Man.hs0000644000000000000000000000150113035210046014273 0ustar0000000000000000{-| The man command. |-} module Hledger.Cli.Man ( manmode ,man ) where import Prelude () import Prelude.Compat import Data.List import System.Console.CmdArgs.Explicit import Hledger.Data.RawOptions import Hledger.Cli.CliOptions import Hledger.Cli.DocFiles manmode = (defCommandMode $ ["man"] ++ aliases) { modeHelp = "show any of the hledger manuals with man" `withAliases` aliases ,modeGroupFlags = Group { groupUnnamed = [] ,groupHidden = [] ,groupNamed = [] } } where aliases = [] -- | Try to use man to view the selected manual. man :: CliOpts -> IO () man opts = do let args = listofstringopt "args" $ rawopts_ opts case args of [] -> putStrLn $ "Choose a topic, eg: hledger man cli\n" ++ intercalate ", " docTopics topic:_ -> runManForTopic topic hledger-1.2/Hledger/Cli/Print.hs0000644000000000000000000001406113067077532014701 0ustar0000000000000000{-| A ledger-compatible @print@ command. -} {-# LANGUAGE OverloadedStrings #-} module Hledger.Cli.Print ( printmode ,print' ,entriesReportAsText ,originalTransaction ,tests_Hledger_Cli_Print ) where import Data.Text (Text) import qualified Data.Text as T import System.Console.CmdArgs.Explicit import Test.HUnit import Text.CSV import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Utils import Hledger.Cli.Add ( transactionsSimilarTo ) printmode = (defCommandMode $ ["print"] ++ aliases) { modeHelp = "show transaction journal entries" `withAliases` aliases ,modeGroupFlags = Group { groupUnnamed = [ let matcharg = "STR" in flagReq ["match","m"] (\s opts -> Right $ setopt "match" s opts) matcharg ("show the transaction whose description is most similar to "++matcharg ++ ", and is most recent"), flagNone ["explicit","x"] (setboolopt "explicit") "show all amounts explicitly" ] ++ outputflags ,groupHidden = [] ,groupNamed = [generalflagsgroup1] } } where aliases = [] showTransaction' :: CliOpts -> Transaction -> String showTransaction' opts | boolopt "explicit" $ rawopts_ opts = showTransactionUnelided | otherwise = showTransactionUnelided . originalTransaction originalTransaction :: Transaction -> Transaction originalTransaction t = t { tpostings = map originalPosting' $ tpostings t } where -- We don't want plain original postings because print wouldn't issue alias -- directives. Thus we are going to print effective account name. originalPosting' p = (originalPosting p) { paccount = paccount p } -- | 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, ropts') = case fmt of "csv" -> ((++"\n") . printCSV . entriesReportAsCsv, ropts{accountlistmode_=ALFlat}) _ -> (entriesReportAsText' opts, ropts) writeOutput opts $ render $ entriesReport ropts' q j entriesReportAsText :: EntriesReport -> String entriesReportAsText items = concatMap showTransactionUnelided items entriesReportAsText' :: CliOpts -> EntriesReport -> String entriesReportAsText' = concatMap . showTransaction' -- 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" -- ,"" -- ] -- ] 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})) -> let a_ = a{acommodity=""} 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 $ showTransactionUnelided 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 -- tests tests_Hledger_Cli_Print = TestList [] -- tests_showTransactions hledger-1.2/Hledger/Cli/Register.hs0000644000000000000000000002111013042200120015330 0ustar0000000000000000{-| A ledger-compatible @register@ command. -} {-# LANGUAGE CPP, OverloadedStrings #-} module Hledger.Cli.Register ( registermode ,register ,postingsReportAsText ,postingsReportItemAsText -- ,showPostingWithBalanceForVty ,tests_Hledger_Cli_Register ) where import Data.List import Data.Maybe -- import Data.Text (Text) import qualified Data.Text as T import System.Console.CmdArgs.Explicit import Text.CSV import Test.HUnit import Hledger import Hledger.Cli.CliOptions import Hledger.Cli.Utils registermode = (defCommandMode $ ["register"] ++ aliases) { modeHelp = "show postings and running total" `withAliases` aliases ,modeGroupFlags = Group { groupUnnamed = [ flagNone ["cumulative"] (\opts -> setboolopt "change" opts) "show running total from report start date (default)" ,flagNone ["historical","H"] (\opts -> setboolopt "historical" opts) "show historical running total/balance (includes postings before report start date)\n " ,flagNone ["average","A"] (\opts -> setboolopt "average" opts) "show running average of posting amounts instead of total (implies --empty)" ,flagNone ["related","r"] (\opts -> setboolopt "related" opts) "show postings' siblings instead" ,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." ) ] ++ outputflags ,groupHidden = [] ,groupNamed = [generalflagsgroup1] } } where aliases = ["reg"] -- | Print a (posting) register report. register :: CliOpts -> Journal -> IO () register opts@CliOpts{reportopts_=ropts} j = do d <- getCurrentDay let fmt = outputFormatFromOpts opts render | fmt=="csv" = const ((++"\n") . printCSV . postingsReportAsCsv) | otherwise = postingsReportAsText writeOutput opts $ render opts $ postingsReport ropts (queryFromOpts d ropts) j postingsReportAsCsv :: PostingsReport -> CSV postingsReportAsCsv (_,is) = ["txnidx","date","description","account","amount","total"] : map postingsReportItemAsCsvRecord is postingsReportItemAsCsvRecord :: PostingsReportItem -> Record postingsReportItemAsCsvRecord (_, _, _, p, b) = [idx,date,desc,acct,amt,bal] where idx = show $ maybe 0 tindex $ ptransaction p date = showDate $ postingDate p -- XXX csv should show date2 with --date2 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 $ pamount p bal = showMixedAmountOneLineWithoutPrice 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 tests_postingsReportAsText = [ "postingsReportAsText" ~: do -- "unicode in register layout" ~: do j <- readJournal' "2009/01/01 * медвежья шкура\n расходы:покупки 100\n актив:наличные\n" let opts = defreportopts (postingsReportAsText defcliopts $ postingsReport opts (queryFromOpts (parsedate "2008/11/26") opts) j) `is` unlines ["2009/01/01 медвежья шкура расходы:покупки 100 100" ," актив:наличные -100 0"] ] -- | 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) amt = showMixedAmountWithoutPrice $ pamount p bal = showMixedAmountWithoutPrice 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_Hledger_Cli_Register :: Test tests_Hledger_Cli_Register = TestList tests_postingsReportAsText hledger-1.2/Hledger/Cli/Stats.hs0000644000000000000000000001115413035210046014663 0ustar0000000000000000{-| Print some statistics for the journal. -} {-# LANGUAGE OverloadedStrings #-} module Hledger.Cli.Stats ( statsmode ,stats ) where import Data.List 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 = (defCommandMode $ ["stats"] ++ aliases) { modeHelp = "show some journal statistics" `withAliases` aliases ,modeGroupFlags = Group { groupUnnamed = [ 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." ] ,groupHidden = [] ,groupNamed = [generalflagsgroup1] } } where aliases = [] -- 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)) -- Transactions this month : %(monthtxns)s (last month in the same period: %(lastmonthtxns)s) -- Uncleared transactions : %(uncleared)s -- Days since reconciliation : %(reconcileelapsed)s -- Days since last transaction : %(recentelapsed)s ] where j = ljournal l path = journalFilePath j ts = sortBy (comparing tdate) $ filter (spanContainsDate span . tdate) $ jtxns j as = nub $ map paccount $ concatMap tpostings ts cs = Map.keys $ commodityStylesFromAmounts $ concatMap amounts $ map pamount $ concatMap tpostings ts lastdate | null ts = Nothing | otherwise = Just $ tdate $ last ts lastelapsed = maybe Nothing (Just . 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 hledger-1.2/Text/Tabular/AsciiWide.hs0000644000000000000000000000753313066774455015720 0ustar0000000000000000-- | Text.Tabular.AsciiArt from tabular-0.2.2.7, modified to treat -- wide characters as double width. module Text.Tabular.AsciiWide where import Data.List (intersperse, transpose) import Text.Tabular import Hledger.Utils.String -- | for simplicity, we assume that each cell is rendered -- on a single line render :: Bool -- ^ pretty tables -> (rh -> String) -> (ch -> String) -> (a -> String) -> Table rh ch a -> String render pretty fr fc f (Table rh ch cells) = unlines $ [ bar SingleLine -- +--------------------------------------+ , renderColumns pretty sizes ch2 , bar DoubleLine -- +======================================+ ] ++ (renderRs $ fmap renderR $ zipHeader [] cells $ fmap fr rh) ++ [ bar SingleLine ] -- +--------------------------------------+ where bar = concat . renderHLine pretty sizes ch2 -- ch2 and cell2 include the row and column labels ch2 = Group DoubleLine [Header "", fmap fc ch] cells2 = headerContents ch2 : zipWith (\h cs -> h : map f cs) rhStrings cells -- renderR (cs,h) = renderColumns pretty sizes $ Group DoubleLine [ Header h , fmap fst $ zipHeader "" (map f cs) ch] rhStrings = map fr $ headerContents rh -- maximum width for each column sizes = map (maximum . map strWidth) . transpose $ cells2 renderRs (Header s) = [s] renderRs (Group p hs) = concat . intersperse sep . map renderRs $ hs where sep = renderHLine pretty sizes ch2 p verticalBar :: Bool -> Char verticalBar pretty = if pretty then '│' else '|' leftBar :: Bool -> String leftBar pretty = verticalBar pretty : " " rightBar :: Bool -> String rightBar pretty = " " ++ [verticalBar pretty] midBar :: Bool -> String midBar pretty = " " ++ verticalBar pretty : " " doubleMidBar :: Bool -> String doubleMidBar pretty = if pretty then " ║ " else " || " horizontalBar :: Bool -> Char horizontalBar pretty = if pretty then '─' else '-' doubleHorizontalBar :: Bool -> Char doubleHorizontalBar pretty = if pretty then '═' else '=' -- | We stop rendering on the shortest list! renderColumns :: Bool -- ^ pretty -> [Int] -- ^ max width for each column -> Header String -> String renderColumns pretty is h = leftBar pretty ++ coreLine ++ rightBar pretty where coreLine = concatMap helper $ flattenHeader $ zipHeader 0 is h helper = either hsep (uncurry padLeftWide) hsep :: Properties -> String hsep NoLine = " " hsep SingleLine = midBar pretty hsep DoubleLine = doubleMidBar pretty renderHLine :: Bool -- ^ pretty -> [Int] -- ^ width specifications -> Header String -> Properties -> [String] renderHLine _ _ _ NoLine = [] renderHLine pretty w h SingleLine = [renderHLine' pretty SingleLine w (horizontalBar pretty) h] renderHLine pretty w h DoubleLine = [renderHLine' pretty DoubleLine w (doubleHorizontalBar pretty) h] doubleCross :: Bool -> String doubleCross pretty = if pretty then "╬" else "++" doubleVerticalCross :: Bool -> String doubleVerticalCross pretty = if pretty then "╫" else "++" cross :: Bool -> Char cross pretty = if pretty then '┼' else '+' renderHLine' :: Bool -> Properties -> [Int] -> Char -> Header String -> String renderHLine' pretty prop is sep h = [ cross pretty, sep ] ++ coreLine ++ [sep, cross pretty] where coreLine = concatMap helper $ flattenHeader $ zipHeader 0 is h helper = either vsep dashes dashes (i,_) = replicate i sep vsep NoLine = [sep] vsep SingleLine = sep : cross pretty : [sep] vsep DoubleLine = sep : cross' ++ [sep] cross' = case prop of DoubleLine -> doubleCross pretty _ -> doubleVerticalCross pretty -- padLeft :: Int -> String -> String -- padLeft l s = padding ++ s -- where padding = replicate (l - length s) ' ' hledger-1.2/app/hledger-cli.hs0000755000000000000000000000022313035210046014441 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.2/test/test.hs0000644000000000000000000000033313035210046013437 0ustar0000000000000000import Hledger.Cli (tests_Hledger_Cli) import Test.Framework.Providers.HUnit (hUnitTestToTests) import Test.Framework.Runners.Console (defaultMain) main :: IO () main = defaultMain $ hUnitTestToTests tests_Hledger_Cli hledger-1.2/bench/bench.hs0000644000000000000000000000425713042200120013636 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 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 Nothing Nothing True inputfile (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 Nothing Nothing True inputfile Criterion.Main.defaultMainWith defaultConfig $ [ bench ("read "++inputfile) $ nfIO $ (either error const <$> readJournalFile Nothing Nothing True inputfile), 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.2/doc/hledger.10000644000000000000000000022630113067574772013443 0ustar0000000000000000.\"t .TH "hledger" "1" "March 2017" "hledger 1.2" "hledger User Manuals" .SH NAME .PP hledger \- a command\-line accounting tool .SH SYNOPSIS .PP \f[C]hledger\ [\-f\ FILE]\ COMMAND\ [OPTIONS]\ [ARGS]\f[] .PD 0 .P .PD \f[C]hledger\ [\-f\ FILE]\ ADDONCMD\ \-\-\ [OPTIONS]\ [ARGS]\f[] .PD 0 .P .PD \f[C]hledger\f[] .SH DESCRIPTION .PP hledger is a cross\-platform program 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). .PD 0 .P .PD Tested on unix, mac, windows, hledger aims to be a reliable, practical tool for daily use. .PP This is hledger's command\-line interface (there are also curses 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. .PP hledger reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]\-f\f[], or \f[C]$LEDGER_FILE\f[], or \f[C]$HOME/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). If using \f[C]$LEDGER_FILE\f[], note this must be a real environment variable, not a shell variable. You can specify standard input with \f[C]\-f\-\f[]. .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[] .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'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]~/.hledger.journal\f[], or run \f[C]hledger\ add\f[] and follow the prompts. Then try some commands like \f[C]hledger\ print\f[] or \f[C]hledger\ balance\f[]. Run \f[C]hledger\f[] with no arguments for a list of commands. .SH EXAMPLES .PP Two simple transactions in hledger journal format: .IP .nf \f[C] 2015/9/30\ gift\ received \ \ assets:cash\ \ \ $20 \ \ income:gifts 2015/10/16\ farmers\ market \ \ expenses:food\ \ \ \ $10 \ \ assets:cash \f[] .fi .PP Some basic reports: .IP .nf \f[C] $\ hledger\ print 2015/09/30\ gift\ received \ \ \ \ assets:cash\ \ \ \ \ \ \ \ \ \ \ \ $20 \ \ \ \ income:gifts\ \ \ \ \ \ \ \ \ \ $\-20 2015/10/16\ farmers\ market \ \ \ \ expenses:food\ \ \ \ \ \ \ \ \ \ \ $10 \ \ \ \ assets:cash\ \ \ \ \ \ \ \ \ \ \ \ $\-10 \f[] .fi .IP .nf \f[C] $\ hledger\ accounts\ \-\-tree assets \ \ cash expenses \ \ food income \ \ gifts \f[] .fi .IP .nf \f[C] $\ hledger\ balance \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $10\ \ assets:cash \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $10\ \ expenses:food \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-20\ \ income:gifts \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ 0 \f[] .fi .IP .nf \f[C] $\ hledger\ register\ cash 2015/09/30\ gift\ received\ \ \ assets:cash\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $20\ \ \ \ \ \ \ \ \ \ \ $20 2015/10/16\ farmers\ market\ \ assets:cash\ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-10\ \ \ \ \ \ \ \ \ \ \ $10 \f[] .fi .PP More commands: .IP .nf \f[C] $\ hledger\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ show\ available\ commands $\ hledger\ add\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ add\ more\ transactions\ to\ the\ journal\ file $\ hledger\ balance\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ all\ accounts\ with\ aggregated\ balances $\ hledger\ balance\ \-\-help\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ show\ detailed\ help\ for\ balance\ command $\ hledger\ balance\ \-\-depth\ 1\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ only\ top\-level\ accounts $\ hledger\ register\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ show\ account\ postings,\ with\ running\ total $\ hledger\ reg\ income\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ show\ postings\ to/from\ income\ accounts $\ hledger\ reg\ \[aq]assets:some\ bank:checking\[aq]\ #\ show\ postings\ to/from\ this\ checking\ account $\ hledger\ print\ desc:shop\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ show\ transactions\ with\ shop\ in\ the\ description $\ hledger\ activity\ \-W\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ show\ transaction\ counts\ per\ week\ as\ a\ bar\ chart \f[] .fi .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[]. (Note \-h and \-\-help are different, like git.) .PP General help options: .TP .B \f[C]\-h\f[] show general usage (or after COMMAND, command usage) .RS .RE .TP .B \f[C]\-\-help\f[] show this program\[aq]s manual as plain text (or after an add\-on COMMAND, the add\-on\[aq]s manual) .RS .RE .TP .B \f[C]\-\-man\f[] show this program\[aq]s manual with man .RS .RE .TP .B \f[C]\-\-info\f[] show this program\[aq]s manual with info .RS .RE .TP .B \f[C]\-\-version\f[] show version .RS .RE .TP .B \f[C]\-\-debug[=N]\f[] show debug output (levels 1\-9, default: 1) .RS .RE .PP General input options: .TP .B \f[C]\-f\ FILE\ \-\-file=FILE\f[] use a different input file. For stdin, use \- (default: \f[C]$LEDGER_FILE\f[] or \f[C]$HOME/.hledger.journal\f[]) .RS .RE .TP .B \f[C]\-\-rules\-file=RULESFILE\f[] Conversion rules file to use when reading CSV (default: FILE.rules) .RS .RE .TP .B \f[C]\-\-alias=OLD=NEW\f[] rename accounts named OLD to NEW .RS .RE .TP .B \f[C]\-\-anon\f[] anonymize accounts and payees .RS .RE .TP .B \f[C]\-\-pivot\ TAGNAME\f[] use some other field/tag for account names .RS .RE .TP .B \f[C]\-I\ \-\-ignore\-assertions\f[] ignore any failing balance assertions .RS .RE .PP General reporting options: .TP .B \f[C]\-b\ \-\-begin=DATE\f[] include postings/txns on or after this date .RS .RE .TP .B \f[C]\-e\ \-\-end=DATE\f[] include postings/txns before this date .RS .RE .TP .B \f[C]\-D\ \-\-daily\f[] multiperiod/multicolumn report by day .RS .RE .TP .B \f[C]\-W\ \-\-weekly\f[] multiperiod/multicolumn report by week .RS .RE .TP .B \f[C]\-M\ \-\-monthly\f[] multiperiod/multicolumn report by month .RS .RE .TP .B \f[C]\-Q\ \-\-quarterly\f[] multiperiod/multicolumn report by quarter .RS .RE .TP .B \f[C]\-Y\ \-\-yearly\f[] multiperiod/multicolumn report by year .RS .RE .TP .B \f[C]\-p\ \-\-period=PERIODEXP\f[] set start date, end date, and/or reporting interval all at once (overrides the flags above) .RS .RE .TP .B \f[C]\-\-date2\f[] show, and match with \-b/\-e/\-p/date:, secondary dates instead .RS .RE .TP .B \f[C]\-C\ \-\-cleared\f[] include only cleared postings/txns .RS .RE .TP .B \f[C]\-\-pending\f[] include only pending postings/txns .RS .RE .TP .B \f[C]\-U\ \-\-uncleared\f[] include only uncleared (and pending) postings/txns .RS .RE .TP .B \f[C]\-R\ \-\-real\f[] include only non\-virtual postings .RS .RE .TP .B \f[C]\-\-depth=N\f[] hide accounts/postings deeper than N .RS .RE .TP .B \f[C]\-E\ \-\-empty\f[] show items with zero amount, normally hidden .RS .RE .TP .B \f[C]\-B\ \-\-cost\f[] convert amounts to their cost at transaction time (using the transaction price, if any) .RS .RE .TP .B \f[C]\-V\ \-\-value\f[] convert amounts to their market value on the report end date (using the most recent applicable market price, if any) .RS .RE .PP Note when multiple similar reporting options are provided, the last one takes precedence. Eg \f[C]\-p\ feb\ \-p\ mar\f[] is equivalent to \f[C]\-p\ mar\f[]. .PP Some of these can also be written as queries. .SS Command options .PP To see options for a particular command, including command\-specific options, run: \f[C]hledger\ COMMAND\ \-h\f[]. .PP Command\-specific options must be written after the command name, eg: \f[C]hledger\ print\ \-x\f[]. .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[]. Or, you can run the addon executable directly: \f[C]hledger\-ui\ \-\-watch\f[]. .SS Command arguments .PP Most hledger commands accept arguments after the command name, which are often a query, filtering the data in some way. .SS Special characters .PP Option and argument values which contain problematic characters should be escaped with double quotes, backslashes, or (best) single quotes. Problematic characters means spaces, and also characters which are significant to your command shell, such as less\-than/greater\-than. Eg: \f[C]hledger\ register\ \-p\ \[aq]last\ year\[aq]\ "accounts\ receivable\ (receivable|payable)"\ amt:\\>100\f[]. .PP Characters which are significant both to the shell and in regular expressions sometimes need to be double\-escaped. These include parentheses, the pipe symbol and the dollar sign. Eg, to match the dollar symbol, bash users should do: \f[C]hledger\ balance\ cur:\[aq]\\$\[aq]\f[] or \f[C]hledger\ balance\ cur:\\\\$\f[]. .PP There\[aq]s more.. options and arguments get de\-escaped when hledger is passing them to an addon executable. In this case you might need \f[I]triple\f[]\-escaping. Eg: \f[C]hledger\ ui\ cur:\[aq]\\\\$\[aq]\f[] or \f[C]hledger\ ui\ cur:\\\\\\\\$\f[]. .PP If in doubt, keep things simple: .IP \[bu] 2 run add\-on executables directly .IP \[bu] 2 write options after the command .IP \[bu] 2 enclose problematic args in single quotes .IP \[bu] 2 if needed, also add a backslash to escape regexp metacharacters .PP If you\[aq]re really stumped, add \f[C]\-\-debug=2\f[] to troubleshoot. .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[] (or on Windows, something like \f[C]C:/Users/USER/.hledger.journal\f[]). You can override this with the \f[C]$LEDGER_FILE\f[] environment variable: .IP .nf \f[C] $\ setenv\ LEDGER_FILE\ ~/finance/2016.journal $\ hledger\ stats \f[] .fi .PP or with the \f[C]\-f/\-\-file\f[] option: .IP .nf \f[C] $\ hledger\ \-f\ /some/file\ stats \f[] .fi .PP The file name \f[C]\-\f[] (hyphen) means standard input: .IP .nf \f[C] $\ cat\ some.journal\ |\ hledger\ \-f\- \f[] .fi .PP Usually the data file is in hledger\[aq]s journal format, but it can also be one of several other formats, listed below. hledger detects the format automatically based on the file extension, or if that is not recognised, by trying each built\-in "reader" in turn: .PP .TS tab(@); lw(10.7n) lw(33.2n) lw(26.1n). T{ Reader: T}@T{ Reads: T}@T{ Used for file extensions: T} _ T{ \f[C]journal\f[] T}@T{ hledger\[aq]s journal format, also some Ledger journals T}@T{ \f[C]\&.journal\f[] \f[C]\&.j\f[] \f[C]\&.hledger\f[] \f[C]\&.ledger\f[] T} T{ \f[C]timeclock\f[] T}@T{ timeclock files (precise time logging) T}@T{ \f[C]\&.timeclock\f[] T} T{ \f[C]timedot\f[] T}@T{ timedot files (approximate time logging) T}@T{ \f[C]\&.timedot\f[] T} T{ \f[C]csv\f[] T}@T{ comma\-separated values (data interchange) T}@T{ \f[C]\&.csv\f[] T} .TE .PP If needed (eg to ensure correct error messages when a file has the "wrong" extension), you can force a specific reader/format by prepending it to the file path with a colon. Examples: .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[] .fi .PP You can also specify multiple \f[C]\-f\f[] 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 those, either use the include directive, or concatenate the files, eg: \f[C]cat\ a.journal\ b.journal\ |\ hledger\ \-f\-\ CMD\f[]. .SS Smart dates .PP hledger\[aq]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\[aq]s date, and can have less\-significant date parts omitted (defaulting to 1). .PP Examples: .PP .TS tab(@); l l. T{ \f[C]2009/1/1\f[], \f[C]2009/01/01\f[], \f[C]2009\-1\-1\f[], \f[C]2009.1.1\f[] T}@T{ simple dates, several separators allowed T} T{ \f[C]2009/1\f[], \f[C]2009\f[] T}@T{ same as above \- a missing day or month defaults to 1 T} T{ \f[C]1/1\f[], \f[C]january\f[], \f[C]jan\f[], \f[C]this\ year\f[] T}@T{ relative dates, meaning january 1 of the current year T} T{ \f[C]next\ year\f[] T}@T{ january 1 of next year T} T{ \f[C]this\ month\f[] T}@T{ the 1st of the current month T} T{ \f[C]this\ week\f[] T}@T{ the most recent monday T} T{ \f[C]last\ week\f[] T}@T{ the monday of the week before this one T} T{ \f[C]lastweek\f[] T}@T{ spaces are optional T} T{ \f[C]today\f[], \f[C]yesterday\f[], \f[C]tomorrow\f[] T}@T{ 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[], \f[C]\-e/\-\-end\f[], \f[C]\-p/\-\-period\f[] or a \f[C]date:\f[] query (described below). All of these accept the smart date syntax. One important thing to be aware of when specifying end dates: as in Ledger, end dates are exclusive, so you need to write the date \f[I]after\f[] the last day you want to include. .PP Examples: .PP .TS tab(@); l l. T{ \f[C]\-b\ 2016/3/17\f[] T}@T{ begin on St. Patrick\[aq]s day 2016 T} T{ \f[C]\-e\ 12/1\f[] 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[] T}@T{ all transactions on or after the 1st of the current month T} T{ \f[C]\-p\ thismonth\f[] T}@T{ all transactions in the current month T} T{ \f[C]date:2016/3/17\-\f[] T}@T{ the above written as queries instead T} T{ \f[C]date:\-12/1\f[] T}@T{ T} T{ \f[C]date:thismonth\-\f[] T}@T{ T} T{ \f[C]date:thismonth\f[] 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[], \f[C]\-W/\-\-weekly\f[], \f[C]\-M/\-\-monthly\f[], \f[C]\-Q/\-\-quarterly\f[], or \f[C]\-Y/\-\-yearly\f[]. More complex intervals may be specified with a period expression. Report intervals can not be specified with a query, currently. .SS Period expressions .PP The \f[C]\-p/\-\-period\f[] 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\ "from\ 2009/1/1\ to\ 2009/4/1"\f[] .PP Keywords like "from" and "to" are optional, and so are the spaces, as long as you don\[aq]t run two dates together. "to" can also be written as "\-". These are equivalent to the above: .PP .TS tab(@); l. T{ \f[C]\-p\ "2009/1/1\ 2009/4/1"\f[] T} T{ \f[C]\-p2009/1/1to2009/4/1\f[] T} T{ \f[C]\-p2009/1/1\-2009/4/1\f[] 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\ "1/1\ 4/1"\f[] T} T{ \f[C]\-p\ "january\-apr"\f[] T} T{ \f[C]\-p\ "this\ year\ to\ 4/1"\f[] 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\ "from\ 2009/1/1"\f[] T}@T{ everything after january 1, 2009 T} T{ \f[C]\-p\ "from\ 2009/1"\f[] T}@T{ the same T} T{ \f[C]\-p\ "from\ 2009"\f[] T}@T{ the same T} T{ \f[C]\-p\ "to\ 2009"\f[] T}@T{ everything before january 1, 2009 T} .TE .PP A single date with no "from" or "to" defines both the start and end date like so: .PP .TS tab(@); l l. T{ \f[C]\-p\ "2009"\f[] T}@T{ the year 2009; equivalent to "2009/1/1 to 2010/1/1" T} T{ \f[C]\-p\ "2009/1"\f[] T}@T{ the month of jan; equivalent to "2009/1/1 to 2009/2/1" T} T{ \f[C]\-p\ "2009/1/1"\f[] T}@T{ just that day; equivalent to "2009/1/1 to 2009/1/2" T} .TE .PP The argument of \f[C]\-p\f[] can also begin with, or be, a report interval expression. The basic report intervals are \f[C]daily\f[], \f[C]weekly\f[], \f[C]monthly\f[], \f[C]quarterly\f[], or \f[C]yearly\f[], which have the same effect as the \f[C]\-D\f[],\f[C]\-W\f[],\f[C]\-M\f[],\f[C]\-Q\f[], or \f[C]\-Y\f[] flags. Between report interval and start/end dates (if any), the word \f[C]in\f[] is optional. Examples: .PP .TS tab(@); l. T{ \f[C]\-p\ "weekly\ from\ 2009/1/1\ to\ 2009/4/1"\f[] T} T{ \f[C]\-p\ "monthly\ in\ 2008"\f[] T} T{ \f[C]\-p\ "quarterly"\f[] T} .TE .PP The following more complex report intervals are also supported: \f[C]biweekly\f[], \f[C]bimonthly\f[], \f[C]every\ N\ days|weeks|months|quarters|years\f[], \f[C]every\ Nth\ day\ [of\ month]\f[], \f[C]every\ Nth\ day\ of\ week\f[]. .PP Examples: .PP .TS tab(@); l. T{ \f[C]\-p\ "bimonthly\ from\ 2008"\f[] T} T{ \f[C]\-p\ "every\ 2\ weeks"\f[] T} T{ \f[C]\-p\ "every\ 5\ days\ from\ 1/3"\f[] T} .TE .PP Show historical balances at end of 15th each month (N is exclusive end date): .PP \f[C]hledger\ balance\ \-H\ \-p\ "every\ 16th\ day"\f[] .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\ "every\ 3rd\ day\ of\ week"\f[] .SS Depth limiting .PP With the \f[C]\-\-depth\ N\f[] option, 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. .SS Pivoting .PP Normally hledger sums amounts, and organizes them in a hierarchy, based on account name. The \f[C]\-\-pivot\ TAGNAME\f[] option causes it to sum and organize hierarchy based on some other field instead. .PP TAGNAME is the full, case\-insensitive name of a tag you have defined, or one of the built\-in implicit tags (like \f[C]code\f[] or \f[C]payee\f[]). As with account names, when tag values have \f[C]multiple:colon\-separated:parts\f[] hledger will build hierarchy, displayed in tree\-mode reports, summarisable with a depth limit, and so on. .PP \f[C]\-\-pivot\f[] 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 tag 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[] .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[] .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[] .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[] .fi .PP Another way (the acct: query matches against the pivoted "account name"): .IP .nf \f[C] $\ hledger\ balance\ \-\-pivot\ member\ acct:. \ \ \ \ \ \ \ \ \ \ \ \ \ \ \-2\ EUR\ \ John\ Doe \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \ \ \ \ \ \ \ \ \ \ \ \ \ \ \-2\ EUR \f[] .fi .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[], \f[C]desc:REGEX\f[], \f[C]cur:REGEX\f[], \f[C]tag:...=REGEX\f[] .IP \[bu] 2 CSV rules conditional blocks: \f[C]if\ REGEX\ ...\f[] .IP \[bu] 2 account alias directives and options: \f[C]alias\ /REGEX/\ =\ REPLACEMENT\f[], \f[C]\-\-alias\ /REGEX/=REPLACEMENT\f[] .PP hledger\[aq]s regular expressions come from the regex\-tdfa library. In general they: .IP \[bu] 2 are case insensitive .IP \[bu] 2 are infix matching (do not need to match the entire thing being matched) .IP \[bu] 2 are POSIX extended regular expressions .IP \[bu] 2 also support GNU word boundaries (\\<, \\>, \\b, \\B) .IP \[bu] 2 and parenthesised capturing groups and numeric backreferences in replacement strings .IP \[bu] 2 do not support mode modifiers like (?s) .PP Some things to note: .IP \[bu] 2 In the \f[C]alias\f[] directive and \f[C]\-\-alias\f[] option, regular expressions must be enclosed in forward slashes (\f[C]/REGEX/\f[]). Elsewhere in hledger, these are not required. .IP \[bu] 2 In queries, to match a regular expression metacharacter like \f[C]$\f[] as a literal character, prepend a backslash. Eg to search for amounts with the dollar sign in hledger\-web, write \f[C]cur:\\$\f[]. .IP \[bu] 2 On the command line, some metacharacters like \f[C]$\f[] have a special meaning to the shell and so must be escaped at least once more. See Special characters. .SH 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, optional prefixes to match specific fields. Multiple search terms are combined as follows: .PP All commands except print: 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 all the other terms. .PP The print command: show 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: .TP .B \f[B]\f[C]REGEX\f[]\f[] match account names by this regular expression .RS .RE .TP .B \f[B]\f[C]acct:REGEX\f[]\f[] same as above .RS .RE .TP .B \f[B]\f[C]amt:N,\ amt:N,\ amt:>=N\f[]\f[] 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. .RS .RE .TP .B \f[B]\f[C]code:REGEX\f[]\f[] match by transaction code (eg check number) .RS .RE .TP .B \f[B]\f[C]cur:REGEX\f[]\f[] 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[]). Note, to match characters which are regex\-significant, like the dollar sign (\f[C]$\f[]), you need to prepend \f[C]\\\f[]. 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]\\$\[aq]\f[] or \f[C]hledger\ print\ cur:\\\\$\f[]. .RS .RE .TP .B \f[B]\f[C]desc:REGEX\f[]\f[] match transaction descriptions .RS .RE .TP .B \f[B]\f[C]date:PERIODEXPR\f[]\f[] match dates within the specified period. PERIODEXPR is a period expression (with no report interval). Examples: \f[C]date:2016\f[], \f[C]date:thismonth\f[], \f[C]date:2000/2/1\-2/15\f[], \f[C]date:lastweek\-\f[]. If the \f[C]\-\-date2\f[] command line flag is present, this matches secondary dates instead. .RS .RE .TP .B \f[B]\f[C]date2:PERIODEXPR\f[]\f[] match secondary dates within the specified period. .RS .RE .TP .B \f[B]\f[C]depth:N\f[]\f[] match (or display, depending on command) accounts at or above this depth .RS .RE .TP .B \f[B]\f[C]real:,\ real:0\f[]\f[] match real or virtual postings respectively .RS .RE .TP .B \f[B]\f[C]status:*,\ status:!,\ status:\f[]\f[] match cleared, pending, or uncleared/pending transactions respectively .RS .RE .TP .B \f[B]\f[C]tag:REGEX[=REGEX]\f[]\f[] 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. .RS .RE .TP .B \f[B]\f[C]not:\f[]\f[] before any of the above negates the match. .RS .RE .TP .B \f[B]\f[C]inacct:ACCTNAME\f[]\f[] a special term used automatically when you click an account name in hledger\-web, specifying the account register we are currently in (selects the transactions of that account and how to show them, can be filtered further with \f[C]acct\f[] etc). Not supported elsewhere in hledger. .RS .RE .PP Some of these can also be expressed as command\-line options (eg \f[C]depth:2\f[] is equivalent to \f[C]\-\-depth\ 2\f[]). Generally you can mix options and query arguments, and the resulting query will be their intersection (perhaps excluding the \f[C]\-p/\-\-period\f[] option). .SH COMMANDS .PP hledger provides a number of subcommands; \f[C]hledger\f[] with no arguments shows a list. .PP If you install additional \f[C]hledger\-*\f[] packages, or if you put programs or scripts named \f[C]hledger\-NAME\f[] 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[]). You can also write any unambiguous prefix of a command name (\f[C]hledger\ inc\f[]), or one of the standard short aliases displayed in the command list (\f[C]hledger\ is\f[]). .SS accounts .PP Show account names. .TP .B \f[C]\-\-tree\f[] show short account names, as a tree .RS .RE .TP .B \f[C]\-\-flat\f[] show full account names, as a list (default) .RS .RE .TP .B \f[C]\-\-drop=N\f[] in flat mode: omit N leading account name parts .RS .RE .PP This command lists all account names that are in use (ie, all the accounts which have at least one transaction posting to them). With query arguments, only matched account names are shown. .PP It shows a flat list by default. With \f[C]\-\-tree\f[], it uses indentation to show the account hierarchy. .PP In flat mode you can add \f[C]\-\-drop\ N\f[] to omit the first few account name components. .PP Examples: .IP .nf \f[C] $\ hledger\ accounts\ \-\-tree assets \ \ bank \ \ \ \ checking \ \ \ \ saving \ \ cash expenses \ \ food \ \ supplies income \ \ gifts \ \ salary liabilities \ \ debts \f[] .fi .IP .nf \f[C] $\ hledger\ accounts\ \-\-drop\ 1 bank:checking bank:saving cash food supplies gifts salary debts \f[] .fi .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[] .fi .SS activity .PP 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. .IP .nf \f[C] $\ hledger\ activity\ \-\-quarterly 2008\-01\-01\ ** 2008\-04\-01\ ******* 2008\-07\-01\ 2008\-10\-01\ ** \f[] .fi .SS add .PP Prompt for transactions and add them to the journal. .TP .B \f[C]\-\-no\-new\-accounts\f[] don\[aq]t allow creating new accounts; helps prevent typos when entering account names .RS .RE .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[] 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[] 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[] and follow the prompts. You can add as many transactions as you like; when you are finished, enter \f[C]\&.\f[] or press control\-d or control\-c to exit. .PP Features: .IP \[bu] 2 add tries to provide useful defaults, using the most similar recent transaction (by description) 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[], \f[C]today\f[], \f[C]tomorrow\f[]). 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[] at any prompt to restart the transaction. .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\ restart\ the\ transaction. 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[] .fi .SS balance .PP Show accounts and their balances. Alias: bal. .TP .B \f[C]\-\-change\f[] show balance change in each period (default) .RS .RE .TP .B \f[C]\-\-cumulative\f[] show balance change accumulated across periods (in multicolumn reports) .RS .RE .TP .B \f[C]\-H\ \-\-historical\f[] show historical ending balance in each period (includes postings before report start date) .RS .RE .TP .B \f[C]\-\-tree\f[] show accounts as a tree; amounts include subaccounts (default in simple reports) .RS .RE .TP .B \f[C]\-\-flat\f[] show accounts as a list; amounts exclude subaccounts except when account is depth\-clipped (default in multicolumn reports) .RS .RE .TP .B \f[C]\-A\ \-\-average\f[] show a row average column (in multicolumn mode) .RS .RE .TP .B \f[C]\-T\ \-\-row\-total\f[] show a row total column (in multicolumn mode) .RS .RE .TP .B \f[C]\-N\ \-\-no\-total\f[] don\[aq]t show the final total row .RS .RE .TP .B \f[C]\-\-drop=N\f[] omit N leading account name parts (in flat mode) .RS .RE .TP .B \f[C]\-\-no\-elide\f[] don\[aq]t squash boring parent accounts (in tree mode) .RS .RE .TP .B \f[C]\-\-format=LINEFORMAT\f[] in single\-column balance reports: use this custom line format .RS .RE .TP .B \f[C]\-O\ FMT\ \-\-output\-format=FMT\f[] select the output format. Supported formats: txt, csv. .RS .RE .TP .B \f[C]\-o\ FILE\ \-\-output\-file=FILE\f[] write output to FILE. A file extension matching one of the above formats selects that format. .RS .RE .TP .B \f[C]\-\-pretty\-tables\f[] Use unicode to display prettier tables. .RS .RE .PP The balance command displays accounts and balances. It is hledger\[aq]s most featureful and most useful command. .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[] .fi .PP More precisely, the balance command shows the \f[I]change\f[] to each account\[aq]s balance caused by all (matched) postings. In the common case where you do not filter by date and your journal sets the correct opening balances, this is the same as the account\[aq]s ending balance. .PP By default, accounts are displayed hierarchically, with subaccounts indented below their parent. "Boring" accounts, which contain a single interesting subaccount and no balance of their own, are elided into the following line for more compact output. (Use \f[C]\-\-no\-elide\f[] to prevent this.) .PP Each account\[aq]s balance is the "inclusive" balance \- it includes the balances of any subaccounts. .PP Accounts which have zero balance (and no non\-zero subaccounts) are omitted. Use \f[C]\-E/\-\-empty\f[] to show them. .PP A final total is displayed by default; use \f[C]\-N/\-\-no\-total\f[] to suppress it: .IP .nf \f[C] $\ hledger\ balance\ \-p\ 2008/6\ expenses\ \-\-no\-total \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $2\ \ expenses \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $1\ \ \ \ food \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $1\ \ \ \ supplies \f[] .fi .SS Flat mode .PP To see a flat list of full account names instead of the default hierarchical display, use \f[C]\-\-flat\f[]. In this mode, accounts (unless depth\-clipped) show their "exclusive" balance, excluding any subaccount balances. In this mode, you can also use \f[C]\-\-drop\ N\f[] 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[] .fi .SS Depth limited balance reports .PP With \f[C]\-\-depth\ N\f[], balance shows accounts only to the specified depth. This is very useful to show a complex charts of accounts in less detail. In flat mode, balances from accounts below the depth limit will be shown as part of a parent account at the depth limit. .IP .nf \f[C] $\ hledger\ balance\ \-N\ \-\-depth\ 1 \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-1\ \ assets \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $2\ \ expenses \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-2\ \ income \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $1\ \ liabilities \f[] .fi .SS Multicolumn balance reports .PP With a reporting interval, multiple balance columns will be shown, one for each report period. There are three types of multi\-column 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[] .fi .RE .IP "2." 3 With \f[C]\-\-cumulative\f[]: 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[] .fi .RE .IP "3." 3 With \f[C]\-\-historical/\-H\f[]: 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\ ^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\ \f[] .fi .RE .PP Multi\-column balance reports display accounts in flat mode by default; to see the hierarchy, use \f[C]\-\-tree\f[]. .PP With a reporting interval (like \f[C]\-\-quarterly\f[] 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. .PP The \f[C]\-E/\-\-empty\f[] 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[] flag adds an additional column showing the total for each row. .PP The \f[C]\-A/\-\-average\f[] 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[] .fi .SS Market value .PP The \f[C]\-V/\-\-value\f[] flag converts the reported amounts to their market value on the report end date, using the most recent applicable market prices, when known. Specifically, when there is a market price (P directive) for the amount\[aq]s commodity, dated on or before the report end date (see hledger \-> Report start & end date), the amount will be converted to the price\[aq]s commodity. If multiple applicable prices are defined, the latest\-dated one is used (and if dates are equal, the one last parsed). .PP For example: .IP .nf \f[C] #\ 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 \f[] .fi .PP How many euros do I have ? .IP .nf \f[C] $\ hledger\ \-f\ t.j\ bal\ euros \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ €100\ \ assets:euros \f[] .fi .PP What are they worth on nov 3 ? (no report end date specified, defaults to the last date in the journal) .IP .nf \f[C] $\ hledger\ \-f\ t.j\ bal\ euros\ \-V \ \ \ \ \ \ \ \ \ \ \ \ \ $110.00\ \ assets:euros \f[] .fi .PP What are they worth on dec 21 ? .IP .nf \f[C] $\ hledger\ \-f\ t.j\ bal\ euros\ \-V\ \-e\ 2016/12/21 \ \ \ \ \ \ \ \ \ \ \ \ \ $103.00\ \ assets:euros \f[] .fi .PP Currently, hledger\[aq]s \-V only uses market prices recorded with P directives, not transaction prices (unlike Ledger). .PP Using \-B and \-V together is allowed. .SS Custom balance output .PP In simple (non\-multi\-column) balance reports, you can customise the output with \f[C]\-\-format\ FMT\f[]: .IP .nf \f[C] $\ 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 \f[] .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[] .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[] \- 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[] \- the account\[aq]s name .IP \[bu] 2 \f[C]total\f[] \- 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[] \- render on multiple lines, bottom\-aligned (the default) .IP \[bu] 2 \f[C]%^\f[] \- render on multiple lines, top\-aligned .IP \[bu] 2 \f[C]%,\f[] \- render on one line, comma\-separated .PP There are some quirks. Eg in one\-line mode, \f[C]%(depth_spacer)\f[] has no effect, instead \f[C]%(account)\f[] has indentation built in. Experimentation may be needed to get pleasing results. .PP Some example formats: .IP \[bu] 2 \f[C]%(total)\f[] \- the account\[aq]s total .IP \[bu] 2 \f[C]%\-20.20(account)\f[] \- 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[] \- 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[] \- the default format for the single\-column balance report .SS Output destination .PP The balance, print, register and stats commands can write their output to a destination other than the console. This is controlled by the \f[C]\-o/\-\-output\-file\f[] option. .IP .nf \f[C] $\ hledger\ balance\ \-o\ \-\ \ \ \ \ #\ write\ to\ stdout\ (the\ default) $\ hledger\ balance\ \-o\ FILE\ \ #\ write\ to\ FILE \f[] .fi .SS CSV output .PP The balance, print and register commands can write their output as CSV. This is useful for exporting data to other applications, eg to make charts in a spreadsheet. This is controlled by the \f[C]\-O/\-\-output\-format\f[] option, or by specifying a \f[C]\&.csv\f[] file extension with \f[C]\-o/\-\-output\-file\f[]. .IP .nf \f[C] $\ hledger\ balance\ \-O\ csv\ \ \ \ \ \ \ #\ write\ CSV\ to\ stdout $\ hledger\ balance\ \-o\ FILE.csv\ \ #\ write\ CSV\ to\ FILE.csv \f[] .fi .SS balancesheet .PP Show a balance sheet. Alias: bs. .TP .B \f[C]\-\-change\f[] show balance change in each period, instead of historical ending balances .RS .RE .TP .B \f[C]\-\-cumulative\f[] show balance change accumulated across periods (in multicolumn reports), instead of historical ending balances .RS .RE .TP .B \f[C]\-H\ \-\-historical\f[] show historical ending balance in each period (includes postings before report start date) (default) .RS .RE .TP .B \f[C]\-\-tree\f[] show accounts as a tree; amounts include subaccounts (default in simple reports) .RS .RE .TP .B \f[C]\-\-flat\f[] show accounts as a list; amounts exclude subaccounts except when account is depth\-clipped (default in multicolumn reports) .RS .RE .TP .B \f[C]\-A\ \-\-average\f[] show a row average column (in multicolumn mode) .RS .RE .TP .B \f[C]\-T\ \-\-row\-total\f[] show a row total column (in multicolumn mode) .RS .RE .TP .B \f[C]\-N\ \-\-no\-total\f[] don\[aq]t show the final total row .RS .RE .TP .B \f[C]\-\-drop=N\f[] omit N leading account name parts (in flat mode) .RS .RE .TP .B \f[C]\-\-no\-elide\f[] don\[aq]t squash boring parent accounts (in tree mode) .RS .RE .TP .B \f[C]\-\-format=LINEFORMAT\f[] in single\-column balance reports: use this custom line format .RS .RE .PP This command displays a simple balance sheet. It currently assumes that you have top\-level accounts named \f[C]asset\f[] and \f[C]liability\f[] (plural forms also allowed.) .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[] .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[]/\f[C]\-\-cumulative\f[]/\f[C]\-\-historical\f[]. Normally balancesheet shows historical ending balances, which is what you need for a balance sheet; note this means it ignores report begin dates. .SS cashflow .PP Show a cashflow statement. Alias: cf. .TP .B \f[C]\-\-change\f[] show balance change in each period (default) .RS .RE .TP .B \f[C]\-\-cumulative\f[] show balance change accumulated across periods (in multicolumn reports), instead of changes during periods .RS .RE .TP .B \f[C]\-H\ \-\-historical\f[] show historical ending balance in each period (includes postings before report start date), instead of changes during each period .RS .RE .TP .B \f[C]\-\-tree\f[] show accounts as a tree; amounts include subaccounts (default in simple reports) .RS .RE .TP .B \f[C]\-\-flat\f[] show accounts as a list; amounts exclude subaccounts except when account is depth\-clipped (default in multicolumn reports) .RS .RE .TP .B \f[C]\-A\ \-\-average\f[] show a row average column (in multicolumn mode) .RS .RE .TP .B \f[C]\-T\ \-\-row\-total\f[] show a row total column (in multicolumn mode) .RS .RE .TP .B \f[C]\-N\ \-\-no\-total\f[] don\[aq]t show the final total row (in simple reports) .RS .RE .TP .B \f[C]\-\-drop=N\f[] omit N leading account name parts (in flat mode) .RS .RE .TP .B \f[C]\-\-no\-elide\f[] don\[aq]t squash boring parent accounts (in tree mode) .RS .RE .TP .B \f[C]\-\-format=LINEFORMAT\f[] in single\-column balance reports: use this custom line format .RS .RE .PP This command displays a simple cashflow statement It shows the change in all "cash" (ie, liquid assets) accounts for the period. It currently assumes that cash accounts are under a top\-level account named \f[C]asset\f[] and do not contain \f[C]receivable\f[] or \f[C]A/R\f[] (plural forms also allowed.) .IP .nf \f[C] $\ hledger\ cashflow Cashflow\ Statement Cash\ flows: \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-1\ \ assets \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $1\ \ \ \ bank:saving \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-2\ \ \ \ cash \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-1 Total: \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-1 \f[] .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[]/\f[C]\-\-cumulative\f[]/\f[C]\-\-historical\f[]. .SS help .PP Show any of the hledger manuals. .PP The \f[C]help\f[] command displays any of the main hledger man pages. (Unlike \f[C]hledger\ \-\-help\f[], which displays only the hledger man page.) Run it with no arguments to list available topics (their names are shortened for easier typing), and run \f[C]hledger\ help\ TOPIC\f[] to select one. The output is similar to a man page, but fixed width. It may be long, so you may wish to pipe it into a pager. See also info and man. .IP .nf \f[C] $\ hledger\ help Choose\ a\ topic,\ eg:\ hledger\ help\ cli cli,\ ui,\ web,\ api,\ journal,\ csv,\ timeclock,\ timedot \f[] .fi .IP .nf \f[C] $\ hledger\ help\ cli\ |\ less hledger(1)\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ hledger\ User\ Manuals\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ hledger(1) NAME \ \ \ \ \ \ \ hledger\ \-\ a\ command\-line\ accounting\ tool SYNOPSIS \ \ \ \ \ \ \ hledger\ [\-f\ FILE]\ COMMAND\ [OPTIONS]\ [CMDARGS] \ \ \ \ \ \ \ hledger\ [\-f\ FILE]\ ADDONCMD\ \-\-\ [OPTIONS]\ [CMDARGS] : \f[] .fi .SS incomestatement .PP Show an income statement. Alias: is. .TP .B \f[C]\-\-change\f[] show balance change in each period (default) .RS .RE .TP .B \f[C]\-\-cumulative\f[] show balance change accumulated across periods (in multicolumn reports), instead of changes during periods .RS .RE .TP .B \f[C]\-H\ \-\-historical\f[] show historical ending balance in each period (includes postings before report start date), instead of changes during each period .RS .RE .TP .B \f[C]\-\-tree\f[] show accounts as a tree; amounts include subaccounts (default in simple reports) .RS .RE .TP .B \f[C]\-\-flat\f[] show accounts as a list; amounts exclude subaccounts except when account is depth\-clipped (default in multicolumn reports) .RS .RE .TP .B \f[C]\-A\ \-\-average\f[] show a row average column (in multicolumn mode) .RS .RE .TP .B \f[C]\-T\ \-\-row\-total\f[] show a row total column (in multicolumn mode) .RS .RE .TP .B \f[C]\-N\ \-\-no\-total\f[] don\[aq]t show the final total row .RS .RE .TP .B \f[C]\-\-drop=N\f[] omit N leading account name parts (in flat mode) .RS .RE .TP .B \f[C]\-\-no\-elide\f[] don\[aq]t squash boring parent accounts (in tree mode) .RS .RE .TP .B \f[C]\-\-format=LINEFORMAT\f[] in single\-column balance reports: use this custom line format .RS .RE .PP This command displays a simple income statement. It currently assumes that you have top\-level accounts named \f[C]income\f[] (or \f[C]revenue\f[]) and \f[C]expense\f[] (plural forms also allowed.) .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[] .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[]/\f[C]\-\-cumulative\f[]/\f[C]\-\-historical\f[]. .SS info .PP Show any of the hledger manuals using info. .PP The \f[C]info\f[] command displays any of the hledger reference manuals using the info hypertextual documentation viewer. This can be a very efficient way to browse large manuals. It requires the "info" program to be available in your PATH. .PP As with help, run it with no arguments to list available topics (manuals). .SS man .PP Show any of the hledger manuals using man. .PP The \f[C]man\f[] command displays any of the hledger reference manuals using man, the standard documentation viewer on unix systems. This will fit the text to your terminal width, and probably invoke a pager automatically. It requires the "man" program to be available in your PATH. .PP As with help, run it with no arguments to list available topics (manuals). .SS print .PP Show transactions from the journal. .TP .B \f[C]\-x\ \ \ \ \ \-\-explicit\f[] show all amounts explicitly .RS .RE .TP .B \f[C]\-m\ STR\ \-\-match=STR\f[] show the transaction whose description is most similar to STR, and is most recent .RS .RE .TP .B \f[C]\-O\ FMT\ \-\-output\-format=FMT\f[] select the output format. Supported formats: txt, csv. .RS .RE .TP .B \f[C]\-o\ FILE\ \-\-output\-file=FILE\f[] write output to FILE. A file extension matching one of the above formats selects that format. .RS .RE .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[] .fi .PP The print command displays full journal entries (transactions) from the journal file, tidily formatted. .PP As of hledger 1.2, print\[aq]s output is always a valid hledger journal. However it may not preserve all original content, eg it does not print directives or inter\-transaction comments. .PP Normally, transactions\[aq] implicit/explicit amount style is preserved: when an amount is omitted in the journal, it will be omitted in the output. You can use the \f[C]\-x/\-\-explicit\f[] flag to make all amounts explicit, which can be useful for troubleshooting or for making your journal more readable and robust against data entry errors. Note, in this mode postings with a multi\-commodity amount (possible with an implicit amount in a multi\-commodity transaction) will be split into multiple single\-commodity postings, for valid journal output. .PP With \-B/\-\-cost, amounts with transaction prices are converted to cost (using the transaction price). .PP The print command also supports output destination and CSV output. Here\[aq]s an example of print\[aq]s CSV output: .IP .nf \f[C] $\ 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","","","" \f[] .fi .IP \[bu] 2 There is one CSV record per posting, with the parent transaction\[aq]s fields repeated. .IP \[bu] 2 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.) .IP \[bu] 2 The amount is separated into "commodity" (the symbol) and "amount" (numeric quantity) fields. .IP \[bu] 2 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.) .SS register .PP Show postings and their running total. Alias: reg. .TP .B \f[C]\-\-cumulative\f[] show running total from report start date (default) .RS .RE .TP .B \f[C]\-H\ \-\-historical\f[] show historical running total/balance (includes postings before report start date) .RS .RE .TP .B \f[C]\-A\ \-\-average\f[] show running average of posting amounts instead of total (implies \-\-empty) .RS .RE .TP .B \f[C]\-r\ \-\-related\f[] show postings\[aq] siblings instead .RS .RE .TP .B \f[C]\-w\ N\ \-\-width=N\f[] set output width (default: terminal width or COLUMNS. \-wN,M sets description width as well) .RS .RE .TP .B \f[C]\-O\ FMT\ \-\-output\-format=FMT\f[] select the output format. Supported formats: txt, csv. .RS .RE .TP .B \f[C]\-o\ FILE\ \-\-output\-file=FILE\f[] write output to FILE. A file extension matching one of the above formats selects that format. .RS .RE .PP The register command displays postings, one per line, and their running total. This 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[] .fi .PP The \f[C]\-\-historical\f[]/\f[C]\-H\f[] 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[] .fi .PP The \f[C]\-\-depth\f[] option limits the amount of sub\-account detail displayed. .PP The \f[C]\-\-average\f[]/\f[C]\-A\f[] 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[] (see below). It is affected by \f[C]\-\-historical\f[]. It works best when showing just one account and one commodity. .PP The \f[C]\-\-related\f[]/\f[C]\-r\f[] flag shows the \f[I]other\f[] postings in the transactions of the postings which would normally be shown. .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[] .fi .PP Periods with no activity, and summary postings with a zero amount, are not shown by default; use the \f[C]\-\-empty\f[]/\f[C]\-E\f[] 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[] .fi .PP Often, you\[aq]ll want to see just one line per interval. The \f[C]\-\-depth\f[] 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[] .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[] environment variable (not a bash shell variable) or by using the \f[C]\-\-width\f[]/\f[C]\-w\f[] 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[] . Here\[aq]s a diagram: .IP .nf \f[C] <\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\ width\ (W)\ \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-> date\ (10)\ \ description\ (D)\ \ \ \ \ \ \ account\ (W\-41\-D)\ \ \ \ \ amount\ (12)\ \ \ balance\ (12) DDDDDDDDDD\ dddddddddddddddddddd\ \ aaaaaaaaaaaaaaaaaaa\ \ AAAAAAAAAAAA\ \ AAAAAAAAAAAA \f[] .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,\ and\ set\ description\ width \f[] .fi .PP The register command also supports the \f[C]\-o/\-\-output\-file\f[] and \f[C]\-O/\-\-output\-format\f[] options for controlling output destination and CSV output. .SS stats .PP Show some journal statistics. .TP .B \f[C]\-o\ FILE\ \-\-output\-file=FILE\f[] write output to FILE. A file extension matching one of the above formats selects that format. .RS .RE .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\ ($) \f[] .fi .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 The stats command also supports \f[C]\-o/\-\-output\-file\f[] for controlling output destination. .SS test .PP Run built\-in unit tests. .IP .nf \f[C] $\ hledger\ test Cases:\ 74\ \ Tried:\ 74\ \ Errors:\ 0\ \ Failures:\ 0 \f[] .fi .PP This command runs hledger\[aq]s built\-in unit tests and displays a quick report. With a regular expression argument, it selects only tests with matching names. It\[aq]s mainly used in development, but it\[aq]s also nice to be able to check your hledger executable for smoke at any time. .SH 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[] and ends with a recognised file extension (currently: no extension, \f[C]bat\f[],\f[C]com\f[],\f[C]exe\f[], \f[C]hs\f[],\f[C]lhs\f[],\f[C]pl\f[],\f[C]py\f[],\f[C]rb\f[],\f[C]rkt\f[],\f[C]sh\f[]). .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[] add\-on is installed, .IP \[bu] 2 \f[C]hledger\ \-h\ web\f[] shows hledger\[aq]s help, while \f[C]hledger\ web\ \-h\f[] shows hledger\-web\[aq]s help. .IP \[bu] 2 Flags specific to the add\-on must have a preceding \f[C]\-\-\f[] to hide them from hledger. So \f[C]hledger\ web\ \-\-serve\ \-\-port\ 9000\f[] will be rejected; you must use \f[C]hledger\ web\ \-\-\ \-\-serve\ \-\-port\ 9000\f[]. .IP \[bu] 2 You can always run add\-ons directly if preferred: \f[C]hledger\-web\ \-\-serve\ \-\-port\ 9000\f[]. .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 Here are some hledger add\-ons available: .SS Official add\-ons .PP These are maintained and released along with hledger. .SS api .PP hledger\-api serves hledger data as a JSON web API. .SS ui .PP hledger\-ui provides an efficient curses\-style interface. .SS web .PP hledger\-web provides a simple web interface. .SS Third party add\-ons .PP These are maintained separately, and usually updated shortly after a hledger release. .SS diff .PP hledger\-diff shows differences in an account\[aq]s transactions between one journal file and another. .SS iadd .PP hledger\-iadd is a curses\-style, more interactive replacement for the add command. .SS interest .PP hledger\-interest generates interest transactions for an account according to various schemes. .SS irr .PP hledger\-irr calculates the internal rate of return of an investment account. .SS Experimental add\-ons .PP These are available in source form in the hledger repo\[aq]s bin/ directory; installing them is pretty easy. They may be less mature and documented than built\-in commands. Reading and tweaking these is a good way to start making your own! .SS autosync .PP hledger\-autosync is a symbolic link for easily running ledger\-autosync, if installed. ledger\-autosync does deduplicating conversion of OFX data and some CSV formats, and can also download the data if your bank offers OFX Direct Connect. .SS budget .PP hledger\-budget.hs adds more budget\-tracking features to hledger. .SS chart .PP hledger\-chart.hs is an old pie chart generator, in need of some love. .SS check .PP hledger\-check.hs checks more powerful account balance assertions. .SS check\-dates .PP hledger\-check\-dates.hs checks that journal entries are ordered by date. .SS check\-dupes .PP hledger\-check\-dupes.hs checks for account names sharing the same leaf name. .SS equity .PP hledger\-equity.hs prints balance\-resetting transactions, useful for bringing account balances across file boundaries. .SS prices .PP hledger\-prices.hs prints all prices from the journal. .SS print\-unique .PP hledger\-print\-unique.hs prints transactions which do not reuse an already\-seen description. .SS register\-match .PP hledger\-register\-match.hs helps ledger\-autosync detect already\-seen transactions when importing. .SS rewrite .PP hledger\-rewrite.hs Adds one or more custom postings to matched transactions. .SH ENVIRONMENT .PP \f[B]COLUMNS\f[] The screen width used by the register command. Default: the full terminal width. .PP \f[B]LEDGER_FILE\f[] The journal file path when not specified with \f[C]\-f\f[]. Default: \f[C]~/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). .SH FILES .PP Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]\-f\f[], or \f[C]$LEDGER_FILE\f[], or \f[C]$HOME/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). .SH BUGS .PP The need to precede addon command options with \f[C]\-\-\f[] 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 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 "No command \[aq]hledger\[aq] found"\f[] .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 ~/.local/bin and ~/.cabal/bin respectively. .PP \f[B]I set a custom LEDGER_FILE, but hledger is still using the default file\f[] .PD 0 .P .PD \f[C]LEDGER_FILE\f[] should be a real environment variable, not just a shell variable. The command \f[C]env\ |\ grep\ LEDGER_FILE\f[] should show it. You may need to use \f[C]export\f[]. Here\[aq]s an explanation. .PP \f[B]"Illegal byte sequence" or "Invalid or incomplete multibyte or wide character" errors\f[] .PD 0 .P .PD In order to handle non\-ascii letters and symbols (like £), hledger needs an appropriate locale. This is usually configured system\-wide; you can also configure it temporarily. The locale may need to be one that supports UTF\-8, if you built hledger with GHC < 7.2 (or possibly always, I\[aq]m not sure yet). .PP Here\[aq]s an example of setting the locale temporarily, on ubuntu gnu/linux: .IP .nf \f[C] $\ file\ my.journal my.journal:\ UTF\-8\ Unicode\ text\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ <\-\ the\ file\ is\ UTF8\-encoded $\ locale\ \-a C en_US.utf8\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ #\ <\-\ a\ UTF8\-aware\ locale\ is\ available POSIX $\ LANG=en_US.utf8\ hledger\ \-f\ my.journal\ print\ \ \ #\ <\-\ use\ it\ for\ this\ command \f[] .fi .PP Here\[aq]s one way to set it permanently, there are probably better ways: .IP .nf \f[C] $\ echo\ "export\ LANG=en_US.UTF\-8"\ >>~/.bash_profile $\ bash\ \-\-login \f[] .fi .PP If we preferred to use eg \f[C]fr_FR.utf8\f[], we might have to install that first: .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[] .fi .PP Note some platforms allow variant locale spellings, but not all (ubuntu accepts \f[C]fr_FR.UTF8\f[], mac osx requires exactly \f[C]fr_FR.UTF\-8\f[]). .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-2016 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.2/doc/hledger.1.info0000644000000000000000000021263213067574770014375 0ustar0000000000000000This is hledger.1.info, produced by makeinfo version 6.0 from stdin.  File: hledger.1.info, Node: Top, Next: EXAMPLES, Up: (dir) hledger(1) hledger 1.2 ********************** This is hledger's command-line interface (there are also curses 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: * EXAMPLES:: * OPTIONS:: * QUERIES:: * COMMANDS:: * ADD-ON COMMANDS::  File: hledger.1.info, Node: EXAMPLES, Next: OPTIONS, Prev: Top, Up: Top 1 EXAMPLES ********** Two simple transactions in hledger journal format: 2015/9/30 gift received assets:cash $20 income:gifts 2015/10/16 farmers market expenses:food $10 assets:cash Some basic reports: $ hledger print 2015/09/30 gift received assets:cash $20 income:gifts $-20 2015/10/16 farmers market expenses:food $10 assets:cash $-10 $ hledger accounts --tree assets cash expenses food income gifts $ hledger balance $10 assets:cash $10 expenses:food $-20 income:gifts -------------------- 0 $ hledger register cash 2015/09/30 gift received assets:cash $20 $20 2015/10/16 farmers market assets:cash $-10 $10 More commands: $ hledger # show available commands $ hledger add # add more transactions to the journal file $ hledger balance # all accounts with aggregated balances $ hledger balance --help # show detailed help for balance command $ hledger balance --depth 1 # only top-level accounts $ hledger register # show account postings, with running total $ hledger reg income # show postings to/from income accounts $ hledger reg 'assets:some bank:checking' # show postings to/from this checking account $ hledger print desc:shop # show transactions with shop in the description $ hledger activity -W # show transaction counts per week as a bar chart  File: hledger.1.info, Node: OPTIONS, Next: QUERIES, Prev: EXAMPLES, Up: Top 2 OPTIONS ********* * Menu: * General options:: * Command options:: * Command arguments:: * Special characters:: * Input files:: * Smart dates:: * Report start & end date:: * Report intervals:: * Period expressions:: * Depth limiting:: * Pivoting:: * Regular expressions::  File: hledger.1.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'. (Note -h and -help are different, like git.) General help options: '-h' show general usage (or after COMMAND, command usage) '--help' show this program's manual as plain text (or after an add-on COMMAND, the add-on's manual) '--man' show this program's manual with man '--info' show this program's manual with info '--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) '--alias=OLD=NEW' rename accounts named OLD to NEW '--anon' anonymize accounts and payees '--pivot TAGNAME' use some other field/tag for account names '-I --ignore-assertions' ignore any failing balance assertions 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 (overrides the flags above) '--date2' show, and match with -b/-e/-p/date:, secondary dates instead '-C --cleared' include only cleared postings/txns '--pending' include only pending postings/txns '-U --uncleared' include only uncleared (and pending) postings/txns '-R --real' include only non-virtual postings '--depth=N' hide accounts/postings deeper than N '-E --empty' show items with zero amount, normally hidden '-B --cost' convert amounts to their cost at transaction time (using the transaction price, if any) '-V --value' convert amounts to their market value on the report end date (using the most recent applicable market price, if any) Note when multiple similar reporting options are provided, the last one takes precedence. Eg '-p feb -p mar' is equivalent to '-p mar'. Some of these can also be written as queries.  File: hledger.1.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.1.info, Node: Command arguments, Next: Special characters, 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.  File: hledger.1.info, Node: Special characters, Next: Input files, Prev: Command arguments, Up: OPTIONS 2.4 Special characters ====================== Option and argument values which contain problematic characters should be escaped with double quotes, backslashes, or (best) single quotes. Problematic characters means spaces, and also characters which are significant to your command shell, such as less-than/greater-than. Eg: 'hledger register -p 'last year' "accounts receivable (receivable|payable)" amt:\>100'. Characters which are significant both to the shell and in regular expressions sometimes need to be double-escaped. 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:\\$'. There's more.. options and arguments get de-escaped when hledger is passing them to an addon executable. In this case you might need _triple_-escaping. Eg: 'hledger ui cur:'\\$'' or 'hledger ui cur:\\\\$'. If in doubt, keep things simple: * run add-on executables directly * write options after the command * enclose problematic args in single quotes * if needed, also add a backslash to escape regexp metacharacters If you're really stumped, add '--debug=2' to troubleshoot.  File: hledger.1.info, Node: Input files, Next: Smart dates, Prev: Special characters, Up: OPTIONS 2.5 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 also be one of several other formats, listed below. hledger detects the format automatically based on the file extension, or if that is not recognised, by trying each built-in "reader" in turn: Reader: Reads: Used for file extensions: --------------------------------------------------------------------------- 'journal' hledger's journal format, also '.journal' '.j' some Ledger journals '.hledger' '.ledger' 'timeclock' timeclock files (precise time '.timeclock' logging) 'timedot' timedot files (approximate time '.timedot' logging) 'csv' comma-separated values (data '.csv' interchange) If needed (eg to ensure correct error messages when a file has the "wrong" extension), you can force a specific reader/format by prepending it to the file path with a colon. Examples: $ hledger -f csv:/some/csv-file.dat stats $ echo 'i 2009/13/1 08:00:00' | hledger print -ftimeclock:- You can also 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 those, either use the include directive, or concatenate the files, eg: 'cat a.journal b.journal | hledger -f- CMD'.  File: hledger.1.info, Node: Smart dates, Next: Report start & end date, Prev: Input files, Up: OPTIONS 2.6 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: '2009/1/1', '2009/01/01', '2009-1-1', '2009.1.1' simple dates, several separators allowed '2009/1', '2009' same as above - a missing day or month defaults to 1 '1/1', 'january', 'jan', 'this year' relative dates, meaning january 1 of the current year 'next year' january 1 of next year 'this month' the 1st of the current month 'this week' the most recent monday 'last week' the monday of the week before this one 'lastweek' spaces are optional 'today', 'yesterday', 'tomorrow'  File: hledger.1.info, Node: Report start & end date, Next: Report intervals, Prev: Smart dates, Up: OPTIONS 2.7 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. One important thing to be aware of when specifying end dates: as in Ledger, end dates are exclusive, so you need to write the date _after_ the last day you want to include. 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 'date:-12/1' 'date:thismonth-' 'date:thismonth'  File: hledger.1.info, Node: Report intervals, Next: Period expressions, Prev: Report start & end date, Up: OPTIONS 2.8 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, currently.  File: hledger.1.info, Node: Period expressions, Next: Depth limiting, Prev: Report intervals, Up: OPTIONS 2.9 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 "-". 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" 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"' The following more complex report intervals are also supported: 'biweekly', 'bimonthly', 'every N days|weeks|months|quarters|years', 'every Nth day [of month]', 'every Nth day of week'. Examples: '-p "bimonthly from 2008"' '-p "every 2 weeks"' '-p "every 5 days from 1/3"' 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.1.info, Node: Depth limiting, Next: Pivoting, Prev: Period expressions, Up: OPTIONS 2.10 Depth limiting =================== With the '--depth N' option, 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.  File: hledger.1.info, Node: Pivoting, Next: Regular expressions, Prev: Depth limiting, Up: OPTIONS 2.11 Pivoting ============= Normally hledger sums amounts, and organizes them in a hierarchy, based on account name. The '--pivot TAGNAME' option causes it to sum and organize hierarchy based on some other field instead. TAGNAME is the full, case-insensitive name of a tag you have defined, or one of the built-in implicit tags (like 'code' or 'payee'). As with account names, when tag values have 'multiple:colon-separated:parts' hledger will build hierarchy, displayed in tree-mode reports, summarisable with a depth limit, and so on. '--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 tag 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.1.info, Node: Regular expressions, Prev: Pivoting, Up: OPTIONS 2.12 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. In general they: * are case insensitive * are infix matching (do not need to match the entire thing being matched) * are POSIX extended regular expressions * also support GNU word boundaries (\<, \>, \b, \B) * and parenthesised capturing groups and numeric backreferences in replacement strings * do not support mode modifiers like (?s) 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.1.info, Node: QUERIES, Next: COMMANDS, Prev: OPTIONS, Up: Top 3 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, optional prefixes to match specific fields. Multiple search terms are combined as follows: All commands except print: show transactions/postings/accounts which match (or negatively match) * any of the description terms AND * any of the account terms AND * all the other terms. The print command: show 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: *'REGEX'* match account names by this regular expression *'acct:REGEX'* 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 *'real:, real:0'* match real or virtual postings respectively *'status:*, status:!, status:'* match cleared, pending, or uncleared/pending 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. *'not:'* before any of the above negates the match. *'inacct:ACCTNAME'* a special term used automatically when you click an account name in hledger-web, specifying the account register we are currently in (selects the transactions of that account and how to show them, can be filtered further with 'acct' etc). Not supported elsewhere in hledger. 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.1.info, Node: COMMANDS, Next: ADD-ON COMMANDS, Prev: QUERIES, Up: Top 4 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 any unambiguous prefix of a command name ('hledger inc'), or one of the standard short aliases displayed in the command list ('hledger is'). * Menu: * accounts:: * activity:: * add:: * balance:: * balancesheet:: * cashflow:: * help:: * incomestatement:: * info:: * man:: * print:: * register:: * stats:: * test::  File: hledger.1.info, Node: accounts, Next: activity, Up: COMMANDS 4.1 accounts ============ Show account names. '--tree' show short account names, as a tree '--flat' show full account names, as a list (default) '--drop=N' in flat mode: omit N leading account name parts This command lists all account names that are in use (ie, all the accounts which have at least one transaction posting to them). With query arguments, only matched account names 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. Examples: $ hledger accounts --tree assets bank checking saving cash expenses food supplies income gifts salary liabilities debts $ hledger accounts --drop 1 bank:checking bank:saving cash food supplies gifts salary debts $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts  File: hledger.1.info, Node: activity, Next: add, Prev: accounts, Up: COMMANDS 4.2 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. $ hledger activity --quarterly 2008-01-01 ** 2008-04-01 ******* 2008-07-01 2008-10-01 **  File: hledger.1.info, Node: add, Next: balance, Prev: activity, Up: COMMANDS 4.3 add ======= Prompt for transactions and add them to the journal. '--no-new-accounts' don't allow creating new accounts; helps prevent typos when entering account names 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 recent transaction (by description) 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 restart the transaction. * 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 restart the transaction. 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]: $  File: hledger.1.info, Node: balance, Next: balancesheet, Prev: add, Up: COMMANDS 4.4 balance =========== Show accounts and their balances. Alias: bal. '--change' show balance change in each period (default) '--cumulative' show balance change accumulated across periods (in multicolumn reports) '-H --historical' show historical ending balance in each period (includes postings before report start date) '--tree' show accounts as a tree; amounts include subaccounts (default in simple reports) '--flat' show accounts as a list; amounts exclude subaccounts except when account is depth-clipped (default in multicolumn reports) '-A --average' show a row average column (in multicolumn mode) '-T --row-total' show a row total column (in multicolumn mode) '-N --no-total' don't show the final total row '--drop=N' omit N leading account name parts (in flat mode) '--no-elide' don't squash boring parent accounts (in tree mode) '--format=LINEFORMAT' in single-column balance reports: use this custom line format '-O FMT --output-format=FMT' select the output format. Supported formats: txt, csv. '-o FILE --output-file=FILE' write output to FILE. A file extension matching one of the above formats selects that format. '--pretty-tables' Use unicode to display prettier tables. The balance command displays accounts and balances. It is hledger's most featureful and most useful command. $ 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 More precisely, the balance command shows the _change_ to each account's balance caused by all (matched) postings. In the common case where you do not filter by date and your journal sets the correct opening balances, this is the same as the account's ending balance. By default, accounts are displayed hierarchically, with subaccounts indented below their parent. "Boring" accounts, which contain a single interesting subaccount and no balance of their own, are elided into the following line for more compact output. (Use '--no-elide' to prevent this.) Each account's balance is the "inclusive" balance - it includes 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: $ hledger balance -p 2008/6 expenses --no-total $2 expenses $1 food $1 supplies * Menu: * Flat mode:: * Depth limited balance reports:: * Multicolumn balance reports:: * Market value:: * Custom balance output:: * Output destination:: * CSV output::  File: hledger.1.info, Node: Flat mode, Next: Depth limited balance reports, Up: balance 4.4.1 Flat mode --------------- To see a flat list of full account names instead of the default hierarchical display, use '--flat'. In this mode, accounts (unless depth-clipped) show their "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.1.info, Node: Depth limited balance reports, Next: Multicolumn balance reports, Prev: Flat mode, Up: balance 4.4.2 Depth limited balance reports ----------------------------------- With '--depth N', balance shows accounts only to the specified depth. This is very useful to show a complex charts of accounts in less detail. In flat mode, balances from accounts below the depth limit will be shown as part of a parent account at the depth limit. $ hledger balance -N --depth 1 $-1 assets $2 expenses $-2 income $1 liabilities  File: hledger.1.info, Node: Multicolumn balance reports, Next: Market value, Prev: Depth limited balance reports, Up: balance 4.4.3 Multicolumn balance reports --------------------------------- With a reporting interval, multiple balance columns will be shown, one for each report period. There are three types of multi-column 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 Multi-column 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  File: hledger.1.info, Node: Market value, Next: Custom balance output, Prev: Multicolumn balance reports, Up: balance 4.4.4 Market value ------------------ The '-V/--value' flag converts the reported amounts to their market value on the report end date, using the most recent applicable market prices, when known. Specifically, when there is a market price (P directive) for the amount's commodity, dated on or before the report end date (see hledger -> Report start & end date), the amount will be converted to the price's commodity. If multiple applicable prices are defined, the latest-dated one is used (and if dates are equal, the one last parsed). For example: # 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 euros €100 assets:euros What are they worth on nov 3 ? (no report end date specified, defaults to the last date in the journal) $ hledger -f t.j bal euros -V $110.00 assets:euros What are they worth on dec 21 ? $ hledger -f t.j bal euros -V -e 2016/12/21 $103.00 assets:euros Currently, hledger's -V only uses market prices recorded with P directives, not transaction prices (unlike Ledger). Using -B and -V together is allowed.  File: hledger.1.info, Node: Custom balance output, Next: Output destination, Prev: Market value, Up: balance 4.4.5 Custom balance output --------------------------- In simple (non-multi-column) balance reports, you can customise the output 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.1.info, Node: Output destination, Next: CSV output, Prev: Custom balance output, Up: balance 4.4.6 Output destination ------------------------ The balance, print, register and stats commands can write their output to a destination other than the console. This is controlled by the '-o/--output-file' option. $ hledger balance -o - # write to stdout (the default) $ hledger balance -o FILE # write to FILE  File: hledger.1.info, Node: CSV output, Prev: Output destination, Up: balance 4.4.7 CSV output ---------------- The balance, print and register commands can write their output as CSV. This is useful for exporting data to other applications, eg to make charts in a spreadsheet. This is controlled by the '-O/--output-format' option, or by specifying a '.csv' file extension with '-o/--output-file'. $ hledger balance -O csv # write CSV to stdout $ hledger balance -o FILE.csv # write CSV to FILE.csv  File: hledger.1.info, Node: balancesheet, Next: cashflow, Prev: balance, Up: COMMANDS 4.5 balancesheet ================ Show a balance sheet. Alias: bs. '--change' show balance change in each period, instead of historical ending balances '--cumulative' show balance change accumulated across periods (in multicolumn reports), instead of historical ending balances '-H --historical' show historical ending balance in each period (includes postings before report start date) (default) '--tree' show accounts as a tree; amounts include subaccounts (default in simple reports) '--flat' show accounts as a list; amounts exclude subaccounts except when account is depth-clipped (default in multicolumn reports) '-A --average' show a row average column (in multicolumn mode) '-T --row-total' show a row total column (in multicolumn mode) '-N --no-total' don't show the final total row '--drop=N' omit N leading account name parts (in flat mode) '--no-elide' don't squash boring parent accounts (in tree mode) '--format=LINEFORMAT' in single-column balance reports: use this custom line format This command displays a simple balance sheet. It currently assumes that you have top-level accounts named 'asset' and 'liability' (plural forms also allowed.) $ 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.  File: hledger.1.info, Node: cashflow, Next: help, Prev: balancesheet, Up: COMMANDS 4.6 cashflow ============ Show a cashflow statement. Alias: cf. '--change' show balance change in each period (default) '--cumulative' show balance change accumulated across periods (in multicolumn reports), instead of changes during periods '-H --historical' show historical ending balance in each period (includes postings before report start date), instead of changes during each period '--tree' show accounts as a tree; amounts include subaccounts (default in simple reports) '--flat' show accounts as a list; amounts exclude subaccounts except when account is depth-clipped (default in multicolumn reports) '-A --average' show a row average column (in multicolumn mode) '-T --row-total' show a row total column (in multicolumn mode) '-N --no-total' don't show the final total row (in simple reports) '--drop=N' omit N leading account name parts (in flat mode) '--no-elide' don't squash boring parent accounts (in tree mode) '--format=LINEFORMAT' in single-column balance reports: use this custom line format This command displays a simple cashflow statement It shows the change in all "cash" (ie, liquid assets) accounts for the period. It currently assumes that cash accounts are under a top-level account named 'asset' and do not contain 'receivable' or 'A/R' (plural forms also allowed.) $ 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'.  File: hledger.1.info, Node: help, Next: incomestatement, Prev: cashflow, Up: COMMANDS 4.7 help ======== Show any of the hledger manuals. The 'help' command displays any of the main hledger man pages. (Unlike 'hledger --help', which displays only the hledger man page.) Run it with no arguments to list available topics (their names are shortened for easier typing), and run 'hledger help TOPIC' to select one. The output is similar to a man page, but fixed width. It may be long, so you may wish to pipe it into a pager. See also info and man. $ hledger help Choose a topic, eg: hledger help cli cli, ui, web, api, journal, csv, timeclock, timedot $ hledger help cli | less hledger(1) hledger User Manuals hledger(1) NAME hledger - a command-line accounting tool SYNOPSIS hledger [-f FILE] COMMAND [OPTIONS] [CMDARGS] hledger [-f FILE] ADDONCMD -- [OPTIONS] [CMDARGS] :  File: hledger.1.info, Node: incomestatement, Next: info, Prev: help, Up: COMMANDS 4.8 incomestatement =================== Show an income statement. Alias: is. '--change' show balance change in each period (default) '--cumulative' show balance change accumulated across periods (in multicolumn reports), instead of changes during periods '-H --historical' show historical ending balance in each period (includes postings before report start date), instead of changes during each period '--tree' show accounts as a tree; amounts include subaccounts (default in simple reports) '--flat' show accounts as a list; amounts exclude subaccounts except when account is depth-clipped (default in multicolumn reports) '-A --average' show a row average column (in multicolumn mode) '-T --row-total' show a row total column (in multicolumn mode) '-N --no-total' don't show the final total row '--drop=N' omit N leading account name parts (in flat mode) '--no-elide' don't squash boring parent accounts (in tree mode) '--format=LINEFORMAT' in single-column balance reports: use this custom line format This command displays a simple income statement. It currently assumes that you have top-level accounts named 'income' (or 'revenue') and 'expense' (plural forms also allowed.) $ 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'.  File: hledger.1.info, Node: info, Next: man, Prev: incomestatement, Up: COMMANDS 4.9 info ======== Show any of the hledger manuals using info. The 'info' command displays any of the hledger reference manuals using the info hypertextual documentation viewer. This can be a very efficient way to browse large manuals. It requires the "info" program to be available in your PATH. As with help, run it with no arguments to list available topics (manuals).  File: hledger.1.info, Node: man, Next: print, Prev: info, Up: COMMANDS 4.10 man ======== Show any of the hledger manuals using man. The 'man' command displays any of the hledger reference manuals using man, the standard documentation viewer on unix systems. This will fit the text to your terminal width, and probably invoke a pager automatically. It requires the "man" program to be available in your PATH. As with help, run it with no arguments to list available topics (manuals).  File: hledger.1.info, Node: print, Next: register, Prev: man, Up: COMMANDS 4.11 print ========== Show transactions from the journal. '-x --explicit' show all amounts explicitly '-m STR --match=STR' show the transaction whose description is most similar to STR, and is most recent '-O FMT --output-format=FMT' select the output format. Supported formats: txt, csv. '-o FILE --output-file=FILE' write output to FILE. A file extension matching one of the above formats selects that format. $ 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 The print command displays full journal entries (transactions) from the journal file, tidily formatted. As of hledger 1.2, print's output is always a valid hledger journal. However it may not preserve all original content, eg it does not print directives or inter-transaction comments. Normally, transactions' implicit/explicit amount style is preserved: when an amount is omitted in the journal, it will be omitted in the output. You can use the '-x/--explicit' flag to make all amounts explicit, which can be useful for troubleshooting or for making your journal more readable and robust against data entry errors. Note, in this mode postings with a multi-commodity amount (possible with an implicit amount in a multi-commodity transaction) will be split into multiple single-commodity postings, for valid journal output. With -B/-cost, amounts with transaction prices are converted to cost (using the transaction price). The print command also supports output destination and CSV output. 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.1.info, Node: register, Next: stats, Prev: print, Up: COMMANDS 4.12 register ============= Show postings and their running total. Alias: reg. '--cumulative' show running total from report start date (default) '-H --historical' show historical running total/balance (includes postings before report start date) '-A --average' show running average of posting amounts instead of total (implies -empty) '-r --related' show postings' siblings instead '-w N --width=N' set output width (default: terminal width or COLUMNS. -wN,M sets description width as well) '-O FMT --output-format=FMT' select the output format. Supported formats: txt, csv. '-o FILE --output-file=FILE' write output to FILE. A file extension matching one of the above formats selects that format. The register command displays postings, one per line, and their running total. This 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 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. 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.1.info, Node: Custom register output, Up: register 4.12.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: <--------------------------------- 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, and set description width The register command also supports the '-o/--output-file' and '-O/--output-format' options for controlling output destination and CSV output.  File: hledger.1.info, Node: stats, Next: test, Prev: register, Up: COMMANDS 4.13 stats ========== Show some journal statistics. '-o FILE --output-file=FILE' write output to FILE. A file extension matching one of the above formats selects that format. $ 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 ($) 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. The stats command also supports '-o/--output-file' for controlling output destination.  File: hledger.1.info, Node: test, Prev: stats, Up: COMMANDS 4.14 test ========= Run built-in unit tests. $ hledger test Cases: 74 Tried: 74 Errors: 0 Failures: 0 This command runs hledger's built-in unit tests and displays a quick report. With a regular expression argument, it selects only tests with matching names. It's mainly used in development, but it's also nice to be able to check your hledger executable for smoke at any time.  File: hledger.1.info, Node: ADD-ON COMMANDS, Prev: COMMANDS, Up: Top 5 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. Here are some hledger add-ons available: * Menu: * Official add-ons:: * Third party add-ons:: * Experimental add-ons::  File: hledger.1.info, Node: Official add-ons, Next: Third party add-ons, Up: ADD-ON COMMANDS 5.1 Official add-ons ==================== These are maintained and released along with hledger. * Menu: * api:: * ui:: * web::  File: hledger.1.info, Node: api, Next: ui, Up: Official add-ons 5.1.1 api --------- hledger-api serves hledger data as a JSON web API.  File: hledger.1.info, Node: ui, Next: web, Prev: api, Up: Official add-ons 5.1.2 ui -------- hledger-ui provides an efficient curses-style interface.  File: hledger.1.info, Node: web, Prev: ui, Up: Official add-ons 5.1.3 web --------- hledger-web provides a simple web interface.  File: hledger.1.info, Node: Third party add-ons, Next: Experimental add-ons, Prev: Official add-ons, Up: ADD-ON COMMANDS 5.2 Third party add-ons ======================= These are maintained separately, and usually updated shortly after a hledger release. * Menu: * diff:: * iadd:: * interest:: * irr::  File: hledger.1.info, Node: diff, Next: iadd, Up: Third party add-ons 5.2.1 diff ---------- hledger-diff shows differences in an account's transactions between one journal file and another.  File: hledger.1.info, Node: iadd, Next: interest, Prev: diff, Up: Third party add-ons 5.2.2 iadd ---------- hledger-iadd is a curses-style, more interactive replacement for the add command.  File: hledger.1.info, Node: interest, Next: irr, Prev: iadd, Up: Third party add-ons 5.2.3 interest -------------- hledger-interest generates interest transactions for an account according to various schemes.  File: hledger.1.info, Node: irr, Prev: interest, Up: Third party add-ons 5.2.4 irr --------- hledger-irr calculates the internal rate of return of an investment account.  File: hledger.1.info, Node: Experimental add-ons, Prev: Third party add-ons, Up: ADD-ON COMMANDS 5.3 Experimental add-ons ======================== These are available in source form in the hledger repo's bin/ directory; installing them is pretty easy. They may be less mature and documented than built-in commands. Reading and tweaking these is a good way to start making your own! * Menu: * autosync:: * budget:: * chart:: * check:: * check-dates:: * check-dupes:: * equity:: * prices:: * print-unique:: * register-match:: * rewrite::  File: hledger.1.info, Node: autosync, Next: budget, Up: Experimental add-ons 5.3.1 autosync -------------- hledger-autosync is a symbolic link for easily running ledger-autosync, if installed. ledger-autosync does deduplicating conversion of OFX data and some CSV formats, and can also download the data if your bank offers OFX Direct Connect.  File: hledger.1.info, Node: budget, Next: chart, Prev: autosync, Up: Experimental add-ons 5.3.2 budget ------------ hledger-budget.hs adds more budget-tracking features to hledger.  File: hledger.1.info, Node: chart, Next: check, Prev: budget, Up: Experimental add-ons 5.3.3 chart ----------- hledger-chart.hs is an old pie chart generator, in need of some love.  File: hledger.1.info, Node: check, Next: check-dates, Prev: chart, Up: Experimental add-ons 5.3.4 check ----------- hledger-check.hs checks more powerful account balance assertions.  File: hledger.1.info, Node: check-dates, Next: check-dupes, Prev: check, Up: Experimental add-ons 5.3.5 check-dates ----------------- hledger-check-dates.hs checks that journal entries are ordered by date.  File: hledger.1.info, Node: check-dupes, Next: equity, Prev: check-dates, Up: Experimental add-ons 5.3.6 check-dupes ----------------- hledger-check-dupes.hs checks for account names sharing the same leaf name.  File: hledger.1.info, Node: equity, Next: prices, Prev: check-dupes, Up: Experimental add-ons 5.3.7 equity ------------ hledger-equity.hs prints balance-resetting transactions, useful for bringing account balances across file boundaries.  File: hledger.1.info, Node: prices, Next: print-unique, Prev: equity, Up: Experimental add-ons 5.3.8 prices ------------ hledger-prices.hs prints all prices from the journal.  File: hledger.1.info, Node: print-unique, Next: register-match, Prev: prices, Up: Experimental add-ons 5.3.9 print-unique ------------------ hledger-print-unique.hs prints transactions which do not reuse an already-seen description.  File: hledger.1.info, Node: register-match, Next: rewrite, Prev: print-unique, Up: Experimental add-ons 5.3.10 register-match --------------------- hledger-register-match.hs helps ledger-autosync detect already-seen transactions when importing.  File: hledger.1.info, Node: rewrite, Prev: register-match, Up: Experimental add-ons 5.3.11 rewrite -------------- hledger-rewrite.hs Adds one or more custom postings to matched transactions.  Tag Table: Node: Top70 Node: EXAMPLES1886 Ref: #examples1988 Node: OPTIONS3634 Ref: #options3738 Node: General options3993 Ref: #general-options4120 Node: Command options6643 Ref: #command-options6796 Node: Command arguments7194 Ref: #command-arguments7354 Node: Special characters7475 Ref: #special-characters7633 Node: Input files8801 Ref: #input-files8939 Node: Smart dates10902 Ref: #smart-dates11045 Node: Report start & end date12024 Ref: #report-start-end-date12196 Node: Report intervals13262 Ref: #report-intervals13427 Node: Period expressions13828 Ref: #period-expressions13988 Node: Depth limiting16328 Ref: #depth-limiting16474 Node: Pivoting16675 Ref: #pivoting16810 Node: Regular expressions18581 Ref: #regular-expressions18715 Node: QUERIES20076 Ref: #queries20180 Node: COMMANDS23826 Ref: #commands23940 Node: accounts24613 Ref: #accounts24713 Node: activity25695 Ref: #activity25807 Node: add26166 Ref: #add26267 Node: balance28925 Ref: #balance29038 Node: Flat mode31980 Ref: #flat-mode32107 Node: Depth limited balance reports32527 Ref: #depth-limited-balance-reports32730 Node: Multicolumn balance reports33150 Ref: #multicolumn-balance-reports33352 Node: Market value38000 Ref: #market-value38164 Node: Custom balance output39464 Ref: #custom-balance-output39637 Node: Output destination41730 Ref: #output-destination41895 Node: CSV output42165 Ref: #csv-output42284 Node: balancesheet42681 Ref: #balancesheet42809 Node: cashflow44716 Ref: #cashflow44833 Node: help46701 Ref: #help46813 Node: incomestatement47651 Ref: #incomestatement47781 Node: info49673 Ref: #info49780 Node: man50144 Ref: #man50241 Node: print50646 Ref: #print50751 Node: register54507 Ref: #register54620 Node: Custom register output59116 Ref: #custom-register-output59247 Node: stats60544 Ref: #stats60650 Node: test61531 Ref: #test61618 Node: ADD-ON COMMANDS61986 Ref: #add-on-commands62098 Node: Official add-ons63385 Ref: #official-add-ons63527 Node: api63614 Ref: #api63705 Node: ui63757 Ref: #ui63858 Node: web63916 Ref: #web64007 Node: Third party add-ons64053 Ref: #third-party-add-ons64230 Node: diff64365 Ref: #diff64464 Node: iadd64563 Ref: #iadd64679 Node: interest64762 Ref: #interest64885 Node: irr64980 Ref: #irr65080 Node: Experimental add-ons65158 Ref: #experimental-add-ons65312 Node: autosync65705 Ref: #autosync65819 Node: budget66058 Ref: #budget66182 Node: chart66248 Ref: #chart66367 Node: check66438 Ref: #check66562 Node: check-dates66629 Ref: #check-dates66771 Node: check-dupes66844 Ref: #check-dupes66987 Node: equity67064 Ref: #equity67192 Node: prices67311 Ref: #prices67440 Node: print-unique67495 Ref: #print-unique67644 Node: register-match67737 Ref: #register-match67893 Node: rewrite67991 Ref: #rewrite68112  End Tag Table hledger-1.2/doc/hledger.1.txt0000644000000000000000000022506713067574772014271 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 cross-platform program 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). Tested on unix, mac, windows, hledger aims to be a reliable, practical tool for daily use. This is hledger's command-line interface (there are also curses and web interfaces). Its basic function is to read a plain text file describ- ing 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, trans- lating 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. EXAMPLES Two simple transactions in hledger journal format: 2015/9/30 gift received assets:cash $20 income:gifts 2015/10/16 farmers market expenses:food $10 assets:cash Some basic reports: $ hledger print 2015/09/30 gift received assets:cash $20 income:gifts $-20 2015/10/16 farmers market expenses:food $10 assets:cash $-10 $ hledger accounts --tree assets cash expenses food income gifts $ hledger balance $10 assets:cash $10 expenses:food $-20 income:gifts -------------------- 0 $ hledger register cash 2015/09/30 gift received assets:cash $20 $20 2015/10/16 farmers market assets:cash $-10 $10 More commands: $ hledger # show available commands $ hledger add # add more transactions to the journal file $ hledger balance # all accounts with aggregated balances $ hledger balance --help # show detailed help for balance command $ hledger balance --depth 1 # only top-level accounts $ hledger register # show account postings, with running total $ hledger reg income # show postings to/from income accounts $ hledger reg 'assets:some bank:checking' # show postings to/from this checking account $ hledger print desc:shop # show transactions with shop in the description $ hledger activity -W # show transaction counts per week as a bar chart OPTIONS General options To see general usage help, including general options which are sup- ported by most hledger commands, run hledger -h. (Note -h and --help are different, like git.) General help options: -h show general usage (or after COMMAND, command usage) --help show this program's manual as plain text (or after an add-on COMMAND, the add-on's manual) --man show this program's manual with man --info show this program's manual with info --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) --alias=OLD=NEW rename accounts named OLD to NEW --anon anonymize accounts and payees --pivot TAGNAME use some other field/tag for account names -I --ignore-assertions ignore any failing balance assertions 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 (overrides the flags above) --date2 show, and match with -b/-e/-p/date:, secondary dates instead -C --cleared include only cleared postings/txns --pending include only pending postings/txns -U --uncleared include only uncleared (and pending) postings/txns -R --real include only non-virtual postings --depth=N hide accounts/postings deeper than N -E --empty show items with zero amount, normally hidden -B --cost convert amounts to their cost at transaction time (using the transaction price, if any) -V --value convert amounts to their market value on the report end date (using the most recent applicable market price, if any) Note when multiple similar reporting options are provided, the last one takes precedence. Eg -p feb -p mar is equivalent to -p mar. Some of these can also be written as queries. 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. Command arguments Most hledger commands accept arguments after the command name, which are often a query, filtering the data in some way. Special characters Option and argument values which contain problematic characters should be escaped with double quotes, backslashes, or (best) single quotes. Problematic characters means spaces, and also characters which are sig- nificant to your command shell, such as less-than/greater-than. Eg: hledger register -p 'last year' "accounts receivable (receiv- able|payable)" amt:\>100. Characters which are significant both to the shell and in regular expressions sometimes need to be double-escaped. These include paren- theses, the pipe symbol and the dollar sign. Eg, to match the dollar symbol, bash users should do: hledger balance cur:'\$' or hledger bal- ance cur:\\$. There's more.. options and arguments get de-escaped when hledger is passing them to an addon executable. In this case you might need triple-escaping. Eg: hledger ui cur:'\\$' or hledger ui cur:\\\\$. If in doubt, keep things simple: o run add-on executables directly o write options after the command o enclose problematic args in single quotes o if needed, also add a backslash to escape regexp metacharacters If you're really stumped, add --debug=2 to troubleshoot. 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 also be one of several other formats, listed below. hledger detects the format automatically based on the file extension, or if that is not recognised, by trying each built-in "reader" in turn: Reader: Reads: Used for file extensions: ----------------------------------------------------------------------------- journal hledger's journal format, also .journal .j .hledger some Ledger journals .ledger timeclock timeclock files (precise time .timeclock logging) timedot timedot files (approximate time .timedot logging) csv comma-separated values (data .csv interchange) If needed (eg to ensure correct error messages when a file has the "wrong" extension), you can force a specific reader/format by prepend- ing it to the file path with a colon. Examples: $ hledger -f csv:/some/csv-file.dat stats $ echo 'i 2009/13/1 08:00:00' | hledger print -ftimeclock:- You can also 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 those, either use the include directive, or concatenate the files, eg: cat a.journal b.journal | hledger -f- CMD. 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: 2009/1/1, 2009/01/01, simple dates, several sep- 2009-1-1, 2009.1.1 arators allowed 2009/1, 2009 same as above - a missing day or month defaults to 1 1/1, january, jan, relative dates, meaning this year january 1 of the current year next year january 1 of next year this month the 1st of the current month this week the most recent monday last week the monday of the week before this one lastweek spaces are optional today, yesterday, tomorrow 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. One important thing to be aware of when specifying end dates: as in Ledger, end dates are exclusive, so you need to write the date after the last day you want to include. Examples: -b 2016/3/17 begin on St. Patrick's day 2016 -e 12/1 end at the start of decem- ber 1st of the current year (11/30 will be the last date included) -b thismonth all transactions on or after the 1st of the cur- rent month -p thismonth all transactions in the current month date:2016/3/17- the above written as queries instead 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 intervals can not be specified with a query, currently. 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 "-". 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" 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" The following more complex report intervals are also supported: biweekly, bimonthly, every N days|weeks|months|quarters|years, every Nth day [of month], every Nth day of week. Examples: -p "bimonthly from 2008" -p "every 2 weeks" -p "every 5 days from 1/3" 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, 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. Pivoting Normally hledger sums amounts, and organizes them in a hierarchy, based on account name. The --pivot TAGNAME option causes it to sum and orga- nize hierarchy based on some other field instead. TAGNAME is the full, case-insensitive name of a tag you have defined, or one of the built-in implicit tags (like code or payee). As with account names, when tag values have multiple:colon-separated:parts hledger will build hierarchy, displayed in tree-mode reports, summaris- able with a depth limit, and so on. --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 tag 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 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. In general they: o are case insensitive o are infix matching (do not need to match the entire thing being matched) o are POSIX extended regular expressions o also support GNU word boundaries (\<, \>, \b, \B) o and parenthesised capturing groups and numeric backreferences in replacement strings o do not support mode modifiers like (?s) 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. 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, optional prefixes to match specific fields. Multiple search terms are combined as follows: All commands except print: show transactions/postings/accounts which match (or negatively match) o any of the description terms AND o any of the account terms AND o all the other terms. The print command: show 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: REGEX match account names by this regular expression acct:REGEX 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 real:, real:0 match real or virtual postings respectively status:*, status:!, status: match cleared, pending, or uncleared/pending 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. not: before any of the above negates the match. inacct:ACCTNAME a special term used automatically when you click an account name in hledger-web, specifying the account register we are currently in (selects the transactions of that account and how to show them, can be filtered further with acct etc). Not supported elsewhere in hledger. 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). 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 any unambiguous prefix of a command name (hledger inc), or one of the standard short aliases dis- played in the command list (hledger is). accounts Show account names. --tree show short account names, as a tree --flat show full account names, as a list (default) --drop=N in flat mode: omit N leading account name parts This command lists all account names that are in use (ie, all the accounts which have at least one transaction posting to them). With query arguments, only matched account names 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. Examples: $ hledger accounts --tree assets bank checking saving cash expenses food supplies income gifts salary liabilities debts $ hledger accounts --drop 1 bank:checking bank:saving cash food supplies gifts salary debts $ hledger accounts assets:bank:checking assets:bank:saving assets:cash expenses:food expenses:supplies income:gifts income:salary liabilities:debts 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. $ hledger activity --quarterly 2008-01-01 ** 2008-04-01 ******* 2008-07-01 2008-10-01 ** add Prompt for transactions and add them to the journal. --no-new-accounts don't allow creating new accounts; helps prevent typos when entering account names 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 recent transaction (by description) 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 restart the transac- tion. 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 restart the transaction. 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]: $ balance Show accounts and their balances. Alias: bal. --change show balance change in each period (default) --cumulative show balance change accumulated across periods (in multicolumn reports) -H --historical show historical ending balance in each period (includes postings before report start date) --tree show accounts as a tree; amounts include subaccounts (default in simple reports) --flat show accounts as a list; amounts exclude subaccounts except when account is depth-clipped (default in multicolumn reports) -A --average show a row average column (in multicolumn mode) -T --row-total show a row total column (in multicolumn mode) -N --no-total don't show the final total row --drop=N omit N leading account name parts (in flat mode) --no-elide don't squash boring parent accounts (in tree mode) --format=LINEFORMAT in single-column balance reports: use this custom line format -O FMT --output-format=FMT select the output format. Supported formats: txt, csv. -o FILE --output-file=FILE write output to FILE. A file extension matching one of the above formats selects that format. --pretty-tables Use unicode to display prettier tables. The balance command displays accounts and balances. It is hledger's most featureful and most useful command. $ 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 More precisely, the balance command shows the change to each account's balance caused by all (matched) postings. In the common case where you do not filter by date and your journal sets the correct opening bal- ances, this is the same as the account's ending balance. By default, accounts are displayed hierarchically, with subaccounts indented below their parent. "Boring" accounts, which contain a single interesting subaccount and no balance of their own, are elided into the following line for more compact output. (Use --no-elide to prevent this.) Each account's balance is the "inclusive" balance - it includes 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: $ hledger balance -p 2008/6 expenses --no-total $2 expenses $1 food $1 supplies Flat mode To see a flat list of full account names instead of the default hierar- chical display, use --flat. In this mode, accounts (unless depth-clipped) show their "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, balance shows accounts only to the specified depth. This is very useful to show a complex charts of accounts in less detail. In flat mode, balances from accounts below the depth limit will be shown as part of a parent account at the depth limit. $ hledger balance -N --depth 1 $-1 assets $2 expenses $-2 income $1 liabilities Multicolumn balance reports With a reporting interval, multiple balance columns will be shown, one for each report period. There are three types of multi-column 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 Multi-column 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 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 oth- erwise 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 Market value The -V/--value flag converts the reported amounts to their market value on the report end date, using the most recent applicable market prices, when known. Specifically, when there is a market price (P directive) for the amount's commodity, dated on or before the report end date (see hledger -> Report start & end date), the amount will be converted to the price's commodity. If multiple applicable prices are defined, the latest-dated one is used (and if dates are equal, the one last parsed). For example: # 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 euros 100 assets:euros What are they worth on nov 3 ? (no report end date specified, defaults to the last date in the journal) $ hledger -f t.j bal euros -V $110.00 assets:euros What are they worth on dec 21 ? $ hledger -f t.j bal euros -V -e 2016/12/21 $103.00 assets:euros Currently, hledger's -V only uses market prices recorded with P direc- tives, not transaction prices (unlike Ledger). Using -B and -V together is allowed. Custom balance output In simple (non-multi-column) balance reports, you can customise the output 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 effect, 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 Output destination The balance, print, register and stats commands can write their output to a destination other than the console. This is controlled by the -o/--output-file option. $ hledger balance -o - # write to stdout (the default) $ hledger balance -o FILE # write to FILE CSV output The balance, print and register commands can write their output as CSV. This is useful for exporting data to other applications, eg to make charts in a spreadsheet. This is controlled by the -O/--output-format option, or by specifying a .csv file extension with -o/--output-file. $ hledger balance -O csv # write CSV to stdout $ hledger balance -o FILE.csv # write CSV to FILE.csv balancesheet Show a balance sheet. Alias: bs. --change show balance change in each period, instead of historical ending balances --cumulative show balance change accumulated across periods (in multicolumn reports), instead of historical ending balances -H --historical show historical ending balance in each period (includes postings before report start date) (default) --tree show accounts as a tree; amounts include subaccounts (default in simple reports) --flat show accounts as a list; amounts exclude subaccounts except when account is depth-clipped (default in multicolumn reports) -A --average show a row average column (in multicolumn mode) -T --row-total show a row total column (in multicolumn mode) -N --no-total don't show the final total row --drop=N omit N leading account name parts (in flat mode) --no-elide don't squash boring parent accounts (in tree mode) --format=LINEFORMAT in single-column balance reports: use this custom line format This command displays a simple balance sheet. It currently assumes that you have top-level accounts named asset and liability (plural forms also allowed.) $ 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. cashflow Show a cashflow statement. Alias: cf. --change show balance change in each period (default) --cumulative show balance change accumulated across periods (in multicolumn reports), instead of changes during periods -H --historical show historical ending balance in each period (includes postings before report start date), instead of changes during each period --tree show accounts as a tree; amounts include subaccounts (default in simple reports) --flat show accounts as a list; amounts exclude subaccounts except when account is depth-clipped (default in multicolumn reports) -A --average show a row average column (in multicolumn mode) -T --row-total show a row total column (in multicolumn mode) -N --no-total don't show the final total row (in simple reports) --drop=N omit N leading account name parts (in flat mode) --no-elide don't squash boring parent accounts (in tree mode) --format=LINEFORMAT in single-column balance reports: use this custom line format This command displays a simple cashflow statement It shows the change in all "cash" (ie, liquid assets) accounts for the period. It cur- rently assumes that cash accounts are under a top-level account named asset and do not contain receivable or A/R (plural forms also allowed.) $ 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. help Show any of the hledger manuals. The help command displays any of the main hledger man pages. (Unlike hledger --help, which displays only the hledger man page.) Run it with no arguments to list available topics (their names are shortened for easier typing), and run hledger help TOPIC to select one. The output is similar to a man page, but fixed width. It may be long, so you may wish to pipe it into a pager. See also info and man. $ hledger help Choose a topic, eg: hledger help cli cli, ui, web, api, journal, csv, timeclock, timedot $ hledger help cli | less hledger(1) hledger User Manuals hledger(1) NAME hledger - a command-line accounting tool SYNOPSIS hledger [-f FILE] COMMAND [OPTIONS] [CMDARGS] hledger [-f FILE] ADDONCMD -- [OPTIONS] [CMDARGS] : incomestatement Show an income statement. Alias: is. --change show balance change in each period (default) --cumulative show balance change accumulated across periods (in multicolumn reports), instead of changes during periods -H --historical show historical ending balance in each period (includes postings before report start date), instead of changes during each period --tree show accounts as a tree; amounts include subaccounts (default in simple reports) --flat show accounts as a list; amounts exclude subaccounts except when account is depth-clipped (default in multicolumn reports) -A --average show a row average column (in multicolumn mode) -T --row-total show a row total column (in multicolumn mode) -N --no-total don't show the final total row --drop=N omit N leading account name parts (in flat mode) --no-elide don't squash boring parent accounts (in tree mode) --format=LINEFORMAT in single-column balance reports: use this custom line format This command displays a simple income statement. It currently assumes that you have top-level accounts named income (or revenue) and expense (plural forms also allowed.) $ 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. info Show any of the hledger manuals using info. The info command displays any of the hledger reference manuals using the info hypertextual documentation viewer. This can be a very effi- cient way to browse large manuals. It requires the "info" program to be available in your PATH. As with help, run it with no arguments to list available topics (manu- als). man Show any of the hledger manuals using man. The man command displays any of the hledger reference manuals using man, the standard documentation viewer on unix systems. This will fit the text to your terminal width, and probably invoke a pager automati- cally. It requires the "man" program to be available in your PATH. As with help, run it with no arguments to list available topics (manu- als). print Show transactions from the journal. -x --explicit show all amounts explicitly -m STR --match=STR show the transaction whose description is most similar to STR, and is most recent -O FMT --output-format=FMT select the output format. Supported formats: txt, csv. -o FILE --output-file=FILE write output to FILE. A file extension matching one of the above formats selects that format. $ 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 The print command displays full journal entries (transactions) from the journal file, tidily formatted. As of hledger 1.2, print's output is always a valid hledger journal. However it may not preserve all original content, eg it does not print directives or inter-transaction comments. Normally, transactions' implicit/explicit amount style is preserved: when an amount is omitted in the journal, it will be omitted in the output. You can use the -x/--explicit flag to make all amounts explicit, which can be useful for troubleshooting or for making your journal more readable and robust against data entry errors. Note, in this mode postings with a multi-commodity amount (possible with an implicit amount in a multi-commodity transaction) will be split into multiple single-commodity postings, for valid journal output. With -B/--cost, amounts with transaction prices are converted to cost (using the transaction price). The print command also supports output destination and CSV output. Here's an example of print's CSV output: $ hledger print -Ocsv "txnidx","date","date2","status","code","description","comment","account","amount","commodity","credit","debit","posting-status","posting-comment" "1","2008/01/01","","","","income","","assets:bank:checking","1","$","","1","","" "1","2008/01/01","","","","income","","income:salary","-1","$","1","","","" "2","2008/06/01","","","","gift","","assets:bank:checking","1","$","","1","","" "2","2008/06/01","","","","gift","","income:gifts","-1","$","1","","","" "3","2008/06/02","","","","save","","assets:bank:saving","1","$","","1","","" "3","2008/06/02","","","","save","","assets:bank:checking","-1","$","1","","","" "4","2008/06/03","","*","","eat & shop","","expenses:food","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","expenses:supplies","1","$","","1","","" "4","2008/06/03","","*","","eat & shop","","assets:cash","-2","$","2","","","" "5","2008/12/31","","*","","pay off","","liabilities:debts","1","$","","1","","" "5","2008/12/31","","*","","pay off","","assets:bank:checking","-1","$","1","","","" o There is one CSV record per posting, with the parent transaction's fields repeated. o The "txnidx" (transaction index) field shows which postings belong to the same transaction. (This number might change if transactions are reordered within the file, files are parsed/included in a different order, etc.) o The amount is separated into "commodity" (the symbol) and "amount" (numeric quantity) fields. o The numeric amount is repeated in either the "credit" or "debit" col- umn, for convenience. (Those names are not accurate in the account- ing sense; it just puts negative amounts under credit and zero or greater amounts under debit.) register Show postings and their running total. Alias: reg. --cumulative show running total from report start date (default) -H --historical show historical running total/balance (includes postings before report start date) -A --average show running average of posting amounts instead of total (implies --empty) -r --related show postings' siblings instead -w N --width=N set output width (default: terminal width or COLUMNS. -wN,M sets description width as well) -O FMT --output-format=FMT select the output format. Supported formats: txt, csv. -o FILE --output-file=FILE write output to FILE. A file extension matching one of the above formats selects that format. The register command displays postings, one per line, and their running total. This 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 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. 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: <--------------------------------- 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, and set description width The register command also supports the -o/--output-file and -O/--out- put-format options for controlling output destination and CSV output. stats Show some journal statistics. -o FILE --output-file=FILE write output to FILE. A file extension matching one of the above formats selects that format. $ 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 ($) 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. The stats command also supports -o/--output-file for controlling output destination. test Run built-in unit tests. $ hledger test Cases: 74 Tried: 74 Errors: 0 Failures: 0 This command runs hledger's built-in unit tests and displays a quick report. With a regular expression argument, it selects only tests with matching names. It's mainly used in development, but it's also nice to be able to check your hledger executable for smoke at any time. 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. Here are some hledger add-ons available: Official add-ons These are maintained and released along with hledger. api hledger-api serves hledger data as a JSON web API. ui hledger-ui provides an efficient curses-style interface. web hledger-web provides a simple web interface. Third party add-ons These are maintained separately, and usually updated shortly after a hledger release. diff hledger-diff shows differences in an account's transactions between one journal file and another. iadd hledger-iadd is a curses-style, more interactive replacement for the add command. interest hledger-interest generates interest transactions for an account accord- ing to various schemes. irr hledger-irr calculates the internal rate of return of an investment account. Experimental add-ons These are available in source form in the hledger repo's bin/ direc- tory; installing them is pretty easy. They may be less mature and doc- umented than built-in commands. Reading and tweaking these is a good way to start making your own! autosync hledger-autosync is a symbolic link for easily running ledger-autosync, if installed. ledger-autosync does deduplicating conversion of OFX data and some CSV formats, and can also download the data if your bank offers OFX Direct Connect. budget hledger-budget.hs adds more budget-tracking features to hledger. chart hledger-chart.hs is an old pie chart generator, in need of some love. check hledger-check.hs checks more powerful account balance assertions. check-dates hledger-check-dates.hs checks that journal entries are ordered by date. check-dupes hledger-check-dupes.hs checks for account names sharing the same leaf name. equity hledger-equity.hs prints balance-resetting transactions, useful for bringing account balances across file boundaries. prices hledger-prices.hs prints all prices from the journal. print-unique hledger-print-unique.hs prints transactions which do not reuse an already-seen description. register-match hledger-register-match.hs helps ledger-autosync detect already-seen transactions when importing. rewrite hledger-rewrite.hs Adds one or more custom postings to matched transac- tions. ENVIRONMENT COLUMNS The screen width used by the register command. 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). 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 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. 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 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. "Illegal byte sequence" or "Invalid or incomplete multibyte or wide character" errors In order to handle non-ascii letters and symbols (like ), hledger needs an appropriate locale. This is usually configured system-wide; you can also configure it temporarily. The locale may need to be one that sup- ports UTF-8, if you built hledger with GHC < 7.2 (or possibly always, I'm not sure yet). Here's an example of setting the locale temporarily, on ubuntu gnu/linux: $ file my.journal my.journal: UTF-8 Unicode text # <- the file is UTF8-encoded $ locale -a C en_US.utf8 # <- a UTF8-aware locale is available POSIX $ LANG=en_US.utf8 hledger -f my.journal print # <- use it for this command Here's one way to set it permanently, there are probably better ways: $ echo "export LANG=en_US.UTF-8" >>~/.bash_profile $ bash --login If we preferred to use eg fr_FR.utf8, we might have to install that first: $ 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 Note some platforms allow variant locale spellings, but not all (ubuntu accepts fr_FR.UTF8, mac osx requires exactly fr_FR.UTF-8). 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-2016 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.2 March 2017 hledger(1) hledger-1.2/doc/other/hledger-api.10000644000000000000000000000662013067574771015332 0ustar0000000000000000 .TH "hledger\-api" "1" "March 2017" "hledger\-api 1.2" "hledger User Manuals" .SH NAME .PP hledger\-api \- web API server for the hledger accounting tool .SH SYNOPSIS .PP \f[C]hledger\-api\ [OPTIONS]\f[] .PD 0 .P .PD \f[C]hledger\ api\ \-\-\ [OPTIONS]\f[] .SH DESCRIPTION .PP hledger is a cross\-platform program 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\-api is a simple web API server, intended to support client\-side web apps operating on hledger data. It comes with a series of simple client\-side app examples, which drive its evolution. .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[], or \f[C]$LEDGER_FILE\f[], or \f[C]$HOME/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). For more about this see hledger(1), hledger_journal(5) etc. .PP The server listens on IP address 127.0.0.1, accessible only to local requests, by default. You can change this with \f[C]\-\-host\f[], eg \f[C]\-\-host\ 0.0.0.0\f[] to listen on all addresses. Note there is no other access control, so you will need to hide hledger\-api behind an authenticating proxy if you want to restrict access. You can change the TCP port (default: 8001) with \f[C]\-p\ PORT\f[]. .PP If invoked as \f[C]hledger\-api\ \-\-swagger\f[], instead of starting a server the API docs will be printed in Swagger 2.0 format. .SH OPTIONS .PP Note: if invoking hledger\-api as a hledger subcommand, write \f[C]\-\-\f[] before options as shown above. .TP .B \f[C]\-f\ \-\-file=FILE\f[] use a different input file. For stdin, use \- (default: \f[C]$LEDGER_FILE\f[] or \f[C]$HOME/.hledger.journal\f[]) .RS .RE .TP .B \f[C]\-d\ \-\-static\-dir=DIR\f[] serve files from a different directory (default: \f[C]\&.\f[]) .RS .RE .TP .B \f[C]\-\-host=IPADDR\f[] listen on this IP address (default: 127.0.0.1) .RS .RE .TP .B \f[C]\-p\ \-\-port=PORT\f[] listen on this TCP port (default: 8001) .RS .RE .TP .B \f[C]\-\-swagger\f[] print API docs in Swagger 2.0 format, and exit .RS .RE .TP .B \f[C]\-\-version\f[] show version .RS .RE .TP .B \f[C]\-h\f[] show usage .RS .RE .TP .B \f[C]\-\-help\f[] show manual as plain text .RS .RE .TP .B \f[C]\-\-man\f[] show manual with man .RS .RE .TP .B \f[C]\-\-info\f[] show manual with info .RS .RE .SH ENVIRONMENT .PP \f[B]LEDGER_FILE\f[] The journal file path when not specified with \f[C]\-f\f[]. Default: \f[C]~/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). .SH FILES .PP Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]\-f\f[], or \f[C]$LEDGER_FILE\f[], or \f[C]$HOME/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). .SH BUGS .PP The need to precede options with \f[C]\-\-\f[] when invoked from hledger is awkward. .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-2016 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.2/doc/other/hledger-api.1.info0000644000000000000000000000401313067574766016262 0ustar0000000000000000This is hledger-api.1.info, produced by makeinfo version 6.0 from stdin.  File: hledger-api.1.info, Node: Top, Next: OPTIONS, Up: (dir) hledger-api(1) hledger-api 1.2 ****************************** hledger-api is a simple web API server, intended to support client-side web apps operating on hledger data. It comes with a series of simple client-side app examples, which drive its evolution. 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. The server listens on IP address 127.0.0.1, accessible only to local requests, by default. You can change this with '--host', eg '--host 0.0.0.0' to listen on all addresses. Note there is no other access control, so you will need to hide hledger-api behind an authenticating proxy if you want to restrict access. You can change the TCP port (default: 8001) with '-p PORT'. If invoked as 'hledger-api --swagger', instead of starting a server the API docs will be printed in Swagger 2.0 format. * Menu: * OPTIONS::  File: hledger-api.1.info, Node: OPTIONS, Prev: Top, Up: Top 1 OPTIONS ********* Note: if invoking hledger-api as a hledger subcommand, write '--' before options as shown above. '-f --file=FILE' use a different input file. For stdin, use - (default: '$LEDGER_FILE' or '$HOME/.hledger.journal') '-d --static-dir=DIR' serve files from a different directory (default: '.') '--host=IPADDR' listen on this IP address (default: 127.0.0.1) '-p --port=PORT' listen on this TCP port (default: 8001) '--swagger' print API docs in Swagger 2.0 format, and exit '--version' show version '-h' show usage '--help' show manual as plain text '--man' show manual with man '--info' show manual with info  Tag Table: Node: Top74 Node: OPTIONS1220 Ref: #options1307  End Tag Table hledger-1.2/doc/other/hledger-api.1.txt0000644000000000000000000000700713067574771016150 0ustar0000000000000000 hledger-api(1) hledger User Manuals hledger-api(1) NAME hledger-api - web API server for the hledger accounting tool SYNOPSIS hledger-api [OPTIONS] hledger api -- [OPTIONS] DESCRIPTION hledger is a cross-platform program 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-api is a simple web API server, intended to support client-side web apps operating on hledger data. It comes with a series of simple client-side app examples, which drive its evolution. 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. The server listens on IP address 127.0.0.1, accessible only to local requests, by default. You can change this with --host, eg --host 0.0.0.0 to listen on all addresses. Note there is no other access control, so you will need to hide hledger-api behind an authen- ticating proxy if you want to restrict access. You can change the TCP port (default: 8001) with -p PORT. If invoked as hledger-api --swagger, instead of starting a server the API docs will be printed in Swagger 2.0 format. OPTIONS Note: if invoking hledger-api as a hledger subcommand, write -- before options as shown above. -f --file=FILE use a different input file. For stdin, use - (default: $LEDGER_FILE or $HOME/.hledger.journal) -d --static-dir=DIR serve files from a different directory (default: .) --host=IPADDR listen on this IP address (default: 127.0.0.1) -p --port=PORT listen on this TCP port (default: 8001) --swagger print API docs in Swagger 2.0 format, and exit --version show version -h show usage --help show manual as plain text --man show manual with man --info show manual with info ENVIRONMENT LEDGER_FILE The journal file path when not specified with -f. Default: ~/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.jour- nal). 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. 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-2016 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-api 1.2 March 2017 hledger-api(1) hledger-1.2/doc/other/hledger-ui.10000644000000000000000000003440713067574771015202 0ustar0000000000000000 .TH "hledger\-ui" "1" "March 2017" "hledger\-ui 1.2" "hledger User Manuals" .SH NAME .PP hledger\-ui \- curses\-style interface for the hledger accounting tool .SH SYNOPSIS .PP \f[C]hledger\-ui\ [OPTIONS]\ [QUERYARGS]\f[] .PD 0 .P .PD \f[C]hledger\ ui\ \-\-\ [OPTIONS]\ [QUERYARGS]\f[] .SH DESCRIPTION .PP hledger is a cross\-platform program 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 curses\-style 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[], or \f[C]$LEDGER_FILE\f[], or \f[C]$HOME/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). For more about this see hledger(1), hledger_journal(5) etc. .SH OPTIONS .PP Note: if invoking hledger\-ui as a hledger subcommand, write \f[C]\-\-\f[] before options as shown above. .PP Any QUERYARGS are interpreted as a hledger search query which filters the data. .TP .B \f[C]\-\-watch\f[] watch for data and date changes and reload automatically .RS .RE .TP .B \f[C]\-\-theme=default|terminal|greenterm\f[] use this custom display theme .RS .RE .TP .B \f[C]\-\-register=ACCTREGEX\f[] start in the (first) matched account\[aq]s register screen .RS .RE .TP .B \f[C]\-\-change\f[] show period balances (changes) at startup instead of historical balances .RS .RE .TP .B \f[C]\-\-flat\f[] show full account names, unindented .RS .RE .PP hledger input options: .TP .B \f[C]\-f\ FILE\ \-\-file=FILE\f[] use a different input file. For stdin, use \- (default: \f[C]$LEDGER_FILE\f[] or \f[C]$HOME/.hledger.journal\f[]) .RS .RE .TP .B \f[C]\-\-rules\-file=RULESFILE\f[] Conversion rules file to use when reading CSV (default: FILE.rules) .RS .RE .TP .B \f[C]\-\-alias=OLD=NEW\f[] rename accounts named OLD to NEW .RS .RE .TP .B \f[C]\-\-anon\f[] anonymize accounts and payees .RS .RE .TP .B \f[C]\-\-pivot\ TAGNAME\f[] use some other field/tag for account names .RS .RE .TP .B \f[C]\-I\ \-\-ignore\-assertions\f[] ignore any failing balance assertions .RS .RE .PP hledger reporting options: .TP .B \f[C]\-b\ \-\-begin=DATE\f[] include postings/txns on or after this date .RS .RE .TP .B \f[C]\-e\ \-\-end=DATE\f[] include postings/txns before this date .RS .RE .TP .B \f[C]\-D\ \-\-daily\f[] multiperiod/multicolumn report by day .RS .RE .TP .B \f[C]\-W\ \-\-weekly\f[] multiperiod/multicolumn report by week .RS .RE .TP .B \f[C]\-M\ \-\-monthly\f[] multiperiod/multicolumn report by month .RS .RE .TP .B \f[C]\-Q\ \-\-quarterly\f[] multiperiod/multicolumn report by quarter .RS .RE .TP .B \f[C]\-Y\ \-\-yearly\f[] multiperiod/multicolumn report by year .RS .RE .TP .B \f[C]\-p\ \-\-period=PERIODEXP\f[] set start date, end date, and/or reporting interval all at once (overrides the flags above) .RS .RE .TP .B \f[C]\-\-date2\f[] show, and match with \-b/\-e/\-p/date:, secondary dates instead .RS .RE .TP .B \f[C]\-C\ \-\-cleared\f[] include only cleared postings/txns .RS .RE .TP .B \f[C]\-\-pending\f[] include only pending postings/txns .RS .RE .TP .B \f[C]\-U\ \-\-uncleared\f[] include only uncleared (and pending) postings/txns .RS .RE .TP .B \f[C]\-R\ \-\-real\f[] include only non\-virtual postings .RS .RE .TP .B \f[C]\-\-depth=N\f[] hide accounts/postings deeper than N .RS .RE .TP .B \f[C]\-E\ \-\-empty\f[] show items with zero amount, normally hidden .RS .RE .TP .B \f[C]\-B\ \-\-cost\f[] convert amounts to their cost at transaction time (using the transaction price, if any) .RS .RE .TP .B \f[C]\-V\ \-\-value\f[] convert amounts to their market value on the report end date (using the most recent applicable market price, if any) .RS .RE .PP hledger help options: .TP .B \f[C]\-h\f[] show general usage (or after COMMAND, command usage) .RS .RE .TP .B \f[C]\-\-help\f[] show this program\[aq]s manual as plain text (or after an add\-on COMMAND, the add\-on\[aq]s manual) .RS .RE .TP .B \f[C]\-\-man\f[] show this program\[aq]s manual with man .RS .RE .TP .B \f[C]\-\-info\f[] show this program\[aq]s manual with info .RS .RE .TP .B \f[C]\-\-version\f[] show version .RS .RE .TP .B \f[C]\-\-debug[=N]\f[] show debug output (levels 1\-9, default: 1) .RS .RE .SH KEYS .PP \f[C]?\f[] 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[] again (or \f[C]ESCAPE\f[], or \f[C]LEFT\f[]) to close it. The following keys work on most screens: .PP The cursor keys navigate: \f[C]right\f[] (or \f[C]enter\f[]) goes deeper, \f[C]left\f[] returns to the previous screen, \f[C]up\f[]/\f[C]down\f[]/\f[C]page\ up\f[]/\f[C]page\ down\f[]/\f[C]home\f[]/\f[C]end\f[] move up and down through lists. Vi\-style \f[C]h\f[]/\f[C]j\f[]/\f[C]k\f[]/\f[C]l\f[] movement keys are also supported. A tip: movement speed is limited by your keyboard repeat rate, to move faster you may want to adjust it. (If you\[aq]re on a mac, the Karabiner app is one way to do that.) .PP With shift pressed, the cursor keys adjust the report period, limiting the transactions to be shown (by default, all are shown). \f[C]shift\-down/up\f[] steps downward and upward through these standard report period durations: year, quarter, month, week, day. Then, \f[C]shift\-left/right\f[] moves to the previous/next period. \f[C]t\f[] sets the report period to today. With the \f[C]\-\-watch\f[] 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 \f[C]/\f[] and a \f[C]date:\f[] query. .PP \f[C]/\f[] 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[] to set it, or \f[C]ESCAPE\f[]to cancel. There are also keys for quickly adjusting some common filters like account depth and cleared/uncleared (see below). \f[C]BACKSPACE\f[] or \f[C]DELETE\f[] removes all filters, showing all transactions. .PP \f[C]ESCAPE\f[] removes all filters and jumps back to the top screen. Or, it cancels a minibuffer edit or help dialog in progress. .PP \f[C]g\f[] 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[] toggles balance assertion checking. Disabling balance assertions temporarily can be useful for troubleshooting. .PP \f[C]a\f[] runs command\-line hledger\[aq]s add command, and reloads the updated file. This allows some basic data entry. .PP \f[C]E\f[] runs $HLEDGER_UI_EDITOR, or $EDITOR, or a default (\f[C]emacsclient\ \-a\ ""\ \-nw\f[]) 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]q\f[] 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 normally indented to show the hierarchy (tree mode). To see less detail, set a depth limit by pressing a number key, \f[C]1\f[] to \f[C]9\f[]. \f[C]0\f[] shows even less detail, collapsing all accounts to a single total. \f[C]\-\f[] and \f[C]+\f[] (or \f[C]=\f[]) decrease and increase the depth limit. To remove the depth limit, set it higher than the maximum account depth, or press \f[C]ESCAPE\f[]. .PP \f[C]F\f[] toggles flat mode, in which accounts are shown as a flat list, with their full names. In this mode, account balances exclude subaccounts, except for accounts at the depth limit (as with hledger\[aq]s balance command). .PP \f[C]H\f[] 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]C\f[] toggles cleared mode, in which uncleared transactions and postings are not shown. \f[C]U\f[] toggles uncleared mode, in which only uncleared transactions/postings are shown. .PP \f[C]R\f[] toggles real mode, in which virtual postings are ignored. .PP \f[C]Z\f[] 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[] or \f[C]enter\f[] 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[]. 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 If the accounts screen was in tree mode, the register screen will include transactions from both the current account and its subaccounts. If the accounts screen was in flat mode, and a non\-depth\-clipped account was selected, the register screen will exclude transactions from subaccounts. In other words, the register always shows the transactions responsible for the period balance shown on the accounts screen. As on the accounts screen, this can be toggled with \f[C]F\f[]. .PP \f[C]C\f[] toggles cleared mode, in which uncleared transactions and postings are not shown. \f[C]U\f[] toggles uncleared mode, in which only uncleared transactions/postings are shown. .PP \f[C]R\f[] toggles real mode, in which virtual postings are ignored. .PP \f[C]Z\f[] 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[] (or \f[C]enter\f[]) 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[] and \f[C]down\f[] 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[] The screen width to use. Default: the full terminal width. .PP \f[B]LEDGER_FILE\f[] The journal file path when not specified with \f[C]\-f\f[]. Default: \f[C]~/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). .SH FILES .PP Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]\-f\f[], or \f[C]$LEDGER_FILE\f[], or \f[C]$HOME/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). .SH BUGS .PP The need to precede options with \f[C]\-\-\f[] when invoked from hledger is awkward. .PP \f[C]\-f\-\f[] doesn\[aq]t work (hledger\-ui can\[aq]t read from stdin). .PP \f[C]\-V\f[] affects only the accounts screen. .PP When you press \f[C]g\f[], 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[] 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. .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-2016 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.2/doc/other/hledger-ui.1.info0000644000000000000000000003032713067574767016136 0ustar0000000000000000This is hledger-ui.1.info, produced by makeinfo version 6.0 from stdin.  File: hledger-ui.1.info, Node: Top, Next: OPTIONS, Up: (dir) hledger-ui(1) hledger-ui 1.2 **************************** hledger-ui is hledger's curses-style 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. * Menu: * OPTIONS:: * KEYS:: * SCREENS::  File: hledger-ui.1.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 '--flat' show full account names, unindented 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) '--alias=OLD=NEW' rename accounts named OLD to NEW '--anon' anonymize accounts and payees '--pivot TAGNAME' use some other field/tag for account names '-I --ignore-assertions' ignore any failing balance assertions 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 (overrides the flags above) '--date2' show, and match with -b/-e/-p/date:, secondary dates instead '-C --cleared' include only cleared postings/txns '--pending' include only pending postings/txns '-U --uncleared' include only uncleared (and pending) postings/txns '-R --real' include only non-virtual postings '--depth=N' hide accounts/postings deeper than N '-E --empty' show items with zero amount, normally hidden '-B --cost' convert amounts to their cost at transaction time (using the transaction price, if any) '-V --value' convert amounts to their market value on the report end date (using the most recent applicable market price, if any) hledger help options: '-h' show general usage (or after COMMAND, command usage) '--help' show this program's manual as plain text (or after an add-on COMMAND, the add-on's manual) '--man' show this program's manual with man '--info' show this program's manual with info '--version' show version '--debug[=N]' show debug output (levels 1-9, default: 1)  File: hledger-ui.1.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') 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. Vi-style 'h'/'j'/'k'/'l' movement keys are also supported. A tip: movement speed is limited by your keyboard repeat rate, to move faster you may want to adjust it. (If you're on a mac, the Karabiner app is one way to do that.) With shift pressed, the cursor keys adjust the report period, limiting the transactions to be shown (by default, all are shown). 'shift-down/up' steps downward and upward through these standard report period durations: year, quarter, month, week, day. Then, 'shift-left/right' moves to the previous/next period. 't' sets the report period to today. With the '--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 cleared/uncleared (see below). 'BACKSPACE' or 'DELETE' removes all filters, showing all transactions. 'ESCAPE' removes all filters and jumps back to the top screen. Or, it cancels a minibuffer edit or help dialog in progress. '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. '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. 'q' quits the application. Additional screen-specific keys are described below.  File: hledger-ui.1.info, Node: SCREENS, Prev: KEYS, Up: Top 3 SCREENS ********* * Menu: * Accounts screen:: * Register screen:: * Transaction screen:: * Error screen::  File: hledger-ui.1.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 normally indented to show the hierarchy (tree mode). To see less detail, set a depth limit by pressing a number key, '1' to '9'. '0' shows even less detail, collapsing all accounts to a single total. '-' and '+' (or '=') decrease and increase the depth limit. To remove the depth limit, set it higher than the maximum account depth, or press 'ESCAPE'. 'F' toggles flat mode, in which accounts are shown as a flat list, with their full names. In this mode, account balances exclude subaccounts, except for accounts at the depth limit (as with hledger's balance command). '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. 'C' toggles cleared mode, in which uncleared transactions and postings are not shown. 'U' toggles uncleared mode, in which only uncleared transactions/postings are shown. '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.1.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. If the accounts screen was in tree mode, the register screen will include transactions from both the current account and its subaccounts. If the accounts screen was in flat mode, and a non-depth-clipped account was selected, the register screen will exclude transactions from subaccounts. In other words, the register always shows the transactions responsible for the period balance shown on the accounts screen. As on the accounts screen, this can be toggled with 'F'. 'C' toggles cleared mode, in which uncleared transactions and postings are not shown. 'U' toggles uncleared mode, in which only uncleared transactions/postings are shown. '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.1.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.1.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.)  Tag Table: Node: Top73 Node: OPTIONS825 Ref: #options924 Node: KEYS3650 Ref: #keys3747 Node: SCREENS6335 Ref: #screens6422 Node: Accounts screen6512 Ref: #accounts-screen6642 Node: Register screen8691 Ref: #register-screen8848 Node: Transaction screen10737 Ref: #transaction-screen10897 Node: Error screen11767 Ref: #error-screen11891  End Tag Table hledger-1.2/doc/other/hledger-ui.1.txt0000644000000000000000000003543013067574771016015 0ustar0000000000000000 hledger-ui(1) hledger User Manuals hledger-ui(1) NAME hledger-ui - curses-style interface for the hledger accounting tool SYNOPSIS hledger-ui [OPTIONS] [QUERYARGS] hledger ui -- [OPTIONS] [QUERYARGS] DESCRIPTION hledger is a cross-platform program 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 curses-style interface, providing an efficient full-window text UI for viewing accounts and transactions, and some limited data entry capability. It is easier than hledger's com- mand-line interface, and sometimes quicker and more convenient than the web interface. Like hledger, it reads 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 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 --flat show full account names, unindented 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) --alias=OLD=NEW rename accounts named OLD to NEW --anon anonymize accounts and payees --pivot TAGNAME use some other field/tag for account names -I --ignore-assertions ignore any failing balance assertions 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 (overrides the flags above) --date2 show, and match with -b/-e/-p/date:, secondary dates instead -C --cleared include only cleared postings/txns --pending include only pending postings/txns -U --uncleared include only uncleared (and pending) postings/txns -R --real include only non-virtual postings --depth=N hide accounts/postings deeper than N -E --empty show items with zero amount, normally hidden -B --cost convert amounts to their cost at transaction time (using the transaction price, if any) -V --value convert amounts to their market value on the report end date (using the most recent applicable market price, if any) hledger help options: -h show general usage (or after COMMAND, command usage) --help show this program's manual as plain text (or after an add-on COMMAND, the add-on's manual) --man show this program's manual with man --info show this program's manual with info --version show version --debug[=N] show debug output (levels 1-9, default: 1) 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) 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. Vi-style h/j/k/l movement keys are also supported. A tip: movement speed is limited by your keyboard repeat rate, to move faster you may want to adjust it. (If you're on a mac, the Karabiner app is one way to do that.) With shift pressed, the cursor keys adjust the report period, limiting the transactions to be shown (by default, all are shown). shift-down/up steps downward and upward through these standard report period durations: year, quarter, month, week, day. Then, shift-left/right moves to the previous/next period. t sets the report period to today. With the --watch option, when viewing a "current" period (the current day, week, month, quarter, or year), the period will move automatically to track the current date. To set a non-stan- dard period, you can use / and a date: query. / 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 cleared/uncleared (see below). BACKSPACE or DELETE removes all filters, showing all transactions. ESCAPE removes all filters and jumps back to the top screen. Or, it cancels a minibuffer edit or help dialog in progress. 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. E runs $HLEDGER_UI_EDITOR, or $EDITOR, or a default (emac- sclient -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. 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 normally indented to show the hierarchy (tree mode). To see less detail, set a depth limit by pressing a number key, 1 to 9. 0 shows even less detail, collapsing all accounts to a single total. - and + (or =) decrease and increase the depth limit. To remove the depth limit, set it higher than the maximum account depth, or press ESCAPE. F toggles flat mode, in which accounts are shown as a flat list, with their full names. In this mode, account balances exclude subaccounts, except for accounts at the depth limit (as with hledger's balance com- mand). 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 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. C toggles cleared mode, in which uncleared transactions and postings are not shown. U toggles uncleared mode, in which only uncleared transactions/postings are shown. 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. If the accounts screen was in tree mode, the register screen will include transactions from both the current account and its subaccounts. If the accounts screen was in flat mode, and a non-depth-clipped account was selected, the register screen will exclude transactions from subaccounts. In other words, the register always shows the trans- actions responsible for the period balance shown on the accounts screen. As on the accounts screen, this can be toggled with F. C toggles cleared mode, in which uncleared transactions and postings are not shown. U toggles uncleared mode, in which only uncleared transactions/postings are shown. 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, 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 trans- actions 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). 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. 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-2016 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.2 March 2017 hledger-ui(1) hledger-1.2/doc/other/hledger-web.10000644000000000000000000002016213067574771015333 0ustar0000000000000000 .TH "hledger\-web" "1" "March 2017" "hledger\-web 1.2" "hledger User Manuals" .SH NAME .PP hledger\-web \- web interface for the hledger accounting tool .SH SYNOPSIS .PP \f[C]hledger\-web\ [OPTIONS]\f[] .PD 0 .P .PD \f[C]hledger\ web\ \-\-\ [OPTIONS]\f[] .SH DESCRIPTION .PP hledger is a cross\-platform program 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[], or \f[C]$LEDGER_FILE\f[], or \f[C]$HOME/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). For more about this see hledger(1), hledger_journal(5) etc. .PP 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 \f[C]\-\-serve\f[], it just runs the web app without exiting, and logs requests to the console. .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[] to change this, eg \f[C]\-\-host\ 0.0.0.0\f[] to listen on all configured addresses. .PP Similarly, use \f[C]\-\-port\f[] to set a TCP port other than 5000, eg if you are running multiple hledger\-web instances. .PP You can use \f[C]\-\-base\-url\f[] 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[] using the server\[aq]s configured host address and TCP port (or \f[C]http://HOST\f[] if PORT is 80). .PP With \f[C]\-\-file\-url\f[] you can set a different base url for static files, eg for better caching or cookie\-less serving on high performance websites. .PP Note there is no built\-in access control (aside from listening on 127.0.0.1 by default). So you will need to hide hledger\-web behind an authenticating proxy (such as apache or nginx) if you want to restrict who can see and add entries to your journal. .PP Command\-line options and arguments may be used to set an initial filter on the data. This is not shown in the web UI, but it will be applied in addition to any search query entered there. .PP With journal and timeclock files (but not CSV files, currently) the web app detects changes made by other means and will show the new data on the next request. If a change makes the file unparseable, hledger\-web will show an error until the file has been fixed. .SH OPTIONS .PP Note: if invoking hledger\-web as a hledger subcommand, write \f[C]\-\-\f[] before options as shown above. .TP .B \f[C]\-\-serve\f[] serve and log requests, don\[aq]t browse or auto\-exit .RS .RE .TP .B \f[C]\-\-host=IPADDR\f[] listen on this IP address (default: 127.0.0.1) .RS .RE .TP .B \f[C]\-\-port=PORT\f[] listen on this TCP port (default: 5000) .RS .RE .TP .B \f[C]\-\-base\-url=URL\f[] set the base url (default: http://IPADDR:PORT). You would change this when sharing over the network, or integrating within a larger website. .RS .RE .TP .B \f[C]\-\-file\-url=URL\f[] 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. .RS .RE .PP hledger input options: .TP .B \f[C]\-f\ FILE\ \-\-file=FILE\f[] use a different input file. For stdin, use \- (default: \f[C]$LEDGER_FILE\f[] or \f[C]$HOME/.hledger.journal\f[]) .RS .RE .TP .B \f[C]\-\-rules\-file=RULESFILE\f[] Conversion rules file to use when reading CSV (default: FILE.rules) .RS .RE .TP .B \f[C]\-\-alias=OLD=NEW\f[] rename accounts named OLD to NEW .RS .RE .TP .B \f[C]\-\-anon\f[] anonymize accounts and payees .RS .RE .TP .B \f[C]\-\-pivot\ TAGNAME\f[] use some other field/tag for account names .RS .RE .TP .B \f[C]\-I\ \-\-ignore\-assertions\f[] ignore any failing balance assertions .RS .RE .PP hledger reporting options: .TP .B \f[C]\-b\ \-\-begin=DATE\f[] include postings/txns on or after this date .RS .RE .TP .B \f[C]\-e\ \-\-end=DATE\f[] include postings/txns before this date .RS .RE .TP .B \f[C]\-D\ \-\-daily\f[] multiperiod/multicolumn report by day .RS .RE .TP .B \f[C]\-W\ \-\-weekly\f[] multiperiod/multicolumn report by week .RS .RE .TP .B \f[C]\-M\ \-\-monthly\f[] multiperiod/multicolumn report by month .RS .RE .TP .B \f[C]\-Q\ \-\-quarterly\f[] multiperiod/multicolumn report by quarter .RS .RE .TP .B \f[C]\-Y\ \-\-yearly\f[] multiperiod/multicolumn report by year .RS .RE .TP .B \f[C]\-p\ \-\-period=PERIODEXP\f[] set start date, end date, and/or reporting interval all at once (overrides the flags above) .RS .RE .TP .B \f[C]\-\-date2\f[] show, and match with \-b/\-e/\-p/date:, secondary dates instead .RS .RE .TP .B \f[C]\-C\ \-\-cleared\f[] include only cleared postings/txns .RS .RE .TP .B \f[C]\-\-pending\f[] include only pending postings/txns .RS .RE .TP .B \f[C]\-U\ \-\-uncleared\f[] include only uncleared (and pending) postings/txns .RS .RE .TP .B \f[C]\-R\ \-\-real\f[] include only non\-virtual postings .RS .RE .TP .B \f[C]\-\-depth=N\f[] hide accounts/postings deeper than N .RS .RE .TP .B \f[C]\-E\ \-\-empty\f[] show items with zero amount, normally hidden .RS .RE .TP .B \f[C]\-B\ \-\-cost\f[] convert amounts to their cost at transaction time (using the transaction price, if any) .RS .RE .TP .B \f[C]\-V\ \-\-value\f[] convert amounts to their market value on the report end date (using the most recent applicable market price, if any) .RS .RE .PP hledger help options: .TP .B \f[C]\-h\f[] show general usage (or after COMMAND, command usage) .RS .RE .TP .B \f[C]\-\-help\f[] show this program\[aq]s manual as plain text (or after an add\-on COMMAND, the add\-on\[aq]s manual) .RS .RE .TP .B \f[C]\-\-man\f[] show this program\[aq]s manual with man .RS .RE .TP .B \f[C]\-\-info\f[] show this program\[aq]s manual with info .RS .RE .TP .B \f[C]\-\-version\f[] show version .RS .RE .TP .B \f[C]\-\-debug[=N]\f[] show debug output (levels 1\-9, default: 1) .RS .RE .SH ENVIRONMENT .PP \f[B]LEDGER_FILE\f[] The journal file path when not specified with \f[C]\-f\f[]. Default: \f[C]~/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). .SH FILES .PP Reads data from one or more files in hledger journal, timeclock, timedot, or CSV format specified with \f[C]\-f\f[], or \f[C]$LEDGER_FILE\f[], or \f[C]$HOME/.hledger.journal\f[] (on windows, perhaps \f[C]C:/Users/USER/.hledger.journal\f[]). .SH BUGS .PP The need to precede options with \f[C]\-\-\f[] when invoked from hledger is awkward. .PP \f[C]\-f\-\f[] 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-2016 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.2/doc/other/hledger-web.1.info0000644000000000000000000001407013067574766016272 0ustar0000000000000000This is hledger-web.1.info, produced by makeinfo version 6.0 from stdin.  File: hledger-web.1.info, Node: Top, Next: OPTIONS, Up: (dir) hledger-web(1) hledger-web 1.2 ****************************** 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. 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. 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. 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. Note there is no built-in access control (aside from listening on 127.0.0.1 by default). So you will need to hide hledger-web behind an authenticating proxy (such as apache or nginx) if you want to restrict who can see and add entries to your journal. Command-line options and arguments may be used to set an initial filter on the data. This is not shown in the web UI, but it will be applied in addition to any search query entered there. With journal and timeclock files (but not CSV files, currently) the web app detects changes made by other means and will show the new data on the next request. If a change makes the file unparseable, hledger-web will show an error until the file has been fixed. * Menu: * OPTIONS::  File: hledger-web.1.info, Node: OPTIONS, Prev: Top, Up: Top 1 OPTIONS ********* Note: if invoking hledger-web as a hledger subcommand, write '--' before options as shown above. '--serve' serve and log requests, don't browse or auto-exit '--host=IPADDR' listen on this IP address (default: 127.0.0.1) '--port=PORT' listen on this TCP port (default: 5000) '--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. 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) '--alias=OLD=NEW' rename accounts named OLD to NEW '--anon' anonymize accounts and payees '--pivot TAGNAME' use some other field/tag for account names '-I --ignore-assertions' ignore any failing balance assertions 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 (overrides the flags above) '--date2' show, and match with -b/-e/-p/date:, secondary dates instead '-C --cleared' include only cleared postings/txns '--pending' include only pending postings/txns '-U --uncleared' include only uncleared (and pending) postings/txns '-R --real' include only non-virtual postings '--depth=N' hide accounts/postings deeper than N '-E --empty' show items with zero amount, normally hidden '-B --cost' convert amounts to their cost at transaction time (using the transaction price, if any) '-V --value' convert amounts to their market value on the report end date (using the most recent applicable market price, if any) hledger help options: '-h' show general usage (or after COMMAND, command usage) '--help' show this program's manual as plain text (or after an add-on COMMAND, the add-on's manual) '--man' show this program's manual with man '--info' show this program's manual with info '--version' show version '--debug[=N]' show debug output (levels 1-9, default: 1)  Tag Table: Node: Top74 Node: OPTIONS3156 Ref: #options3243  End Tag Table hledger-1.2/doc/other/hledger-web.1.txt0000644000000000000000000002064013067574771016152 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 cross-platform program 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 (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. 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. 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. 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. Note there is no built-in access control (aside from listening on 127.0.0.1 by default). So you will need to hide hledger-web behind an authenticating proxy (such as apache or nginx) if you want to restrict who can see and add entries to your journal. Command-line options and arguments may be used to set an initial filter on the data. This is not shown in the web UI, but it will be applied in addition to any search query entered there. With journal and timeclock files (but not CSV files, currently) the web app detects changes made by other means and will show the new data on the next request. If a change makes the file unparseable, hledger-web will show an error until the file has been fixed. OPTIONS Note: if invoking hledger-web as a hledger subcommand, write -- before options as shown above. --serve serve and log requests, don't browse or auto-exit --host=IPADDR listen on this IP address (default: 127.0.0.1) --port=PORT listen on this TCP port (default: 5000) --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. 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) --alias=OLD=NEW rename accounts named OLD to NEW --anon anonymize accounts and payees --pivot TAGNAME use some other field/tag for account names -I --ignore-assertions ignore any failing balance assertions 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 (overrides the flags above) --date2 show, and match with -b/-e/-p/date:, secondary dates instead -C --cleared include only cleared postings/txns --pending include only pending postings/txns -U --uncleared include only uncleared (and pending) postings/txns -R --real include only non-virtual postings --depth=N hide accounts/postings deeper than N -E --empty show items with zero amount, normally hidden -B --cost convert amounts to their cost at transaction time (using the transaction price, if any) -V --value convert amounts to their market value on the report end date (using the most recent applicable market price, if any) hledger help options: -h show general usage (or after COMMAND, command usage) --help show this program's manual as plain text (or after an add-on COMMAND, the add-on's manual) --man show this program's manual with man --info show this program's manual with info --version show version --debug[=N] show debug output (levels 1-9, default: 1) ENVIRONMENT LEDGER_FILE The journal file path when not specified with -f. Default: ~/.hledger.journal (on windows, perhaps C:/Users/USER/.hledger.jour- nal). 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-2016 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.2 March 2017 hledger-web(1) hledger-1.2/doc/other/hledger_csv.50000644000000000000000000001407413067574770015443 0ustar0000000000000000 .TH "hledger_csv" "5" "March 2017" "hledger 1.2" "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, converting each CSV record into a journal entry (transaction), if you provide some conversion hints in a "rules file". This file should be named like the CSV file with an additional \f[C]\&.rules\f[] suffix (eg: \f[C]mybank.csv.rules\f[]); or, you can specify the file with \f[C]\-\-rules\-file\ PATH\f[]. hledger will create it if necessary, with some default rules which you\[aq]ll need to adjust. At minimum, the rules file must specify the \f[C]date\f[] and \f[C]amount\f[] fields. For an example, see How to read CSV files. .PP To learn about \f[I]exporting\f[] CSV, see CSV output. .SH CSV RULES .PP The following six kinds of rule can appear in the rules file, in any order. Blank lines and lines beginning with \f[C]#\f[] or \f[C];\f[] are ignored. .SS skip .PP \f[C]skip\f[]\f[I]\f[C]N\f[]\f[] .PP Skip this number of CSV records at the beginning. You\[aq]ll need this whenever your CSV data contains header lines. Eg: .IP .nf \f[C] #\ ignore\ the\ first\ CSV\ line skip\ 1 \f[] .fi .SS date\-format .PP \f[C]date\-format\f[]\f[I]\f[C]DATEFMT\f[]\f[] .PP When your CSV date fields are not formatted like \f[C]YYYY/MM/DD\f[] (or \f[C]YYYY\-MM\-DD\f[] or \f[C]YYYY.MM.DD\f[]), you\[aq]ll need to specify the format. DATEFMT is a strptime\-like date parsing pattern, which must parse the date field values completely. Examples: .IP .nf \f[C] #\ for\ dates\ like\ "6/11/2013": date\-format\ %\-d/%\-m/%Y \f[] .fi .IP .nf \f[C] #\ for\ dates\ like\ "11/06/2013": date\-format\ %m/%d/%Y \f[] .fi .IP .nf \f[C] #\ for\ dates\ like\ "2013\-Nov\-06": date\-format\ %Y\-%h\-%d \f[] .fi .IP .nf \f[C] #\ for\ dates\ like\ "11/6/2013\ 11:32\ PM": date\-format\ %\-m/%\-d/%Y\ %l:%M\ %p \f[] .fi .SS field list .PP \f[C]fields\f[]\f[I]\f[C]FIELDNAME1\f[]\f[], \f[I]\f[C]FIELDNAME2\f[]\f[]... .PP This (a) names the CSV fields, in order (names may not contain whitespace; uninteresting names may be left blank), and (b) assigns them to journal entry fields if you use any of these standard field names: \f[C]date\f[], \f[C]date2\f[], \f[C]status\f[], \f[C]code\f[], \f[C]description\f[], \f[C]comment\f[], \f[C]account1\f[], \f[C]account2\f[], \f[C]amount\f[], \f[C]amount\-in\f[], \f[C]amount\-out\f[], \f[C]currency\f[]. Eg: .IP .nf \f[C] #\ use\ the\ 1st,\ 2nd\ and\ 4th\ CSV\ fields\ as\ the\ entry\[aq]s\ date,\ description\ and\ amount, #\ and\ give\ the\ 7th\ and\ 8th\ fields\ meaningful\ names\ for\ later\ reference: # #\ CSV\ field: #\ \ \ \ \ \ 1\ \ \ \ \ 2\ \ \ \ \ \ \ \ \ \ \ \ 3\ 4\ \ \ \ \ \ \ 5\ 6\ 7\ \ \ \ \ \ \ \ \ \ 8 #\ entry\ field: fields\ date,\ description,\ ,\ amount,\ ,\ ,\ somefield,\ anotherfield \f[] .fi .SS field assignment .PP \f[I]\f[C]ENTRYFIELDNAME\f[]\f[] \f[I]\f[C]FIELDVALUE\f[]\f[] .PP This sets a journal entry field (one of the standard names above) to the given text value, which can include CSV field values interpolated by name (\f[C]%CSVFIELDNAME\f[]) or 1\-based position (\f[C]%N\f[]). Eg: .IP .nf \f[C] #\ set\ the\ amount\ to\ the\ 4th\ CSV\ field\ with\ "USD\ "\ prepended amount\ USD\ %4 \f[] .fi .IP .nf \f[C] #\ combine\ three\ fields\ to\ make\ a\ comment\ (containing\ two\ tags) comment\ note:\ %somefield\ \-\ %anotherfield,\ date:\ %1 \f[] .fi .PP Field assignments can be used instead of or in addition to a field list. .SS conditional block .PP \f[C]if\f[] \f[I]\f[C]PATTERN\f[]\f[] .PD 0 .P .PD \ \ \ \ \f[I]\f[C]FIELDASSIGNMENTS\f[]\f[]... .PP \f[C]if\f[] .PD 0 .P .PD \f[I]\f[C]PATTERN\f[]\f[] .PD 0 .P .PD \f[I]\f[C]PATTERN\f[]\f[]... .PD 0 .P .PD \ \ \ \ \f[I]\f[C]FIELDASSIGNMENTS\f[]\f[]... .PP This applies one or more field assignments, only to those CSV records matched by one of the PATTERNs. The patterns are case\-insensitive regular expressions which match anywhere within the whole CSV record (it\[aq]s not yet possible to match within a specific field). When there are multiple patterns they can be written on separate lines, unindented. The field assignments are on separate lines indented by at least one space. Examples: .IP .nf \f[C] #\ if\ the\ CSV\ record\ contains\ "groceries",\ set\ account2\ to\ "expenses:groceries" if\ groceries \ account2\ expenses:groceries \f[] .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[] .fi .SS include .PP \f[C]include\f[]\f[I]\f[C]RULESFILE\f[]\f[] .PP Include another rules file at this point. \f[C]RULESFILE\f[] is either an absolute file path or a path relative to the current file\[aq]s directory. Eg: .IP .nf \f[C] #\ rules\ reused\ with\ several\ CSV\ files include\ common.rules \f[] .fi .SH TIPS .PP Each generated journal entry will have two postings, to \f[C]account1\f[] and \f[C]account2\f[] respectively. Currently it\[aq]s not possible to generate entries with more than two postings. .PP If the CSV has debit/credit amounts in separate fields, assign to the \f[C]amount\-in\f[] and \f[C]amount\-out\f[] pseudo fields instead of \f[C]amount\f[]. .PP If the CSV has the currency in a separate field, assign that to the \f[C]currency\f[] pseudo field which will be automatically prepended to the amount. (Or you can do the same thing with a field assignment.) .PP If an amount value is parenthesised, it will be de\-parenthesised and sign\-flipped automatically. .PP The generated journal entries will be sorted by date. The original order of same\-day entries will be preserved, usually. .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-2016 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.2/doc/other/hledger_csv.5.info0000644000000000000000000001401713067574765016376 0ustar0000000000000000This is hledger_csv.5.info, produced by makeinfo version 6.0 from stdin.  File: hledger_csv.5.info, Node: Top, Next: CSV RULES, Up: (dir) hledger_csv(5) hledger 1.2 ************************** hledger can read CSV files, converting each CSV record into a journal entry (transaction), if you provide some conversion hints in a "rules file". This file should be named like the CSV file with an additional '.rules' suffix (eg: 'mybank.csv.rules'); or, you can specify the file with '--rules-file PATH'. hledger will create it if necessary, with some default rules which you'll need to adjust. At minimum, the rules file must specify the 'date' and 'amount' fields. For an example, see How to read CSV files. To learn about _exporting_ CSV, see CSV output. * Menu: * CSV RULES:: * TIPS::  File: hledger_csv.5.info, Node: CSV RULES, Next: TIPS, Prev: Top, Up: Top 1 CSV RULES *********** The following six kinds of rule can appear in the rules file, in any order. Blank lines and lines beginning with '#' or ';' are ignored. * Menu: * skip:: * date-format:: * field list:: * field assignment:: * conditional block:: * include::  File: hledger_csv.5.info, Node: skip, Next: date-format, Up: CSV RULES 1.1 skip ======== 'skip'_'N'_ Skip this number of CSV records at the beginning. You'll need this whenever your CSV data contains header lines. Eg: # ignore the first CSV line skip 1  File: hledger_csv.5.info, Node: date-format, Next: field list, Prev: skip, Up: CSV RULES 1.2 date-format =============== 'date-format'_'DATEFMT'_ When your CSV date fields are not formatted like 'YYYY/MM/DD' (or 'YYYY-MM-DD' or 'YYYY.MM.DD'), you'll need to specify the format. DATEFMT is a strptime-like date parsing pattern, which must parse the date field values completely. Examples: # for dates like "6/11/2013": date-format %-d/%-m/%Y # for dates like "11/06/2013": date-format %m/%d/%Y # for dates like "2013-Nov-06": date-format %Y-%h-%d # for dates like "11/6/2013 11:32 PM": date-format %-m/%-d/%Y %l:%M %p  File: hledger_csv.5.info, Node: field list, Next: field assignment, Prev: date-format, Up: CSV RULES 1.3 field list ============== 'fields'_'FIELDNAME1'_, _'FIELDNAME2'_... This (a) names the CSV fields, in order (names may not contain whitespace; uninteresting names may be left blank), and (b) assigns them to journal entry fields if you use any of these standard field names: 'date', 'date2', 'status', 'code', 'description', 'comment', 'account1', 'account2', 'amount', 'amount-in', 'amount-out', 'currency'. Eg: # use the 1st, 2nd and 4th CSV fields as the entry's date, description and amount, # and give the 7th and 8th fields meaningful names for later reference: # # CSV field: # 1 2 3 4 5 6 7 8 # entry field: fields date, description, , amount, , , somefield, anotherfield  File: hledger_csv.5.info, Node: field assignment, Next: conditional block, Prev: field list, Up: CSV RULES 1.4 field assignment ==================== _'ENTRYFIELDNAME'_ _'FIELDVALUE'_ This sets a journal entry field (one of the standard names above) to the given text value, which can include CSV field values interpolated by name ('%CSVFIELDNAME') or 1-based position ('%N'). Eg: # set the amount to the 4th CSV field with "USD " prepended amount USD %4 # combine three fields to make a comment (containing two tags) comment note: %somefield - %anotherfield, date: %1 Field assignments can be used instead of or in addition to a field list.  File: hledger_csv.5.info, Node: conditional block, Next: include, Prev: field assignment, Up: CSV RULES 1.5 conditional block ===================== 'if' _'PATTERN'_ _'FIELDASSIGNMENTS'_... 'if' _'PATTERN'_ _'PATTERN'_... _'FIELDASSIGNMENTS'_... This applies one or more field assignments, only to those CSV records matched by one of the PATTERNs. The patterns are case-insensitive regular expressions which match anywhere within the whole CSV record (it's not yet possible to match within a specific field). When there are multiple patterns they can be written on separate lines, unindented. The field assignments are on separate lines indented by at least one space. 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.5.info, Node: include, Prev: conditional block, Up: CSV RULES 1.6 include =========== 'include'_'RULESFILE'_ Include another rules file at this point. 'RULESFILE' is either an absolute file path or a path relative to the current file's directory. Eg: # rules reused with several CSV files include common.rules  File: hledger_csv.5.info, Node: TIPS, Prev: CSV RULES, Up: Top 2 TIPS ****** Each generated journal entry will have two postings, to 'account1' and 'account2' respectively. Currently it's not possible to generate entries with more than two postings. If the CSV has debit/credit amounts in separate fields, assign to the 'amount-in' and 'amount-out' pseudo fields instead of 'amount'. If the CSV has the currency in a separate field, assign that to the 'currency' pseudo field which will be automatically prepended to the amount. (Or you can do the same thing with a field assignment.) If an amount value is parenthesised, it will be de-parenthesised and sign-flipped automatically. The generated journal entries will be sorted by date. The original order of same-day entries will be preserved, usually.  Tag Table: Node: Top74 Node: CSV RULES800 Ref: #csv-rules906 Node: skip1149 Ref: #skip1245 Node: date-format1417 Ref: #date-format1546 Node: field list2052 Ref: #field-list2191 Node: field assignment2886 Ref: #field-assignment3043 Node: conditional block3547 Ref: #conditional-block3703 Node: include4599 Ref: #include4710 Node: TIPS4941 Ref: #tips5025  End Tag Table hledger-1.2/doc/other/hledger_csv.5.txt0000644000000000000000000001400213067574770016250 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, converting each CSV record into a journal entry (transaction), if you provide some conversion hints in a "rules file". This file should be named like the CSV file with an additional .rules suffix (eg: mybank.csv.rules); or, you can specify the file with --rules-file PATH. hledger will create it if necessary, with some default rules which you'll need to adjust. At minimum, the rules file must specify the date and amount fields. For an example, see How to read CSV files. To learn about exporting CSV, see CSV output. CSV RULES The following six kinds of rule can appear in the rules file, in any order. Blank lines and lines beginning with # or ; are ignored. skip skipN Skip this number of CSV records at the beginning. You'll need this whenever your CSV data contains header lines. Eg: # ignore the first CSV line skip 1 date-format date-formatDATEFMT When your CSV date fields are not formatted like YYYY/MM/DD (or YYYY-MM-DD or YYYY.MM.DD), you'll need to specify the format. DATEFMT is a strptime-like date parsing pattern, which must parse the date field values completely. Examples: # for dates like "6/11/2013": date-format %-d/%-m/%Y # for dates like "11/06/2013": date-format %m/%d/%Y # for dates like "2013-Nov-06": date-format %Y-%h-%d # for dates like "11/6/2013 11:32 PM": date-format %-m/%-d/%Y %l:%M %p field list fieldsFIELDNAME1, FIELDNAME2... This (a) names the CSV fields, in order (names may not contain white- space; uninteresting names may be left blank), and (b) assigns them to journal entry fields if you use any of these standard field names: date, date2, status, code, description, comment, account1, account2, amount, amount-in, amount-out, currency. Eg: # use the 1st, 2nd and 4th CSV fields as the entry's date, description and amount, # and give the 7th and 8th fields meaningful names for later reference: # # CSV field: # 1 2 3 4 5 6 7 8 # entry field: fields date, description, , amount, , , somefield, anotherfield field assignment ENTRYFIELDNAME FIELDVALUE This sets a journal entry field (one of the standard names above) to the given text value, which can include CSV field values interpolated by name (%CSVFIELDNAME) or 1-based position (%N). Eg: # set the amount to the 4th CSV field with "USD " prepended amount USD %4 # combine three fields to make a comment (containing two tags) comment note: %somefield - %anotherfield, date: %1 Field assignments can be used instead of or in addition to a field list. conditional block if PATTERN FIELDASSIGNMENTS... if PATTERN PATTERN... FIELDASSIGNMENTS... This applies one or more field assignments, only to those CSV records matched by one of the PATTERNs. The patterns are case-insensitive reg- ular expressions which match anywhere within the whole CSV record (it's not yet possible to match within a specific field). When there are multiple patterns they can be written on separate lines, unindented. The field assignments are on separate lines indented by at least one space. 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 include includeRULESFILE Include another rules file at this point. RULESFILE is either an abso- lute file path or a path relative to the current file's directory. Eg: # rules reused with several CSV files include common.rules TIPS Each generated journal entry will have two postings, to account1 and account2 respectively. Currently it's not possible to generate entries with more than two postings. If the CSV has debit/credit amounts in separate fields, assign to the amount-in and amount-out pseudo fields instead of amount. If the CSV has the currency in a separate field, assign that to the currency pseudo field which will be automatically prepended to the amount. (Or you can do the same thing with a field assignment.) If an amount value is parenthesised, it will be de-parenthesised and sign-flipped automatically. The generated journal entries will be sorted by date. The original order of same-day entries will be preserved, usually. 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-2016 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.2 March 2017 hledger_csv(5) hledger-1.2/doc/other/hledger_journal.50000644000000000000000000007545013067574771016330 0ustar0000000000000000.\"t .TH "hledger_journal" "5" "March 2017" "hledger 1.2" "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[], 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 commands to create and update it. Many users, though, also edit the journal file directly with a text editor, perhaps assisted by the helper modes for emacs or vim. .PP Here\[aq]s an example: .IP .nf \f[C] ;\ A\ sample\ journal\ file.\ This\ is\ a\ comment. 2008/01/01\ income\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ ;\ <\-\ transaction\[aq]s\ first\ line\ starts\ in\ column\ 0,\ contains\ date\ and\ description \ \ \ \ assets:bank:checking\ \ $1\ \ \ \ ;\ <\-\ posting\ lines\ start\ with\ whitespace,\ each\ contains\ an\ account\ name \ \ \ \ income:salary\ \ \ \ \ \ \ \ $\-1\ \ \ \ ;\ \ \ \ followed\ by\ at\ least\ two\ spaces\ and\ an\ amount 2008/06/01\ gift \ \ \ \ assets:bank:checking\ \ $1\ \ \ \ ;\ <\-\ at\ least\ two\ postings\ in\ a\ transaction \ \ \ \ income:gifts\ \ \ \ \ \ \ \ \ $\-1\ \ \ \ ;\ <\-\ their\ amounts\ must\ balance\ to\ 0 2008/06/02\ save \ \ \ \ assets:bank:saving\ \ \ \ $1 \ \ \ \ assets:bank:checking\ \ \ \ \ \ \ \ ;\ <\-\ one\ amount\ may\ be\ omitted;\ here\ $\-1\ is\ inferred 2008/06/03\ eat\ &\ shop\ \ \ \ \ \ \ \ \ \ \ ;\ <\-\ description\ can\ be\ anything \ \ \ \ expenses:food\ \ \ \ \ \ \ \ \ $1 \ \ \ \ expenses:supplies\ \ \ \ \ $1\ \ \ \ ;\ <\-\ this\ transaction\ debits\ two\ expense\ accounts \ \ \ \ assets:cash\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ ;\ <\-\ $\-2\ inferred 2008/12/31\ *\ pay\ off\ \ \ \ \ \ \ \ \ \ \ \ ;\ <\-\ an\ optional\ *\ or\ !\ after\ the\ date\ means\ "cleared"\ (or\ anything\ you\ want) \ \ \ \ liabilities:debts\ \ \ \ \ $1 \ \ \ \ assets:bank:checking \f[] .fi .SH FILE FORMAT .SS Transactions .PP Transactions are represented by journal entries. Each begins with a simple date in column 0, followed by three optional fields with spaces between them: .IP \[bu] 2 a status flag, which can be empty or \f[C]!\f[] or \f[C]*\f[] (meaning "uncleared", "pending" and "cleared", or whatever you want) .IP \[bu] 2 a transaction code (eg a check number), .IP \[bu] 2 and/or a description .PP then some number of postings, of some amount to some account. Each posting is on its own line, consisting of: .IP \[bu] 2 indentation of one or more spaces (or tabs) .IP \[bu] 2 optionally, a \f[C]!\f[] or \f[C]*\f[] status flag followed by a space .IP \[bu] 2 an account name, optionally containing single spaces .IP \[bu] 2 optionally, two or more spaces or tabs followed by an amount .PP Usually there are two or more postings, though one or none is also possible. The posting amounts within a transaction must always balance, ie add up to 0. Optionally one amount can be left blank, in which case it will be inferred. .SS Dates .SS Simple dates .PP Within a journal file, transaction dates use Y/M/D (or Y\-M\-D or Y.M.D) Leading zeros are 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[], \f[C]1/31\f[], \f[C]2010\-01\-31\f[], \f[C]2010.1.31\f[]. .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, eg for more accurate balances, you can specify individual posting dates, which I recommend. Or, you can use the secondary dates (aka auxiliary/effective dates) feature, supported for compatibility with Ledger. .PP A secondary date can be written after the primary date, separated by an equals sign. The primary date, on the left, is used by default; the secondary date, on the right, is used when the \f[C]\-\-date2\f[] flag is specified (\f[C]\-\-aux\-date\f[] or \f[C]\-\-effective\f[] also work). .PP The meaning of secondary dates is up to you, but it\[aq]s best to follow a consistent rule. Eg write the bank\[aq]s clearing date as primary, and when needed, the date the transaction was initiated as secondary. .PP Here\[aq]s an example. Note that a secondary date will use the year of the primary date if unspecified. .IP .nf \f[C] 2010/2/23=2/19\ movie\ ticket \ \ expenses:cinema\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $10 \ \ assets:checking \f[] .fi .IP .nf \f[C] $\ hledger\ register\ checking 2010/02/23\ movie\ ticket\ \ \ \ \ \ \ \ \ assets:checking\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-10\ \ \ \ \ \ \ \ \ $\-10 \f[] .fi .IP .nf \f[C] $\ hledger\ register\ checking\ \-\-date2 2010/02/19\ movie\ ticket\ \ \ \ \ \ \ \ \ assets:checking\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-10\ \ \ \ \ \ \ \ \ $\-10 \f[] .fi .PP Secondary dates require some effort; you must use them consistently in your journal entries and remember whether to use or not use the \f[C]\-\-date2\f[] flag for your reports. They are included in hledger for Ledger compatibility, but posting dates are a more powerful and less confusing alternative. .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[]. 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[] .fi .IP .nf \f[C] $\ hledger\ \-f\ t.j\ register\ food 2015/05/30\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ expenses:food\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $10\ \ \ \ \ \ \ \ \ \ \ $10 \f[] .fi .IP .nf \f[C] $\ hledger\ \-f\ t.j\ register\ checking 2015/06/01\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ assets:checking\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-10\ \ \ \ \ \ \ \ \ \ $\-10 \f[] .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[]. The \f[C]date:\f[] or \f[C]date2:\f[] tags must have a valid simple date value if they are present, eg a \f[C]date:\f[] tag with no value is not allowed. .PP Ledger\[aq]s earlier, more compact bracketed date syntax is also supported: \f[C][DATE]\f[], \f[C][DATE=DATE2]\f[] or \f[C][=DATE2]\f[]. hledger will attempt to parse any square\-bracketed sequence of the \f[C]0123456789/\-.=\f[] characters in this way. With this syntax, DATE infers its year from the transaction and DATE2 infers its year from DATE. .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[], \f[C]liabilities\f[], \f[C]income\f[], \f[C]expenses\f[], and \f[C]equity\f[]. .PP Account names may contain single spaces, eg: \f[C]assets:accounts\ receivable\f[]. Because of this, they must always be followed by \f[B]two or more spaces\f[] (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[]. .PP Amounts consist of a number and (usually) a currency symbol or commodity name. Some examples: .PP \f[C]2.00001\f[] .PD 0 .P .PD \f[C]$1\f[] .PD 0 .P .PD \f[C]4000\ AAPL\f[] .PD 0 .P .PD \f[C]3\ "green\ apples"\f[] .PD 0 .P .PD \f[C]\-$1,000,000.00\f[] .PD 0 .P .PD \f[C]INR\ 9,99,99,999.00\f[] .PD 0 .P .PD \f[C]EUR\ \-2.000.000,00\f[] .PP As you can see, the amount format is somewhat flexible: .IP \[bu] 2 amounts are a number (the "quantity") and optionally a currency symbol/commodity name (the "commodity"). .IP \[bu] 2 the commodity is a symbol, word, or phrase, on the left or right, with or without a separating space. If the commodity contains numbers, spaces or non\-word punctuation it must be enclosed in double quotes. .IP \[bu] 2 negative amounts with a commodity on the left can have the minus sign before or after it .IP \[bu] 2 digit groups (thousands, or any other grouping) can be separated by commas (in which case period is used for decimal point) or periods (in which case comma is used for decimal point) .PP You can use any of these variations when recording data, but when hledger displays amounts, it will choose a consistent format for each commodity. (Except for price amounts, which are always formatted as written). The display format is chosen as follows: .IP \[bu] 2 if there is a commodity directive specifying the format, that is used .IP \[bu] 2 otherwise the format is inferred from the first posting amount in that commodity in the journal, and the precision (number of decimal places) will be the maximum from all posting amounts in that commmodity .IP \[bu] 2 or if there are no such amounts in the journal, a default format is used (like \f[C]$1000.00\f[]). .PP Price amounts and amounts in D directives usually don\[aq]t affect amount format inference, but in some situations they can do so indirectly. (Eg when D\[aq]s default commodity is applied to a commodity\-less amount, or when an amountless posting is balanced using a price\[aq]s commodity, or when \-V is used.) If you find this causing problems, set the desired format with a commodity directive. .SS Virtual Postings .PP When you parenthesise the account name in a posting, we call that a \f[I]virtual posting\f[], which means: .IP \[bu] 2 it is ignored when checking that the transaction is balanced .IP \[bu] 2 it is excluded from reports when the \f[C]\-\-real/\-R\f[] flag is used, or the \f[C]real:1\f[] query. .PP You could use this, eg, to set an account\[aq]s opening balance without needing to use the \f[C]equity:opening\ balances\f[] account: .IP .nf \f[C] 1/1\ special\ unbalanced\ posting\ to\ set\ initial\ balance \ \ (assets:checking)\ \ \ $1000 \f[] .fi .PP When the account name is bracketed, we call it a \f[I]balanced virtual posting\f[]. This is like an ordinary virtual posting except the balanced virtual postings in a transaction must balance to 0, like the real postings (but separately from them). Balanced virtual postings are also excluded by \f[C]\-\-real/\-R\f[] or \f[C]real:1\f[]. .IP .nf \f[C] 1/1\ buy\ food\ with\ cash,\ and\ update\ some\ budget\-tracking\ subaccounts\ elsewhere \ \ expenses:food\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $10 \ \ assets:cash\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-10 \ \ [assets:checking:available]\ \ \ \ \ $10 \ \ [assets:checking:budget:food]\ \ $\-10 \f[] .fi .PP Virtual postings have some legitimate uses, but those are few. You can usually find an equivalent journal entry using real postings, which is more correct and provides better error checking. .SS Balance Assertions .PP hledger supports Ledger\-style balance assertions in journal files. These look like \f[C]=EXPECTEDBALANCE\f[] following a posting\[aq]s amount. Eg in this example 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[] .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]\-\-ignore\-assertions\f[] flag, which can be useful for troubleshooting or for reading Ledger files. .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. We could call this a partial balance assertion. This is compatible with Ledger, and makes it possible to make assertions about accounts containing multiple commodities. .PP To assert each commodity\[aq]s balance in such a multi\-commodity account, you can add multiple postings (with amount 0 if necessary). But note that no matter how many assertions you add, you can\[aq]t be sure the account does not contain some unexpected commodity. (We\[aq]ll add support for this kind of total balance assertion if there\[aq]s demand.) .SS Assertions and subaccounts .PP Balance assertions do not count the balance from subaccounts; they check the posted account\[aq]s exclusive balance. For example: .IP .nf \f[C] 1/1 \ \ checking:fund\ \ \ 1\ =\ 1\ \ ;\ post\ to\ this\ subaccount,\ its\ balance\ is\ now\ 1 \ \ checking\ \ \ \ \ \ \ \ 1\ =\ 1\ \ ;\ post\ to\ the\ parent\ account,\ its\ exclusive\ balance\ is\ now\ 1 \ \ equity \f[] .fi .PP The balance report\[aq]s flat mode shows these exclusive balances more clearly: .IP .nf \f[C] $\ hledger\ bal\ checking\ \-\-flat \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ 1\ \ checking \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ 1\ \ checking:fund \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ 2 \f[] .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[] flag or \f[C]real:\f[] query. .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[] .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[] .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 Prices .SS Transaction prices .PP Within a transaction posting, you can record an amount\[aq]s price in another commodity. This can be used to document the cost (for a purchase), or selling price (for a sale), or the exchange rate that was used, for this transaction. These transaction prices are fixed, and do not change over time. .PP Amounts with transaction prices can be displayed in the transaction price\[aq]s commodity, by using the \f[C]\-\-cost/\-B\f[] flag supported by most hledger commands (mnemonic: "cost Basis"). .PP There are several ways to record a transaction price: .IP "1." 3 Write the unit price (aka exchange rate), as \f[C]\@\ UNITPRICE\f[] after the amount: .RS 4 .IP .nf \f[C] 2009/1/1 \ \ assets:foreign\ currency\ \ \ €100\ \@\ $1.35\ \ ;\ one\ hundred\ euros\ at\ $1.35\ each \ \ assets:cash \f[] .fi .RE .IP "2." 3 Or write the total price, as \f[C]\@\@\ TOTALPRICE\f[] after the amount: .RS 4 .IP .nf \f[C] 2009/1/1 \ \ assets:foreign\ currency\ \ \ €100\ \@\@\ $135\ \ ;\ one\ hundred\ euros\ at\ $135\ for\ the\ lot \ \ assets:cash \f[] .fi .RE .IP "3." 3 Or let hledger infer the price so as to balance the transaction. To permit this, you must fully specify all posting amounts, and their sum must have a non\-zero amount in exactly two commodities: .RS 4 .IP .nf \f[C] 2009/1/1 \ \ assets:foreign\ currency\ \ \ €100\ \ \ \ \ \ \ \ \ \ ;\ one\ hundred\ euros \ \ assets:cash\ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-135\ \ \ \ \ \ \ \ \ \ ;\ exchanged\ for\ $135 \f[] .fi .RE .PP With any of the above examples we get: .IP .nf \f[C] $\ hledger\ print\ \-B 2009/01/01 \ \ \ \ assets:foreign\ currency\ \ \ \ \ \ \ $135.00 \ \ \ \ assets:cash\ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ $\-135.00 \f[] .fi .PP Example use for transaction prices: recording the effective conversion rate of purchases made in a foreign currency. .SS Market prices .PP Market prices are not tied to a particular transaction; they represent historical exchange rates between two commodities. (Ledger calls them historical prices.) For example, the prices published by a stock exchange or the foreign exchange market. Some commands (balance, currently) can use this information to show the market value of things at a given date. .PP To record market prices, use P directives in the main journal or in an included file. Their format is: .IP .nf \f[C] P\ DATE\ COMMODITYBEINGPRICED\ UNITPRICE \f[] .fi .PP DATE is a simple date as usual. COMMODITYBEINGPRICED is the symbol of the commodity being priced. UNITPRICE is an ordinary amount (symbol and quantity) in a second commodity, specifying the unit price or conversion rate for the first commodity in terms of the second, on the given date. .PP For example, the following 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\ €\ $1.35 P\ 2010/1/1\ €\ $1.40 \f[] .fi .SS Comments .PP Lines in the journal beginning with a semicolon (\f[C];\f[]) or hash (\f[C]#\f[]) or asterisk (\f[C]*\f[]) are comments, and will be ignored. (Asterisk comments make it easy to treat your journal like an org\-mode outline in emacs.) .PP Also, anything between \f[C]comment\f[] and \f[C]end\ comment\f[] directives is a (multi\-line) comment. If there is no \f[C]end\ comment\f[], the comment extends to the end of the file. .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. .PP Some examples: .IP .nf \f[C] #\ a\ journal\ comment ;\ also\ a\ journal\ comment comment This\ is\ a\ multiline\ comment, which\ continues\ until\ a\ line where\ the\ "end\ comment"\ string appears\ on\ its\ own. 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\ journal\ comment\ (because\ not\ indented) \f[] .fi .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[] .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[] .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[] .fi .PP Here, .IP \[bu] 2 "\f[C]a\ comment\ containing\f[]" is just comment text, not a tag .IP \[bu] 2 "\f[C]tag1\f[]" is a tag with no value .IP \[bu] 2 "\f[C]tag2\f[]" is another tag, whose value is "\f[C]some\ value\ ...\f[]" .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[], \f[C]TAG2\f[], \f[C]third\-tag\f[]) and the posting has four (those plus \f[C]posting\-tag\f[]): .IP .nf \f[C] 1/1\ a\ transaction\ \ ;\ A:,\ TAG2: \ \ \ \ ;\ third\-tag:\ a\ third\ transaction\ tag,\ <\-\ with\ a\ value \ \ \ \ (a)\ \ $1\ \ ;\ posting\-tag: \f[] .fi .PP Tags are like Ledger\[aq]s metadata feature, except hledger\[aq]s tag values are simple strings. .SS Implicit tags .PP Some predefined "implicit" tags are also provided: .IP \[bu] 2 \f[C]code\f[] \- the transaction\[aq]s code field .IP \[bu] 2 \f[C]description\f[] \- the transaction\[aq]s description .IP \[bu] 2 \f[C]payee\f[] \- the part of description before \f[C]|\f[], or all of it .IP \[bu] 2 \f[C]note\f[] \- the part of description after \f[C]|\f[], or all of it .PP \f[C]payee\f[] and \f[C]note\f[] support descriptions written in a special \f[C]PAYEE\ |\ NOTE\f[] format, accessing the parts before and after the pipe character respectively. For descriptions not containing a pipe character they are the same as \f[C]description\f[]. .SS Directives .SS Account aliases .PP You can define aliases which rewrite your account names (after reading the journal, before generating reports). hledger\[aq]s account aliases 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 See also Cookbook: rewrite account names. .SS Basic aliases .PP To set an account alias, use the \f[C]alias\f[] 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[] .fi .PP Or, you can use the \f[C]\-\-alias\ \[aq]OLD=NEW\[aq]\f[] option on the command line. This affects all entries. It\[aq]s useful for trying out aliases interactively. .PP OLD and NEW are 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\ "checking"\ to\ "assets:bank:wells\ fargo:checking",\ or\ "checking:a"\ to\ "assets:bank:wells\ fargo:checking:a" \f[] .fi .SS Regex aliases .PP There is also a more powerful variant that uses a regular expression, indicated by the forward slashes. (This was the default behaviour in hledger 0.24\-0.25): .IP .nf \f[C] alias\ /REGEX/\ =\ REPLACEMENT \f[] .fi .PP or \f[C]\-\-alias\ \[aq]/REGEX/=REPLACEMENT\[aq]\f[]. .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. Note, currently regular expression aliases may cause noticeable slow\-downs. (And if you use Ledger on your hledger file, they will be ignored.) Eg: .IP .nf \f[C] alias\ /^(.+):bank:([^:]+)(.*)/\ =\ \\1:\\2\ \\3 #\ rewrites\ "assets:bank:wells\ fargo:checking"\ to\ \ "assets:wells\ fargo\ checking" \f[] .fi .SS Multiple aliases .PP You can define as many aliases as you like using directives or command\-line options. Aliases are recursive \- each alias sees the result of applying previous ones. (This is different from Ledger, where aliases are non\-recursive by default). Aliases are applied in the following order: .IP "1." 3 alias directives, most recently seen first (recent directives take precedence over earlier ones; directives not yet seen are ignored) .IP "2." 3 alias options, in the order they appear on the command line .SS end aliases .PP You can clear (forget) all currently defined aliases with the \f[C]end\ aliases\f[] directive: .IP .nf \f[C] end\ aliases \f[] .fi .SS account directive .PP The \f[C]account\f[] directive predefines account names, as in Ledger and Beancount. This may be useful for your own documentation; hledger doesn\[aq]t make use of it yet. .IP .nf \f[C] ;\ account\ ACCT ;\ \ \ OPTIONAL\ COMMENTS/TAGS... account\ assets:bank:checking \ a\ comment \ acct\-no:12345 account\ expenses:food ;\ etc. \f[] .fi .SS apply account directive .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[] and \f[C]end\ apply\ account\f[] directives like so: .IP .nf \f[C] apply\ account\ home 2010/1/1 \ \ \ \ food\ \ \ \ $10 \ \ \ \ cash end\ apply\ account \f[] .fi .PP which is equivalent to: .IP .nf \f[C] 2010/01/01 \ \ \ \ home:food\ \ \ \ \ \ \ \ \ \ \ $10 \ \ \ \ home:cash\ \ \ \ \ \ \ \ \ \ $\-10 \f[] .fi .PP If \f[C]end\ apply\ account\f[] 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[] .fi .PP Prior to hledger 1.0, legacy \f[C]account\f[] and \f[C]end\f[] spellings were also supported. .SS Multi\-line comments .PP A line containing just \f[C]comment\f[] starts a multi\-line comment, and a line containing just \f[C]end\ comment\f[] ends it. See comments. .SS commodity directive .PP The \f[C]commodity\f[] directive predefines commodities (currently this is just informational), and also it may define the display format for amounts in this commodity (overriding the automatically inferred format). .PP 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[] .fi .PP or on multiple lines, using the "format" 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\ 9,99,99,999.00 \f[] .fi .SS Default commodity .PP The D directive sets a default commodity (and display format), to be used for amounts without a commodity symbol (ie, plain numbers). (Note this differs from Ledger\[aq]s default commodity directive.) The commodity and display format will be applied to all subsequent commodity\-less amounts, or until the next D directive. .IP .nf \f[C] #\ commodity\-less\ amounts\ should\ be\ treated\ as\ dollars #\ (and\ displayed\ with\ symbol\ on\ the\ left,\ thousands\ separators\ and\ two\ decimal\ places) D\ $1,000.00 1/1 \ \ a\ \ \ \ \ 5\ \ \ \ #\ <\-\ commodity\-less\ amount,\ becomes\ $1 \ \ b \f[] .fi .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[] 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[] .fi .SS Including other files .PP You can pull in the content of additional journal files by writing an include directive, like this: .IP .nf \f[C] include\ path/to/file.journal \f[] .fi .PP If the path does not begin with a slash, it is relative to the current file. Glob patterns (\f[C]*\f[]) are not currently supported. .PP The \f[C]include\f[] directive can only be used in journal files. It can include journal, timeclock or timedot files, but not CSV files. .SH EDITOR SUPPORT .PP Add\-on modes exist for various text editors, to make working with journal files easier. They add colour, navigation aids and helpful commands. For hledger users who edit the journal file directly (the majority), using one of these modes is quite recommended. .PP These were written with Ledger in mind, but also work with hledger files: .PP .TS tab(@); lw(16.5n) lw(51.5n). T{ Emacs T}@T{ http://www.ledger\-cli.org/3.0/doc/ledger\-mode.html T} T{ Vim T}@T{ https://github.com/ledger/ledger/wiki/Getting\-started T} T{ Sublime Text T}@T{ https://github.com/ledger/ledger/wiki/Using\-Sublime\-Text T} T{ Textmate T}@T{ https://github.com/ledger/ledger/wiki/Using\-TextMate\-2 T} T{ Text Wrangler \ T}@T{ https://github.com/ledger/ledger/wiki/Editing\-Ledger\-files\-with\-TextWrangler T} .TE .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-2016 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.2/doc/other/hledger_journal.5.info0000644000000000000000000010577013067574766017265 0ustar0000000000000000This is hledger_journal.5.info, produced by makeinfo version 6.0 from stdin.  File: hledger_journal.5.info, Node: Top, Next: FILE FORMAT, Up: (dir) hledger_journal(5) hledger 1.2 ****************************** 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 commands to create and update it. Many users, though, also edit the journal file directly with a text editor, perhaps assisted by the helper modes for emacs or vim. Here's an example: ; A sample journal file. This is a comment. 2008/01/01 income ; <- transaction's first line starts in column 0, contains date and description assets:bank:checking $1 ; <- posting lines start with whitespace, each contains an account name income:salary $-1 ; followed by at least two spaces and an amount 2008/06/01 gift assets:bank:checking $1 ; <- at least two postings in a transaction income:gifts $-1 ; <- their amounts must balance to 0 2008/06/02 save assets:bank:saving $1 assets:bank:checking ; <- one amount may be omitted; here $-1 is inferred 2008/06/03 eat & shop ; <- description can be anything expenses:food $1 expenses:supplies $1 ; <- this transaction debits two expense accounts assets:cash ; <- $-2 inferred 2008/12/31 * pay off ; <- an optional * or ! after the date means "cleared" (or anything you want) liabilities:debts $1 assets:bank:checking * Menu: * FILE FORMAT:: * EDITOR SUPPORT::  File: hledger_journal.5.info, Node: FILE FORMAT, Next: EDITOR SUPPORT, Prev: Top, Up: Top 1 FILE FORMAT ************* * Menu: * Transactions:: * Dates:: * Account names:: * Amounts:: * Virtual Postings:: * Balance Assertions:: * Balance Assignments:: * Prices:: * Comments:: * Tags:: * Directives::  File: hledger_journal.5.info, Node: Transactions, Next: Dates, Up: FILE FORMAT 1.1 Transactions ================ Transactions are represented by journal entries. Each begins with a simple date in column 0, followed by three optional fields with spaces between them: * a status flag, which can be empty or '!' or '*' (meaning "uncleared", "pending" and "cleared", or whatever you want) * a transaction code (eg a check number), * and/or a description then some number of postings, of some amount to some account. Each posting is on its own line, consisting of: * indentation of one or more spaces (or tabs) * optionally, a '!' or '*' status flag followed by a space * an account name, optionally containing single spaces * optionally, two or more spaces or tabs followed by an amount Usually there are two or more postings, though one or none is also possible. The posting amounts within a transaction must always balance, ie add up to 0. Optionally one amount can be left blank, in which case it will be inferred.  File: hledger_journal.5.info, Node: Dates, Next: Account names, Prev: Transactions, Up: FILE FORMAT 1.2 Dates ========= * Menu: * Simple dates:: * Secondary dates:: * Posting dates::  File: hledger_journal.5.info, Node: Simple dates, Next: Secondary dates, Up: Dates 1.2.1 Simple dates ------------------ Within a journal file, transaction dates use Y/M/D (or Y-M-D or Y.M.D) Leading zeros are 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', '1/31', '2010-01-31', '2010.1.31'.  File: hledger_journal.5.info, Node: Secondary dates, Next: Posting dates, Prev: Simple dates, Up: Dates 1.2.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, eg for more accurate balances, you can specify individual posting dates, which I recommend. Or, you can use the secondary dates (aka auxiliary/effective dates) feature, supported for compatibility with Ledger. A secondary date can be written after the primary date, separated by an equals sign. The primary date, on the left, is used by default; the secondary date, on the right, is used when the '--date2' flag is specified ('--aux-date' or '--effective' also work). The meaning of secondary dates is up to you, but it's best to follow a consistent rule. Eg write the bank's clearing date as primary, and when needed, the date the transaction was initiated as secondary. Here's an example. Note that a secondary date will use the year of the primary date if unspecified. 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 Secondary dates require some effort; you must use them consistently in your journal entries and remember whether to use or not use the '--date2' flag for your reports. They are included in hledger for Ledger compatibility, but posting dates are a more powerful and less confusing alternative.  File: hledger_journal.5.info, Node: Posting dates, Prev: Secondary dates, Up: Dates 1.2.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.5.info, Node: Account names, Next: Amounts, Prev: Dates, Up: FILE FORMAT 1.3 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.5.info, Node: Amounts, Next: Virtual Postings, Prev: Account names, Up: FILE FORMAT 1.4 Amounts =========== After the account name, there is usually an amount. Important: between account name and amount, there must be *two or more spaces*. Amounts consist of a number and (usually) a currency symbol or commodity name. Some examples: '2.00001' '$1' '4000 AAPL' '3 "green apples"' '-$1,000,000.00' 'INR 9,99,99,999.00' 'EUR -2.000.000,00' As you can see, the amount format is somewhat flexible: * amounts are a number (the "quantity") and optionally a currency symbol/commodity name (the "commodity"). * the commodity is a symbol, word, or phrase, on the left or right, with or without a separating space. If the commodity contains numbers, spaces or non-word punctuation it must be enclosed in double quotes. * negative amounts with a commodity on the left can have the minus sign before or after it * digit groups (thousands, or any other grouping) can be separated by commas (in which case period is used for decimal point) or periods (in which case comma is used for decimal point) You can use any of these variations when recording data, but when hledger displays amounts, it will choose a consistent format for each commodity. (Except for price amounts, which are always formatted as written). The display format is chosen as follows: * if there is a commodity directive specifying the format, that is used * otherwise the format is inferred from the first posting amount in that commodity in the journal, and the precision (number of decimal places) will be the maximum from all posting amounts in that commmodity * or if there are no such amounts in the journal, a default format is used (like '$1000.00'). Price amounts and amounts in D directives usually don't affect amount format inference, but in some situations they can do so indirectly. (Eg when D's default commodity is applied to a commodity-less amount, or when an amountless posting is balanced using a price's commodity, or when -V is used.) If you find this causing problems, set the desired format with a commodity directive.  File: hledger_journal.5.info, Node: Virtual Postings, Next: Balance Assertions, Prev: Amounts, Up: FILE FORMAT 1.5 Virtual Postings ==================== When you parenthesise the account name in a posting, we call that a _virtual posting_, which means: * it is ignored when checking that the transaction is balanced * it is excluded from reports when the '--real/-R' flag is used, or the 'real:1' query. You could use this, eg, to set an account's opening balance without needing to use the 'equity:opening balances' account: 1/1 special unbalanced posting to set initial balance (assets:checking) $1000 When the account name is bracketed, we call it a _balanced virtual posting_. This is like an ordinary virtual posting except the balanced virtual postings in a transaction must balance to 0, like the real postings (but separately from them). Balanced virtual postings are also excluded by '--real/-R' or 'real:1'. 1/1 buy food with cash, and update some budget-tracking subaccounts elsewhere expenses:food $10 assets:cash $-10 [assets:checking:available] $10 [assets:checking:budget:food] $-10 Virtual postings have some legitimate uses, but those are few. You can usually find an equivalent journal entry using real postings, which is more correct and provides better error checking.  File: hledger_journal.5.info, Node: Balance Assertions, Next: Balance Assignments, Prev: Virtual Postings, Up: FILE FORMAT 1.6 Balance Assertions ====================== hledger supports Ledger-style balance assertions in journal files. These look like '=EXPECTEDBALANCE' following a posting's amount. Eg in this example 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 '--ignore-assertions' flag, which can be useful for troubleshooting or for reading Ledger files. * Menu: * Assertions and ordering:: * Assertions and included files:: * Assertions and multiple -f options:: * Assertions and commodities:: * Assertions and subaccounts:: * Assertions and virtual postings::  File: hledger_journal.5.info, Node: Assertions and ordering, Next: Assertions and included files, Up: Balance Assertions 1.6.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.5.info, Node: Assertions and included files, Next: Assertions and multiple -f options, Prev: Assertions and ordering, Up: Balance Assertions 1.6.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.5.info, Node: Assertions and multiple -f options, Next: Assertions and commodities, Prev: Assertions and included files, Up: Balance Assertions 1.6.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.5.info, Node: Assertions and commodities, Next: Assertions and subaccounts, Prev: Assertions and multiple -f options, Up: Balance Assertions 1.6.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. We could call this a partial balance assertion. This is compatible with Ledger, and makes it possible to make assertions about accounts containing multiple commodities. To assert each commodity's balance in such a multi-commodity account, you can add multiple postings (with amount 0 if necessary). But note that no matter how many assertions you add, you can't be sure the account does not contain some unexpected commodity. (We'll add support for this kind of total balance assertion if there's demand.)  File: hledger_journal.5.info, Node: Assertions and subaccounts, Next: Assertions and virtual postings, Prev: Assertions and commodities, Up: Balance Assertions 1.6.5 Assertions and subaccounts -------------------------------- Balance assertions do not count the balance from subaccounts; they check the posted account's exclusive balance. For example: 1/1 checking:fund 1 = 1 ; post to this subaccount, its balance is now 1 checking 1 = 1 ; post to the parent account, its exclusive balance is now 1 equity The balance report's flat mode shows these exclusive balances more clearly: $ hledger bal checking --flat 1 checking 1 checking:fund -------------------- 2  File: hledger_journal.5.info, Node: Assertions and virtual postings, Prev: Assertions and subaccounts, Up: Balance Assertions 1.6.6 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.5.info, Node: Balance Assignments, Next: Prices, Prev: Balance Assertions, Up: FILE FORMAT 1.7 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.  File: hledger_journal.5.info, Node: Prices, Next: Comments, Prev: Balance Assignments, Up: FILE FORMAT 1.8 Prices ========== * Menu: * Transaction prices:: * Market prices::  File: hledger_journal.5.info, Node: Transaction prices, Next: Market prices, Up: Prices 1.8.1 Transaction prices ------------------------ Within a transaction posting, you can record an amount's price in another commodity. This can be used to document the cost (for a purchase), or selling price (for a sale), or the exchange rate that was used, for this transaction. These transaction prices are fixed, and do not change over time. Amounts with transaction prices can be displayed in the transaction price's commodity, by using the '--cost/-B' flag supported by most hledger commands (mnemonic: "cost Basis"). There are several ways to record a transaction price: 1. Write the unit price (aka exchange rate), as '@ UNITPRICE' after the amount: 2009/1/1 assets:foreign currency €100 @ $1.35 ; one hundred euros at $1.35 each assets:cash 2. Or write the total price, as '@@ TOTALPRICE' after the amount: 2009/1/1 assets:foreign currency €100 @@ $135 ; one hundred euros at $135 for the lot assets:cash 3. Or let hledger infer the price so as to balance the transaction. To permit this, you must fully specify all posting amounts, and their sum must have a non-zero amount in exactly two commodities: 2009/1/1 assets:foreign currency €100 ; one hundred euros assets:cash $-135 ; exchanged for $135 With any of the above examples we get: $ hledger print -B 2009/01/01 assets:foreign currency $135.00 assets:cash $-135.00 Example use for transaction prices: recording the effective conversion rate of purchases made in a foreign currency.  File: hledger_journal.5.info, Node: Market prices, Prev: Transaction prices, Up: Prices 1.8.2 Market prices ------------------- Market prices are not tied to a particular transaction; they represent historical exchange rates between two commodities. (Ledger calls them historical prices.) For example, the prices published by a stock exchange or the foreign exchange market. Some commands (balance, currently) can use this information to show the market value of things at a given date. To record market prices, use P directives in the main journal or in an included file. Their format is: P DATE COMMODITYBEINGPRICED UNITPRICE DATE is a simple date as usual. COMMODITYBEINGPRICED is the symbol of the commodity being priced. UNITPRICE is an ordinary amount (symbol and quantity) in a second commodity, specifying the unit price or conversion rate for the first commodity in terms of the second, on the given date. For example, the following 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  File: hledger_journal.5.info, Node: Comments, Next: Tags, Prev: Prices, Up: FILE FORMAT 1.9 Comments ============ Lines in the journal beginning with a semicolon (';') or hash ('#') or asterisk ('*') are comments, and will be ignored. (Asterisk comments make it easy to treat your journal like an org-mode outline in emacs.) Also, anything between 'comment' and 'end comment' directives is a (multi-line) comment. If there is no 'end comment', the comment extends to the end of the file. 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. Some examples: # a journal comment ; also a journal comment comment This is a multiline comment, which continues until a line where the "end comment" string appears on its own. 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 journal comment (because not indented)  File: hledger_journal.5.info, Node: Tags, Next: Directives, Prev: Comments, Up: FILE FORMAT 1.10 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. * Menu: * Implicit tags::  File: hledger_journal.5.info, Node: Implicit tags, Up: Tags 1.10.1 Implicit tags -------------------- Some predefined "implicit" tags are also provided: * 'code' - the transaction's code field * 'description' - the transaction's description * 'payee' - the part of description before '|', or all of it * 'note' - the part of description after '|', or all of it 'payee' and 'note' support descriptions written in a special 'PAYEE | NOTE' format, accessing the parts before and after the pipe character respectively. For descriptions not containing a pipe character they are the same as 'description'.  File: hledger_journal.5.info, Node: Directives, Prev: Tags, Up: FILE FORMAT 1.11 Directives =============== * Menu: * Account aliases:: * account directive:: * apply account directive:: * Multi-line comments:: * commodity directive:: * Default commodity:: * Default year:: * Including other files::  File: hledger_journal.5.info, Node: Account aliases, Next: account directive, Up: Directives 1.11.1 Account aliases ---------------------- You can define aliases which rewrite your account names (after reading the journal, before generating reports). hledger's account aliases 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 See also Cookbook: rewrite account names. * Menu: * Basic aliases:: * Regex aliases:: * Multiple aliases:: * end aliases::  File: hledger_journal.5.info, Node: Basic aliases, Next: Regex aliases, Up: Account aliases 1.11.1.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 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.5.info, Node: Regex aliases, Next: Multiple aliases, Prev: Basic aliases, Up: Account aliases 1.11.1.2 Regex aliases ...................... There is also a more powerful variant that uses a regular expression, indicated by the forward slashes. (This was the default behaviour in hledger 0.24-0.25): 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. Note, currently regular expression aliases may cause noticeable slow-downs. (And if you use Ledger on your hledger file, they will be ignored.) Eg: alias /^(.+):bank:([^:]+)(.*)/ = \1:\2 \3 # rewrites "assets:bank:wells fargo:checking" to "assets:wells fargo checking"  File: hledger_journal.5.info, Node: Multiple aliases, Next: end aliases, Prev: Regex aliases, Up: Account aliases 1.11.1.3 Multiple aliases ......................... You can define as many aliases as you like using directives or command-line options. Aliases are recursive - each alias sees the result of applying previous ones. (This is different from Ledger, where aliases are non-recursive by default). Aliases are applied in the following order: 1. alias directives, most recently seen first (recent directives take precedence over earlier ones; directives not yet seen are ignored) 2. alias options, in the order they appear on the command line  File: hledger_journal.5.info, Node: end aliases, Prev: Multiple aliases, Up: Account aliases 1.11.1.4 end aliases .................... You can clear (forget) all currently defined aliases with the 'end aliases' directive: end aliases  File: hledger_journal.5.info, Node: account directive, Next: apply account directive, Prev: Account aliases, Up: Directives 1.11.2 account directive ------------------------ The 'account' directive predefines account names, as in Ledger and Beancount. This may be useful for your own documentation; hledger doesn't make use of it yet. ; account ACCT ; OPTIONAL COMMENTS/TAGS... account assets:bank:checking a comment acct-no:12345 account expenses:food ; etc.  File: hledger_journal.5.info, Node: apply account directive, Next: Multi-line comments, Prev: account directive, Up: Directives 1.11.3 apply account directive ------------------------------ 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.  File: hledger_journal.5.info, Node: Multi-line comments, Next: commodity directive, Prev: apply account directive, Up: Directives 1.11.4 Multi-line comments -------------------------- A line containing just 'comment' starts a multi-line comment, and a line containing just 'end comment' ends it. See comments.  File: hledger_journal.5.info, Node: commodity directive, Next: Default commodity, Prev: Multi-line comments, Up: Directives 1.11.5 commodity directive -------------------------- The 'commodity' directive predefines commodities (currently this is just informational), and also it may define the display format for amounts in this commodity (overriding the automatically inferred format). 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 9,99,99,999.00  File: hledger_journal.5.info, Node: Default commodity, Next: Default year, Prev: commodity directive, Up: Directives 1.11.6 Default commodity ------------------------ The D directive sets a default commodity (and display format), to be used for amounts without a commodity symbol (ie, plain numbers). (Note this differs from Ledger's default commodity directive.) The commodity and display format will be applied to all subsequent commodity-less amounts, or until the next D directive. # commodity-less amounts should be treated as dollars # (and displayed with symbol on the left, thousands separators and two decimal places) D $1,000.00 1/1 a 5 # <- commodity-less amount, becomes $1 b  File: hledger_journal.5.info, Node: Default year, Next: Including other files, Prev: Default commodity, Up: Directives 1.11.7 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.5.info, Node: Including other files, Prev: Default year, Up: Directives 1.11.8 Including other files ---------------------------- You can pull in the content of additional journal files by writing an include directive, like this: include path/to/file.journal If the path does not begin with a slash, it is relative to the current file. Glob patterns ('*') are not currently supported. The 'include' directive can only be used in journal files. It can include journal, timeclock or timedot files, but not CSV files.  File: hledger_journal.5.info, Node: EDITOR SUPPORT, Prev: FILE FORMAT, Up: Top 2 EDITOR SUPPORT **************** Add-on modes exist for various text editors, to make working with journal files easier. They add colour, navigation aids and helpful commands. For hledger users who edit the journal file directly (the majority), using one of these modes is quite recommended. These were written with Ledger in mind, but also work with hledger files: Emacs http://www.ledger-cli.org/3.0/doc/ledger-mode.html Vim https://github.com/ledger/ledger/wiki/Getting-started Sublime Text https://github.com/ledger/ledger/wiki/Using-Sublime-Text Textmate https://github.com/ledger/ledger/wiki/Using-TextMate-2 Text Wrangler https://github.com/ledger/ledger/wiki/Editing-Ledger-files-with-TextWrangler  Tag Table: Node: Top78 Node: FILE FORMAT2292 Ref: #file-format2418 Node: Transactions2601 Ref: #transactions2721 Node: Dates3663 Ref: #dates3791 Node: Simple dates3856 Ref: #simple-dates3984 Node: Secondary dates4350 Ref: #secondary-dates4506 Node: Posting dates6069 Ref: #posting-dates6200 Node: Account names7574 Ref: #account-names7713 Node: Amounts8200 Ref: #amounts8338 Node: Virtual Postings10439 Ref: #virtual-postings10600 Node: Balance Assertions11820 Ref: #balance-assertions11997 Node: Assertions and ordering12893 Ref: #assertions-and-ordering13081 Node: Assertions and included files13781 Ref: #assertions-and-included-files14024 Node: Assertions and multiple -f options14357 Ref: #assertions-and-multiple--f-options14613 Node: Assertions and commodities14745 Ref: #assertions-and-commodities14982 Node: Assertions and subaccounts15678 Ref: #assertions-and-subaccounts15912 Node: Assertions and virtual postings16433 Ref: #assertions-and-virtual-postings16642 Node: Balance Assignments16784 Ref: #balance-assignments16953 Node: Prices18072 Ref: #prices18205 Node: Transaction prices18256 Ref: #transaction-prices18401 Node: Market prices19978 Ref: #market-prices20113 Node: Comments21086 Ref: #comments21208 Node: Tags22321 Ref: #tags22441 Node: Implicit tags23870 Ref: #implicit-tags23978 Node: Directives24495 Ref: #directives24610 Node: Account aliases24803 Ref: #account-aliases24949 Node: Basic aliases25553 Ref: #basic-aliases25698 Node: Regex aliases26388 Ref: #regex-aliases26558 Node: Multiple aliases27329 Ref: #multiple-aliases27503 Node: end aliases28001 Ref: #end-aliases28143 Node: account directive28244 Ref: #account-directive28426 Node: apply account directive28722 Ref: #apply-account-directive28920 Node: Multi-line comments29579 Ref: #multi-line-comments29771 Node: commodity directive29899 Ref: #commodity-directive30085 Node: Default commodity30957 Ref: #default-commodity31132 Node: Default year31669 Ref: #default-year31836 Node: Including other files32259 Ref: #including-other-files32418 Node: EDITOR SUPPORT32815 Ref: #editor-support32935  End Tag Table hledger-1.2/doc/other/hledger_journal.5.txt0000644000000000000000000010033613067574771017136 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 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 get- ting. You can use hledger without learning any more about this file; just use the add or web commands to create and update it. Many users, though, also edit the journal file directly with a text editor, perhaps assisted by the helper modes for emacs or vim. Here's an example: ; A sample journal file. This is a comment. 2008/01/01 income ; <- transaction's first line starts in column 0, contains date and description assets:bank:checking $1 ; <- posting lines start with whitespace, each contains an account name income:salary $-1 ; followed by at least two spaces and an amount 2008/06/01 gift assets:bank:checking $1 ; <- at least two postings in a transaction income:gifts $-1 ; <- their amounts must balance to 0 2008/06/02 save assets:bank:saving $1 assets:bank:checking ; <- one amount may be omitted; here $-1 is inferred 2008/06/03 eat & shop ; <- description can be anything expenses:food $1 expenses:supplies $1 ; <- this transaction debits two expense accounts assets:cash ; <- $-2 inferred 2008/12/31 * pay off ; <- an optional * or ! after the date means "cleared" (or anything you want) liabilities:debts $1 assets:bank:checking FILE FORMAT Transactions Transactions are represented by journal entries. Each begins with a simple date in column 0, followed by three optional fields with spaces between them: o a status flag, which can be empty or ! or * (meaning "uncleared", "pending" and "cleared", or whatever you want) o a transaction code (eg a check number), o and/or a description then some number of postings, of some amount to some account. Each posting is on its own line, consisting of: o indentation of one or more spaces (or tabs) o optionally, a ! or * status flag followed by a space o an account name, optionally containing single spaces o optionally, two or more spaces or tabs followed by an amount Usually there are two or more postings, though one or none is also pos- sible. The posting amounts within a transaction must always balance, ie add up to 0. Optionally one amount can be left blank, in which case it will be inferred. Dates Simple dates Within a journal file, transaction dates use Y/M/D (or Y-M-D or Y.M.D) Leading zeros are 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, 1/31, 2010-01-31, 2010.1.31. 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, eg for more accurate balances, you can specify individual posting dates, which I recommend. Or, you can use the sec- ondary dates (aka auxiliary/effective dates) feature, supported for compatibility with Ledger. A secondary date can be written after the primary date, separated by an equals sign. The primary date, on the left, is used by default; the secondary date, on the right, is used when the --date2 flag is speci- fied (--aux-date or --effective also work). The meaning of secondary dates is up to you, but it's best to follow a consistent rule. Eg write the bank's clearing date as primary, and when needed, the date the transaction was initiated as secondary. Here's an example. Note that a secondary date will use the year of the primary date if unspecified. 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 Secondary dates require some effort; you must use them consistently in your journal entries and remember whether to use or not use the --date2 flag for your reports. They are included in hledger for Ledger compat- ibility, but posting dates are a more powerful and less confusing alternative. 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. 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: between account name and amount, there must be two or more spaces. Amounts consist of a number and (usually) a currency symbol or commod- ity name. Some examples: 2.00001 $1 4000 AAPL 3 "green apples" -$1,000,000.00 INR 9,99,99,999.00 EUR -2.000.000,00 As you can see, the amount format is somewhat flexible: o amounts are a number (the "quantity") and optionally a currency sym- bol/commodity name (the "commodity"). o the commodity is a symbol, word, or phrase, on the left or right, with or without a separating space. If the commodity contains num- bers, spaces or non-word punctuation it must be enclosed in double quotes. o negative amounts with a commodity on the left can have the minus sign before or after it o digit groups (thousands, or any other grouping) can be separated by commas (in which case period is used for decimal point) or periods (in which case comma is used for decimal point) You can use any of these variations when recording data, but when hledger displays amounts, it will choose a consistent format for each commodity. (Except for price amounts, which are always formatted as written). The display format is chosen as follows: o if there is a commodity directive specifying the format, that is used o otherwise the format is inferred from the first posting amount in that commodity in the journal, and the precision (number of decimal places) will be the maximum from all posting amounts in that commmod- ity o or if there are no such amounts in the journal, a default format is used (like $1000.00). Price amounts and amounts in D directives usually don't affect amount format inference, but in some situations they can do so indirectly. (Eg when D's default commodity is applied to a commodity-less amount, or when an amountless posting is balanced using a price's commodity, or when -V is used.) If you find this causing problems, set the desired format with a commodity directive. Virtual Postings When you parenthesise the account name in a posting, we call that a virtual posting, which means: o it is ignored when checking that the transaction is balanced o it is excluded from reports when the --real/-R flag is used, or the real:1 query. You could use this, eg, to set an account's opening balance without needing to use the equity:opening balances account: 1/1 special unbalanced posting to set initial balance (assets:checking) $1000 When the account name is bracketed, we call it a balanced virtual post- ing. This is like an ordinary virtual posting except the balanced vir- tual postings in a transaction must balance to 0, like the real post- ings (but separately from them). Balanced virtual postings are also excluded by --real/-R or real:1. 1/1 buy food with cash, and update some budget-tracking subaccounts elsewhere expenses:food $10 assets:cash $-10 [assets:checking:available] $10 [assets:checking:budget:food] $-10 Virtual postings have some legitimate uses, but those are few. You can usually find an equivalent journal entry using real postings, which is more correct and provides better error checking. Balance Assertions hledger supports Ledger-style balance assertions in journal files. These look like =EXPECTEDBALANCE following a posting's amount. Eg in this example 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 --ignore-assertions flag, which can be useful for troubleshooting or for reading Ledger files. Assertions and ordering hledger sorts an account's postings and assertions first by date and then (for postings on the same day) by parse order. Note this is dif- ferent from Ledger, which sorts assertions only by parse order. (Also, Ledger assertions do not see the accumulated effect of repeated post- ings to the same account within a transaction.) So, hledger balance assertions keep working if you reorder differ- ently-dated transactions within the journal. But if you reorder same-dated transactions or postings, assertions might break and require updating. This order dependence does bring an advantage: precise con- trol over the order of postings and assertions within a day, so you can assert intra-day balances. Assertions and 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. We could call this a par- tial balance assertion. This is compatible with Ledger, and makes it possible to make assertions about accounts containing multiple commodi- ties. To assert each commodity's balance in such a multi-commodity account, you can add multiple postings (with amount 0 if necessary). But note that no matter how many assertions you add, you can't be sure the account does not contain some unexpected commodity. (We'll add support for this kind of total balance assertion if there's demand.) Assertions and subaccounts Balance assertions do not count the balance from subaccounts; they check the posted account's exclusive balance. For example: 1/1 checking:fund 1 = 1 ; post to this subaccount, its balance is now 1 checking 1 = 1 ; post to the parent account, its exclusive balance is now 1 equity The balance report's flat mode shows these exclusive balances more clearly: $ hledger bal checking --flat 1 checking 1 checking:fund -------------------- 2 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. 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. Prices Transaction prices Within a transaction posting, you can record an amount's price in another commodity. This can be used to document the cost (for a pur- chase), or selling price (for a sale), or the exchange rate that was used, for this transaction. These transaction prices are fixed, and do not change over time. Amounts with transaction prices can be displayed in the transaction price's commodity, by using the --cost/-B flag supported by most hledger commands (mnemonic: "cost Basis"). There are several ways to record a transaction price: 1. Write the unit price (aka exchange rate), as @ UNITPRICE after the amount: 2009/1/1 assets:foreign currency 100 @ $1.35 ; one hundred euros at $1.35 each assets:cash 2. Or write the total price, as @@ TOTALPRICE after the amount: 2009/1/1 assets:foreign currency 100 @@ $135 ; one hundred euros at $135 for the lot assets:cash 3. Or let hledger infer the price so as to balance the transaction. To permit this, you must fully specify all posting amounts, and their sum must have a non-zero amount in exactly two commodities: 2009/1/1 assets:foreign currency 100 ; one hundred euros assets:cash $-135 ; exchanged for $135 With any of the above examples we get: $ hledger print -B 2009/01/01 assets:foreign currency $135.00 assets:cash $-135.00 Example use for transaction prices: recording the effective conversion rate of purchases made in a foreign currency. Market prices Market prices are not tied to a particular transaction; they represent historical exchange rates between two commodities. (Ledger calls them historical prices.) For example, the prices published by a stock exchange or the foreign exchange market. Some commands (balance, cur- rently) can use this information to show the market value of things at a given date. To record market prices, use P directives in the main journal or in an included file. Their format is: P DATE COMMODITYBEINGPRICED UNITPRICE DATE is a simple date as usual. COMMODITYBEINGPRICED is the symbol of the commodity being priced. UNITPRICE is an ordinary amount (symbol and quantity) in a second commodity, specifying the unit price or con- version rate for the first commodity in terms of the second, on the given date. For example, the following 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 Comments Lines in the journal beginning with a semicolon (;) or hash (#) or asterisk (*) are comments, and will be ignored. (Asterisk comments make it easy to treat your journal like an org-mode outline in emacs.) Also, anything between comment and end comment directives is a (multi-line) comment. If there is no end comment, the comment extends to the end of the file. You can attach comments to a transaction by writing them after the description and/or indented on the following lines (before the post- ings). Similarly, you can attach comments to an individual posting by writing them after the amount and/or indented on the following lines. Some examples: # a journal comment ; also a journal comment comment This is a multiline comment, which continues until a line where the "end comment" string appears on its own. 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 journal comment (because not indented) 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. Implicit tags Some predefined "implicit" tags are also provided: o code - the transaction's code field o description - the transaction's description o payee - the part of description before |, or all of it o note - the part of description after |, or all of it payee and note support descriptions written in a special PAYEE | NOTE format, accessing the parts before and after the pipe character respec- tively. For descriptions not containing a pipe character they are the same as description. Directives Account aliases You can define aliases which rewrite your account names (after reading the journal, before generating reports). hledger's account aliases 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 See also Cookbook: 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 full account names. hledger will replace any occur- rence 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" Regex aliases There is also a more powerful variant that uses a regular expression, indicated by the forward slashes. (This was the default behaviour in hledger 0.24-0.25): 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. Note, cur- rently regular expression aliases may cause noticeable slow-downs. (And if you use Ledger on your hledger file, they will be ignored.) Eg: alias /^(.+):bank:([^:]+)(.*)/ = \1:\2 \3 # rewrites "assets:bank:wells fargo:checking" to "assets:wells fargo checking" Multiple aliases You can define as many aliases as you like using directives or com- mand-line options. Aliases are recursive - each alias sees the result of applying previous ones. (This is different from Ledger, where aliases are non-recursive by default). Aliases are applied in the fol- lowing order: 1. alias directives, most recently seen first (recent directives take precedence over earlier ones; directives not yet seen are ignored) 2. alias options, in the order they appear on the command line end aliases You can clear (forget) all currently defined aliases with the end aliases directive: end aliases account directive The account directive predefines account names, as in Ledger and Bean- count. This may be useful for your own documentation; hledger doesn't make use of it yet. ; account ACCT ; OPTIONAL COMMENTS/TAGS... account assets:bank:checking a comment acct-no:12345 account expenses:food ; etc. apply account directive 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 sup- ported. Multi-line comments A line containing just comment starts a multi-line comment, and a line containing just end comment ends it. See comments. commodity directive The commodity directive predefines commodities (currently this is just informational), and also it may define the display format for amounts in this commodity (overriding the automatically inferred format). 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 9,99,99,999.00 Default commodity The D directive sets a default commodity (and display format), to be used for amounts without a commodity symbol (ie, plain numbers). (Note this differs from Ledger's default commodity directive.) The commodity and display format will be applied to all subsequent commodity-less amounts, or until the next D directive. # commodity-less amounts should be treated as dollars # (and displayed with symbol on the left, thousands separators and two decimal places) D $1,000.00 1/1 a 5 # <- commodity-less amount, becomes $1 b 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 Including other files You can pull in the content of additional journal files by writing an include directive, like this: include path/to/file.journal If the path does not begin with a slash, it is relative to the current file. Glob patterns (*) are not currently supported. The include directive can only be used in journal files. It can include journal, timeclock or timedot files, but not CSV files. EDITOR SUPPORT Add-on modes exist for various text editors, to make working with jour- nal files easier. They add colour, navigation aids and helpful com- mands. For hledger users who edit the journal file directly (the majority), using one of these modes is quite recommended. These were written with Ledger in mind, but also work with hledger files: Emacs http://www.ledger-cli.org/3.0/doc/ledger-mode.html Vim https://github.com/ledger/ledger/wiki/Get- ting-started Sublime Text https://github.com/ledger/ledger/wiki/Using-Sub- lime-Text Textmate https://github.com/ledger/ledger/wiki/Using-Text- Mate-2 Text Wrangler https://github.com/ledger/ledger/wiki/Edit- ing-Ledger-files-with-TextWrangler 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-2016 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.2 March 2017 hledger_journal(5) hledger-1.2/doc/other/hledger_timeclock.50000644000000000000000000000557613067574770016631 0ustar0000000000000000 .TH "hledger_timeclock" "5" "March 2017" "hledger 1.2" "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[] .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[] 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[] .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[] .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: .RS 2 .IP .nf \f[C] alias\ ti="echo\ i\ `date\ \[aq]+%Y\-%m\-%d\ %H:%M:%S\[aq]`\ \\$*\ >>$TIMELOG" alias\ to="echo\ o\ `date\ \[aq]+%Y\-%m\-%d\ %H:%M:%S\[aq]`\ >>$TIMELOG" \f[] .fi .RE .IP \[bu] 2 or use the old \f[C]ti\f[] and \f[C]to\f[] scripts in the ledger 2.x repository. These rely on a "timeclock" 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-2016 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.2/doc/other/hledger_timeclock.5.info0000644000000000000000000000426013067574765017554 0ustar0000000000000000This is hledger_timeclock.5.info, produced by makeinfo version 6.0 from stdin.  File: hledger_timeclock.5.info, Node: Top, Up: (dir) hledger_timeclock(5) hledger 1.2 ******************************** 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: 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: Top80  End Tag Table hledger-1.2/doc/other/hledger_timeclock.5.txt0000644000000000000000000000601713067574770017436 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 time- clock-x.el and perhaps the extras in ledgerutils.el o at the command line, use these bash aliases: 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-2016 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.2 March 2017 hledger_timeclock(5) hledger-1.2/doc/other/hledger_timedot.50000644000000000000000000001035513067574770016313 0ustar0000000000000000 .TH "hledger_timedot" "5" "March 2017" "hledger 1.2" "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 (eg time), 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 "timedot", the format does not specify the commodity being logged, so could represent other dated, quantifiable things. Eg you could record a single\-entry journal of financial transactions, perhaps slightly more conveniently than with hledger_journal(5) format. .SH FILE FORMAT .PP A timedot file contains a series of day entries. A day entry begins with a date, and is followed by category/quantity pairs, one per line. Dates are hledger\-style simple dates (see hledger_journal(5)). Categories are hledger\-style account names, optionally indented. There must be at least two spaces between the category and the quantity. Quantities can be written in two ways: .IP "1." 3 a series of dots (period characters). Each dot represents "a quarter" \- eg, a quarter hour. Spaces can be used to group dots into hours, for easier counting. .IP "2." 3 a number (integer or decimal), representing "units" \- eg, hours. A good alternative when dots are cumbersome. (A number also can record negative quantities.) .PP Blank lines and lines beginning with #, ; or * are ignored. An example: .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[] .fi .PP Or with numbers: .IP .nf \f[C] 2016/2/3 inc:client1\ \ \ 4 fos:hledger\ \ \ 3 biz:research\ \ 1 \f[] .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[] .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[] .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[] .fi .IP .nf \f[C] $\ hledger\ \-f\ t.timedot\ \-\-alias\ /\\\\./=:\ bal\ date:2016/2/4 \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ 4.50\ \ fos \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ 4.00\ \ \ \ hledger:timedot \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ 0.50\ \ \ \ ledger \-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\-\- \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ \ 4.50 \f[] .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-2016 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.2/doc/other/hledger_timedot.5.info0000644000000000000000000000651413067574764017252 0ustar0000000000000000This is hledger_timedot.5.info, produced by makeinfo version 6.0 from stdin.  File: hledger_timedot.5.info, Node: Top, Next: FILE FORMAT, Up: (dir) hledger_timedot(5) hledger 1.2 ****************************** Timedot is a plain text format for logging dated, categorised quantities (eg time), 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", the format does not specify the commodity being logged, so could represent other dated, quantifiable things. Eg you could record a single-entry journal of financial transactions, perhaps slightly more conveniently than with hledger_journal(5) format. * Menu: * FILE FORMAT::  File: hledger_timedot.5.info, Node: FILE FORMAT, Prev: Top, Up: Top 1 FILE FORMAT ************* A timedot file contains a series of day entries. A day entry begins with a date, and is followed by category/quantity pairs, one per line. Dates are hledger-style simple dates (see hledger_journal(5)). Categories are hledger-style account names, optionally indented. There must be at least two spaces between the category and the quantity. Quantities can be written in two ways: 1. a series of dots (period characters). Each dot represents "a quarter" - eg, a quarter hour. Spaces can be used to group dots into hours, for easier counting. 2. a number (integer or decimal), representing "units" - eg, hours. A good alternative when dots are cumbersome. (A number also can record negative quantities.) Blank lines and lines beginning with #, ; or * are ignored. An example: # 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 . Or with numbers: 2016/2/3 inc:client1 4 fos:hledger 3 biz:research 1 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: Top78 Node: FILE FORMAT882 Ref: #file-format985  End Tag Table hledger-1.2/doc/other/hledger_timedot.5.txt0000644000000000000000000001065013067574770017127 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 (eg time), 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", the format does not specify the commodity being logged, so could represent other dated, quantifiable things. Eg you could record a single-entry journal of financial transactions, per- haps slightly more conveniently than with hledger_journal(5) format. FILE FORMAT A timedot file contains a series of day entries. A day entry begins with a date, and is followed by category/quantity pairs, one per line. Dates are hledger-style simple dates (see hledger_journal(5)). Cate- gories are hledger-style account names, optionally indented. There must be at least two spaces between the category and the quantity. Quantities can be written in two ways: 1. a series of dots (period characters). Each dot represents "a quar- ter" - eg, a quarter hour. Spaces can be used to group dots into hours, for easier counting. 2. a number (integer or decimal), representing "units" - eg, hours. A good alternative when dots are cumbersome. (A number also can record negative quantities.) Blank lines and lines beginning with #, ; or * are ignored. An exam- ple: # 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 . Or with numbers: 2016/2/3 inc:client1 4 fos:hledger 3 biz:research 1 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-2016 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.2 March 2017 hledger_timedot(5) hledger-1.2/LICENSE0000644000000000000000000010451313035210046012157 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.2/Setup.hs0000644000000000000000000000005613035210046012603 0ustar0000000000000000import Distribution.Simple main = defaultMain hledger-1.2/hledger.cabal0000644000000000000000000001756413067575305013602 0ustar0000000000000000-- This file has been generated from package.yaml by hpack version 0.17.0. -- -- see: https://github.com/sol/hpack name: hledger version: 1.2 synopsis: Command-line interface for the hledger accounting tool description: This is hledger's command-line interface. Its basic function is to read a plain text file describing financial transactions and produce useful reports. . hledger is a cross-platform program for tracking money, time, or any other commodity, using double-entry accounting and a simple, editable file format. It is inspired by and largely compatible with ledger(1). hledger provides command-line, curses and web interfaces, and aims to be a reliable, practical tool for daily use. 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==7.10.3, GHC==8.0 build-type: Simple cabal-version: >= 1.10 extra-source-files: bench/10000x1000x10.journal CHANGES README.md test/test.hs data-files: doc/hledger.1 doc/hledger.1.info doc/hledger.1.txt doc/other/hledger-api.1 doc/other/hledger-api.1.info doc/other/hledger-api.1.txt doc/other/hledger-ui.1 doc/other/hledger-ui.1.info doc/other/hledger-ui.1.txt doc/other/hledger-web.1 doc/other/hledger-web.1.info doc/other/hledger-web.1.txt doc/other/hledger_csv.5 doc/other/hledger_csv.5.info doc/other/hledger_csv.5.txt doc/other/hledger_journal.5 doc/other/hledger_journal.5.info doc/other/hledger_journal.5.txt doc/other/hledger_timeclock.5 doc/other/hledger_timeclock.5.info doc/other/hledger_timeclock.5.txt doc/other/hledger_timedot.5 doc/other/hledger_timedot.5.info doc/other/hledger_timedot.5.txt source-repository head type: git location: https://github.com/simonmichael/hledger flag oldtime description: If building with time < 1.5, also depend on old-locale. Set automatically by cabal. manual: False default: False 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 ghc-options: -Wall -fno-warn-unused-do-bind -fno-warn-name-shadowing -fno-warn-missing-signatures -fno-warn-type-defaults -fno-warn-orphans cpp-options: -DVERSION="1.2" build-depends: base >=4.8 && <5 , base-compat >=0.8.1 , directory , file-embed >=0.0.10 && <0.1 , filepath , here , pretty-show >=1.6.4 , process , temporary , tabular >=0.2 && <0.3 , hledger-lib >= 1.2 && < 1.3 , bytestring , containers , unordered-containers , cmdargs >=0.10 && <0.11 , csv , data-default >=0.5 , hashable >=1.2.4 , haskeline >=0.6 && <=0.8 , HUnit , mtl , mtl-compat , old-time , megaparsec >=5.0 && < 5.3 , regex-tdfa , safe >=0.2 , split >=0.1 && <0.3 , transformers , text >=0.11 , utf8-string >=0.3.5 && <1.1 , wizards ==1.0.* if impl(ghc <7.6) build-depends: ghc-prim if impl(ghc >=7.10) build-depends: shakespeare >=2.0.2.2 && <2.1 else build-depends: shakespeare >=1.0 && <2.1 , shakespeare-text >=1.0 && <1.2 if flag(oldtime) build-depends: time <1.5 , old-locale else build-depends: time >=1.5 if (!(os(windows))) && (flag(terminfo)) build-depends: terminfo exposed-modules: Hledger.Cli Hledger.Cli.Main Hledger.Cli.CliOptions Hledger.Cli.DocFiles Hledger.Cli.Tests Hledger.Cli.Utils Hledger.Cli.Version Hledger.Cli.Add Hledger.Cli.Accounts Hledger.Cli.Balance Hledger.Cli.Balancesheet Hledger.Cli.BalanceView Hledger.Cli.Cashflow Hledger.Cli.Help Hledger.Cli.Histogram Hledger.Cli.Incomestatement Hledger.Cli.Info Hledger.Cli.Man Hledger.Cli.Print Hledger.Cli.Register Hledger.Cli.Stats Text.Tabular.AsciiWide other-modules: Paths_hledger default-language: Haskell2010 executable hledger main-is: hledger-cli.hs 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 cpp-options: -DVERSION="1.2" build-depends: base >=4.8 && <5 , base-compat >=0.8.1 , directory , file-embed >=0.0.10 && <0.1 , filepath , here , pretty-show >=1.6.4 , process , temporary , tabular >=0.2 && <0.3 , hledger-lib >= 1.2 && < 1.3 , hledger == 1.2 , bytestring , containers , unordered-containers , cmdargs >=0.10 && <0.11 , csv , data-default >=0.5 , haskeline >=0.6 && <=0.8 , HUnit , mtl , mtl-compat , old-time , parsec >=3 , regex-tdfa , safe >=0.2 , split >=0.1 && <0.3 , text >=0.11 , utf8-string >=0.3.5 && <1.1 , wizards ==1.0.* if flag(threaded) ghc-options: -threaded if impl(ghc <7.6) build-depends: ghc-prim if impl(ghc >=7.10) build-depends: shakespeare >=2.0.2.2 && <2.1 else build-depends: shakespeare >=1.0 && <2.1 , shakespeare-text >=1.0 && <1.2 if flag(oldtime) build-depends: time <1.5 , old-locale else build-depends: time >=1.5 if (!(os(windows))) && (flag(terminfo)) build-depends: terminfo default-language: Haskell2010 test-suite test type: exitcode-stdio-1.0 main-is: test.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 cpp-options: -DVERSION="1.2" build-depends: base >=4.8 && <5 , base-compat >=0.8.1 , directory , file-embed >=0.0.10 && <0.1 , filepath , here , pretty-show >=1.6.4 , process , temporary , tabular >=0.2 && <0.3 , hledger-lib >= 1.2 && < 1.3 , hledger == 1.2 , bytestring , containers , unordered-containers , cmdargs >=0.10 && <0.11 , csv , data-default >=0.5 , haskeline >=0.6 && <=0.8 , HUnit , mtl , mtl-compat , old-time , parsec >=3 , regex-tdfa , safe >=0.2 , split >=0.1 && <0.3 , text >=0.11 , utf8-string >=0.3.5 && <1.1 , wizards ==1.0.* , test-framework , test-framework-hunit if impl(ghc <7.6) build-depends: ghc-prim if impl(ghc >=7.10) build-depends: shakespeare >=2.0.2.2 && <2.1 else build-depends: shakespeare >=1.0 && <2.1 , shakespeare-text >=1.0 && <1.2 if flag(oldtime) build-depends: time <1.5 , old-locale else build-depends: time >=1.5 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 build-depends: base >=4.8 && <5 , base-compat >=0.8.1 , directory , file-embed >=0.0.10 && <0.1 , filepath , here , pretty-show >=1.6.4 , process , temporary , tabular >=0.2 && <0.3 , hledger-lib >= 1.2 && < 1.3 , hledger == 1.2 , criterion , html , timeit if flag(oldtime) build-depends: time <1.5 , old-locale else build-depends: time >=1.5 default-language: Haskell2010 hledger-1.2/bench/10000x1000x10.journal0000644000000000000000000454013613035210046015320 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.2/CHANGES0000644000000000000000000006425613067576503012200 0ustar0000000000000000User-visible changes in the hledger and hledger-lib packages. See also the project change log. # 1.2 (2016/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: ```journal = ^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 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: - The hledger packages now have man pages, based on the current user manual, thanks to the mighty pandoc (#282). 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 libaries, 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.2/README.md0000644000000000000000000003107113067314162012440 0ustar0000000000000000# hledger ## lightweight, portable, dependable accounting tools hledger is a computer program for easily tracking money, time, or other commodities, on unix, mac and windows (and web-capable mobile devices, to some extent). It is first a command-line tool, but there are also curses-style and web interfaces, and a Haskell library (http://hackage.haskell.org/package/hledger-lib) for building your own programs and scripts (hledger is written in Haskell). hledger was inspired by and is largely compatible with Ledger. hledger is free software available under the GNU General Public License v3+. hledger aims to help both computer experts and regular folks to gain clarity and control in their finances and time management, but currently it is a bit more suited to techies. I use it every day to: - track spending and income - see time reports by day/week/month/project - get accurate numbers for client billing and tax filing - track invoices Though limited in features, hledger is lightweight, usable and reliable. For some, it is a simpler, less distracting, more future-proof alternative to Quicken or GnuCash. For more, see http://hledger.org. ##Support ### Backers Support us with a monthly donation and help us continue our activities. [[Become a backer](https://opencollective.com/hledger#backer)] ### Sponsors Become a sponsor and get your logo on our README on Github with a link to your site. [[Become a sponsor](https://opencollective.com/hledger#sponsor)] [![license](https://img.shields.io/badge/license-GPLv3+-brightgreen.svg)](http://www.gnu.org/licenses/gpl.html) [![OpenCollective](https://opencollective.com/hledger/backers/badge.svg)](#backers) [![OpenCollective](https://opencollective.com/hledger/sponsors/badge.svg)](#sponsors) [![bountysource](https://api.bountysource.com/badge/team?team_id=75979&style=bounties_received)](https://github.com/simonmichael/hledger/issues?q=label:bounty) [![github issues](https://img.shields.io/github/issues/simonmichael/hledger.svg)](http://bugs.hledger.org) [![on hackage](https://img.shields.io/hackage/v/hledger.svg?label=hackage&colorB=green)](http://hackage.haskell.org/package/hledger) [![on stackage nightly](http://stackage.org/package/hledger/badge/nightly)](http://stackage.org/nightly/package/hledger) [![on stackage lts](http://stackage.org/package/hledger/badge/lts)](http://stackage.org/lts/package/hledger) [![on stackage lts 7](http://stackage.org/package/hledger/badge/lts-7)](http://stackage.org/lts-7/package/hledger) [![travis build status](https://img.shields.io/travis/simonmichael/hledger.svg)](https://travis-ci.org/simonmichael/hledger) [![](https://img.shields.io/hackage-deps/v/hledger-lib.svg?label=hledger-lib+bounds)](http://packdeps.haskellers.com/feed?needle=hledger-lib) [![](https://img.shields.io/hackage-deps/v/hledger.svg?label=hledger+bounds)](http://packdeps.haskellers.com/feed?needle=hledger) [![](https://img.shields.io/hackage-deps/v/hledger-ui.svg?label=hledger-ui+bounds)](http://packdeps.haskellers.com/feed?needle=hledger-ui) [![](https://img.shields.io/hackage-deps/v/hledger-web.svg?label=hledger-web+bounds)](http://packdeps.haskellers.com/feed?needle=hledger-web) [![](https://img.shields.io/hackage-deps/v/hledger-api.svg?label=hledger-api+bounds)](http://packdeps.haskellers.com/feed?needle=hledger-api) hledger-1.2/test/test.hs0000644000000000000000000000033313035210046013437 0ustar0000000000000000import Hledger.Cli (tests_Hledger_Cli) import Test.Framework.Providers.HUnit (hUnitTestToTests) import Test.Framework.Runners.Console (defaultMain) main :: IO () main = defaultMain $ hUnitTestToTests tests_Hledger_Cli