{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE RecordWildCards #-}
module Hledger.Data.Transaction (
nulltransaction,
transaction,
txnTieKnot,
txnUntieKnot,
showAccountName,
hasRealPostings,
realPostings,
assignmentPostings,
virtualPostings,
balancedVirtualPostings,
transactionsPostings,
isTransactionBalanced,
balanceTransaction,
balanceTransactionHelper,
transactionTransformPostings,
transactionApplyValuation,
transactionToCost,
transactionDate2,
transactionPostingBalances,
transactionPayee,
transactionNote,
showTransaction,
showTransactionOneLineAmounts,
showTransactionUnelided,
showTransactionUnelidedOneLineAmounts,
showPostingLines,
sourceFilePath,
sourceFirstLine,
showGenericSourcePos,
annotateErrorWithTransaction,
tests_Transaction
)
where
import Data.List
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar
import Text.Printf
import qualified Data.Map as M
import Hledger.Utils
import Hledger.Data.Types
import Hledger.Data.Dates
import Hledger.Data.Posting
import Hledger.Data.Amount
import Hledger.Data.Valuation
sourceFilePath :: GenericSourcePos -> FilePath
sourceFilePath = \case
GenericSourcePos fp _ _ -> fp
JournalSourcePos fp _ -> fp
sourceFirstLine :: GenericSourcePos -> Int
sourceFirstLine = \case
GenericSourcePos _ line _ -> line
JournalSourcePos _ (line, _) -> line
showGenericSourcePos :: GenericSourcePos -> String
showGenericSourcePos = \case
GenericSourcePos fp line column -> show fp ++ " (line " ++ show line ++ ", column " ++ show column ++ ")"
JournalSourcePos fp (line, line') -> show fp ++ " (lines " ++ show line ++ "-" ++ show line' ++ ")"
nulltransaction :: Transaction
nulltransaction = Transaction {
tindex=0,
tsourcepos=nullsourcepos,
tdate=nulldate,
tdate2=Nothing,
tstatus=Unmarked,
tcode="",
tdescription="",
tcomment="",
ttags=[],
tpostings=[],
tprecedingcomment=""
}
transaction :: String -> [Posting] -> Transaction
transaction datestr ps = txnTieKnot $ nulltransaction{tdate=parsedate datestr, tpostings=ps}
transactionPayee :: Transaction -> Text
transactionPayee = fst . payeeAndNoteFromDescription . tdescription
transactionNote :: Transaction -> Text
transactionNote = snd . payeeAndNoteFromDescription . tdescription
payeeAndNoteFromDescription :: Text -> (Text,Text)
payeeAndNoteFromDescription t
| T.null n = (t, t)
| otherwise = (textstrip p, textstrip $ T.drop 1 n)
where
(p, n) = T.span (/= '|') t
showTransaction :: Transaction -> String
showTransaction = showTransactionHelper False
showTransactionUnelided :: Transaction -> String
showTransactionUnelided = showTransaction
showTransactionOneLineAmounts :: Transaction -> String
showTransactionOneLineAmounts = showTransactionHelper True
showTransactionUnelidedOneLineAmounts = showTransactionOneLineAmounts
showTransactionHelper :: Bool -> Transaction -> String
showTransactionHelper onelineamounts t =
unlines $ [descriptionline]
++ newlinecomments
++ (postingsAsLines onelineamounts (tpostings t))
++ [""]
where
descriptionline = rstrip $ concat [date, status, code, desc, samelinecomment]
date = showDate (tdate t) ++ maybe "" (("="++) . showDate) (tdate2 t)
status | tstatus t == Cleared = " *"
| tstatus t == Pending = " !"
| otherwise = ""
code = if T.length (tcode t) > 0 then printf " (%s)" $ T.unpack $ tcode t else ""
desc = if null d then "" else " " ++ d where d = T.unpack $ tdescription t
(samelinecomment, newlinecomments) =
case renderCommentLines (tcomment t) of [] -> ("",[])
c:cs -> (c,cs)
renderCommentLines :: Text -> [String]
renderCommentLines t =
case lines $ T.unpack t of
[] -> []
[l] -> [(commentSpace . comment) l]
("":ls) -> "" : map (lineIndent . comment) ls
(l:ls) -> (commentSpace . comment) l : map (lineIndent . comment) ls
where
comment = ("; "++)
postingsAsLines :: Bool -> [Posting] -> [String]
postingsAsLines onelineamounts ps = concatMap (postingAsLines False onelineamounts ps) ps
postingAsLines :: Bool -> Bool -> [Posting] -> Posting -> [String]
postingAsLines elideamount onelineamounts pstoalignwith p = concat [
postingblock
++ newlinecomments
| postingblock <- postingblocks]
where
postingblocks = [map rstrip $ lines $ concatTopPadded [statusandaccount, " ", amount, assertion, samelinecomment] | amount <- shownAmounts]
assertion = maybe "" ((' ':).showBalanceAssertion) $ pbalanceassertion p
statusandaccount = lineIndent $ fitString (Just $ minwidth) Nothing False True $ pstatusandacct p
where
minwidth = maximum $ map ((2+) . textWidth . T.pack . pacctstr) pstoalignwith
pstatusandacct p' = pstatusprefix p' ++ pacctstr p'
pstatusprefix p' | null s = ""
| otherwise = s ++ " "
where s = show $ pstatus p'
pacctstr p' = showAccountName Nothing (ptype p') (paccount p')
shownAmounts
| elideamount = [""]
| onelineamounts = [fitString (Just amtwidth) Nothing False False $ showMixedAmountOneLine $ pamount p]
| null (amounts $ pamount p) = [""]
| otherwise = map (fitStringMulti (Just amtwidth) Nothing False False . showAmount ) . amounts $ pamount p
where
amtwidth = maximum $ 12 : map (strWidth . showMixedAmount . pamount) pstoalignwith
(samelinecomment, newlinecomments) =
case renderCommentLines (pcomment p) of [] -> ("",[])
c:cs -> (c,cs)
showBalanceAssertion BalanceAssertion{..} =
"=" ++ ['=' | batotal] ++ ['*' | bainclusive] ++ " " ++ showAmountWithZeroCommodity baamount
showPostingLines :: Posting -> [String]
showPostingLines p = postingAsLines False False ps p where
ps | Just t <- ptransaction p = tpostings t
| otherwise = [p]
lineIndent :: String -> String
lineIndent = (" "++)
commentSpace :: String -> String
commentSpace = (" "++)
showAccountName :: Maybe Int -> PostingType -> AccountName -> String
showAccountName w = fmt
where
fmt RegularPosting = take w' . T.unpack
fmt VirtualPosting = parenthesise . reverse . take (w'-2) . reverse . T.unpack
fmt BalancedVirtualPosting = bracket . reverse . take (w'-2) . reverse . T.unpack
w' = fromMaybe 999999 w
parenthesise :: String -> String
parenthesise s = "("++s++")"
bracket :: String -> String
bracket s = "["++s++"]"
hasRealPostings :: Transaction -> Bool
hasRealPostings = not . null . realPostings
realPostings :: Transaction -> [Posting]
realPostings = filter isReal . tpostings
assignmentPostings :: Transaction -> [Posting]
assignmentPostings = filter hasBalanceAssignment . tpostings
virtualPostings :: Transaction -> [Posting]
virtualPostings = filter isVirtual . tpostings
balancedVirtualPostings :: Transaction -> [Posting]
balancedVirtualPostings = filter isBalancedVirtual . tpostings
transactionsPostings :: [Transaction] -> [Posting]
transactionsPostings = concatMap tpostings
transactionPostingBalances :: Transaction -> (MixedAmount,MixedAmount,MixedAmount)
transactionPostingBalances t = (sumPostings $ realPostings t
,sumPostings $ virtualPostings t
,sumPostings $ balancedVirtualPostings t)
isTransactionBalanced :: Maybe (M.Map CommoditySymbol AmountStyle) -> Transaction -> Bool
isTransactionBalanced styles t =
isZeroMixedAmount rsum' && isZeroMixedAmount bvsum'
where
(rsum, _, bvsum) = transactionPostingBalances t
rsum' = canonicalise $ costOfMixedAmount rsum
bvsum' = canonicalise $ costOfMixedAmount bvsum
canonicalise = maybe id canonicaliseMixedAmount styles
balanceTransaction ::
Maybe (M.Map CommoditySymbol AmountStyle)
-> Transaction
-> Either String Transaction
balanceTransaction mstyles = fmap fst . balanceTransactionHelper mstyles
balanceTransactionHelper ::
Maybe (M.Map CommoditySymbol AmountStyle)
-> Transaction
-> Either String (Transaction, [(AccountName, MixedAmount)])
balanceTransactionHelper mstyles t = do
(t', inferredamtsandaccts) <-
inferBalancingAmount (fromMaybe M.empty mstyles) $ inferBalancingPrices t
if isTransactionBalanced mstyles t'
then Right (txnTieKnot t', inferredamtsandaccts)
else Left $ annotateErrorWithTransaction t' $ nonzerobalanceerror t'
where
nonzerobalanceerror :: Transaction -> String
nonzerobalanceerror t = printf "could not balance this transaction (%s%s%s)" rmsg sep bvmsg
where
(rsum, _, bvsum) = transactionPostingBalances t
rmsg | isReallyZeroMixedAmountCost rsum = ""
| otherwise = "real postings are off by "
++ showMixedAmount (costOfMixedAmount rsum)
bvmsg | isReallyZeroMixedAmountCost bvsum = ""
| otherwise = "balanced virtual postings are off by "
++ showMixedAmount (costOfMixedAmount bvsum)
sep = if not (null rmsg) && not (null bvmsg) then "; " else "" :: String
annotateErrorWithTransaction :: Transaction -> String -> String
annotateErrorWithTransaction t s = intercalate "\n" [showGenericSourcePos $ tsourcepos t, s, showTransaction t]
inferBalancingAmount ::
M.Map CommoditySymbol AmountStyle
-> Transaction
-> Either String (Transaction, [(AccountName, MixedAmount)])
inferBalancingAmount styles t@Transaction{tpostings=ps}
| length amountlessrealps > 1
= Left $ annotateErrorWithTransaction t "could not balance this transaction - can't have more than one real posting with no amount (remember to put 2 or more spaces before amounts)"
| length amountlessbvps > 1
= Left $ annotateErrorWithTransaction t "could not balance this transaction - can't have more than one balanced virtual posting with no amount (remember to put 2 or more spaces before amounts)"
| otherwise
= let psandinferredamts = map inferamount ps
inferredacctsandamts = [(paccount p, amt) | (p, Just amt) <- psandinferredamts]
in Right (t{tpostings=map fst psandinferredamts}, inferredacctsandamts)
where
(amountfulrealps, amountlessrealps) = partition hasAmount (realPostings t)
realsum = sumStrict $ map pamount amountfulrealps
(amountfulbvps, amountlessbvps) = partition hasAmount (balancedVirtualPostings t)
bvsum = sumStrict $ map pamount amountfulbvps
inferamount :: Posting -> (Posting, Maybe MixedAmount)
inferamount p =
let
minferredamt = case ptype p of
RegularPosting | not (hasAmount p) -> Just realsum
BalancedVirtualPosting | not (hasAmount p) -> Just bvsum
_ -> Nothing
in
case minferredamt of
Nothing -> (p, Nothing)
Just a -> (p{pamount=a', poriginal=Just $ originalPosting p}, Just a')
where
a' = styleMixedAmount styles $ normaliseMixedAmount $ costOfMixedAmount (-a)
inferBalancingPrices :: Transaction -> Transaction
inferBalancingPrices t@Transaction{tpostings=ps} = t{tpostings=ps'}
where
ps' = map (priceInferrerFor t BalancedVirtualPosting . priceInferrerFor t RegularPosting) ps
priceInferrerFor :: Transaction -> PostingType -> (Posting -> Posting)
priceInferrerFor t pt = inferprice
where
postings = filter ((==pt).ptype) $ tpostings t
pmixedamounts = map pamount postings
pamounts = concatMap amounts pmixedamounts
pcommodities = map acommodity pamounts
sumamounts = amounts $ sumStrict pmixedamounts
sumcommodities = map acommodity sumamounts
sumprices = filter (/=Nothing) $ map aprice sumamounts
caninferprices = length sumcommodities == 2 && null sumprices
inferprice p@Posting{pamount=Mixed [a]}
| caninferprices && ptype p == pt && acommodity a == fromcommodity
= p{pamount=Mixed [a{aprice=Just conversionprice}], poriginal=Just $ originalPosting p}
where
fromcommodity = head $ filter (`elem` sumcommodities) pcommodities
conversionprice
| fromcount==1 = TotalPrice $ abs toamount `withPrecision` maxprecision
| otherwise = UnitPrice $ abs unitprice `withPrecision` unitprecision
where
fromcount = length $ filter ((==fromcommodity).acommodity) pamounts
fromamount = head $ filter ((==fromcommodity).acommodity) sumamounts
tocommodity = head $ filter (/=fromcommodity) sumcommodities
toamount = head $ filter ((==tocommodity).acommodity) sumamounts
unitprice = (aquantity fromamount) `divideAmount` toamount
unitprecision = max 2 (asprecision (astyle toamount) + asprecision (astyle fromamount))
inferprice p = p
transactionDate2 :: Transaction -> Day
transactionDate2 t = fromMaybe (tdate t) $ tdate2 t
txnTieKnot :: Transaction -> Transaction
txnTieKnot t@Transaction{tpostings=ps} = t' where
t' = t{tpostings=map (postingSetTransaction t') ps}
txnUntieKnot :: Transaction -> Transaction
txnUntieKnot t@Transaction{tpostings=ps} = t{tpostings=map (\p -> p{ptransaction=Nothing}) ps}
postingSetTransaction :: Transaction -> Posting -> Posting
postingSetTransaction t p = p{ptransaction=Just t}
transactionTransformPostings :: (Posting -> Posting) -> Transaction -> Transaction
transactionTransformPostings f t@Transaction{tpostings=ps} = t{tpostings=map f ps}
transactionApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Maybe Day -> Day -> Bool -> Transaction -> ValuationType -> Transaction
transactionApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod t v =
transactionTransformPostings (\p -> postingApplyValuation priceoracle styles periodlast mreportlast today ismultiperiod p v) t
transactionToCost :: M.Map CommoditySymbol AmountStyle -> Transaction -> Transaction
transactionToCost styles t@Transaction{tpostings=ps} = t{tpostings=map (postingToCost styles) ps}
tests_Transaction =
tests "Transaction" [
tests "postingAsLines" [
test "null posting" $ postingAsLines False False [posting] posting @?= [""]
, test "non-null posting" $
let p =
posting
{ pstatus = Cleared
, paccount = "a"
, pamount = Mixed [usd 1, hrs 2]
, pcomment = "pcomment1\npcomment2\n tag3: val3 \n"
, ptype = RegularPosting
, ptags = [("ptag1", "val1"), ("ptag2", "val2")]
}
in postingAsLines False False [p] p @?=
[ " * a $1.00 ; pcomment1"
, " ; pcomment2"
, " ; tag3: val3 "
, " * a 2.00h ; pcomment1"
, " ; pcomment2"
, " ; tag3: val3 "
]
]
, let
timp = nulltransaction {tpostings = ["a" `post` usd 1, "b" `post` missingamt]}
texp = nulltransaction {tpostings = ["a" `post` usd 1, "b" `post` usd (-1)]}
texp1 = nulltransaction {tpostings = ["(a)" `post` usd 1]}
texp2 = nulltransaction {tpostings = ["a" `post` usd 1, "b" `post` (hrs (-1) `at` usd 1)]}
texp2b = nulltransaction {tpostings = ["a" `post` usd 1, "b" `post` hrs (-1)]}
t3 = nulltransaction {tpostings = ["a" `post` usd 1, "b" `post` missingamt, "c" `post` usd (-1)]}
in tests "postingsAsLines" [
test "null-transaction" $ postingsAsLines False (tpostings nulltransaction) @?= []
, test "implicit-amount" $ postingsAsLines False (tpostings timp) @?=
[ " a $1.00"
, " b"
]
, test "explicit-amounts" $ postingsAsLines False (tpostings texp) @?=
[ " a $1.00"
, " b $-1.00"
]
, test "one-explicit-amount" $ postingsAsLines False (tpostings texp1) @?=
[ " (a) $1.00"
]
, test "explicit-amounts-two-commodities" $ postingsAsLines False (tpostings texp2) @?=
[ " a $1.00"
, " b -1.00h @ $1.00"
]
, test "explicit-amounts-not-explicitly-balanced" $ postingsAsLines False (tpostings texp2b) @?=
[ " a $1.00"
, " b -1.00h"
]
, test "implicit-amount-not-last" $ postingsAsLines False (tpostings t3) @?=
[" a $1.00", " b", " c $-1.00"]
]
, test "inferBalancingAmount" $ do
(fst <$> inferBalancingAmount M.empty nulltransaction) @?= Right nulltransaction
(fst <$> inferBalancingAmount M.empty nulltransaction{tpostings = ["a" `post` usd (-5), "b" `post` missingamt]}) @?=
Right nulltransaction{tpostings = ["a" `post` usd (-5), "b" `post` usd 5]}
(fst <$> inferBalancingAmount M.empty nulltransaction{tpostings = ["a" `post` usd (-5), "b" `post` (eur 3 @@ usd 4), "c" `post` missingamt]}) @?=
Right nulltransaction{tpostings = ["a" `post` usd (-5), "b" `post` (eur 3 @@ usd 4), "c" `post` usd 1]}
, tests "showTransaction" [
test "null transaction" $ showTransaction nulltransaction @?= "0000/01/01\n\n"
, test "non-null transaction" $ showTransaction
nulltransaction
{ tdate = parsedate "2012/05/14"
, tdate2 = Just $ parsedate "2012/05/15"
, tstatus = Unmarked
, tcode = "code"
, tdescription = "desc"
, tcomment = "tcomment1\ntcomment2\n"
, ttags = [("ttag1", "val1")]
, tpostings =
[ nullposting
{ pstatus = Cleared
, paccount = "a"
, pamount = Mixed [usd 1, hrs 2]
, pcomment = "\npcomment2\n"
, ptype = RegularPosting
, ptags = [("ptag1", "val1"), ("ptag2", "val2")]
}
]
} @?=
unlines
[ "2012/05/14=2012/05/15 (code) desc ; tcomment1"
, " ; tcomment2"
, " * a $1.00"
, " ; pcomment2"
, " * a 2.00h"
, " ; pcomment2"
, ""
]
, test "show a balanced transaction" $
(let t =
Transaction
0
""
nullsourcepos
(parsedate "2007/01/28")
Nothing
Unmarked
""
"coopportunity"
""
[]
[ posting {paccount = "expenses:food:groceries", pamount = Mixed [usd 47.18], ptransaction = Just t}
, posting {paccount = "assets:checking", pamount = Mixed [usd (-47.18)], ptransaction = Just t}
]
in showTransaction t) @?=
(unlines
[ "2007/01/28 coopportunity"
, " expenses:food:groceries $47.18"
, " assets:checking $-47.18"
, ""
])
, test "show an unbalanced transaction, should not elide" $
(showTransaction
(txnTieKnot $
Transaction
0
""
nullsourcepos
(parsedate "2007/01/28")
Nothing
Unmarked
""
"coopportunity"
""
[]
[ posting {paccount = "expenses:food:groceries", pamount = Mixed [usd 47.18]}
, posting {paccount = "assets:checking", pamount = Mixed [usd (-47.19)]}
])) @?=
(unlines
[ "2007/01/28 coopportunity"
, " expenses:food:groceries $47.18"
, " assets:checking $-47.19"
, ""
])
, test "show a transaction with one posting and a missing amount" $
(showTransaction
(txnTieKnot $
Transaction
0
""
nullsourcepos
(parsedate "2007/01/28")
Nothing
Unmarked
""
"coopportunity"
""
[]
[posting {paccount = "expenses:food:groceries", pamount = missingmixedamt}])) @?=
(unlines ["2007/01/28 coopportunity", " expenses:food:groceries", ""])
, test "show a transaction with a priced commodityless amount" $
(showTransaction
(txnTieKnot $
Transaction
0
""
nullsourcepos
(parsedate "2010/01/01")
Nothing
Unmarked
""
"x"
""
[]
[ posting {paccount = "a", pamount = Mixed [num 1 `at` (usd 2 `withPrecision` 0)]}
, posting {paccount = "b", pamount = missingmixedamt}
])) @?=
(unlines ["2010/01/01 x", " a 1 @ $2", " b", ""])
]
, tests "balanceTransaction" [
test "detect unbalanced entry, sign error" $
assertLeft
(balanceTransaction
Nothing
(Transaction
0
""
nullsourcepos
(parsedate "2007/01/28")
Nothing
Unmarked
""
"test"
""
[]
[posting {paccount = "a", pamount = Mixed [usd 1]}, posting {paccount = "b", pamount = Mixed [usd 1]}]))
,test "detect unbalanced entry, multiple missing amounts" $
assertLeft $
balanceTransaction
Nothing
(Transaction
0
""
nullsourcepos
(parsedate "2007/01/28")
Nothing
Unmarked
""
"test"
""
[]
[ posting {paccount = "a", pamount = missingmixedamt}
, posting {paccount = "b", pamount = missingmixedamt}
])
,test "one missing amount is inferred" $
(pamount . last . tpostings <$>
balanceTransaction
Nothing
(Transaction
0
""
nullsourcepos
(parsedate "2007/01/28")
Nothing
Unmarked
""
""
""
[]
[posting {paccount = "a", pamount = Mixed [usd 1]}, posting {paccount = "b", pamount = missingmixedamt}])) @?=
Right (Mixed [usd (-1)])
,test "conversion price is inferred" $
(pamount . head . tpostings <$>
balanceTransaction
Nothing
(Transaction
0
""
nullsourcepos
(parsedate "2007/01/28")
Nothing
Unmarked
""
""
""
[]
[ posting {paccount = "a", pamount = Mixed [usd 1.35]}
, posting {paccount = "b", pamount = Mixed [eur (-1)]}
])) @?=
Right (Mixed [usd 1.35 @@ (eur 1 `withPrecision` maxprecision)])
,test "balanceTransaction balances based on cost if there are unit prices" $
assertRight $
balanceTransaction
Nothing
(Transaction
0
""
nullsourcepos
(parsedate "2011/01/01")
Nothing
Unmarked
""
""
""
[]
[ posting {paccount = "a", pamount = Mixed [usd 1 `at` eur 2]}
, posting {paccount = "a", pamount = Mixed [usd (-2) `at` eur 1]}
])
,test "balanceTransaction balances based on cost if there are total prices" $
assertRight $
balanceTransaction
Nothing
(Transaction
0
""
nullsourcepos
(parsedate "2011/01/01")
Nothing
Unmarked
""
""
""
[]
[ posting {paccount = "a", pamount = Mixed [usd 1 @@ eur 1]}
, posting {paccount = "a", pamount = Mixed [usd (-2) @@ eur 1]}
])
]
, tests "isTransactionBalanced" [
test "detect balanced" $
assertBool "" $
isTransactionBalanced Nothing $
Transaction
0
""
nullsourcepos
(parsedate "2009/01/01")
Nothing
Unmarked
""
"a"
""
[]
[ posting {paccount = "b", pamount = Mixed [usd 1.00]}
, posting {paccount = "c", pamount = Mixed [usd (-1.00)]}
]
,test "detect unbalanced" $
assertBool "" $
not $
isTransactionBalanced Nothing $
Transaction
0
""
nullsourcepos
(parsedate "2009/01/01")
Nothing
Unmarked
""
"a"
""
[]
[ posting {paccount = "b", pamount = Mixed [usd 1.00]}
, posting {paccount = "c", pamount = Mixed [usd (-1.01)]}
]
,test "detect unbalanced, one posting" $
assertBool "" $
not $
isTransactionBalanced Nothing $
Transaction
0
""
nullsourcepos
(parsedate "2009/01/01")
Nothing
Unmarked
""
"a"
""
[]
[posting {paccount = "b", pamount = Mixed [usd 1.00]}]
,test "one zero posting is considered balanced for now" $
assertBool "" $
isTransactionBalanced Nothing $
Transaction
0
""
nullsourcepos
(parsedate "2009/01/01")
Nothing
Unmarked
""
"a"
""
[]
[posting {paccount = "b", pamount = Mixed [usd 0]}]
,test "virtual postings don't need to balance" $
assertBool "" $
isTransactionBalanced Nothing $
Transaction
0
""
nullsourcepos
(parsedate "2009/01/01")
Nothing
Unmarked
""
"a"
""
[]
[ posting {paccount = "b", pamount = Mixed [usd 1.00]}
, posting {paccount = "c", pamount = Mixed [usd (-1.00)]}
, posting {paccount = "d", pamount = Mixed [usd 100], ptype = VirtualPosting}
]
,test "balanced virtual postings need to balance among themselves" $
assertBool "" $
not $
isTransactionBalanced Nothing $
Transaction
0
""
nullsourcepos
(parsedate "2009/01/01")
Nothing
Unmarked
""
"a"
""
[]
[ posting {paccount = "b", pamount = Mixed [usd 1.00]}
, posting {paccount = "c", pamount = Mixed [usd (-1.00)]}
, posting {paccount = "d", pamount = Mixed [usd 100], ptype = BalancedVirtualPosting}
]
,test "balanced virtual postings need to balance among themselves (2)" $
assertBool "" $
isTransactionBalanced Nothing $
Transaction
0
""
nullsourcepos
(parsedate "2009/01/01")
Nothing
Unmarked
""
"a"
""
[]
[ posting {paccount = "b", pamount = Mixed [usd 1.00]}
, posting {paccount = "c", pamount = Mixed [usd (-1.00)]}
, posting {paccount = "d", pamount = Mixed [usd 100], ptype = BalancedVirtualPosting}
, posting {paccount = "3", pamount = Mixed [usd (-100)], ptype = BalancedVirtualPosting}
]
]
]