rename LedgerTransaction to RawTransaction

This commit is contained in:
Simon Michael 2008-10-02 23:55:01 +00:00
parent f93b988e93
commit 99358f207b
11 changed files with 50 additions and 45 deletions

View File

@ -5,7 +5,7 @@ import Types
import AccountName import AccountName
import Amount import Amount
import LedgerEntry import LedgerEntry
import LedgerTransaction import RawTransaction
import Transaction import Transaction

View File

@ -73,7 +73,7 @@ filterLedgerEntries (acctpat,descpat) (RawLedger ms ps es f) =
where where
filteredentries :: [LedgerEntry] filteredentries :: [LedgerEntry]
filteredentries = (filter matchdesc $ filter (any matchtxn . etransactions) es) filteredentries = (filter matchdesc $ filter (any matchtxn . etransactions) es)
matchtxn :: LedgerTransaction -> Bool matchtxn :: RawTransaction -> Bool
matchtxn t = case matchRegex acctpat (taccount t) of matchtxn t = case matchRegex acctpat (taccount t) of
Nothing -> False Nothing -> False
otherwise -> True otherwise -> True

View File

@ -2,7 +2,7 @@ module LedgerEntry
where where
import Utils import Utils
import Types import Types
import LedgerTransaction import RawTransaction
import Amount import Amount

View File

@ -1,10 +1,13 @@
{-| all data types & behaviours -} {-|
This module makes it easier to import all the hledger "models",
the main data types and their "methods".
-}
module Models ( module Models (
module Types, module Types,
module Currency, module Currency,
module Amount, module Amount,
module AccountName, module AccountName,
module LedgerTransaction, module RawTransaction,
module LedgerEntry, module LedgerEntry,
module TimeLog, module TimeLog,
module Transaction, module Transaction,
@ -19,7 +22,7 @@ import Types
import Currency import Currency
import Amount import Amount
import AccountName import AccountName
import LedgerTransaction import RawTransaction
import LedgerEntry import LedgerEntry
import TimeLog import TimeLog
import Transaction import Transaction

View File

@ -248,10 +248,10 @@ ledgerstatus = try (do { char '*'; many1 spacenonewline; return True } ) <|> ret
ledgercode :: Parser String ledgercode :: Parser String
ledgercode = try (do { char '('; code <- anyChar `manyTill` char ')'; many1 spacenonewline; return code } ) <|> return "" ledgercode = try (do { char '('; code <- anyChar `manyTill` char ')'; many1 spacenonewline; return code } ) <|> return ""
ledgertransactions :: Parser [LedgerTransaction] ledgertransactions :: Parser [RawTransaction]
ledgertransactions = (ledgertransaction <?> "transaction") `manyTill` (do {newline <?> "blank line"; return ()} <|> eof) ledgertransactions = (ledgertransaction <?> "transaction") `manyTill` (do {newline <?> "blank line"; return ()} <|> eof)
ledgertransaction :: Parser LedgerTransaction ledgertransaction :: Parser RawTransaction
ledgertransaction = do ledgertransaction = do
many1 spacenonewline many1 spacenonewline
account <- ledgeraccount account <- ledgeraccount
@ -259,7 +259,7 @@ ledgertransaction = do
many spacenonewline many spacenonewline
comment <- ledgercomment comment <- ledgercomment
restofline restofline
return (LedgerTransaction account amount comment) return (RawTransaction account amount comment)
-- | account names may have single spaces in them, and are terminated by two or more spaces -- | account names may have single spaces in them, and are terminated by two or more spaces
ledgeraccount :: Parser String ledgeraccount :: Parser String

View File

@ -1,4 +1,4 @@
module LedgerTransaction module RawTransaction
where where
import Utils import Utils
import Types import Types
@ -6,9 +6,9 @@ import AccountName
import Amount import Amount
instance Show LedgerTransaction where show = showLedgerTransaction instance Show RawTransaction where show = showLedgerTransaction
showLedgerTransaction :: LedgerTransaction -> String showLedgerTransaction :: RawTransaction -> String
showLedgerTransaction t = (showaccountname $ taccount t) ++ " " ++ (showamount $ tamount t) showLedgerTransaction t = (showaccountname $ taccount t) ++ " " ++ (showamount $ tamount t)
where where
showaccountname = printf "%-22s" . elideRight 22 showaccountname = printf "%-22s" . elideRight 22
@ -19,7 +19,7 @@ elideRight width s =
True -> take (width - 2) s ++ ".." True -> take (width - 2) s ++ ".."
False -> s False -> s
autofillTransactions :: [LedgerTransaction] -> [LedgerTransaction] autofillTransactions :: [RawTransaction] -> [RawTransaction]
autofillTransactions ts = autofillTransactions ts =
case (length blanks) of case (length blanks) of
0 -> ts 0 -> ts
@ -30,8 +30,8 @@ autofillTransactions ts =
isnormal t = (symbol $ currency $ tamount t) /= "AUTO" isnormal t = (symbol $ currency $ tamount t) /= "AUTO"
balance t = if isnormal t then t else t{tamount = -(sumLedgerTransactions normals)} balance t = if isnormal t then t else t{tamount = -(sumLedgerTransactions normals)}
sumLedgerTransactions :: [LedgerTransaction] -> Amount sumLedgerTransactions :: [RawTransaction] -> Amount
sumLedgerTransactions = sum . map tamount sumLedgerTransactions = sum . map tamount
ledgerTransactionSetPrecision :: Int -> LedgerTransaction -> LedgerTransaction ledgerTransactionSetPrecision :: Int -> RawTransaction -> RawTransaction
ledgerTransactionSetPrecision p (LedgerTransaction a amt c) = LedgerTransaction a amt{precision=p} c ledgerTransactionSetPrecision p (RawTransaction a amt c) = RawTransaction a amt{precision=p} c

View File

@ -59,7 +59,7 @@ assertParseEqual expected parsed =
transaction1_str = " expenses:food:dining $10.00\n" transaction1_str = " expenses:food:dining $10.00\n"
transaction1 = LedgerTransaction "expenses:food:dining" (dollars 10) "" transaction1 = RawTransaction "expenses:food:dining" (dollars 10) ""
entry1_str = "\ entry1_str = "\
\2007/01/28 coopportunity\n\ \2007/01/28 coopportunity\n\
@ -69,8 +69,8 @@ entry1_str = "\
entry1 = entry1 =
(LedgerEntry "2007/01/28" False "" "coopportunity" "" (LedgerEntry "2007/01/28" False "" "coopportunity" ""
[LedgerTransaction "expenses:food:groceries" (Amount (getcurrency "$") 47.18 2) "", [RawTransaction "expenses:food:groceries" (Amount (getcurrency "$") 47.18 2) "",
LedgerTransaction "assets:checking" (Amount (getcurrency "$") (-47.18) 2) ""] "") RawTransaction "assets:checking" (Amount (getcurrency "$") (-47.18) 2) ""] "")
entry2_str = "\ entry2_str = "\
\2007/01/27 * joes diner\n\ \2007/01/27 * joes diner\n\
@ -207,10 +207,10 @@ ledger7 = RawLedger
LedgerEntry { LedgerEntry {
edate="2007/01/01", estatus=False, ecode="*", edescription="opening balance", ecomment="", edate="2007/01/01", estatus=False, ecode="*", edescription="opening balance", ecomment="",
etransactions=[ etransactions=[
LedgerTransaction {taccount="assets:cash", RawTransaction {taccount="assets:cash",
tamount=Amount {currency=(getcurrency "$"), quantity=4.82, precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=4.82, precision=2},
tcomment=""}, tcomment=""},
LedgerTransaction {taccount="equity:opening balances", RawTransaction {taccount="equity:opening balances",
tamount=Amount {currency=(getcurrency "$"), quantity=(-4.82), precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=(-4.82), precision=2},
tcomment=""} tcomment=""}
], ],
@ -220,10 +220,10 @@ ledger7 = RawLedger
LedgerEntry { LedgerEntry {
edate="2007/02/01", estatus=False, ecode="*", edescription="ayres suites", ecomment="", edate="2007/02/01", estatus=False, ecode="*", edescription="ayres suites", ecomment="",
etransactions=[ etransactions=[
LedgerTransaction {taccount="expenses:vacation", RawTransaction {taccount="expenses:vacation",
tamount=Amount {currency=(getcurrency "$"), quantity=179.92, precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=179.92, precision=2},
tcomment=""}, tcomment=""},
LedgerTransaction {taccount="assets:checking", RawTransaction {taccount="assets:checking",
tamount=Amount {currency=(getcurrency "$"), quantity=(-179.92), precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=(-179.92), precision=2},
tcomment=""} tcomment=""}
], ],
@ -233,10 +233,10 @@ ledger7 = RawLedger
LedgerEntry { LedgerEntry {
edate="2007/01/02", estatus=False, ecode="*", edescription="auto transfer to savings", ecomment="", edate="2007/01/02", estatus=False, ecode="*", edescription="auto transfer to savings", ecomment="",
etransactions=[ etransactions=[
LedgerTransaction {taccount="assets:saving", RawTransaction {taccount="assets:saving",
tamount=Amount {currency=(getcurrency "$"), quantity=200, precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=200, precision=2},
tcomment=""}, tcomment=""},
LedgerTransaction {taccount="assets:checking", RawTransaction {taccount="assets:checking",
tamount=Amount {currency=(getcurrency "$"), quantity=(-200), precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=(-200), precision=2},
tcomment=""} tcomment=""}
], ],
@ -246,10 +246,10 @@ ledger7 = RawLedger
LedgerEntry { LedgerEntry {
edate="2007/01/03", estatus=False, ecode="*", edescription="poquito mas", ecomment="", edate="2007/01/03", estatus=False, ecode="*", edescription="poquito mas", ecomment="",
etransactions=[ etransactions=[
LedgerTransaction {taccount="expenses:food:dining", RawTransaction {taccount="expenses:food:dining",
tamount=Amount {currency=(getcurrency "$"), quantity=4.82, precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=4.82, precision=2},
tcomment=""}, tcomment=""},
LedgerTransaction {taccount="assets:cash", RawTransaction {taccount="assets:cash",
tamount=Amount {currency=(getcurrency "$"), quantity=(-4.82), precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=(-4.82), precision=2},
tcomment=""} tcomment=""}
], ],
@ -259,10 +259,10 @@ ledger7 = RawLedger
LedgerEntry { LedgerEntry {
edate="2007/01/03", estatus=False, ecode="*", edescription="verizon", ecomment="", edate="2007/01/03", estatus=False, ecode="*", edescription="verizon", ecomment="",
etransactions=[ etransactions=[
LedgerTransaction {taccount="expenses:phone", RawTransaction {taccount="expenses:phone",
tamount=Amount {currency=(getcurrency "$"), quantity=95.11, precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=95.11, precision=2},
tcomment=""}, tcomment=""},
LedgerTransaction {taccount="assets:checking", RawTransaction {taccount="assets:checking",
tamount=Amount {currency=(getcurrency "$"), quantity=(-95.11), precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=(-95.11), precision=2},
tcomment=""} tcomment=""}
], ],
@ -272,10 +272,10 @@ ledger7 = RawLedger
LedgerEntry { LedgerEntry {
edate="2007/01/03", estatus=False, ecode="*", edescription="discover", ecomment="", edate="2007/01/03", estatus=False, ecode="*", edescription="discover", ecomment="",
etransactions=[ etransactions=[
LedgerTransaction {taccount="liabilities:credit cards:discover", RawTransaction {taccount="liabilities:credit cards:discover",
tamount=Amount {currency=(getcurrency "$"), quantity=80, precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=80, precision=2},
tcomment=""}, tcomment=""},
LedgerTransaction {taccount="assets:checking", RawTransaction {taccount="assets:checking",
tamount=Amount {currency=(getcurrency "$"), quantity=(-80), precision=2}, tamount=Amount {currency=(getcurrency "$"), quantity=(-80), precision=2},
tcomment=""} tcomment=""}
], ],

View File

@ -4,7 +4,7 @@ import Utils
import Types import Types
import Currency import Currency
import Amount import Amount
import LedgerTransaction import RawTransaction
import LedgerEntry import LedgerEntry
import RawLedger import RawLedger
@ -32,8 +32,8 @@ entriesFromTimeLogEntries [clockin,clockout] =
edescription = accountname, edescription = accountname,
ecomment = "", ecomment = "",
etransactions = [ etransactions = [
LedgerTransaction accountname amount "", RawTransaction accountname amount "",
LedgerTransaction "TIME" (-amount) "" RawTransaction "TIME" (-amount) ""
], ],
epreceding_comment_lines=""} epreceding_comment_lines=""}
] ]

View File

@ -4,7 +4,7 @@ import Utils
import Types import Types
import AccountName import AccountName
import LedgerEntry import LedgerEntry
import LedgerTransaction import RawTransaction
import Amount import Amount
import Currency import Currency
@ -48,11 +48,11 @@ showTransactionsWithBalances ts b =
showTransactionDescriptionAndBalance :: Transaction -> Amount -> String showTransactionDescriptionAndBalance :: Transaction -> Amount -> String
showTransactionDescriptionAndBalance t b = showTransactionDescriptionAndBalance t b =
(showEntryDescription $ LedgerEntry (date t) False "" (description t) "" [] "") (showEntryDescription $ LedgerEntry (date t) False "" (description t) "" [] "")
++ (showLedgerTransaction $ LedgerTransaction (account t) (amount t) "") ++ (showBalance b) ++ (showLedgerTransaction $ RawTransaction (account t) (amount t) "") ++ (showBalance b)
showTransactionAndBalance :: Transaction -> Amount -> String showTransactionAndBalance :: Transaction -> Amount -> String
showTransactionAndBalance t b = showTransactionAndBalance t b =
(replicate 32 ' ') ++ (showLedgerTransaction $ LedgerTransaction (account t) (amount t) "") ++ (showBalance b) (replicate 32 ' ') ++ (showLedgerTransaction $ RawTransaction (account t) (amount t) "") ++ (showBalance b)
showBalance :: Amount -> String showBalance :: Amount -> String
showBalance b = printf " %12s" (showAmountRoundedOrZero b) showBalance b = printf " %12s" (showAmountRoundedOrZero b)

View File

@ -29,8 +29,9 @@ data Amount = Amount {
-- the chart of accounts -- the chart of accounts
type AccountName = String type AccountName = String
-- | a transaction line within a ledger entry. -- | a single transaction line within a ledger entry. We call it raw to
data LedgerTransaction = LedgerTransaction { -- distinguish from the cached 'Transaction'.
data RawTransaction = RawTransaction {
taccount :: AccountName, taccount :: AccountName,
tamount :: Amount, tamount :: Amount,
tcomment :: String tcomment :: String
@ -39,13 +40,13 @@ data LedgerTransaction = LedgerTransaction {
-- | a ledger "modifier" entry. Currently ignored. -- | a ledger "modifier" entry. Currently ignored.
data ModifierEntry = ModifierEntry { data ModifierEntry = ModifierEntry {
valueexpr :: String, valueexpr :: String,
m_transactions :: [LedgerTransaction] m_transactions :: [RawTransaction]
} deriving (Eq) } deriving (Eq)
-- | a ledger "periodic" entry. Currently ignored. -- | a ledger "periodic" entry. Currently ignored.
data PeriodicEntry = PeriodicEntry { data PeriodicEntry = PeriodicEntry {
periodexpr :: String, periodexpr :: String,
p_transactions :: [LedgerTransaction] p_transactions :: [RawTransaction]
} deriving (Eq) } deriving (Eq)
-- | a regular ledger entry, containing two or more transactions which balance -- | a regular ledger entry, containing two or more transactions which balance
@ -55,12 +56,12 @@ data LedgerEntry = LedgerEntry {
ecode :: String, ecode :: String,
edescription :: String, edescription :: String,
ecomment :: String, ecomment :: String,
etransactions :: [LedgerTransaction], etransactions :: [RawTransaction],
epreceding_comment_lines :: String epreceding_comment_lines :: String
} deriving (Eq) } deriving (Eq)
-- | a parsed ledger file. We call it raw to distinguish from the cached -- | a parsed ledger file. We call it raw to distinguish from the cached
-- version below. -- 'Ledger'.
data RawLedger = RawLedger { data RawLedger = RawLedger {
modifier_entries :: [ModifierEntry], modifier_entries :: [ModifierEntry],
periodic_entries :: [PeriodicEntry], periodic_entries :: [PeriodicEntry],
@ -81,7 +82,8 @@ data TimeLog = TimeLog {
} deriving (Eq) } deriving (Eq)
-- | optimisations: these types provide some caching and are easier to work with. -- | optimisations: these types provide some caching and are easier to work with.
-- A Transaction is a LedgerTransaction with some of its parent --
-- A Transaction is a RawTransaction with some of its parent
-- LedgerEntry's data attached. -- LedgerEntry's data attached.
data Transaction = Transaction { data Transaction = Transaction {
entryno :: Int, entryno :: Int,

View File

@ -28,7 +28,7 @@ hledger ("Main")
"Transaction" "Transaction"
"RawLedger" "RawLedger"
"LedgerEntry" "LedgerEntry"
"LedgerTransaction" "RawTransaction"
"AccountName" "AccountName"
"Amount" "Amount"
"Currency" "Currency"