use MixedAmount everywhere. seems to work.
This commit is contained in:
parent
4f83326f14
commit
648887b36f
@ -47,6 +47,22 @@ import Ledger.Commodity
|
|||||||
instance Show Amount where show = showAmount
|
instance Show Amount where show = showAmount
|
||||||
-- instance Show MixedAmount where show = showMixedAmount
|
-- instance Show MixedAmount where show = showMixedAmount
|
||||||
|
|
||||||
|
instance Num Amount where
|
||||||
|
abs (Amount c q) = Amount c (abs q)
|
||||||
|
signum (Amount c q) = Amount c (signum q)
|
||||||
|
fromInteger i = Amount (comm "") (fromInteger i)
|
||||||
|
(+) = amountop (+)
|
||||||
|
(-) = amountop (-)
|
||||||
|
(*) = amountop (*)
|
||||||
|
|
||||||
|
instance Num MixedAmount where
|
||||||
|
abs = error "programming error, mixed amounts do not support abs"
|
||||||
|
signum = error "programming error, mixed amounts do not support signum"
|
||||||
|
fromInteger i = [Amount (comm "") (fromInteger i)]
|
||||||
|
negate = map negate
|
||||||
|
(+) = (++)
|
||||||
|
(*) = error "programming error, mixed amounts do not support multiplication"
|
||||||
|
|
||||||
showMixedAmount :: MixedAmount -> String
|
showMixedAmount :: MixedAmount -> String
|
||||||
showMixedAmount as = concat $ intersperse ", " $ map show $ normaliseMixedAmount as
|
showMixedAmount as = concat $ intersperse ", " $ map show $ normaliseMixedAmount as
|
||||||
|
|
||||||
@ -60,9 +76,6 @@ groupAmountsByCommodity as = grouped
|
|||||||
hassymbol s a = s == (symbol $ commodity a)
|
hassymbol s a = s == (symbol $ commodity a)
|
||||||
symbols = sort $ nub $ map (symbol . commodity) as
|
symbols = sort $ nub $ map (symbol . commodity) as
|
||||||
|
|
||||||
-- samecommoditysymbol Amount{commodity=c1} Amount{commodity=c2} = samesymbol c1 c2
|
|
||||||
-- samesymbol Commodity{symbol=s1} Commodity{symbol=s2} = s1==s2
|
|
||||||
|
|
||||||
-- | Get the string representation of an amount, based on its commodity's
|
-- | Get the string representation of an amount, based on its commodity's
|
||||||
-- display settings.
|
-- display settings.
|
||||||
showAmount :: Amount -> String
|
showAmount :: Amount -> String
|
||||||
@ -91,6 +104,12 @@ showAmountOrZero a
|
|||||||
| isZeroAmount a = "0"
|
| isZeroAmount a = "0"
|
||||||
| otherwise = showAmount a
|
| otherwise = showAmount a
|
||||||
|
|
||||||
|
-- | Get the string representation of an amount, rounded, or showing just "0" if it's zero.
|
||||||
|
showMixedAmountOrZero :: MixedAmount -> String
|
||||||
|
showMixedAmountOrZero a
|
||||||
|
| isZeroMixedAmount a = "0"
|
||||||
|
| otherwise = showMixedAmount a
|
||||||
|
|
||||||
-- | is this amount zero, when displayed with its given precision ?
|
-- | is this amount zero, when displayed with its given precision ?
|
||||||
isZeroAmount :: Amount -> Bool
|
isZeroAmount :: Amount -> Bool
|
||||||
isZeroAmount a@(Amount c _ ) = nonzerodigits == ""
|
isZeroAmount a@(Amount c _ ) = nonzerodigits == ""
|
||||||
@ -99,14 +118,6 @@ isZeroAmount a@(Amount c _ ) = nonzerodigits == ""
|
|||||||
isZeroMixedAmount :: MixedAmount -> Bool
|
isZeroMixedAmount :: MixedAmount -> Bool
|
||||||
isZeroMixedAmount = all isZeroAmount . normaliseMixedAmount
|
isZeroMixedAmount = all isZeroAmount . normaliseMixedAmount
|
||||||
|
|
||||||
instance Num Amount where
|
|
||||||
abs (Amount c q) = Amount c (abs q)
|
|
||||||
signum (Amount c q) = Amount c (signum q)
|
|
||||||
fromInteger i = Amount (comm "") (fromInteger i)
|
|
||||||
(+) = amountop (+)
|
|
||||||
(-) = amountop (-)
|
|
||||||
(*) = amountop (*)
|
|
||||||
|
|
||||||
-- | Apply a binary arithmetic operator to two amounts, converting to the
|
-- | Apply a binary arithmetic operator to two amounts, converting to the
|
||||||
-- second one's commodity and adopting the lowest precision. (Using the
|
-- second one's commodity and adopting the lowest precision. (Using the
|
||||||
-- second commodity means that folds (like sum [Amount]) will preserve the
|
-- second commodity means that folds (like sum [Amount]) will preserve the
|
||||||
@ -128,7 +139,7 @@ sumAmounts = sum . filter (not . isZeroAmount)
|
|||||||
sumMixedAmounts :: [MixedAmount] -> MixedAmount
|
sumMixedAmounts :: [MixedAmount] -> MixedAmount
|
||||||
sumMixedAmounts = concat
|
sumMixedAmounts = concat
|
||||||
|
|
||||||
nullamt = Amount (comm "") 0
|
nullamt = []
|
||||||
|
|
||||||
-- temporary value for partial entries
|
-- temporary value for partial entries
|
||||||
autoamt = Amount (Commodity {symbol="AUTO",side=L,spaced=False,comma=False,precision=0,rate=1}) 0
|
autoamt = [Amount (Commodity {symbol="AUTO",side=L,spaced=False,comma=False,precision=0,rate=1}) 0]
|
||||||
|
|||||||
@ -53,7 +53,7 @@ showEntry e =
|
|||||||
showtxn t = showacct t ++ " " ++ (showamount $ tamount t) ++ (showcomment $ tcomment t)
|
showtxn t = showacct t ++ " " ++ (showamount $ tamount t) ++ (showcomment $ tcomment t)
|
||||||
showtxnnoamt t = showacct t ++ " " ++ (showcomment $ tcomment t)
|
showtxnnoamt t = showacct t ++ " " ++ (showcomment $ tcomment t)
|
||||||
showacct t = " " ++ (showaccountname $ taccount t)
|
showacct t = " " ++ (showaccountname $ taccount t)
|
||||||
showamount = printf "%12s" . showAmount
|
showamount = printf "%12s" . showMixedAmount
|
||||||
showaccountname s = printf "%-34s" s
|
showaccountname s = printf "%-34s" s
|
||||||
showcomment s = if (length s) > 0 then " ; "++s else ""
|
showcomment s = if (length s) > 0 then " ; "++s else ""
|
||||||
|
|
||||||
@ -77,9 +77,9 @@ balanceEntry e@(Entry{etransactions=ts}) = e{etransactions=ts'}
|
|||||||
1 -> map balance ts
|
1 -> map balance ts
|
||||||
otherwise -> error $ "could not balance this entry, too many missing amounts:\n" ++ show e
|
otherwise -> error $ "could not balance this entry, too many missing amounts:\n" ++ show e
|
||||||
otherstotal = sumRawTransactions withamounts
|
otherstotal = sumRawTransactions withamounts
|
||||||
simpleotherstotal
|
-- simpleotherstotal
|
||||||
| length otherstotal == 1 = head otherstotal
|
-- | length otherstotal == 1 = head otherstotal
|
||||||
| otherwise = error $ "sorry, can't balance a mixed-commodity entry yet:\n" ++ show e
|
-- | otherwise = error $ "sorry, can't balance a mixed-commodity entry yet:\n" ++ show e
|
||||||
balance t
|
balance t
|
||||||
| isReal t && not (hasAmount t) = t{tamount = -simpleotherstotal}
|
| isReal t && not (hasAmount t) = t{tamount = -otherstotal}
|
||||||
| otherwise = t
|
| otherwise = t
|
||||||
|
|||||||
@ -301,7 +301,7 @@ ledgeraccountname = do
|
|||||||
accountnamechar = notFollowedBy (oneOf "()[]") >> nonspace
|
accountnamechar = notFollowedBy (oneOf "()[]") >> nonspace
|
||||||
<?> "account name character (non-bracket, non-parenthesis, non-whitespace)"
|
<?> "account name character (non-bracket, non-parenthesis, non-whitespace)"
|
||||||
|
|
||||||
transactionamount :: Parser Amount
|
transactionamount :: Parser MixedAmount
|
||||||
transactionamount =
|
transactionamount =
|
||||||
try (do
|
try (do
|
||||||
many1 spacenonewline
|
many1 spacenonewline
|
||||||
@ -309,29 +309,29 @@ transactionamount =
|
|||||||
return a
|
return a
|
||||||
) <|> return autoamt
|
) <|> return autoamt
|
||||||
|
|
||||||
leftsymbolamount :: Parser Amount
|
leftsymbolamount :: Parser MixedAmount
|
||||||
leftsymbolamount = do
|
leftsymbolamount = do
|
||||||
sym <- commoditysymbol
|
sym <- commoditysymbol
|
||||||
sp <- many spacenonewline
|
sp <- many spacenonewline
|
||||||
(q,p,comma) <- amountquantity
|
(q,p,comma) <- amountquantity
|
||||||
let c = Commodity {symbol=sym,side=L,spaced=not $ null sp,comma=comma,precision=p,rate=1}
|
let c = Commodity {symbol=sym,side=L,spaced=not $ null sp,comma=comma,precision=p,rate=1}
|
||||||
return $ Amount c q
|
return [Amount c q]
|
||||||
<?> "left-symbol amount"
|
<?> "left-symbol amount"
|
||||||
|
|
||||||
rightsymbolamount :: Parser Amount
|
rightsymbolamount :: Parser MixedAmount
|
||||||
rightsymbolamount = do
|
rightsymbolamount = do
|
||||||
(q,p,comma) <- amountquantity
|
(q,p,comma) <- amountquantity
|
||||||
sp <- many spacenonewline
|
sp <- many spacenonewline
|
||||||
sym <- commoditysymbol
|
sym <- commoditysymbol
|
||||||
let c = Commodity {symbol=sym,side=R,spaced=not $ null sp,comma=comma,precision=p,rate=1}
|
let c = Commodity {symbol=sym,side=R,spaced=not $ null sp,comma=comma,precision=p,rate=1}
|
||||||
return $ Amount c q
|
return [Amount c q]
|
||||||
<?> "right-symbol amount"
|
<?> "right-symbol amount"
|
||||||
|
|
||||||
nosymbolamount :: Parser Amount
|
nosymbolamount :: Parser MixedAmount
|
||||||
nosymbolamount = do
|
nosymbolamount = do
|
||||||
(q,p,comma) <- amountquantity
|
(q,p,comma) <- amountquantity
|
||||||
let c = Commodity {symbol="",side=L,spaced=False,comma=comma,precision=p,rate=1}
|
let c = Commodity {symbol="",side=L,spaced=False,comma=comma,precision=p,rate=1}
|
||||||
return $ Amount c q
|
return [Amount c q]
|
||||||
<?> "no-symbol amount"
|
<?> "no-symbol amount"
|
||||||
|
|
||||||
commoditysymbol :: Parser String
|
commoditysymbol :: Parser String
|
||||||
|
|||||||
@ -11,6 +11,7 @@ import qualified Data.Map as Map
|
|||||||
import Ledger.Utils
|
import Ledger.Utils
|
||||||
import Ledger.Types
|
import Ledger.Types
|
||||||
import Ledger.AccountName
|
import Ledger.AccountName
|
||||||
|
import Ledger.Amount
|
||||||
import Ledger.Entry
|
import Ledger.Entry
|
||||||
import Ledger.Transaction
|
import Ledger.Transaction
|
||||||
|
|
||||||
@ -104,10 +105,9 @@ normaliseRawLedgerAmounts l@(RawLedger ms ps es f) = RawLedger ms ps es' f
|
|||||||
normaliseEntryAmounts (Entry d s c desc comm ts pre) = Entry d s c desc comm ts' pre
|
normaliseEntryAmounts (Entry d s c desc comm ts pre) = Entry d s c desc comm ts' pre
|
||||||
where ts' = map normaliseRawTransactionAmounts ts
|
where ts' = map normaliseRawTransactionAmounts ts
|
||||||
normaliseRawTransactionAmounts (RawTransaction acct a c t) = RawTransaction acct a' c t
|
normaliseRawTransactionAmounts (RawTransaction acct a c t) = RawTransaction acct a' c t
|
||||||
where a' = normaliseAmount a
|
where a' = normaliseMixedAmount a
|
||||||
normaliseAmount (Amount c q) = Amount (firstoccurrenceof c) q
|
|
||||||
firstcommodities = nubBy samesymbol $ allcommodities
|
firstcommodities = nubBy samesymbol $ allcommodities
|
||||||
allcommodities = map (commodity . amount) $ rawLedgerTransactions l
|
allcommodities = map commodity $ concat $ map amount $ rawLedgerTransactions l
|
||||||
samesymbol (Commodity {symbol=s1}) (Commodity {symbol=s2}) = s1==s2
|
samesymbol (Commodity {symbol=s1}) (Commodity {symbol=s2}) = s1==s2
|
||||||
firstoccurrenceof c@(Commodity {symbol=s}) =
|
firstoccurrenceof c@(Commodity {symbol=s}) =
|
||||||
fromMaybe
|
fromMaybe
|
||||||
|
|||||||
@ -20,7 +20,7 @@ showRawTransaction (RawTransaction a amt _ ttype) =
|
|||||||
showaccountname a ++ " " ++ (showamount amt)
|
showaccountname a ++ " " ++ (showamount amt)
|
||||||
where
|
where
|
||||||
showaccountname = printf "%-22s" . bracket . elideAccountName width
|
showaccountname = printf "%-22s" . bracket . elideAccountName width
|
||||||
showamount = printf "%12s" . showAmountOrZero
|
showamount = printf "%12s" . showMixedAmountOrZero
|
||||||
(bracket,width) = case ttype of
|
(bracket,width) = case ttype of
|
||||||
BalancedVirtualTransaction -> (\s -> "["++s++"]", 20)
|
BalancedVirtualTransaction -> (\s -> "["++s++"]", 20)
|
||||||
VirtualTransaction -> (\s -> "("++s++")", 20)
|
VirtualTransaction -> (\s -> "("++s++")", 20)
|
||||||
@ -30,7 +30,7 @@ isReal :: RawTransaction -> Bool
|
|||||||
isReal t = rttype t == RegularTransaction
|
isReal t = rttype t == RegularTransaction
|
||||||
|
|
||||||
hasAmount :: RawTransaction -> Bool
|
hasAmount :: RawTransaction -> Bool
|
||||||
hasAmount = ("AUTO" /=) . symbol . commodity . tamount
|
hasAmount = (/= autoamt) . tamount
|
||||||
|
|
||||||
sumRawTransactions :: [RawTransaction] -> MixedAmount
|
sumRawTransactions :: [RawTransaction] -> MixedAmount
|
||||||
sumRawTransactions = normaliseMixedAmount . map tamount
|
sumRawTransactions = normaliseMixedAmount . sumMixedAmounts . map tamount
|
||||||
|
|||||||
@ -57,7 +57,7 @@ entryFromTimeLogInOut i o =
|
|||||||
showdate = formatTime defaultTimeLocale "%Y/%m/%d"
|
showdate = formatTime defaultTimeLocale "%Y/%m/%d"
|
||||||
intime = parsedatetime $ tldatetime i
|
intime = parsedatetime $ tldatetime i
|
||||||
outtime = parsedatetime $ tldatetime o
|
outtime = parsedatetime $ tldatetime o
|
||||||
amount = hours $ realToFrac (diffUTCTime outtime intime) / 3600
|
amount = [hours $ realToFrac (diffUTCTime outtime intime) / 3600]
|
||||||
txns = [RawTransaction acctname amount "" RegularTransaction
|
txns = [RawTransaction acctname amount "" RegularTransaction
|
||||||
--,RawTransaction "assets:time" (-amount) "" RegularTransaction
|
--,RawTransaction "assets:time" (-amount) "" RegularTransaction
|
||||||
]
|
]
|
||||||
|
|||||||
@ -30,7 +30,6 @@ accountNamesFromTransactions :: [Transaction] -> [AccountName]
|
|||||||
accountNamesFromTransactions ts = nub $ map account ts
|
accountNamesFromTransactions ts = nub $ map account ts
|
||||||
|
|
||||||
sumTransactions :: [Transaction] -> MixedAmount
|
sumTransactions :: [Transaction] -> MixedAmount
|
||||||
-- sumTransactions = sum . map amount
|
sumTransactions = sumMixedAmounts . map amount
|
||||||
sumTransactions = map amount
|
|
||||||
|
|
||||||
nulltxn = Transaction 0 "" "" "" nullamt RegularTransaction
|
nulltxn = Transaction 0 "" "" "" nullamt RegularTransaction
|
||||||
|
|||||||
@ -41,7 +41,7 @@ data TransactionType = RegularTransaction | VirtualTransaction | BalancedVirtual
|
|||||||
|
|
||||||
data RawTransaction = RawTransaction {
|
data RawTransaction = RawTransaction {
|
||||||
taccount :: AccountName,
|
taccount :: AccountName,
|
||||||
tamount :: Amount,
|
tamount :: MixedAmount,
|
||||||
tcomment :: String,
|
tcomment :: String,
|
||||||
rttype :: TransactionType
|
rttype :: TransactionType
|
||||||
} deriving (Eq)
|
} deriving (Eq)
|
||||||
@ -90,7 +90,7 @@ data Transaction = Transaction {
|
|||||||
date :: Date,
|
date :: Date,
|
||||||
description :: String,
|
description :: String,
|
||||||
account :: AccountName,
|
account :: AccountName,
|
||||||
amount :: Amount,
|
amount :: MixedAmount,
|
||||||
ttype :: TransactionType
|
ttype :: TransactionType
|
||||||
} deriving (Eq)
|
} deriving (Eq)
|
||||||
|
|
||||||
|
|||||||
@ -35,19 +35,19 @@ showRegisterReport opts args l = showtxns ts nulltxn nullamt
|
|||||||
-- show transactions, one per line, with a running balance
|
-- show transactions, one per line, with a running balance
|
||||||
showtxns [] _ _ = ""
|
showtxns [] _ _ = ""
|
||||||
showtxns (t@Transaction{amount=a}:ts) tprev bal =
|
showtxns (t@Transaction{amount=a}:ts) tprev bal =
|
||||||
(if isZeroAmount a then "" else this) ++ showtxns ts t bal'
|
(if isZeroMixedAmount a then "" else this) ++ showtxns ts t bal'
|
||||||
where
|
where
|
||||||
this = showtxn (t `issame` tprev) t bal'
|
this = showtxn (t `issame` tprev) t bal'
|
||||||
issame t1 t2 = entryno t1 == entryno t2
|
issame t1 t2 = entryno t1 == entryno t2
|
||||||
bal' = bal + amount t
|
bal' = bal + amount t
|
||||||
|
|
||||||
-- show one transaction line, with or without the entry details
|
-- show one transaction line, with or without the entry details
|
||||||
showtxn :: Bool -> Transaction -> Amount -> String
|
showtxn :: Bool -> Transaction -> MixedAmount -> String
|
||||||
showtxn omitdesc t b = entrydesc ++ txn ++ bal ++ "\n"
|
showtxn omitdesc t b = entrydesc ++ txn ++ bal ++ "\n"
|
||||||
where
|
where
|
||||||
entrydesc = if omitdesc then replicate 32 ' ' else printf "%s %s " date desc
|
entrydesc = if omitdesc then replicate 32 ' ' else printf "%s %s " date desc
|
||||||
date = showDate $ da
|
date = showDate $ da
|
||||||
desc = printf "%-20s" $ elideRight 20 de :: String
|
desc = printf "%-20s" $ elideRight 20 de :: String
|
||||||
txn = showRawTransaction $ RawTransaction a amt "" tt
|
txn = showRawTransaction $ RawTransaction a amt "" tt
|
||||||
bal = printf " %12s" (showAmountOrZero b)
|
bal = printf " %12s" (showMixedAmountOrZero b)
|
||||||
Transaction{date=da,description=de,account=a,amount=amt,ttype=tt} = t
|
Transaction{date=da,description=de,account=a,amount=amt,ttype=tt} = t
|
||||||
|
|||||||
38
Tests.hs
38
Tests.hs
@ -78,7 +78,7 @@ unittests = TestList [
|
|||||||
,
|
,
|
||||||
"balanceEntry" ~: do
|
"balanceEntry" ~: do
|
||||||
assertequal
|
assertequal
|
||||||
(dollars (-47.18))
|
[dollars (-47.18)]
|
||||||
(tamount $ last $ etransactions $ balanceEntry entry1)
|
(tamount $ last $ etransactions $ balanceEntry entry1)
|
||||||
,
|
,
|
||||||
"punctuatethousands" ~: punctuatethousands "" @?= ""
|
"punctuatethousands" ~: punctuatethousands "" @?= ""
|
||||||
@ -103,8 +103,8 @@ unittests = TestList [
|
|||||||
assertequal 15 (length $ Map.keys $ accountmap $ cacheLedger rawledger7)
|
assertequal 15 (length $ Map.keys $ accountmap $ cacheLedger rawledger7)
|
||||||
,
|
,
|
||||||
"transactionamount" ~: do
|
"transactionamount" ~: do
|
||||||
assertparseequal (dollars 47.18) (parsewith transactionamount " $47.18")
|
assertparseequal [dollars 47.18] (parsewith transactionamount " $47.18")
|
||||||
assertparseequal (Amount (Commodity {symbol="$",side=L,spaced=False,comma=False,precision=0,rate=1}) 1) (parsewith transactionamount " $1.")
|
assertparseequal [Amount (Commodity {symbol="$",side=L,spaced=False,comma=False,precision=0,rate=1}) 1] (parsewith transactionamount " $1.")
|
||||||
]
|
]
|
||||||
|
|
||||||
------------------------------------------------------------------------------
|
------------------------------------------------------------------------------
|
||||||
@ -215,7 +215,7 @@ balancecommandtests = TestList [
|
|||||||
]
|
]
|
||||||
|
|
||||||
registercommandtests = TestList [
|
registercommandtests = TestList [
|
||||||
"register does something" ~:
|
"register report" ~:
|
||||||
do
|
do
|
||||||
l <- ledgerfromfile "sample.ledger"
|
l <- ledgerfromfile "sample.ledger"
|
||||||
assertequal (
|
assertequal (
|
||||||
@ -243,7 +243,7 @@ assertparseequal expected parsed = either printParseError (assertequal expected)
|
|||||||
|
|
||||||
rawtransaction1_str = " expenses:food:dining $10.00\n"
|
rawtransaction1_str = " expenses:food:dining $10.00\n"
|
||||||
|
|
||||||
rawtransaction1 = RawTransaction "expenses:food:dining" (dollars 10) "" RegularTransaction
|
rawtransaction1 = RawTransaction "expenses:food:dining" [dollars 10] "" RegularTransaction
|
||||||
|
|
||||||
entry1_str = "\
|
entry1_str = "\
|
||||||
\2007/01/28 coopportunity\n\
|
\2007/01/28 coopportunity\n\
|
||||||
@ -253,8 +253,8 @@ entry1_str = "\
|
|||||||
|
|
||||||
entry1 =
|
entry1 =
|
||||||
(Entry "2007/01/28" False "" "coopportunity" ""
|
(Entry "2007/01/28" False "" "coopportunity" ""
|
||||||
[RawTransaction "expenses:food:groceries" (dollars 47.18) "" RegularTransaction,
|
[RawTransaction "expenses:food:groceries" [dollars 47.18] "" RegularTransaction,
|
||||||
RawTransaction "assets:checking" (dollars (-47.18)) "" RegularTransaction] "")
|
RawTransaction "assets:checking" [dollars (-47.18)] "" RegularTransaction] "")
|
||||||
|
|
||||||
|
|
||||||
entry2_str = "\
|
entry2_str = "\
|
||||||
@ -398,13 +398,13 @@ rawledger7 = RawLedger
|
|||||||
etransactions=[
|
etransactions=[
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="assets:cash",
|
taccount="assets:cash",
|
||||||
tamount=dollars 4.82,
|
tamount=[dollars 4.82],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
},
|
},
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="equity:opening balances",
|
taccount="equity:opening balances",
|
||||||
tamount=dollars (-4.82),
|
tamount=[dollars (-4.82)],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
}
|
}
|
||||||
@ -421,13 +421,13 @@ rawledger7 = RawLedger
|
|||||||
etransactions=[
|
etransactions=[
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="expenses:vacation",
|
taccount="expenses:vacation",
|
||||||
tamount=dollars 179.92,
|
tamount=[dollars 179.92],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
},
|
},
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="assets:checking",
|
taccount="assets:checking",
|
||||||
tamount=dollars (-179.92),
|
tamount=[dollars (-179.92)],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
}
|
}
|
||||||
@ -444,13 +444,13 @@ rawledger7 = RawLedger
|
|||||||
etransactions=[
|
etransactions=[
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="assets:saving",
|
taccount="assets:saving",
|
||||||
tamount=dollars 200,
|
tamount=[dollars 200],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
},
|
},
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="assets:checking",
|
taccount="assets:checking",
|
||||||
tamount=dollars (-200),
|
tamount=[dollars (-200)],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
}
|
}
|
||||||
@ -467,13 +467,13 @@ rawledger7 = RawLedger
|
|||||||
etransactions=[
|
etransactions=[
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="expenses:food:dining",
|
taccount="expenses:food:dining",
|
||||||
tamount=dollars 4.82,
|
tamount=[dollars 4.82],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
},
|
},
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="assets:cash",
|
taccount="assets:cash",
|
||||||
tamount=dollars (-4.82),
|
tamount=[dollars (-4.82)],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
}
|
}
|
||||||
@ -490,13 +490,13 @@ rawledger7 = RawLedger
|
|||||||
etransactions=[
|
etransactions=[
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="expenses:phone",
|
taccount="expenses:phone",
|
||||||
tamount=dollars 95.11,
|
tamount=[dollars 95.11],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
},
|
},
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="assets:checking",
|
taccount="assets:checking",
|
||||||
tamount=dollars (-95.11),
|
tamount=[dollars (-95.11)],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
}
|
}
|
||||||
@ -513,13 +513,13 @@ rawledger7 = RawLedger
|
|||||||
etransactions=[
|
etransactions=[
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="liabilities:credit cards:discover",
|
taccount="liabilities:credit cards:discover",
|
||||||
tamount=dollars 80,
|
tamount=[dollars 80],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
},
|
},
|
||||||
RawTransaction {
|
RawTransaction {
|
||||||
taccount="assets:checking",
|
taccount="assets:checking",
|
||||||
tamount=dollars (-80),
|
tamount=[dollars (-80)],
|
||||||
tcomment="",
|
tcomment="",
|
||||||
rttype=RegularTransaction
|
rttype=RegularTransaction
|
||||||
}
|
}
|
||||||
|
|||||||
Loading…
Reference in New Issue
Block a user