refactor: much renaming of ledger -> journal, hopefully the right amount
This commit is contained in:
parent
ed1c3361b1
commit
7d7159609b
@ -23,15 +23,15 @@ import Text.ParserCombinators.Parsec
|
||||
import Hledger.Cli.Utils (readJournalWithOpts)
|
||||
import qualified Data.Foldable as Foldable (find)
|
||||
|
||||
-- | Read ledger transactions from the terminal, prompting for each field,
|
||||
-- and append them to the ledger file. If the ledger came from stdin, this
|
||||
-- | Read transactions from the terminal, prompting for each field,
|
||||
-- and append them to the journal file. If the journal came from stdin, this
|
||||
-- command has no effect.
|
||||
add :: [Opt] -> [String] -> Journal -> IO ()
|
||||
add opts args j
|
||||
| filepath j == "-" = return ()
|
||||
| otherwise = do
|
||||
hPutStrLn stderr $
|
||||
"Enter one or more transactions, which will be added to your ledger file.\n"
|
||||
"Enter one or more transactions, which will be added to your journal file.\n"
|
||||
++"To complete a transaction, enter . as account name. To quit, press control-c."
|
||||
today <- getCurrentDay
|
||||
getAndAddTransactions j opts args today `catch` (\e -> unless (isEOFError e) $ ioError e)
|
||||
@ -148,13 +148,13 @@ appendToJournalFile Journal{filepath=f, jtext=t} s =
|
||||
then putStr $ sep ++ s
|
||||
else appendFile f $ sep++s
|
||||
where
|
||||
-- XXX we are looking at the original raw text from when the ledger
|
||||
-- XXX we are looking at the original raw text from when the journal
|
||||
-- was first read, but that's good enough for now
|
||||
sep | null $ strip t = ""
|
||||
| otherwise = replicate (2 - min 2 (length lastnls)) '\n'
|
||||
where lastnls = takeWhile (=='\n') $ reverse t
|
||||
|
||||
-- | Convert a string of ledger data into a register report.
|
||||
-- | Convert a string of journal data into a register report.
|
||||
registerFromString :: String -> IO String
|
||||
registerFromString s = do
|
||||
now <- getCurrentLocalTime
|
||||
|
||||
@ -4,7 +4,7 @@
|
||||
A ledger-compatible @balance@ command.
|
||||
|
||||
ledger's balance command is easy to use but not easy to describe
|
||||
precisely. In the examples below we'll use sample.ledger, which has the
|
||||
precisely. In the examples below we'll use sample.journal, which has the
|
||||
following account tree:
|
||||
|
||||
@
|
||||
@ -29,7 +29,7 @@ sum of any transactions in that account plus any balances from
|
||||
subaccounts:
|
||||
|
||||
@
|
||||
$ hledger -f sample.ledger balance
|
||||
$ hledger -f sample.journal balance
|
||||
$-1 assets
|
||||
$1 bank:saving
|
||||
$-2 cash
|
||||
@ -52,7 +52,7 @@ The --depth argument can be used to limit the depth of the balance report.
|
||||
So, to see just the top level accounts:
|
||||
|
||||
@
|
||||
$ hledger -f sample.ledger balance --depth 1
|
||||
$ hledger -f sample.journal balance --depth 1
|
||||
$-1 assets
|
||||
$2 expenses
|
||||
$-2 income
|
||||
@ -67,7 +67,7 @@ accounts whose name matches one of the patterns, plus their parents
|
||||
(elided) and subaccounts. So with the pattern o we get:
|
||||
|
||||
@
|
||||
$ hledger -f sample.ledger balance o
|
||||
$ hledger -f sample.journal balance o
|
||||
$1 expenses:food
|
||||
$-2 income
|
||||
$-1 gifts
|
||||
@ -116,7 +116,7 @@ balance opts args j = do
|
||||
t <- getCurrentLocalTime
|
||||
putStr $ showBalanceReport opts (optsToFilterSpec opts args t) j
|
||||
|
||||
-- | Generate a balance report with the specified options for this ledger.
|
||||
-- | Generate a balance report with the specified options for this journal.
|
||||
showBalanceReport :: [Opt] -> FilterSpec -> Journal -> String
|
||||
showBalanceReport opts filterspec j = acctsstr ++ totalstr
|
||||
where
|
||||
|
||||
@ -1,5 +1,5 @@
|
||||
{-|
|
||||
Convert account data in CSV format (eg downloaded from a bank) to ledger
|
||||
Convert account data in CSV format (eg downloaded from a bank) to journal
|
||||
format, and print it on stdout. See the manual for more details.
|
||||
-}
|
||||
|
||||
@ -31,7 +31,7 @@ import Test.HUnit
|
||||
|
||||
{- |
|
||||
A set of data definitions and account-matching patterns sufficient to
|
||||
convert a particular CSV data file into meaningful ledger transactions. See above.
|
||||
convert a particular CSV data file into meaningful journal transactions. See above.
|
||||
-}
|
||||
data CsvRules = CsvRules {
|
||||
dateField :: Maybe FieldPosition,
|
||||
|
||||
@ -15,7 +15,7 @@ import System.IO.UTF8
|
||||
#endif
|
||||
|
||||
|
||||
-- | Print ledger transactions in standard format.
|
||||
-- | Print journal transactions in standard format.
|
||||
print' :: [Opt] -> [String] -> Journal -> IO ()
|
||||
print' opts args j = do
|
||||
t <- getCurrentLocalTime
|
||||
|
||||
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-|
|
||||
|
||||
Print some statistics for the ledger.
|
||||
Print some statistics for the journal.
|
||||
|
||||
-}
|
||||
|
||||
@ -17,7 +17,7 @@ import System.IO.UTF8
|
||||
|
||||
|
||||
-- like Register.summarisePostings
|
||||
-- | Print various statistics for the ledger.
|
||||
-- | Print various statistics for the journal.
|
||||
stats :: [Opt] -> [String] -> Journal -> IO ()
|
||||
stats opts args j = do
|
||||
today <- getCurrentDay
|
||||
|
||||
@ -44,8 +44,8 @@ data Loc = Loc {
|
||||
-- | The screens available within the user interface.
|
||||
data Screen = BalanceScreen -- ^ like hledger balance, shows accounts
|
||||
| RegisterScreen -- ^ like hledger register, shows transaction-postings
|
||||
| PrintScreen -- ^ like hledger print, shows ledger transactions
|
||||
-- | LedgerScreen -- ^ shows the raw ledger
|
||||
| PrintScreen -- ^ like hledger print, shows journal transactions
|
||||
-- | LedgerScreen -- ^ shows the raw journal
|
||||
deriving (Eq,Show)
|
||||
|
||||
-- | Run the vty (curses-style) ui.
|
||||
|
||||
@ -82,7 +82,7 @@ server opts args j =
|
||||
get "/balance" $ command [] showBalanceReport -- String -> ReaderT Env (StateT Response IO) () -> State Loli ()
|
||||
get "/register" $ command [] showRegisterReport
|
||||
get "/histogram" $ command [] showHistogram
|
||||
get "/transactions" $ ledgerpage [] j''' (showTransactions (optsToFilterSpec opts' args' t))
|
||||
get "/transactions" $ journalpage [] j''' (showTransactions (optsToFilterSpec opts' args' t))
|
||||
post "/transactions" $ handleAddform j'''
|
||||
get "/env" $ getenv >>= (text . show)
|
||||
get "/params" $ getenv >>= (text . show . Hack.Contrib.Request.params)
|
||||
@ -98,8 +98,8 @@ redirect u c = response $ Hack.Contrib.Response.redirect u c
|
||||
reqParamUtf8 :: Hack.Env -> String -> [String]
|
||||
reqParamUtf8 env p = map snd $ filter ((==p).fst) $ Hack.Contrib.Request.params env
|
||||
|
||||
ledgerpage :: [String] -> Journal -> (Journal -> String) -> AppUnit
|
||||
ledgerpage msgs j f = do
|
||||
journalpage :: [String] -> Journal -> (Journal -> String) -> AppUnit
|
||||
journalpage msgs j f = do
|
||||
env <- getenv
|
||||
(jE, _) <- io $ journalReloadIfChanged [] j
|
||||
let (j'', _) = either (\e -> (j,e)) (\j' -> (j',"")) jE
|
||||
@ -309,7 +309,7 @@ handleAddform j = do
|
||||
handle _ (Failure errs) = hsp errs addform
|
||||
handle ti (Success t) = do
|
||||
io $ journalAddTransaction j t >>= journalReload
|
||||
ledgerpage [msg] j (showTransactions (optsToFilterSpec [] [] ti))
|
||||
journalpage [msg] j (showTransactions (optsToFilterSpec [] [] ti))
|
||||
where msg = printf "Added transaction:\n%s" (show t)
|
||||
|
||||
nbsp :: XML
|
||||
|
||||
@ -8,7 +8,7 @@ where
|
||||
import System.Console.GetOpt
|
||||
import System.Environment
|
||||
import Hledger.Cli.Version (timeprogname)
|
||||
import Hledger.Read (myLedgerPath,myTimelogPath)
|
||||
import Hledger.Read (myJournalPath, myTimelogPath)
|
||||
import Hledger.Data.Utils
|
||||
import Hledger.Data.Types
|
||||
import Hledger.Data.Dates
|
||||
@ -25,16 +25,16 @@ help1 =
|
||||
" hledger [OPTIONS] convert CSVFILE\n" ++
|
||||
" hledger [OPTIONS] stats\n" ++
|
||||
"\n" ++
|
||||
"hledger reads your ~/.ledger file, or another specified with $LEDGER or -f\n" ++
|
||||
"hledger reads your ~/.journal file, or another specified with $LEDGER or -f\n" ++
|
||||
"\n" ++
|
||||
"COMMAND is one of (may be abbreviated):\n" ++
|
||||
" add - prompt for new transactions and add them to the ledger\n" ++
|
||||
" add - prompt for new transactions and add them to the journal\n" ++
|
||||
" balance - show accounts, with balances\n" ++
|
||||
" convert - read CSV bank data and display in ledger format\n" ++
|
||||
" convert - read CSV bank data and display in journal format\n" ++
|
||||
" histogram - show a barchart of transactions per day or other interval\n" ++
|
||||
" print - show transactions in ledger format\n" ++
|
||||
" print - show transactions in journal format\n" ++
|
||||
" register - show transactions as a register with running balance\n" ++
|
||||
" stats - show various statistics for a ledger\n" ++
|
||||
" stats - show various statistics for a journal\n" ++
|
||||
" vty - run a simple curses-style UI" ++
|
||||
#ifdef VTY
|
||||
"\n" ++
|
||||
@ -69,7 +69,7 @@ help2 = usageInfo "Options:\n" options
|
||||
-- | Command-line options we accept.
|
||||
options :: [OptDescr Opt]
|
||||
options = [
|
||||
Option "f" ["file"] (ReqArg File "FILE") "use a different ledger/timelog file; - means stdin"
|
||||
Option "f" ["file"] (ReqArg File "FILE") "use a different journal/timelog file; - means stdin"
|
||||
,Option "" ["no-new-accounts"] (NoArg NoNewAccts) "don't allow to create new accounts"
|
||||
,Option "b" ["begin"] (ReqArg Begin "DATE") "report on transactions on or after this date"
|
||||
,Option "e" ["end"] (ReqArg End "DATE") "report on transactions before this date"
|
||||
@ -282,7 +282,7 @@ usingTimeProgramName = do
|
||||
journalFilePathFromOpts :: [Opt] -> IO String
|
||||
journalFilePathFromOpts opts = do
|
||||
istimequery <- usingTimeProgramName
|
||||
f <- if istimequery then myTimelogPath else myLedgerPath
|
||||
f <- if istimequery then myTimelogPath else myJournalPath
|
||||
return $ last $ f : optValuesForConstructor File opts
|
||||
|
||||
-- | Gather filter pattern arguments into a list of account patterns and a
|
||||
|
||||
@ -15,7 +15,7 @@ documentation in the source, run by doing @make doctest@ in the hledger
|
||||
source tree. They are no longer used, but here is an example:
|
||||
|
||||
@
|
||||
$ hledger -f sample.ledger balance o
|
||||
$ hledger -f sample.journal balance o
|
||||
$1 expenses:food
|
||||
$-2 income
|
||||
$-1 gifts
|
||||
@ -107,7 +107,7 @@ tests = TestList [
|
||||
|
||||
,"balance report tests" ~:
|
||||
let (opts,args) `gives` es = do
|
||||
l <- sampleledgerwithopts opts args
|
||||
l <- samplejournalwithopts opts args
|
||||
t <- getCurrentLocalTime
|
||||
showBalanceReport opts (optsToFilterSpec opts args t) l `is` unlines es
|
||||
in TestList
|
||||
@ -384,7 +384,7 @@ tests = TestList [
|
||||
"assets:bank" `isSubAccountNameOf` "my assets" `is` False
|
||||
|
||||
,"default year" ~: do
|
||||
rl <- readJournal Nothing defaultyear_ledger_str >>= either error return
|
||||
rl <- readJournal Nothing defaultyear_journal_str >>= either error return
|
||||
tdate (head $ jtxns rl) `is` fromGregorian 2009 1 1
|
||||
return ()
|
||||
|
||||
@ -410,7 +410,7 @@ tests = TestList [
|
||||
"print expenses" ~:
|
||||
do
|
||||
let args = ["expenses"]
|
||||
l <- sampleledgerwithopts [] args
|
||||
l <- samplejournalwithopts [] args
|
||||
t <- getCurrentLocalTime
|
||||
showTransactions (optsToFilterSpec [] args t) l `is` unlines
|
||||
["2008/06/03 * eat & shop"
|
||||
@ -422,7 +422,7 @@ tests = TestList [
|
||||
|
||||
, "print report with depth arg" ~:
|
||||
do
|
||||
l <- sampleledger
|
||||
l <- samplejournal
|
||||
t <- getCurrentLocalTime
|
||||
showTransactions (optsToFilterSpec [Depth "2"] [] t) l `is` unlines
|
||||
["2008/01/01 income"
|
||||
@ -457,7 +457,7 @@ tests = TestList [
|
||||
|
||||
"register report with no args" ~:
|
||||
do
|
||||
l <- sampleledger
|
||||
l <- samplejournal
|
||||
showRegisterReport [] (optsToFilterSpec [] [] t1) l `is` unlines
|
||||
["2008/01/01 income assets:bank:checking $1 $1"
|
||||
," income:salary $-1 0"
|
||||
@ -475,7 +475,7 @@ tests = TestList [
|
||||
,"register report with cleared option" ~:
|
||||
do
|
||||
let opts = [Cleared]
|
||||
l <- readJournalWithOpts opts sample_ledger_str
|
||||
l <- readJournalWithOpts opts sample_journal_str
|
||||
showRegisterReport opts (optsToFilterSpec opts [] t1) l `is` unlines
|
||||
["2008/06/03 eat & shop expenses:food $1 $1"
|
||||
," expenses:supplies $1 $2"
|
||||
@ -487,7 +487,7 @@ tests = TestList [
|
||||
,"register report with uncleared option" ~:
|
||||
do
|
||||
let opts = [UnCleared]
|
||||
l <- readJournalWithOpts opts sample_ledger_str
|
||||
l <- readJournalWithOpts opts sample_journal_str
|
||||
showRegisterReport opts (optsToFilterSpec opts [] t1) l `is` unlines
|
||||
["2008/01/01 income assets:bank:checking $1 $1"
|
||||
," income:salary $-1 0"
|
||||
@ -512,21 +512,21 @@ tests = TestList [
|
||||
|
||||
,"register report with account pattern" ~:
|
||||
do
|
||||
l <- sampleledger
|
||||
l <- samplejournal
|
||||
showRegisterReport [] (optsToFilterSpec [] ["cash"] t1) l `is` unlines
|
||||
["2008/06/03 eat & shop assets:cash $-2 $-2"
|
||||
]
|
||||
|
||||
,"register report with account pattern, case insensitive" ~:
|
||||
do
|
||||
l <- sampleledger
|
||||
l <- samplejournal
|
||||
showRegisterReport [] (optsToFilterSpec [] ["cAsH"] t1) l `is` unlines
|
||||
["2008/06/03 eat & shop assets:cash $-2 $-2"
|
||||
]
|
||||
|
||||
,"register report with display expression" ~:
|
||||
do
|
||||
l <- sampleledger
|
||||
l <- samplejournal
|
||||
let gives displayexpr =
|
||||
(registerdates (showRegisterReport opts (optsToFilterSpec opts [] t1) l) `is`)
|
||||
where opts = [Display displayexpr]
|
||||
@ -538,9 +538,9 @@ tests = TestList [
|
||||
|
||||
,"register report with period expression" ~:
|
||||
do
|
||||
l <- sampleledger
|
||||
l <- samplejournal
|
||||
let periodexpr `gives` dates = do
|
||||
l' <- sampleledgerwithopts opts []
|
||||
l' <- samplejournalwithopts opts []
|
||||
registerdates (showRegisterReport opts (optsToFilterSpec opts [] t1) l') `is` dates
|
||||
where opts = [Period periodexpr]
|
||||
"" `gives` ["2008/01/01","2008/06/01","2008/06/02","2008/06/03","2008/12/31"]
|
||||
@ -568,7 +568,7 @@ tests = TestList [
|
||||
|
||||
, "register report with depth arg" ~:
|
||||
do
|
||||
l <- sampleledger
|
||||
l <- samplejournal
|
||||
let opts = [Depth "2"]
|
||||
showRegisterReport opts (optsToFilterSpec opts [] t1) l `is` unlines
|
||||
["2008/01/01 income income:salary $-1 $-1"
|
||||
@ -636,7 +636,7 @@ tests = TestList [
|
||||
-- "next january" `gives` "2009/01/01"
|
||||
|
||||
,"subAccounts" ~: do
|
||||
l <- liftM (journalToLedger nullfilterspec) sampleledger
|
||||
l <- liftM (journalToLedger nullfilterspec) samplejournal
|
||||
let a = ledgerAccount l "assets"
|
||||
map aname (ledgerSubAccounts l a) `is` ["assets:bank","assets:cash"]
|
||||
|
||||
@ -683,11 +683,11 @@ tests = TestList [
|
||||
date1 = parsedate "2008/11/26"
|
||||
t1 = LocalTime date1 midday
|
||||
|
||||
sampleledger = readJournalWithOpts [] sample_ledger_str
|
||||
sampleledgerwithopts opts _ = readJournalWithOpts opts sample_ledger_str
|
||||
samplejournal = readJournalWithOpts [] sample_journal_str
|
||||
samplejournalwithopts opts _ = readJournalWithOpts opts sample_journal_str
|
||||
|
||||
sample_ledger_str = unlines
|
||||
["; A sample ledger file."
|
||||
sample_journal_str = unlines
|
||||
["; A sample journal file."
|
||||
,";"
|
||||
,"; Sets up this account tree:"
|
||||
,"; assets"
|
||||
@ -729,7 +729,7 @@ sample_ledger_str = unlines
|
||||
,";final comment"
|
||||
]
|
||||
|
||||
defaultyear_ledger_str = unlines
|
||||
defaultyear_journal_str = unlines
|
||||
["Y2009"
|
||||
,""
|
||||
,"01/01 A"
|
||||
@ -737,7 +737,7 @@ defaultyear_ledger_str = unlines
|
||||
," b"
|
||||
]
|
||||
|
||||
write_sample_ledger = writeFile "sample.ledger" sample_ledger_str
|
||||
write_sample_journal = writeFile "sample.journal" sample_journal_str
|
||||
|
||||
entry2_str = unlines
|
||||
["2007/01/27 * joes diner"
|
||||
@ -787,7 +787,7 @@ periodic_entry3_str = unlines
|
||||
,""
|
||||
]
|
||||
|
||||
ledger1_str = unlines
|
||||
journal1_str = unlines
|
||||
[""
|
||||
,"2007/01/27 * joes diner"
|
||||
," expenses:food:dining $10.00"
|
||||
@ -802,7 +802,7 @@ ledger1_str = unlines
|
||||
,""
|
||||
]
|
||||
|
||||
ledger2_str = unlines
|
||||
journal2_str = unlines
|
||||
[";comment"
|
||||
,"2007/01/27 * joes diner"
|
||||
," expenses:food:dining $10.00"
|
||||
@ -810,7 +810,7 @@ ledger2_str = unlines
|
||||
,""
|
||||
]
|
||||
|
||||
ledger3_str = unlines
|
||||
journal3_str = unlines
|
||||
["2007/01/27 * joes diner"
|
||||
," expenses:food:dining $10.00"
|
||||
,";intra-entry comment"
|
||||
@ -818,7 +818,7 @@ ledger3_str = unlines
|
||||
,""
|
||||
]
|
||||
|
||||
ledger4_str = unlines
|
||||
journal4_str = unlines
|
||||
["!include \"somefile\""
|
||||
,"2007/01/27 * joes diner"
|
||||
," expenses:food:dining $10.00"
|
||||
@ -826,9 +826,9 @@ ledger4_str = unlines
|
||||
,""
|
||||
]
|
||||
|
||||
ledger5_str = ""
|
||||
journal5_str = ""
|
||||
|
||||
ledger6_str = unlines
|
||||
journal6_str = unlines
|
||||
["~ monthly from 2007/1/21"
|
||||
," expenses:entertainment $16.23 ;netflix"
|
||||
," assets:checking"
|
||||
@ -839,7 +839,7 @@ ledger6_str = unlines
|
||||
,""
|
||||
]
|
||||
|
||||
ledger7_str = unlines
|
||||
journal7_str = unlines
|
||||
["2007/01/01 * opening balance"
|
||||
," assets:cash $4.82"
|
||||
," equity:opening balances "
|
||||
@ -1059,7 +1059,7 @@ journal7 = Journal
|
||||
|
||||
ledger7 = journalToLedger nullfilterspec journal7
|
||||
|
||||
ledger8_str = unlines
|
||||
journal8_str = unlines
|
||||
["2008/1/1 test "
|
||||
," a:b 10h @ $40"
|
||||
," c:d "
|
||||
|
||||
162
MANUAL.markdown
162
MANUAL.markdown
@ -24,8 +24,8 @@ hledger because I wanted to build financial tools in the Haskell
|
||||
programming language rather than in C++.
|
||||
|
||||
hledger's basic function is to generate register and balance reports from
|
||||
a plain text ledger file, at the command line or via the web or curses
|
||||
interface. You can use it to, eg,
|
||||
a plain text general journal file, at the command line or via the web or
|
||||
curses interface. You can use it to, eg,
|
||||
|
||||
- track spending and income
|
||||
- see time reports by day/week/month/project
|
||||
@ -96,16 +96,16 @@ Basic usage is:
|
||||
[COMMAND](#commands) is one of: add, balance, chart, convert, histogram,
|
||||
print, register, stats, ui, web, test (defaulting to balance). The
|
||||
optional [PATTERNS](#filter-patterns) are regular expressions which select
|
||||
a subset of the ledger data.
|
||||
a subset of the journal data.
|
||||
|
||||
hledger looks for data in a ledger file, usually `.ledger` in your home
|
||||
hledger looks for data in a journal file, usually `.journal` in your home
|
||||
directory. You can specify a different file with the -f option (use - for
|
||||
standard input) or `LEDGER` environment variable.
|
||||
|
||||
To get started, make yourself a ledger file containing some
|
||||
To get started, make yourself a journal file containing some
|
||||
transactions. You can copy the sample file below (or
|
||||
[sample.ledger](http://joyful.com/repos/hledger/data/sample.ledger)) and save
|
||||
it as `.ledger` in your home directory. Or, just run `hledger add` and
|
||||
[sample.journal](http://joyful.com/repos/hledger/data/sample.journal)) and save
|
||||
it as `.journal` in your home directory. Or, just run `hledger add` and
|
||||
enter a few transactions. Now you can try some of these commands, or read
|
||||
on:
|
||||
|
||||
@ -117,7 +117,7 @@ on:
|
||||
hledger reg checking # checking transactions
|
||||
hledger reg desc:shop # transactions with shop in the description
|
||||
hledger histogram # transactions per day, or other interval
|
||||
hledger add # add some new transactions to the ledger file
|
||||
hledger add # add some new transactions to the journal file
|
||||
hledger vty # curses ui, if installed with -fvty
|
||||
hledger web # web ui, if installed with -fweb or -fweb610
|
||||
hledger chart # make a balance chart, if installed with -fchart
|
||||
@ -126,12 +126,12 @@ You'll find more examples below.
|
||||
|
||||
### File format
|
||||
|
||||
hledger's data file, aka the ledger, is a plain text representation of a
|
||||
standard accounting journal. It contains a number of transactions, each
|
||||
hledger's data file, aka the journal, is a plain text representation of a
|
||||
standard accounting general journal. It contains a number of transactions, each
|
||||
describing a transfer of money (or another commodity) between two or more
|
||||
named accounts. Here's an example:
|
||||
|
||||
; A sample ledger file. This is a comment.
|
||||
; A samplejournal 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
|
||||
@ -174,7 +174,7 @@ tools. For more details, see
|
||||
### Overview
|
||||
|
||||
This version of hledger mimics a subset of ledger 3.x, and adds some
|
||||
features of its own. We currently support regular ledger entries, timelog
|
||||
features of its own. We currently support regular journal transactions, timelog
|
||||
entries, multiple commodities, (fixed) price history, virtual postings,
|
||||
filtering by account and description, the familiar print, register &
|
||||
balance commands and several new commands. We handle (almost) the full
|
||||
@ -183,64 +183,64 @@ of a simple date predicate.
|
||||
|
||||
Here is the command-line help:
|
||||
|
||||
Usage: hledger [OPTIONS] [COMMAND [PATTERNS]]
|
||||
Usage: hledger [OPTIONS] COMMAND [PATTERNS]
|
||||
hledger [OPTIONS] convert CSVFILE
|
||||
hledger [OPTIONS] stats
|
||||
|
||||
hledger uses your ~/.ledger or $LEDGER file, or another specified with -f
|
||||
|
||||
|
||||
hledger reads your ~/.journal file, or another specified with $LEDGER or -f FILE
|
||||
|
||||
COMMAND is one of (may be abbreviated):
|
||||
add - prompt for new transactions and add them to the ledger
|
||||
balance - show accounts, with balances
|
||||
convert - read CSV bank data and display in ledger format
|
||||
histogram - show a barchart of transactions per day or other interval
|
||||
print - show transactions in ledger format
|
||||
register - show transactions as a register with running balance
|
||||
stats - show various statistics for a ledger
|
||||
vty - run a simple curses-style UI
|
||||
web - run a simple web-based UI
|
||||
chart - generate balances pie chart
|
||||
test - run self-tests
|
||||
|
||||
add - prompt for new transactions and add them to the journal
|
||||
balance - show accounts, with balances
|
||||
convert - read CSV bank data and display in journal format
|
||||
histogram - show a barchart of transactions per day or other interval
|
||||
print - show transactions in journal format
|
||||
register - show transactions as a register with running balance
|
||||
stats - show various statistics for a journal
|
||||
vty - run a simple curses-style UI (if installed with -fvty)
|
||||
web - run a simple web-based UI (if installed with -fweb or -fweb610)
|
||||
chart - generate balances pie charts (if installed with -fchart)
|
||||
test - run self-tests
|
||||
|
||||
PATTERNS are regular expressions which filter by account name.
|
||||
Prefix with desc: to filter by transaction description instead.
|
||||
Prefix with not: to negate a pattern. When using both, not: comes last.
|
||||
|
||||
|
||||
DATES can be y/m/d or ledger-style smart dates like "last month".
|
||||
|
||||
|
||||
Use --help-options to see OPTIONS, or --help-all/-H.
|
||||
|
||||
Options:
|
||||
-f FILE --file=FILE use a different ledger/timelog file; - means stdin
|
||||
--no-new-accounts don't allow to create new accounts
|
||||
-b DATE --begin=DATE report on transactions on or after this date
|
||||
-e DATE --end=DATE report on transactions before this date
|
||||
-p EXPR --period=EXPR report on transactions during the specified period
|
||||
and/or with the specified reporting interval
|
||||
-C --cleared report only on cleared transactions
|
||||
-U --uncleared report only on uncleared transactions
|
||||
-B --cost, --basis report cost of commodities
|
||||
--depth=N hide accounts/transactions deeper than this
|
||||
-d EXPR --display=EXPR show only transactions matching EXPR (where
|
||||
EXPR is 'dOP[DATE]' and OP is <, <=, =, >=, >)
|
||||
--effective use transactions' effective dates, if any
|
||||
-E --empty show empty/zero things which are normally elided
|
||||
-R --real report only on real (non-virtual) transactions
|
||||
--flat balance report: show full account names, unindented
|
||||
--no-total balance report: hide the final total
|
||||
-W --weekly register report: show weekly summary
|
||||
-M --monthly register report: show monthly summary
|
||||
-Q --quarterly register report: show quarterly summary
|
||||
-Y --yearly register report: show yearly summary
|
||||
--base-url web: use this base url (default http://localhost:PORT)
|
||||
--port web: serve on tcp port N (default 5000)
|
||||
-h --help show this help
|
||||
-V --version show version information
|
||||
-v --verbose show more verbose output
|
||||
--binary-filename show the download filename for this hledger build
|
||||
--debug show extra debug output; implies verbose
|
||||
--debug-vty run vty command with no vty output, showing console
|
||||
-o FILE --output=FILE chart: output filename (default: hledger.png)
|
||||
--items=N chart: number of accounts to show (default: 10)
|
||||
--size=WIDTHxHEIGHT chart: image size (default: 600x400)
|
||||
|
||||
-f FILE --file=FILE use a different journal/timelog file; - means stdin
|
||||
--no-new-accounts don't allow to create new accounts
|
||||
-b DATE --begin=DATE report on transactions on or after this date
|
||||
-e DATE --end=DATE report on transactions before this date
|
||||
-p EXPR --period=EXPR report on transactions during the specified period
|
||||
and/or with the specified reporting interval
|
||||
-C --cleared report only on cleared transactions
|
||||
-U --uncleared report only on uncleared transactions
|
||||
-B --cost, --basis report cost of commodities
|
||||
--depth=N hide accounts/transactions deeper than this
|
||||
-d EXPR --display=EXPR show only transactions matching EXPR (where
|
||||
EXPR is 'dOP[DATE]' and OP is <, <=, =, >=, >)
|
||||
--effective use transactions' effective dates, if any
|
||||
-E --empty show empty/zero things which are normally elided
|
||||
-R --real report only on real (non-virtual) transactions
|
||||
--flat balance: show full account names, unindented
|
||||
--drop=N balance: with --flat, elide first N account name components
|
||||
--no-total balance: hide the final total
|
||||
-W --weekly register, stats: report by week
|
||||
-M --monthly register, stats: report by month
|
||||
-Q --quarterly register, stats: report by quarter
|
||||
-Y --yearly register, stats: report by year
|
||||
-v --verbose show more verbose output
|
||||
--debug show extra debug output; implies verbose
|
||||
--binary-filename show the download filename for this hledger build
|
||||
-V --version show version information
|
||||
-h --help show basic command-line usage
|
||||
--help-options show command-line options
|
||||
-H --help-all show command-line usage and options
|
||||
|
||||
### Commands
|
||||
|
||||
@ -250,9 +250,9 @@ These commands are read-only, that is they never modify your data.
|
||||
|
||||
##### print
|
||||
|
||||
The print command displays full transactions from the ledger file, tidily
|
||||
The print command displays full transactions from the journal file, tidily
|
||||
formatted and showing all amounts explicitly. The output of print is
|
||||
always valid ledger data.
|
||||
always a valid hledger journal.
|
||||
|
||||
hledger's print command also shows all unit prices in effect, or (with
|
||||
-B/--cost) shows cost amounts.
|
||||
@ -285,7 +285,7 @@ A final total is displayed, use `--no-total` to suppress this. Also, the
|
||||
`--depth N` option shows accounts only to the specified depth, useful for
|
||||
an overview:
|
||||
|
||||
$ for y in 2006 2007 2008 2009 2010; do echo; echo $y; hledger -f $y.ledger balance ^expenses --depth 2; done
|
||||
$ for y in 2006 2007 2008 2009 2010; do echo; echo $y; hledger -f $y.journal balance ^expenses --depth 2; done
|
||||
|
||||
With `--flat`, a non-hierarchical list of full account names is displayed
|
||||
instead. This mode shows just the accounts actually contributing to the
|
||||
@ -330,7 +330,7 @@ Examples:
|
||||
|
||||
##### stats
|
||||
|
||||
The stats command displays quick summary information for the whole ledger,
|
||||
The stats command displays quick summary information for the whole journal,
|
||||
or by period.
|
||||
|
||||
Examples:
|
||||
@ -354,12 +354,12 @@ This is an optional feature; see [installing](#installing).
|
||||
|
||||
#### Modifying commands
|
||||
|
||||
The following commands can alter your ledger file.
|
||||
The following commands can alter your journal file.
|
||||
|
||||
##### add
|
||||
|
||||
The add command prompts interactively for new transactions, and adds them
|
||||
to the ledger. It is experimental.
|
||||
to the journal. It is experimental.
|
||||
|
||||
Examples:
|
||||
|
||||
@ -393,22 +393,22 @@ permissions allow, disk is not full, etc.)
|
||||
|
||||
The convert command reads a
|
||||
[CSV](http://en.wikipedia.org/wiki/Comma-separated_values) file you have
|
||||
downloaded from your bank, and prints out the transactions in ledger
|
||||
format, suitable for adding to your ledger. It does not alter your ledger
|
||||
downloaded from your bank, and prints out the transactions in journal
|
||||
format, suitable for adding to your journal. It does not alter your journal
|
||||
directly.
|
||||
|
||||
This can be a lot quicker than entering every transaction by hand. (The
|
||||
downside is that you are less likely to notice if your bank makes an
|
||||
error!) Use it like this:
|
||||
|
||||
$ hledger convert FILE.csv >FILE.ledger
|
||||
$ hledger convert FILE.csv >FILE.journal
|
||||
|
||||
where FILE.csv is your downloaded csv file. This will convert the csv data
|
||||
using conversion rules defined in FILE.rules (auto-creating this file if
|
||||
needed), and save the output into a temporary ledger file. Then you should
|
||||
review FILE.ledger for problems; update the rules and convert again if
|
||||
needed), and save the output into a temporary journal file. Then you should
|
||||
review FILE.journal for problems; update the rules and convert again if
|
||||
needed; and finally copy/paste transactions which are new into your main
|
||||
ledger.
|
||||
journal.
|
||||
|
||||
###### .rules file
|
||||
|
||||
@ -438,7 +438,7 @@ Fargo checking account:
|
||||
|
||||
This says:
|
||||
|
||||
- the ledger account corresponding to this csv file is
|
||||
- the account corresponding to this csv file is
|
||||
assets:bank:checking
|
||||
- the first csv field is the date, the second is the amount, the
|
||||
fifth is the description
|
||||
@ -523,7 +523,7 @@ The [print](#print) command selects transactions which
|
||||
|
||||
##### Simple dates
|
||||
|
||||
Within a ledger file, dates must follow a fairly simple year/month/day
|
||||
Within a journal file, dates must follow a fairly simple year/month/day
|
||||
format. Examples:
|
||||
|
||||
> `2010/01/31` or `2010/1/31` or `2010-1-31` or `2010.1.31`
|
||||
@ -533,7 +533,7 @@ other places, accept [smart dates](#smart-dates) - more about those below.
|
||||
|
||||
##### Default year
|
||||
|
||||
You can set a default year with a `Y` directive in the ledger, then
|
||||
You can set a default year with a `Y` directive in the journal, then
|
||||
subsequent dates may be written as month/day. Eg:
|
||||
|
||||
Y2009
|
||||
@ -616,7 +616,7 @@ above can also be written as:
|
||||
-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 ledger data:
|
||||
earliest or latest transaction in your journal data:
|
||||
|
||||
-p "from 2009/1/1" (everything after january 1, 2009)
|
||||
-p "from 2009/1" (the same)
|
||||
@ -695,7 +695,7 @@ commodity. Eg, here one hundred euros was purchased at $1.35 per euro:
|
||||
|
||||
Secondly, you can set the price for a commodity as of a certain date, by
|
||||
entering a historical price record. These are lines beginning with "P",
|
||||
appearing anywhere in the ledger between transactions. Eg, here we say the
|
||||
appearing anywhere in the journal between transactions. Eg, here we say the
|
||||
exchange rate for 1 euro is $1.35 on 2009/1/1 (and thereafter, until a
|
||||
newer price record is found):
|
||||
|
||||
@ -734,7 +734,7 @@ fluctuating-value investments or capital gains.
|
||||
hledger will also read timelog files in timeclock.el format. As a
|
||||
convenience, if you invoke hledger via an "hours" symlink or copy, it uses
|
||||
your timelog file (\~/.timelog or $TIMELOG) by default, rather than your
|
||||
ledger.
|
||||
journal.
|
||||
|
||||
Timelog entries look like this:
|
||||
|
||||
@ -781,7 +781,7 @@ but ignored. There are also some subtle differences in parser behaviour
|
||||
has introduced additional syntax, which current hledger probably fails to
|
||||
parse.
|
||||
|
||||
Generally, it's easy to keep a ledger file that works with both hledger
|
||||
Generally, it's easy to keep a journal file that works with both hledger
|
||||
and c++ledger if you avoid the more esoteric syntax. Occasionally you'll
|
||||
need to make small edits to restore compatibility for one or the other.
|
||||
|
||||
|
||||
48
Makefile
48
Makefile
@ -10,7 +10,7 @@ CICMD=test
|
||||
#CICMD=web -f t.journal --debug
|
||||
|
||||
# command line to run during "make prof" and "make heap"
|
||||
PROFCMD=bin/hledgerp -f data/1000x1000x10.ledger balance >/dev/null
|
||||
PROFCMD=bin/hledgerp -f data/1000x1000x10.journal balance >/dev/null
|
||||
|
||||
# command to run during "make coverage"
|
||||
COVCMD=test
|
||||
@ -128,9 +128,9 @@ tools/criterionbench: tools/criterionbench.hs
|
||||
tools/progressionbench: tools/progressionbench.hs
|
||||
ghc --make tools/progressionbench.hs
|
||||
|
||||
# build the generateledger tool
|
||||
tools/generateledger: tools/generateledger.hs
|
||||
ghc --make tools/generateledger.hs
|
||||
# build the generatejournal tool
|
||||
tools/generatejournal: tools/generatejournal.hs
|
||||
ghc --make tools/generatejournal.hs
|
||||
|
||||
######################################################################
|
||||
# TESTING
|
||||
@ -208,27 +208,27 @@ fullcabaltest: setversion
|
||||
|
||||
# run performance benchmarks without saving results.
|
||||
# Requires some commands defined in bench.tests and some BENCHEXES defined above.
|
||||
quickbench: sampleledgers bench.tests tools/simplebench
|
||||
quickbench: samplejournals bench.tests tools/simplebench
|
||||
tools/simplebench -fbench.tests $(BENCHEXES)
|
||||
@rm -f benchresults.*
|
||||
|
||||
# run performance benchmarks and save textual results in profs/.
|
||||
# Requires some commands defined in bench.tests and some BENCHEXES defined above.
|
||||
simplebench: sampleledgers bench.tests tools/simplebench
|
||||
simplebench: samplejournals bench.tests tools/simplebench
|
||||
tools/simplebench -fbench.tests $(BENCHEXES) | tee profs/$(TIME).bench
|
||||
@rm -f benchresults.*
|
||||
@(cd profs; rm -f latest.bench; ln -s $(TIME).bench latest.bench)
|
||||
|
||||
# run criterion benchmark tests and save graphical results
|
||||
criterionbench: sampleledgers tools/criterionbench
|
||||
criterionbench: samplejournals tools/criterionbench
|
||||
tools/criterionbench -t png -k png
|
||||
|
||||
# run progression benchmark tests and save graphical results
|
||||
progressionbench: sampleledgers tools/progressionbench
|
||||
progressionbench: samplejournals tools/progressionbench
|
||||
tools/progressionbench -- -t png -k png
|
||||
|
||||
# generate, save, simplify and display an execution profile
|
||||
prof: sampleledgers hledgerp
|
||||
prof: samplejournals hledgerp
|
||||
@echo "Profiling: $(PROFCMD)"
|
||||
-$(PROFCMD) +RTS -p -RTS
|
||||
mv hledgerp.prof profs/$(TIME)-orig.prof
|
||||
@ -237,13 +237,13 @@ prof: sampleledgers hledgerp
|
||||
echo; cat profs/latest.prof
|
||||
|
||||
# generate and display an execution profile, don't save or simplify
|
||||
quickprof: sampleledgers hledgerp
|
||||
quickprof: samplejournals hledgerp
|
||||
@echo "Profiling: $(PROFCMD)"
|
||||
-$(PROFCMD) +RTS -p -RTS
|
||||
echo; cat hledgerp.prof
|
||||
|
||||
# generate, save and display a graphical heap profile
|
||||
heap: sampleledgers hledgerp
|
||||
heap: samplejournals hledgerp
|
||||
@echo "Profiling heap with: $(PROFCMD)"
|
||||
$(PROFCMD) +RTS -hc -RTS
|
||||
mv hledgerp.hp profs/$(TIME).hp
|
||||
@ -252,14 +252,14 @@ heap: sampleledgers hledgerp
|
||||
$(VIEWPS) profs/latest.ps
|
||||
|
||||
# generate and display a graphical heap profile, don't save
|
||||
quickheap: sampleledgers hledgerp
|
||||
quickheap: samplejournals hledgerp
|
||||
@echo "Profiling heap with: $(PROFCMD)"
|
||||
$(PROFCMD) +RTS -hc -RTS
|
||||
hp2ps hledgerp.hp
|
||||
$(VIEWPS) hledger.ps
|
||||
|
||||
# generate and display a code coverage report
|
||||
coverage: sampleledgers hledgercov
|
||||
coverage: samplejournals hledgercov
|
||||
@echo "Generating coverage report with $(COVCMD)"
|
||||
tools/coverage "markup --destdir=profs/coverage" test
|
||||
cd profs/coverage; rm -f index.html; ln -s hpc_index.html index.html
|
||||
@ -269,23 +269,23 @@ coverage: sampleledgers hledgercov
|
||||
ghci:
|
||||
ghci -DMAKE $(OPTFLAGS) hledger.hs
|
||||
|
||||
# generate standard sample ledgers
|
||||
sampleledgers: data/sample.ledger data/100x100x10.ledger data/1000x1000x10.ledger data/10000x1000x10.ledger data/100000x1000x10.ledger
|
||||
# generate standard sample journals
|
||||
samplejournals: data/sample.journal data/100x100x10.journal data/1000x1000x10.journal data/10000x1000x10.journal data/100000x1000x10.journal
|
||||
|
||||
data/sample.ledger:
|
||||
data/sample.journal:
|
||||
true # XXX should probably regenerate this
|
||||
|
||||
data/100x100x10.ledger: tools/generateledger
|
||||
tools/generateledger 100 100 10 >$@
|
||||
data/100x100x10.journal: tools/generatejournal
|
||||
tools/generatejournal 100 100 10 >$@
|
||||
|
||||
data/1000x1000x10.ledger: tools/generateledger
|
||||
tools/generateledger 1000 1000 10 >$@
|
||||
data/1000x1000x10.journal: tools/generatejournal
|
||||
tools/generatejournal 1000 1000 10 >$@
|
||||
|
||||
data/10000x1000x10.ledger: tools/generateledger
|
||||
tools/generateledger 10000 1000 10 >$@
|
||||
data/10000x1000x10.journal: tools/generatejournal
|
||||
tools/generatejournal 10000 1000 10 >$@
|
||||
|
||||
data/100000x1000x10.ledger: tools/generateledger
|
||||
tools/generateledger 100000 1000 10 >$@
|
||||
data/100000x1000x10.journal: tools/generatejournal
|
||||
tools/generatejournal 100000 1000 10 >$@
|
||||
|
||||
######################################################################
|
||||
# DOCUMENTATION
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
; A sample ledger file.
|
||||
; A sample journal file.
|
||||
;
|
||||
; Sets up this account tree:
|
||||
; assets
|
||||
@ -1,8 +1,8 @@
|
||||
{-|
|
||||
|
||||
The Ledger library allows parsing and querying of ledger files. It
|
||||
generally provides a compatible subset of C++ ledger's functionality.
|
||||
This package re-exports all the Hledger.Data.* modules.
|
||||
The Hledger.Data library allows parsing and querying of C++ ledger-style
|
||||
journal files. It generally provides a compatible subset of C++ ledger's
|
||||
functionality. This package re-exports all the Hledger.Data.* modules.
|
||||
|
||||
-}
|
||||
|
||||
|
||||
@ -16,7 +16,7 @@ import Hledger.Data.Types
|
||||
import Hledger.Data.AccountName
|
||||
import Hledger.Data.Amount
|
||||
import Hledger.Data.Dates (nulldatespan)
|
||||
import Hledger.Data.Transaction (ledgerTransactionWithDate)
|
||||
import Hledger.Data.Transaction (journalTransactionWithDate)
|
||||
import Hledger.Data.Posting
|
||||
import Hledger.Data.TimeLog
|
||||
|
||||
@ -129,20 +129,20 @@ filterJournalPostings FilterSpec{datespan=datespan
|
||||
filterJournalTransactionsByDate datespan .
|
||||
journalSelectingDate whichdate
|
||||
|
||||
-- | Keep only ledger transactions whose description matches the description patterns.
|
||||
-- | Keep only transactions whose description matches the description patterns.
|
||||
filterJournalTransactionsByDescription :: [String] -> Journal -> Journal
|
||||
filterJournalTransactionsByDescription pats j@Journal{jtxns=ts} = j{jtxns=filter matchdesc ts}
|
||||
where matchdesc = matchpats pats . tdescription
|
||||
|
||||
-- | Keep only ledger transactions which fall between begin and end dates.
|
||||
-- | Keep only transactions which fall between begin and end dates.
|
||||
-- We include transactions on the begin date and exclude transactions on the end
|
||||
-- date, like ledger. An empty date string means no restriction.
|
||||
filterJournalTransactionsByDate :: DateSpan -> Journal -> Journal
|
||||
filterJournalTransactionsByDate (DateSpan begin end) j@Journal{jtxns=ts} = j{jtxns=filter match ts}
|
||||
where match t = maybe True (tdate t>=) begin && maybe True (tdate t<) end
|
||||
|
||||
-- | Keep only ledger transactions which have the requested
|
||||
-- cleared/uncleared status, if there is one.
|
||||
-- | Keep only transactions which have the requested cleared/uncleared
|
||||
-- status, if there is one.
|
||||
filterJournalTransactionsByClearedStatus :: Maybe Bool -> Journal -> Journal
|
||||
filterJournalTransactionsByClearedStatus Nothing j = j
|
||||
filterJournalTransactionsByClearedStatus (Just val) j@Journal{jtxns=ts} = j{jtxns=filter match ts}
|
||||
@ -175,7 +175,7 @@ filterJournalTransactionsByDepth (Just d) j@Journal{jtxns=ts} =
|
||||
j{jtxns=(filter (any ((<= d+1) . accountNameLevel . paccount) . tpostings) ts)}
|
||||
|
||||
-- | Strip out any postings to accounts deeper than the specified depth
|
||||
-- (and any ledger transactions which have no postings as a result).
|
||||
-- (and any transactions which have no postings as a result).
|
||||
filterJournalPostingsByDepth :: Maybe Int -> Journal -> Journal
|
||||
filterJournalPostingsByDepth Nothing j = j
|
||||
filterJournalPostingsByDepth (Just d) j@Journal{jtxns=ts} =
|
||||
@ -208,7 +208,7 @@ filterJournalPostingsByAccount apats j@Journal{jtxns=ts} = j{jtxns=map filterpos
|
||||
journalSelectingDate :: WhichDate -> Journal -> Journal
|
||||
journalSelectingDate ActualDate j = j
|
||||
journalSelectingDate EffectiveDate j =
|
||||
j{jtxns=map (ledgerTransactionWithDate EffectiveDate) $ jtxns j}
|
||||
j{jtxns=map (journalTransactionWithDate EffectiveDate) $ jtxns j}
|
||||
|
||||
-- | Do post-parse processing on a journal, to make it ready for use.
|
||||
journalFinalise :: ClockTime -> LocalTime -> FilePath -> String -> Journal -> Journal
|
||||
@ -306,7 +306,7 @@ journalDateSpan j
|
||||
where
|
||||
ts = sortBy (comparing tdate) $ jtxns j
|
||||
|
||||
-- | Check if a set of ledger account/description patterns matches the
|
||||
-- | Check if a set of hledger account/description filter patterns matches the
|
||||
-- given account name or entry description. Patterns are case-insensitive
|
||||
-- regular expressions. Prefixed with not:, they become anti-patterns.
|
||||
matchpats :: [String] -> String -> Bool
|
||||
|
||||
@ -33,7 +33,9 @@ nullledger = Ledger{
|
||||
accountmap = fromList []
|
||||
}
|
||||
|
||||
-- | Filter a ledger's transactions as specified and generate derived data.
|
||||
-- | Filter a journal's transactions as specified, and then process them
|
||||
-- to derive a ledger containing all balances, the chart of accounts,
|
||||
-- canonicalised commodities etc.
|
||||
journalToLedger :: FilterSpec -> Journal -> Ledger
|
||||
journalToLedger fs j = nullledger{journal=j',accountnametree=t,accountmap=m}
|
||||
where j' = filterJournalPostings fs{depth=Nothing} j
|
||||
|
||||
@ -34,7 +34,7 @@ instance Read TimeLogCode where
|
||||
readsPrec _ ('O' : xs) = [(FinalOut, xs)]
|
||||
readsPrec _ _ = []
|
||||
|
||||
-- | Convert time log entries to ledger transactions. When there is no
|
||||
-- | Convert time log entries to journal transactions. When there is no
|
||||
-- clockout, add one with the provided current time. Sessions crossing
|
||||
-- midnight are split into days to give accurate per-day totals.
|
||||
timeLogEntriesToTransactions :: LocalTime -> [TimeLogEntry] -> [Transaction]
|
||||
@ -58,8 +58,8 @@ timeLogEntriesToTransactions now (i:o:rest)
|
||||
o' = o{tldatetime=itime{localDay=idate, localTimeOfDay=TimeOfDay 23 59 59}}
|
||||
i' = i{tldatetime=itime{localDay=addDays 1 idate, localTimeOfDay=midnight}}
|
||||
|
||||
-- | Convert a timelog clockin and clockout entry to an equivalent ledger
|
||||
-- entry, representing the time expenditure. Note this entry is not balanced,
|
||||
-- | Convert a timelog clockin and clockout entry to an equivalent journal
|
||||
-- transaction, representing the time expenditure. Note this entry is not balanced,
|
||||
-- since we omit the \"assets:time\" transaction for simpler output.
|
||||
entryFromTimeLogInOut :: TimeLogEntry -> TimeLogEntry -> Transaction
|
||||
entryFromTimeLogInOut i o
|
||||
|
||||
@ -36,7 +36,7 @@ nulltransaction = Transaction {
|
||||
}
|
||||
|
||||
{-|
|
||||
Show a ledger entry, formatted for the print command. ledger 2.x's
|
||||
Show a journal transaction, formatted for the print command. ledger 2.x's
|
||||
standard format looks like this:
|
||||
|
||||
@
|
||||
@ -156,9 +156,9 @@ nonzerobalanceerror t = printf "could not balance this transaction (%s%s%s)" rms
|
||||
sep = if not (null rmsg) && not (null bvmsg) then "; " else ""
|
||||
|
||||
-- | Convert the primary date to either the actual or effective date.
|
||||
ledgerTransactionWithDate :: WhichDate -> Transaction -> Transaction
|
||||
ledgerTransactionWithDate ActualDate t = t
|
||||
ledgerTransactionWithDate EffectiveDate t = txnTieKnot t{tdate=fromMaybe (tdate t) (teffectivedate t)}
|
||||
journalTransactionWithDate :: WhichDate -> Transaction -> Transaction
|
||||
journalTransactionWithDate ActualDate t = t
|
||||
journalTransactionWithDate EffectiveDate t = txnTieKnot t{tdate=fromMaybe (tdate t) (teffectivedate t)}
|
||||
|
||||
|
||||
-- | Ensure a transaction's postings refer back to it.
|
||||
|
||||
@ -10,7 +10,7 @@ module Hledger.Read (
|
||||
readJournalFile,
|
||||
readJournal,
|
||||
journalFromPathAndString,
|
||||
myLedgerPath,
|
||||
myJournalPath,
|
||||
myTimelogPath,
|
||||
myJournal,
|
||||
myTimelog,
|
||||
@ -37,9 +37,9 @@ import System.IO (hPutStrLn)
|
||||
#endif
|
||||
|
||||
|
||||
ledgerenvvar = "LEDGER"
|
||||
journalenvvar = "LEDGER"
|
||||
timelogenvvar = "TIMELOG"
|
||||
ledgerdefaultfilename = ".ledger"
|
||||
journaldefaultfilename = ".journal"
|
||||
timelogdefaultfilename = ".timelog"
|
||||
|
||||
-- Here are the available readers. The first is the default, used for unknown data formats.
|
||||
@ -92,13 +92,13 @@ readJournalFile format f = withFile f ReadMode $ \h -> hGetContents h >>= jour
|
||||
readJournal :: Maybe String -> String -> IO (Either String Journal)
|
||||
readJournal format s = journalFromPathAndString format "(string)" s
|
||||
|
||||
-- | Get the user's default ledger file path.
|
||||
myLedgerPath :: IO String
|
||||
myLedgerPath =
|
||||
getEnv ledgerenvvar `catch`
|
||||
-- | Get the user's default journal file path.
|
||||
myJournalPath :: IO String
|
||||
myJournalPath =
|
||||
getEnv journalenvvar `catch`
|
||||
(\_ -> do
|
||||
home <- getHomeDirectory `catch` (\_ -> return "")
|
||||
return $ home </> ledgerdefaultfilename)
|
||||
return $ home </> journaldefaultfilename)
|
||||
|
||||
-- | Get the user's default timelog file path.
|
||||
myTimelogPath :: IO String
|
||||
@ -110,7 +110,7 @@ myTimelogPath =
|
||||
|
||||
-- | Read the user's default journal file, or give an error.
|
||||
myJournal :: IO Journal
|
||||
myJournal = myLedgerPath >>= readJournalFile Nothing >>= either error return
|
||||
myJournal = myJournalPath >>= readJournalFile Nothing >>= either error return
|
||||
|
||||
-- | Read the user's default timelog file, or give an error.
|
||||
myTimelog :: IO Journal
|
||||
@ -119,10 +119,10 @@ myTimelog = myTimelogPath >>= readJournalFile Nothing >>= either error return
|
||||
tests_Hledger_Read = TestList
|
||||
[
|
||||
|
||||
"ledgerFile" ~: do
|
||||
assertBool "ledgerFile should parse an empty file" (isRight $ parseWithCtx emptyCtx Journal.ledgerFile "")
|
||||
jE <- readJournal Nothing "" -- don't know how to get it from ledgerFile
|
||||
either error (assertBool "ledgerFile parsing an empty file should give an empty ledger" . null . jtxns) jE
|
||||
"journalFile" ~: do
|
||||
assertBool "journalFile should parse an empty file" (isRight $ parseWithCtx emptyCtx Journal.journalFile "")
|
||||
jE <- readJournal Nothing "" -- don't know how to get it from journalFile
|
||||
either error (assertBool "journalFile parsing an empty file should give an empty journal" . null . jtxns) jE
|
||||
|
||||
,Journal.tests_Journal
|
||||
,Timelog.tests_Timelog
|
||||
|
||||
@ -30,7 +30,7 @@ type JournalUpdate = ErrorT String IO (Journal -> Journal)
|
||||
|
||||
-- | Given a JournalUpdate-generating parsec parser, file path and data string,
|
||||
-- parse and post-process a Journal so that it's ready to use, or give an error.
|
||||
parseJournalWith :: (GenParser Char LedgerFileCtx JournalUpdate) -> FilePath -> String -> ErrorT String IO Journal
|
||||
parseJournalWith :: (GenParser Char JournalContext JournalUpdate) -> FilePath -> String -> ErrorT String IO Journal
|
||||
parseJournalWith p f s = do
|
||||
tc <- liftIO getClockTime
|
||||
tl <- liftIO getCurrentLocalTime
|
||||
@ -38,34 +38,34 @@ parseJournalWith p f s = do
|
||||
Right updates -> liftM (journalFinalise tc tl f s) $ updates `ap` return nulljournal
|
||||
Left err -> throwError $ show err -- XXX raises an uncaught exception if we have a parsec user error, eg from many ?
|
||||
|
||||
-- | Some context kept during parsing.
|
||||
data LedgerFileCtx = Ctx {
|
||||
-- | Some state kept while parsing a journal file.
|
||||
data JournalContext = Ctx {
|
||||
ctxYear :: !(Maybe Integer) -- ^ the default year most recently specified with Y
|
||||
, ctxCommod :: !(Maybe String) -- ^ I don't know
|
||||
, ctxAccount :: ![String] -- ^ the current stack of parent accounts specified by !account
|
||||
} deriving (Read, Show)
|
||||
|
||||
emptyCtx :: LedgerFileCtx
|
||||
emptyCtx :: JournalContext
|
||||
emptyCtx = Ctx { ctxYear = Nothing, ctxCommod = Nothing, ctxAccount = [] }
|
||||
|
||||
setYear :: Integer -> GenParser tok LedgerFileCtx ()
|
||||
setYear :: Integer -> GenParser tok JournalContext ()
|
||||
setYear y = updateState (\ctx -> ctx{ctxYear=Just y})
|
||||
|
||||
getYear :: GenParser tok LedgerFileCtx (Maybe Integer)
|
||||
getYear :: GenParser tok JournalContext (Maybe Integer)
|
||||
getYear = liftM ctxYear getState
|
||||
|
||||
pushParentAccount :: String -> GenParser tok LedgerFileCtx ()
|
||||
pushParentAccount :: String -> GenParser tok JournalContext ()
|
||||
pushParentAccount parent = updateState addParentAccount
|
||||
where addParentAccount ctx0 = ctx0 { ctxAccount = normalize parent : ctxAccount ctx0 }
|
||||
normalize = (++ ":")
|
||||
|
||||
popParentAccount :: GenParser tok LedgerFileCtx ()
|
||||
popParentAccount :: GenParser tok JournalContext ()
|
||||
popParentAccount = do ctx0 <- getState
|
||||
case ctxAccount ctx0 of
|
||||
[] -> unexpected "End of account block with no beginning"
|
||||
(_:rest) -> setState $ ctx0 { ctxAccount = rest }
|
||||
|
||||
getParentAccount :: GenParser tok LedgerFileCtx String
|
||||
getParentAccount :: GenParser tok JournalContext String
|
||||
getParentAccount = liftM (concat . reverse . ctxAccount) getState
|
||||
|
||||
expandPath :: (MonadIO m) => SourcePos -> FilePath -> m FilePath
|
||||
|
||||
@ -106,7 +106,7 @@ i, o, b, h
|
||||
module Hledger.Read.Journal (
|
||||
tests_Journal,
|
||||
reader,
|
||||
ledgerFile,
|
||||
journalFile,
|
||||
someamount,
|
||||
ledgeraccountname,
|
||||
ledgerExclamationDirective,
|
||||
@ -149,20 +149,20 @@ detect f _ = fileSuffix f == format
|
||||
-- | Parse and post-process a "Journal" from hledger's journal file
|
||||
-- format, or give an error.
|
||||
parse :: FilePath -> String -> ErrorT String IO Journal
|
||||
parse = parseJournalWith ledgerFile
|
||||
parse = parseJournalWith journalFile
|
||||
|
||||
-- | Top-level journal parser. Returns a single composite, I/O performing,
|
||||
-- error-raising "JournalUpdate" which can be applied to an empty journal
|
||||
-- to get the final result.
|
||||
ledgerFile :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
ledgerFile = do items <- many ledgerItem
|
||||
eof
|
||||
return $ liftM (foldr (.) id) $ sequence items
|
||||
journalFile :: GenParser Char JournalContext JournalUpdate
|
||||
journalFile = do items <- many journalItem
|
||||
eof
|
||||
return $ liftM (foldr (.) id) $ sequence items
|
||||
where
|
||||
-- As all ledger line types can be distinguished by the first
|
||||
-- As all journal line types can be distinguished by the first
|
||||
-- character, excepting transactions versus empty (blank or
|
||||
-- comment-only) lines, can use choice w/o try
|
||||
ledgerItem = choice [ ledgerExclamationDirective
|
||||
journalItem = choice [ ledgerExclamationDirective
|
||||
, liftM (return . addTransaction) ledgerTransaction
|
||||
, liftM (return . addModifierTransaction) ledgerModifierTransaction
|
||||
, liftM (return . addPeriodicTransaction) ledgerPeriodicTransaction
|
||||
@ -172,7 +172,7 @@ ledgerFile = do items <- many ledgerItem
|
||||
, ledgerTagDirective
|
||||
, ledgerEndTagDirective
|
||||
, emptyLine >> return (return id)
|
||||
] <?> "ledger transaction or directive"
|
||||
] <?> "journal transaction or directive"
|
||||
|
||||
emptyLine :: GenParser Char st ()
|
||||
emptyLine = do many spacenonewline
|
||||
@ -196,7 +196,7 @@ ledgercommentline = do
|
||||
return s
|
||||
<?> "comment"
|
||||
|
||||
ledgerExclamationDirective :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
ledgerExclamationDirective :: GenParser Char JournalContext JournalUpdate
|
||||
ledgerExclamationDirective = do
|
||||
char '!' <?> "directive"
|
||||
directive <- many nonspace
|
||||
@ -206,14 +206,14 @@ ledgerExclamationDirective = do
|
||||
"end" -> ledgerAccountEnd
|
||||
_ -> mzero
|
||||
|
||||
ledgerInclude :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
ledgerInclude :: GenParser Char JournalContext JournalUpdate
|
||||
ledgerInclude = do many1 spacenonewline
|
||||
filename <- restofline
|
||||
outerState <- getState
|
||||
outerPos <- getPosition
|
||||
let inIncluded = show outerPos ++ " in included file " ++ show filename ++ ":\n"
|
||||
return $ do contents <- expandPath outerPos filename >>= readFileE outerPos
|
||||
case runParser ledgerFile outerState filename contents of
|
||||
case runParser journalFile outerState filename contents of
|
||||
Right l -> l `catchError` (throwError . (inIncluded ++))
|
||||
Left perr -> throwError $ inIncluded ++ show perr
|
||||
where readFileE outerPos filename = ErrorT $ liftM Right (readFile filename) `catch` leftError
|
||||
@ -221,17 +221,17 @@ ledgerInclude = do many1 spacenonewline
|
||||
currentPos = show outerPos
|
||||
whileReading = " reading " ++ show filename ++ ":\n"
|
||||
|
||||
ledgerAccountBegin :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
ledgerAccountBegin :: GenParser Char JournalContext JournalUpdate
|
||||
ledgerAccountBegin = do many1 spacenonewline
|
||||
parent <- ledgeraccountname
|
||||
newline
|
||||
pushParentAccount parent
|
||||
return $ return id
|
||||
|
||||
ledgerAccountEnd :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
ledgerAccountEnd :: GenParser Char JournalContext JournalUpdate
|
||||
ledgerAccountEnd = popParentAccount >> return (return id)
|
||||
|
||||
ledgerModifierTransaction :: GenParser Char LedgerFileCtx ModifierTransaction
|
||||
ledgerModifierTransaction :: GenParser Char JournalContext ModifierTransaction
|
||||
ledgerModifierTransaction = do
|
||||
char '=' <?> "modifier transaction"
|
||||
many spacenonewline
|
||||
@ -239,7 +239,7 @@ ledgerModifierTransaction = do
|
||||
postings <- ledgerpostings
|
||||
return $ ModifierTransaction valueexpr postings
|
||||
|
||||
ledgerPeriodicTransaction :: GenParser Char LedgerFileCtx PeriodicTransaction
|
||||
ledgerPeriodicTransaction :: GenParser Char JournalContext PeriodicTransaction
|
||||
ledgerPeriodicTransaction = do
|
||||
char '~' <?> "periodic transaction"
|
||||
many spacenonewline
|
||||
@ -247,7 +247,7 @@ ledgerPeriodicTransaction = do
|
||||
postings <- ledgerpostings
|
||||
return $ PeriodicTransaction periodexpr postings
|
||||
|
||||
ledgerHistoricalPrice :: GenParser Char LedgerFileCtx HistoricalPrice
|
||||
ledgerHistoricalPrice :: GenParser Char JournalContext HistoricalPrice
|
||||
ledgerHistoricalPrice = do
|
||||
char 'P' <?> "historical price"
|
||||
many spacenonewline
|
||||
@ -259,7 +259,7 @@ ledgerHistoricalPrice = do
|
||||
restofline
|
||||
return $ HistoricalPrice date symbol price
|
||||
|
||||
ledgerIgnoredPriceCommodity :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
ledgerIgnoredPriceCommodity :: GenParser Char JournalContext JournalUpdate
|
||||
ledgerIgnoredPriceCommodity = do
|
||||
char 'N' <?> "ignored-price commodity"
|
||||
many1 spacenonewline
|
||||
@ -267,7 +267,7 @@ ledgerIgnoredPriceCommodity = do
|
||||
restofline
|
||||
return $ return id
|
||||
|
||||
ledgerDefaultCommodity :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
ledgerDefaultCommodity :: GenParser Char JournalContext JournalUpdate
|
||||
ledgerDefaultCommodity = do
|
||||
char 'D' <?> "default commodity"
|
||||
many1 spacenonewline
|
||||
@ -275,7 +275,7 @@ ledgerDefaultCommodity = do
|
||||
restofline
|
||||
return $ return id
|
||||
|
||||
ledgerCommodityConversion :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
ledgerCommodityConversion :: GenParser Char JournalContext JournalUpdate
|
||||
ledgerCommodityConversion = do
|
||||
char 'C' <?> "commodity conversion"
|
||||
many1 spacenonewline
|
||||
@ -287,7 +287,7 @@ ledgerCommodityConversion = do
|
||||
restofline
|
||||
return $ return id
|
||||
|
||||
ledgerTagDirective :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
ledgerTagDirective :: GenParser Char JournalContext JournalUpdate
|
||||
ledgerTagDirective = do
|
||||
string "tag" <?> "tag directive"
|
||||
many1 spacenonewline
|
||||
@ -295,14 +295,14 @@ ledgerTagDirective = do
|
||||
restofline
|
||||
return $ return id
|
||||
|
||||
ledgerEndTagDirective :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
ledgerEndTagDirective :: GenParser Char JournalContext JournalUpdate
|
||||
ledgerEndTagDirective = do
|
||||
string "end tag" <?> "end tag directive"
|
||||
restofline
|
||||
return $ return id
|
||||
|
||||
-- like ledgerAccountBegin, updates the LedgerFileCtx
|
||||
ledgerDefaultYear :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
-- like ledgerAccountBegin, updates the JournalContext
|
||||
ledgerDefaultYear :: GenParser Char JournalContext JournalUpdate
|
||||
ledgerDefaultYear = do
|
||||
char 'Y' <?> "default year"
|
||||
many spacenonewline
|
||||
@ -314,7 +314,7 @@ ledgerDefaultYear = do
|
||||
|
||||
-- | Try to parse a ledger entry. If we successfully parse an entry,
|
||||
-- check it can be balanced, and fail if not.
|
||||
ledgerTransaction :: GenParser Char LedgerFileCtx Transaction
|
||||
ledgerTransaction :: GenParser Char JournalContext Transaction
|
||||
ledgerTransaction = do
|
||||
date <- ledgerdate <?> "transaction"
|
||||
edate <- optionMaybe (ledgereffectivedate date) <?> "effective date"
|
||||
@ -330,24 +330,24 @@ ledgerTransaction = do
|
||||
Right t' -> return t'
|
||||
Left err -> fail err
|
||||
|
||||
ledgerdate :: GenParser Char LedgerFileCtx Day
|
||||
ledgerdate :: GenParser Char JournalContext Day
|
||||
ledgerdate = choice' [ledgerfulldate, ledgerpartialdate] <?> "full or partial date"
|
||||
|
||||
ledgerfulldate :: GenParser Char LedgerFileCtx Day
|
||||
ledgerfulldate :: GenParser Char JournalContext Day
|
||||
ledgerfulldate = do
|
||||
(y,m,d) <- ymd
|
||||
return $ fromGregorian (read y) (read m) (read d)
|
||||
|
||||
-- | Match a partial M/D date in a ledger, and also require that a default
|
||||
-- year directive was previously encountered.
|
||||
ledgerpartialdate :: GenParser Char LedgerFileCtx Day
|
||||
ledgerpartialdate :: GenParser Char JournalContext Day
|
||||
ledgerpartialdate = do
|
||||
(_,m,d) <- md
|
||||
y <- getYear
|
||||
when (isNothing y) $ fail "partial date found, but no default year specified"
|
||||
return $ fromGregorian (fromJust y) (read m) (read d)
|
||||
|
||||
ledgerdatetime :: GenParser Char LedgerFileCtx LocalTime
|
||||
ledgerdatetime :: GenParser Char JournalContext LocalTime
|
||||
ledgerdatetime = do
|
||||
day <- ledgerdate
|
||||
many1 spacenonewline
|
||||
@ -360,7 +360,7 @@ ledgerdatetime = do
|
||||
let tod = TimeOfDay (read h) (read m) (maybe 0 (fromIntegral.read) s)
|
||||
return $ LocalTime day tod
|
||||
|
||||
ledgereffectivedate :: Day -> GenParser Char LedgerFileCtx Day
|
||||
ledgereffectivedate :: Day -> GenParser Char JournalContext Day
|
||||
ledgereffectivedate actualdate = do
|
||||
char '='
|
||||
-- kludgy way to use actual date for default year
|
||||
@ -379,7 +379,7 @@ ledgerstatus = try (do { many1 spacenonewline; char '*' <?> "status"; return Tru
|
||||
ledgercode :: GenParser Char st String
|
||||
ledgercode = try (do { many1 spacenonewline; char '(' <?> "code"; code <- anyChar `manyTill` char ')'; return code } ) <|> return ""
|
||||
|
||||
ledgerpostings :: GenParser Char LedgerFileCtx [Posting]
|
||||
ledgerpostings :: GenParser Char JournalContext [Posting]
|
||||
ledgerpostings = do
|
||||
-- complicated to handle intermixed comment lines.. please make me better.
|
||||
ctx <- getState
|
||||
@ -397,7 +397,7 @@ linebeginningwithspaces = do
|
||||
cs <- restofline
|
||||
return $ sp ++ (c:cs) ++ "\n"
|
||||
|
||||
ledgerposting :: GenParser Char LedgerFileCtx Posting
|
||||
ledgerposting :: GenParser Char JournalContext Posting
|
||||
ledgerposting = do
|
||||
many1 spacenonewline
|
||||
status <- ledgerstatus
|
||||
@ -410,7 +410,7 @@ ledgerposting = do
|
||||
return (Posting status account' amount comment ptype Nothing)
|
||||
|
||||
-- qualify with the parent account from parsing context
|
||||
transactionaccountname :: GenParser Char LedgerFileCtx AccountName
|
||||
transactionaccountname :: GenParser Char JournalContext AccountName
|
||||
transactionaccountname = liftM2 (++) getParentAccount ledgeraccountname
|
||||
|
||||
-- | Parse an account name. Account names may have single spaces inside
|
||||
|
||||
@ -71,7 +71,7 @@ detect f _ = fileSuffix f == format
|
||||
parse :: FilePath -> String -> ErrorT String IO Journal
|
||||
parse = parseJournalWith timelogFile
|
||||
|
||||
timelogFile :: GenParser Char LedgerFileCtx JournalUpdate
|
||||
timelogFile :: GenParser Char JournalContext JournalUpdate
|
||||
timelogFile = do items <- many timelogItem
|
||||
eof
|
||||
return $ liftM (foldr (.) id) $ sequence items
|
||||
@ -87,7 +87,7 @@ timelogFile = do items <- many timelogItem
|
||||
] <?> "timelog entry, or default year or historical price directive"
|
||||
|
||||
-- | Parse a timelog entry.
|
||||
timelogentry :: GenParser Char LedgerFileCtx TimeLogEntry
|
||||
timelogentry :: GenParser Char JournalContext TimeLogEntry
|
||||
timelogentry = do
|
||||
code <- oneOf "bhioO"
|
||||
many1 spacenonewline
|
||||
|
||||
@ -3,7 +3,7 @@ version: 0.10
|
||||
category: Finance
|
||||
synopsis: A command-line (or curses or web-based) double-entry accounting tool.
|
||||
description:
|
||||
hledger reads a plain text ledger file or timelog
|
||||
hledger reads a plain text general journal or time log
|
||||
describing your transactions and displays precise
|
||||
balance and register reports via command-line, curses
|
||||
or web interface. It is a remix, in haskell, of John
|
||||
@ -31,7 +31,7 @@ extra-source-files:
|
||||
MANUAL.markdown
|
||||
NEWS.rst
|
||||
CONTRIBUTORS.rst
|
||||
data/sample.ledger
|
||||
data/sample.journal
|
||||
data/sample.timelog
|
||||
data/sample.rules
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user