hledger/hledger-lib/Hledger/Data/Posting.hs

668 lines
27 KiB
Haskell
Raw Permalink Normal View History

{-|
A 'Posting' represents a change (by some 'MixedAmount') of the balance in
some 'Account'. Each 'Transaction' contains two or more postings which
should add up to 0. Postings reference their parent transaction, so we can
look up the date or description there.
-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE NamedFieldPuns #-}
lib: textification begins! account names The first of several conversions from String to (strict) Text, hopefully reducing space and time usage. This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1: hledger -f data/100x100x10.journal stats string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>> text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>> hledger -f data/1000x100x10.journal stats string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>> text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>> hledger -f data/10000x100x10.journal stats string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>> text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>> hledger -f data/100000x100x10.journal stats string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>> text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
{-# LANGUAGE OverloadedStrings #-}
module Hledger.Data.Posting (
-- * Posting
nullposting,
posting,
post,
vpost,
post',
vpost',
nullsourcepos,
nullassertion,
balassert,
balassertTot,
balassertParInc,
balassertTotInc,
-- * operations
originalPosting,
postingStatus,
isReal,
isVirtual,
isBalancedVirtual,
isEmptyPosting,
hasBalanceAssignment,
hasAmount,
2012-05-28 04:27:55 +04:00
postingAllTags,
transactionAllTags,
relatedPostings,
postingStripCosts,
postingApplyAliases,
postingApplyCommodityStyles,
postingStyleAmounts,
postingAddTags,
-- * date operations
postingDate,
postingDate2,
postingDateOrDate2,
isPostingInDateSpan,
isPostingInDateSpan',
-- * account name operations
accountNamesFromPostings,
-- * comment/tag operations
commentJoin,
commentAddTag,
commentAddTagUnspaced,
commentAddTagNextLine,
-- * arithmetic
sumPostings,
-- * rendering
showPosting,
showPostingLines,
postingAsLines,
postingsAsLines,
postingsAsLinesBeancount,
postingAsLinesBeancount,
showAccountName,
showAccountNameBeancount,
renderCommentLines,
showBalanceAssertion,
-- * misc.
postingTransformAmount,
postingApplyValuation,
postingToCost,
postingAddInferredEquityPostings,
postingPriceDirectivesFromCost,
2018-09-06 23:08:26 +03:00
tests_Posting
)
where
import Data.Default (def)
import Data.Foldable (asum)
import Data.Function ((&))
import qualified Data.Map as M
import Data.Maybe (fromMaybe, isJust, mapMaybe)
import Data.List (sort, union)
#if !MIN_VERSION_base(4,20,0)
import Data.List (foldl')
#endif
import qualified Data.Set as S
lib: textification: comments and tags No change. hledger -f data/100x100x10.journal stats <<ghc: 42859576 bytes, 84 GCs, 193781/269984 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.016 MUT (0.020 elapsed), 0.009 GC (0.011 elapsed) :ghc>> <<ghc: 42859576 bytes, 84 GCs, 193781/269984 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.018 elapsed), 0.009 GC (0.013 elapsed) :ghc>> hledger -f data/1000x1000x10.journal stats <<ghc: 349576344 bytes, 681 GCs, 1407388/4091680 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.000 elapsed), 0.124 MUT (0.130 elapsed), 0.047 GC (0.055 elapsed) :ghc>> <<ghc: 349576280 bytes, 681 GCs, 1407388/4091680 avg/max bytes residency (7 samples), 11M in use, 0.000 INIT (0.000 elapsed), 0.126 MUT (0.132 elapsed), 0.049 GC (0.058 elapsed) :ghc>> hledger -f data/10000x1000x10.journal stats <<ghc: 3424030664 bytes, 6658 GCs, 11403359/41071624 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.000 elapsed), 1.207 MUT (1.228 elapsed), 0.473 GC (0.528 elapsed) :ghc>> <<ghc: 3424030760 bytes, 6658 GCs, 11403874/41077288 avg/max bytes residency (11 samples), 111M in use, 0.000 INIT (0.002 elapsed), 1.234 MUT (1.256 elapsed), 0.470 GC (0.520 elapsed) :ghc>> hledger -f data/100000x1000x10.journal stats <<ghc: 34306547448 bytes, 66727 GCs, 76805504/414629288 avg/max bytes residency (14 samples), 1009M in use, 0.000 INIT (0.003 elapsed), 12.615 MUT (12.813 elapsed), 4.656 GC (5.291 elapsed) :ghc>> <<ghc: 34306547320 bytes, 66727 GCs, 76805504/414629288 avg/max bytes residency (14 samples), 1009M in use, 0.000 INIT (0.009 elapsed), 12.802 MUT (13.065 elapsed), 4.774 GC (5.441 elapsed) :ghc>>
2016-05-25 03:09:20 +03:00
import Data.Text (Text)
lib: textification begins! account names The first of several conversions from String to (strict) Text, hopefully reducing space and time usage. This one shows a small improvement, with GHC 7.10.3 and text-1.2.2.1: hledger -f data/100x100x10.journal stats string: <<ghc: 39471064 bytes, 77 GCs, 198421/275048 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.001 elapsed), 0.015 MUT (0.020 elapsed), 0.010 GC (0.014 elapsed) :ghc>> text: <<ghc: 39268024 bytes, 77 GCs, 197018/270840 avg/max bytes residency (3 samples), 2M in use, 0.000 INIT (0.002 elapsed), 0.016 MUT (0.022 elapsed), 0.009 GC (0.011 elapsed) :ghc>> hledger -f data/1000x100x10.journal stats string: <<ghc: 318555920 bytes, 617 GCs, 2178997/7134472 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.001 elapsed), 0.129 MUT (0.136 elapsed), 0.067 GC (0.077 elapsed) :ghc>> text: <<ghc: 314248496 bytes, 612 GCs, 2074045/6617960 avg/max bytes residency (7 samples), 16M in use, 0.000 INIT (0.003 elapsed), 0.137 MUT (0.145 elapsed), 0.067 GC (0.079 elapsed) :ghc>> hledger -f data/10000x100x10.journal stats string: <<ghc: 3114763608 bytes, 6026 GCs, 18858950/75552024 avg/max bytes residency (11 samples), 201M in use, 0.000 INIT (0.000 elapsed), 1.331 MUT (1.372 elapsed), 0.699 GC (0.812 elapsed) :ghc>> text: <<ghc: 3071468920 bytes, 5968 GCs, 14120344/62951360 avg/max bytes residency (9 samples), 124M in use, 0.000 INIT (0.003 elapsed), 1.272 MUT (1.349 elapsed), 0.513 GC (0.578 elapsed) :ghc>> hledger -f data/100000x100x10.journal stats string: <<ghc: 31186579432 bytes, 60278 GCs, 135332581/740228992 avg/max bytes residency (13 samples), 1697M in use, 0.000 INIT (0.008 elapsed), 14.677 MUT (15.508 elapsed), 7.081 GC (8.074 elapsed) :ghc>> text: <<ghc: 30753427672 bytes, 59763 GCs, 117595958/666457240 avg/max bytes residency (14 samples), 1588M in use, 0.000 INIT (0.008 elapsed), 13.713 MUT (13.966 elapsed), 6.220 GC (7.108 elapsed) :ghc>>
2016-05-24 04:16:21 +03:00
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB
import Data.Time.Calendar (Day)
import Safe (maximumBound)
import Text.DocLayout (realLength)
import Text.Tabular.AsciiWide hiding (render)
2011-05-28 08:11:44 +04:00
import Hledger.Utils
2010-05-20 03:08:53 +04:00
import Hledger.Data.Types
import Hledger.Data.Amount
import Hledger.Data.AccountName
import Hledger.Data.Dates (nulldate, spanContainsDate)
import Hledger.Data.Valuation
instance HasAmounts BalanceAssertion where
styleAmounts styles ba@BalanceAssertion{baamount} = ba{baamount=styleAmounts styles baamount}
instance HasAmounts Posting where
styleAmounts styles p@Posting{pamount, pbalanceassertion} =
p{ pamount=styleAmounts styles pamount
,pbalanceassertion=styleAmounts styles pbalanceassertion
}
{-# DEPRECATED postingApplyCommodityStyles "please use styleAmounts instead" #-}
-- | Find and apply the appropriate display style to the posting amounts
-- in each commodity (see journalCommodityStyles).
-- Main amount precisions may be set or not according to the styles, but cost precisions are not set.
postingApplyCommodityStyles :: M.Map CommoditySymbol AmountStyle -> Posting -> Posting
postingApplyCommodityStyles = styleAmounts
{-# DEPRECATED postingStyleAmounts "please use styleAmounts instead" #-}
-- | Like postingApplyCommodityStyles, but neither
-- main amount precisions or cost precisions are set.
postingStyleAmounts :: M.Map CommoditySymbol AmountStyle -> Posting -> Posting
postingStyleAmounts = styleAmounts
nullposting, posting :: Posting
nullposting = Posting
{pdate=Nothing
,pdate2=Nothing
,pstatus=Unmarked
,paccount=""
,pamount=nullmixedamt
,pcomment=""
,ptype=RegularPosting
,ptags=[]
,pbalanceassertion=Nothing
,ptransaction=Nothing
,poriginal=Nothing
}
posting = nullposting
-- constructors
-- | Make a posting to an account.
post :: AccountName -> Amount -> Posting
lib: Change internal representation of MixedAmount to use a strict Map instead of a list of Amounts. No longer export Mixed constructor, to keep API clean (if you really need it, you can import it directly from Hledger.Data.Types). We also ensure the JSON representation of MixedAmount doesn't change: it is stored as a normalised list of Amounts. This commit improves performance. Here are some indicative results. hledger reg -f examples/10000x1000x10.journal - Maximum residency decreases from 65MB to 60MB (8% decrease) - Total memory in use decreases from 178MiB to 157MiB (12% decrease) hledger reg -f examples/10000x10000x10.journal - Maximum residency decreases from 69MB to 60MB (13% decrease) - Total memory in use decreases from 198MiB to 153MiB (23% decrease) hledger bal -f examples/10000x1000x10.journal - Total heap usage decreases from 6.4GB to 6.0GB (6% decrease) - Total memory in use decreases from 178MiB to 153MiB (14% decrease) hledger bal -f examples/10000x10000x10.journal - Total heap usage decreases from 7.3GB to 6.9GB (5% decrease) - Total memory in use decreases from 196MiB to 185MiB (5% decrease) hledger bal -M -f examples/10000x1000x10.journal - Total heap usage decreases from 16.8GB to 10.6GB (47% decrease) - Total time decreases from 14.3s to 12.0s (16% decrease) hledger bal -M -f examples/10000x10000x10.journal - Total heap usage decreases from 108GB to 48GB (56% decrease) - Total time decreases from 62s to 41s (33% decrease) If you never directly use the constructor Mixed or pattern match against it then you don't need to make any changes. If you do, then do the following: - If you really care about the individual Amounts and never normalise your MixedAmount (for example, just storing `Mixed amts` and then extracting `amts` as a pattern match, then use should switch to using [Amount]. This should just involve removing the `Mixed` constructor. - If you ever call `mixed`, `normaliseMixedAmount`, or do any sort of amount arithmetic (+), (-), then you should replace the constructor `Mixed` with the function `mixed`. To extract the list of Amounts, use the function `amounts`. - If you ever call `normaliseMixedAmountSquashPricesForDisplay`, you can replace that with `mixedAmountStripPrices`. (N.B. this does something slightly different from `normaliseMixedAmountSquashPricesForDisplay`, but I don't think there's any use case for squashing prices and then keeping the first of the squashed prices around. If you disagree let me know.) - Any remaining calls to `normaliseMixedAmount` can be removed, as that is now the identity function.
2021-01-29 08:07:11 +03:00
post acc amt = posting {paccount=acc, pamount=mixedAmount amt}
-- | Make a virtual (unbalanced) posting to an account.
vpost :: AccountName -> Amount -> Posting
vpost acc amt = (post acc amt){ptype=VirtualPosting}
-- | Make a posting to an account, maybe with a balance assertion.
post' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
lib: Change internal representation of MixedAmount to use a strict Map instead of a list of Amounts. No longer export Mixed constructor, to keep API clean (if you really need it, you can import it directly from Hledger.Data.Types). We also ensure the JSON representation of MixedAmount doesn't change: it is stored as a normalised list of Amounts. This commit improves performance. Here are some indicative results. hledger reg -f examples/10000x1000x10.journal - Maximum residency decreases from 65MB to 60MB (8% decrease) - Total memory in use decreases from 178MiB to 157MiB (12% decrease) hledger reg -f examples/10000x10000x10.journal - Maximum residency decreases from 69MB to 60MB (13% decrease) - Total memory in use decreases from 198MiB to 153MiB (23% decrease) hledger bal -f examples/10000x1000x10.journal - Total heap usage decreases from 6.4GB to 6.0GB (6% decrease) - Total memory in use decreases from 178MiB to 153MiB (14% decrease) hledger bal -f examples/10000x10000x10.journal - Total heap usage decreases from 7.3GB to 6.9GB (5% decrease) - Total memory in use decreases from 196MiB to 185MiB (5% decrease) hledger bal -M -f examples/10000x1000x10.journal - Total heap usage decreases from 16.8GB to 10.6GB (47% decrease) - Total time decreases from 14.3s to 12.0s (16% decrease) hledger bal -M -f examples/10000x10000x10.journal - Total heap usage decreases from 108GB to 48GB (56% decrease) - Total time decreases from 62s to 41s (33% decrease) If you never directly use the constructor Mixed or pattern match against it then you don't need to make any changes. If you do, then do the following: - If you really care about the individual Amounts and never normalise your MixedAmount (for example, just storing `Mixed amts` and then extracting `amts` as a pattern match, then use should switch to using [Amount]. This should just involve removing the `Mixed` constructor. - If you ever call `mixed`, `normaliseMixedAmount`, or do any sort of amount arithmetic (+), (-), then you should replace the constructor `Mixed` with the function `mixed`. To extract the list of Amounts, use the function `amounts`. - If you ever call `normaliseMixedAmountSquashPricesForDisplay`, you can replace that with `mixedAmountStripPrices`. (N.B. this does something slightly different from `normaliseMixedAmountSquashPricesForDisplay`, but I don't think there's any use case for squashing prices and then keeping the first of the squashed prices around. If you disagree let me know.) - Any remaining calls to `normaliseMixedAmount` can be removed, as that is now the identity function.
2021-01-29 08:07:11 +03:00
post' acc amt ass = posting {paccount=acc, pamount=mixedAmount amt, pbalanceassertion=ass}
-- | Make a virtual (unbalanced) posting to an account, maybe with a balance assertion.
vpost' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
vpost' acc amt ass = (post' acc amt ass){ptype=VirtualPosting, pbalanceassertion=ass}
nullsourcepos :: (SourcePos, SourcePos)
nullsourcepos = (SourcePos "" (mkPos 1) (mkPos 1), SourcePos "" (mkPos 2) (mkPos 1))
nullassertion :: BalanceAssertion
nullassertion = BalanceAssertion
{baamount=nullamt
,batotal=False
,bainclusive=False
,baposition=initialPos ""
}
-- | Make a partial, exclusive balance assertion.
balassert :: Amount -> Maybe BalanceAssertion
balassert amt = Just $ nullassertion{baamount=amt}
-- | Make a total, exclusive balance assertion.
balassertTot :: Amount -> Maybe BalanceAssertion
balassertTot amt = Just $ nullassertion{baamount=amt, batotal=True}
-- | Make a partial, inclusive balance assertion.
balassertParInc :: Amount -> Maybe BalanceAssertion
balassertParInc amt = Just $ nullassertion{baamount=amt, bainclusive=True}
-- | Make a total, inclusive balance assertion.
balassertTotInc :: Amount -> Maybe BalanceAssertion
balassertTotInc amt = Just $ nullassertion{baamount=amt, batotal=True, bainclusive=True}
-- | Render a balance assertion, as the =[=][*] symbol and expected amount.
showBalanceAssertion :: BalanceAssertion -> WideBuilder
showBalanceAssertion ba =
singleton '=' <> eq <> ast <> singleton ' ' <> showAmountB def{displayZeroCommodity=True, displayForceDecimalMark=True} (baamount ba)
where
eq = if batotal ba then singleton '=' else mempty
ast = if bainclusive ba then singleton '*' else mempty
singleton c = WideBuilder (TB.singleton c) 1
-- Get the original posting, if any.
originalPosting :: Posting -> Posting
originalPosting p = fromMaybe p $ poriginal p
showPosting :: Posting -> String
showPosting p = T.unpack . T.unlines $ postingsAsLines False [p]
-- | Render a posting, at the appropriate width for aligning with
-- its siblings if any. Used by the rewrite command.
showPostingLines :: Posting -> [Text]
showPostingLines p = first3 $ postingAsLines False False maxacctwidth maxamtwidth p
where
linesWithWidths = map (postingAsLines False False maxacctwidth maxamtwidth) . maybe [p] tpostings $ ptransaction p
maxacctwidth = maximumBound 0 $ map second3 linesWithWidths
maxamtwidth = maximumBound 0 $ map third3 linesWithWidths
-- | Given a transaction and its postings, render the postings, suitable
-- for `print` output. Normally this output will be valid journal syntax which
-- hledger can reparse (though it may include no-longer-valid balance assertions).
--
-- Explicit amounts are shown, any implicit amounts are not.
--
-- Postings with multicommodity explicit amounts are handled as follows:
-- if onelineamounts is true, these amounts are shown on one line,
-- comma-separated, and the output will not be valid journal syntax.
-- Otherwise, they are shown as several similar postings, one per commodity.
-- When the posting has a balance assertion, it is attached to the last of these postings.
--
-- The output will appear to be a balanced transaction.
-- Amounts' display precisions, which may have been limited by commodity
-- directives, will be increased if necessary to ensure this.
--
-- Posting amounts will be aligned with each other, starting about 4 columns
-- beyond the widest account name (see postingAsLines for details).
postingsAsLines :: Bool -> [Posting] -> [Text]
postingsAsLines onelineamounts ps = concatMap first3 linesWithWidths
where
linesWithWidths = map (postingAsLines False onelineamounts maxacctwidth maxamtwidth) ps
maxacctwidth = maximumBound 0 $ map second3 linesWithWidths
maxamtwidth = maximumBound 0 $ map third3 linesWithWidths
-- | Render one posting, on one or more lines, suitable for `print` output.
-- There will be an indented account name, plus one or more of status flag,
-- posting amount, balance assertion, same-line comment, next-line comments.
--
-- If the posting's amount is implicit or if elideamount is true, no amount is shown.
--
-- If the posting's amount is explicit and multi-commodity, multiple similar
-- postings are shown, one for each commodity, to help produce parseable journal syntax.
-- Or if onelineamounts is true, such amounts are shown on one line, comma-separated
-- (and the output will not be valid journal syntax).
--
-- If an amount is zero, any commodity symbol attached to it is shown
-- (and the corresponding commodity display style is used).
--
-- By default, 4 spaces (2 if there's a status flag) are shown between
-- account name and start of amount area, which is typically 12 chars wide
-- and contains a right-aligned amount (so 10-12 visible spaces between
-- account name and amount is typical).
-- When given a list of postings to be aligned with, the whitespace will be
-- increased if needed to match the posting with the longest account name.
-- This is used to align the amounts of a transaction's postings.
--
-- Also returns the account width and amount width used.
postingAsLines :: Bool -> Bool -> Int -> Int -> Posting -> ([Text], Int, Int)
postingAsLines elideamount onelineamounts acctwidth amtwidth p =
(concatMap (++ newlinecomments) postingblocks, thisacctwidth, thisamtwidth)
where
-- This needs to be converted to strict Text in order to strip trailing
-- spaces. This adds a small amount of inefficiency, and the only difference
-- is whether there are trailing spaces in print (and related) reports. This
-- could be removed and we could just keep everything as a Text Builder, but
-- would require adding trailing spaces to 42 failing tests.
postingblocks = [map T.stripEnd . T.lines . TL.toStrict $
render [ textCell BottomLeft statusandaccount
, textCell BottomLeft " "
, Cell BottomLeft [pad amt]
, Cell BottomLeft [assertion]
, textCell BottomLeft samelinecomment
]
| (amt,assertion) <- shownAmountsAssertions]
render = renderRow def{tableBorders=False, borderSpaces=False} . Group NoLine . map Header
pad amt = WideBuilder (TB.fromText $ T.replicate w " ") w <> amt
where w = max 12 amtwidth - wbWidth amt -- min. 12 for backwards compatibility
pacctstr p' = showAccountName Nothing (ptype p') (paccount p')
pstatusandacct p' = pstatusprefix p' <> pacctstr p'
pstatusprefix p' = case pstatus p' of
Unmarked -> ""
s -> T.pack (show s) <> " "
-- currently prices are considered part of the amount string when right-aligning amounts
-- Since we will usually be calling this function with the knot tied between
-- amtwidth and thisamtwidth, make sure thisamtwidth does not depend on
-- amtwidth at all.
shownAmounts
| elideamount = [mempty]
| otherwise = showMixedAmountLinesB displayopts $ pamount p
where displayopts = defaultFmt{
displayZeroCommodity=True, displayForceDecimalMark=True, displayOneLine=onelineamounts
}
thisamtwidth = maximumBound 0 $ map wbWidth shownAmounts
-- when there is a balance assertion, show it only on the last posting line
shownAmountsAssertions = zip shownAmounts shownAssertions
where
shownAssertions = replicate (length shownAmounts - 1) mempty ++ [assertion]
where
assertion = maybe mempty ((WideBuilder (TB.singleton ' ') 1 <>).showBalanceAssertion) $ pbalanceassertion p
-- pad to the maximum account name width, plus 2 to leave room for status flags, to keep amounts aligned
statusandaccount = lineIndent . fitText (Just $ 2 + acctwidth) Nothing False True $ pstatusandacct p
thisacctwidth = realLength $ pacctstr p
(samelinecomment, newlinecomments) =
case renderCommentLines (pcomment p) of [] -> ("",[])
c:cs -> (c,cs)
-- | Show an account name, clipped to the given width if any, and
-- appropriately bracketed/parenthesised for the given posting type.
showAccountName :: Maybe Int -> PostingType -> AccountName -> Text
showAccountName w = fmt
where
fmt RegularPosting = maybe id T.take w
fmt VirtualPosting = wrap "(" ")" . maybe id (T.takeEnd . subtract 2) w
fmt BalancedVirtualPosting = wrap "[" "]" . maybe id (T.takeEnd . subtract 2) w
-- | Like postingsAsLines but generates Beancount journal format.
postingsAsLinesBeancount :: [Posting] -> [Text]
postingsAsLinesBeancount ps = concatMap first3 linesWithWidths
where
linesWithWidths = map (postingAsLinesBeancount False maxacctwidth maxamtwidth) ps
maxacctwidth = maximumBound 0 $ map second3 linesWithWidths
maxamtwidth = maximumBound 0 $ map third3 linesWithWidths
-- | Like postingAsLines but generates Beancount journal format.
postingAsLinesBeancount :: Bool -> Int -> Int -> Posting -> ([Text], Int, Int)
postingAsLinesBeancount elideamount acctwidth amtwidth p =
(concatMap (++ newlinecomments) postingblocks, thisacctwidth, thisamtwidth)
where
-- This needs to be converted to strict Text in order to strip trailing
-- spaces. This adds a small amount of inefficiency, and the only difference
-- is whether there are trailing spaces in print (and related) reports. This
-- could be removed and we could just keep everything as a Text Builder, but
-- would require adding trailing spaces to 42 failing tests.
postingblocks = [map T.stripEnd . T.lines . TL.toStrict $
render [ textCell BottomLeft statusandaccount
, textCell BottomLeft " "
, Cell BottomLeft [pad amt]
, textCell BottomLeft samelinecomment
]
| (amt,_assertion) <- shownAmountsAssertions]
render = renderRow def{tableBorders=False, borderSpaces=False} . Group NoLine . map Header
pad amt = WideBuilder (TB.fromText $ T.replicate w " ") w <> amt
where w = max 12 amtwidth - wbWidth amt -- min. 12 for backwards compatibility
pacct = showAccountNameBeancount Nothing $ paccount p
pstatusandacct p' = if pstatus p' == Pending then "! " else "" <> pacct
-- currently prices are considered part of the amount string when right-aligning amounts
-- Since we will usually be calling this function with the knot tied between
-- amtwidth and thisamtwidth, make sure thisamtwidth does not depend on
-- amtwidth at all.
shownAmounts
| elideamount = [mempty]
| otherwise = showMixedAmountLinesB displayopts a'
where
displayopts = defaultFmt{ displayZeroCommodity=True, displayForceDecimalMark=True }
a' = mapMixedAmount amountToBeancount $ pamount p
thisamtwidth = maximumBound 0 $ map wbWidth shownAmounts
-- when there is a balance assertion, show it only on the last posting line
shownAmountsAssertions = zip shownAmounts shownAssertions
where
shownAssertions = replicate (length shownAmounts - 1) mempty ++ [assertion]
where
assertion = maybe mempty ((WideBuilder (TB.singleton ' ') 1 <>).showBalanceAssertion) $ pbalanceassertion p
-- pad to the maximum account name width, plus 2 to leave room for status flags, to keep amounts aligned
statusandaccount = lineIndent . fitText (Just $ 2 + acctwidth) Nothing False True $ pstatusandacct p
thisacctwidth = realLength pacct
(samelinecomment, newlinecomments) =
case renderCommentLines (pcomment p) of [] -> ("",[])
c:cs -> (c,cs)
type BeancountAmount = Amount
-- | Do some best effort adjustments to make an amount that renders
-- in a way that Beancount can read: forces the commodity symbol to the right,
-- converts a few currency symbols to names, capitalises all letters.
amountToBeancount :: Amount -> BeancountAmount
amountToBeancount a@Amount{acommodity=c,astyle=s,acost=mp} = a{acommodity=c', astyle=s', acost=mp'}
-- https://beancount.github.io/docs/beancount_language_syntax.html#commodities-currencies
where
c' = T.toUpper $
T.replace "$" "USD" $
T.replace "" "EUR" $
T.replace "¥" "JPY" $
T.replace "£" "GBP" $
c
s' = s{ascommodityside=R, ascommodityspaced=True}
mp' = costToBeancount <$> mp
where
costToBeancount (TotalCost amt) = TotalCost $ amountToBeancount amt
costToBeancount (UnitCost amt) = UnitCost $ amountToBeancount amt
-- | Like showAccountName for Beancount journal format.
-- Calls accountNameToBeancount first.
showAccountNameBeancount :: Maybe Int -> AccountName -> Text
showAccountNameBeancount w = maybe id T.take w . accountNameToBeancount
-- | Render a transaction or posting's comment as indented, semicolon-prefixed comment lines.
-- The first line (unless empty) will have leading space, subsequent lines will have a larger indent.
renderCommentLines :: Text -> [Text]
renderCommentLines t =
case T.lines t of
[] -> []
[l] -> [commentSpace $ comment l] -- single-line comment
("":ls) -> "" : map (lineIndent . comment) ls -- multi-line comment with empty first line
(l:ls) -> commentSpace (comment l) : map (lineIndent . comment) ls
where
comment = ("; "<>)
-- | Prepend a suitable indent for a posting (or transaction/posting comment) line.
lineIndent :: Text -> Text
lineIndent = (" "<>)
-- | Prepend the space required before a same-line comment.
commentSpace :: Text -> Text
commentSpace = (" "<>)
isReal :: Posting -> Bool
isReal p = ptype p == RegularPosting
isVirtual :: Posting -> Bool
isVirtual p = ptype p == VirtualPosting
isBalancedVirtual :: Posting -> Bool
isBalancedVirtual p = ptype p == BalancedVirtualPosting
hasAmount :: Posting -> Bool
hasAmount = not . isMissingMixedAmount . pamount
hasBalanceAssignment :: Posting -> Bool
hasBalanceAssignment p = not (hasAmount p) && isJust (pbalanceassertion p)
-- | Sorted unique account names referenced by these postings.
accountNamesFromPostings :: [Posting] -> [AccountName]
accountNamesFromPostings = S.toList . S.fromList . map paccount
lib: Change internal representation of MixedAmount to use a strict Map instead of a list of Amounts. No longer export Mixed constructor, to keep API clean (if you really need it, you can import it directly from Hledger.Data.Types). We also ensure the JSON representation of MixedAmount doesn't change: it is stored as a normalised list of Amounts. This commit improves performance. Here are some indicative results. hledger reg -f examples/10000x1000x10.journal - Maximum residency decreases from 65MB to 60MB (8% decrease) - Total memory in use decreases from 178MiB to 157MiB (12% decrease) hledger reg -f examples/10000x10000x10.journal - Maximum residency decreases from 69MB to 60MB (13% decrease) - Total memory in use decreases from 198MiB to 153MiB (23% decrease) hledger bal -f examples/10000x1000x10.journal - Total heap usage decreases from 6.4GB to 6.0GB (6% decrease) - Total memory in use decreases from 178MiB to 153MiB (14% decrease) hledger bal -f examples/10000x10000x10.journal - Total heap usage decreases from 7.3GB to 6.9GB (5% decrease) - Total memory in use decreases from 196MiB to 185MiB (5% decrease) hledger bal -M -f examples/10000x1000x10.journal - Total heap usage decreases from 16.8GB to 10.6GB (47% decrease) - Total time decreases from 14.3s to 12.0s (16% decrease) hledger bal -M -f examples/10000x10000x10.journal - Total heap usage decreases from 108GB to 48GB (56% decrease) - Total time decreases from 62s to 41s (33% decrease) If you never directly use the constructor Mixed or pattern match against it then you don't need to make any changes. If you do, then do the following: - If you really care about the individual Amounts and never normalise your MixedAmount (for example, just storing `Mixed amts` and then extracting `amts` as a pattern match, then use should switch to using [Amount]. This should just involve removing the `Mixed` constructor. - If you ever call `mixed`, `normaliseMixedAmount`, or do any sort of amount arithmetic (+), (-), then you should replace the constructor `Mixed` with the function `mixed`. To extract the list of Amounts, use the function `amounts`. - If you ever call `normaliseMixedAmountSquashPricesForDisplay`, you can replace that with `mixedAmountStripPrices`. (N.B. this does something slightly different from `normaliseMixedAmountSquashPricesForDisplay`, but I don't think there's any use case for squashing prices and then keeping the first of the squashed prices around. If you disagree let me know.) - Any remaining calls to `normaliseMixedAmount` can be removed, as that is now the identity function.
2021-01-29 08:07:11 +03:00
-- | Sum all amounts from a list of postings.
sumPostings :: [Posting] -> MixedAmount
sumPostings = foldl' (\amt p -> maPlus amt $ pamount p) nullmixedamt
lib: Change internal representation of MixedAmount to use a strict Map instead of a list of Amounts. No longer export Mixed constructor, to keep API clean (if you really need it, you can import it directly from Hledger.Data.Types). We also ensure the JSON representation of MixedAmount doesn't change: it is stored as a normalised list of Amounts. This commit improves performance. Here are some indicative results. hledger reg -f examples/10000x1000x10.journal - Maximum residency decreases from 65MB to 60MB (8% decrease) - Total memory in use decreases from 178MiB to 157MiB (12% decrease) hledger reg -f examples/10000x10000x10.journal - Maximum residency decreases from 69MB to 60MB (13% decrease) - Total memory in use decreases from 198MiB to 153MiB (23% decrease) hledger bal -f examples/10000x1000x10.journal - Total heap usage decreases from 6.4GB to 6.0GB (6% decrease) - Total memory in use decreases from 178MiB to 153MiB (14% decrease) hledger bal -f examples/10000x10000x10.journal - Total heap usage decreases from 7.3GB to 6.9GB (5% decrease) - Total memory in use decreases from 196MiB to 185MiB (5% decrease) hledger bal -M -f examples/10000x1000x10.journal - Total heap usage decreases from 16.8GB to 10.6GB (47% decrease) - Total time decreases from 14.3s to 12.0s (16% decrease) hledger bal -M -f examples/10000x10000x10.journal - Total heap usage decreases from 108GB to 48GB (56% decrease) - Total time decreases from 62s to 41s (33% decrease) If you never directly use the constructor Mixed or pattern match against it then you don't need to make any changes. If you do, then do the following: - If you really care about the individual Amounts and never normalise your MixedAmount (for example, just storing `Mixed amts` and then extracting `amts` as a pattern match, then use should switch to using [Amount]. This should just involve removing the `Mixed` constructor. - If you ever call `mixed`, `normaliseMixedAmount`, or do any sort of amount arithmetic (+), (-), then you should replace the constructor `Mixed` with the function `mixed`. To extract the list of Amounts, use the function `amounts`. - If you ever call `normaliseMixedAmountSquashPricesForDisplay`, you can replace that with `mixedAmountStripPrices`. (N.B. this does something slightly different from `normaliseMixedAmountSquashPricesForDisplay`, but I don't think there's any use case for squashing prices and then keeping the first of the squashed prices around. If you disagree let me know.) - Any remaining calls to `normaliseMixedAmount` can be removed, as that is now the identity function.
2021-01-29 08:07:11 +03:00
-- | Strip all prices from a Posting.
postingStripCosts :: Posting -> Posting
postingStripCosts = postingTransformAmount mixedAmountStripCosts
-- | Get a posting's (primary) date - it's own primary date if specified,
-- otherwise the parent transaction's primary date, or the null date if
-- there is no parent transaction.
postingDate :: Posting -> Day
postingDate p = fromMaybe nulldate $ asum dates
where dates = [ pdate p, tdate <$> ptransaction p ]
-- | Get a posting's secondary (secondary) date, which is the first of:
-- posting's secondary date, transaction's secondary date, posting's
-- primary date, transaction's primary date, or the null date if there is
-- no parent transaction.
postingDate2 :: Posting -> Day
postingDate2 p = fromMaybe nulldate $ asum dates
where dates = [ pdate2 p
, tdate2 =<< ptransaction p
, pdate p
, tdate <$> ptransaction p
]
-- | Get a posting's primary or secondary date, as specified.
postingDateOrDate2 :: WhichDate -> Posting -> Day
postingDateOrDate2 PrimaryDate = postingDate
postingDateOrDate2 SecondaryDate = postingDate2
-- | Get a posting's status. This is cleared or pending if those are
-- explicitly set on the posting, otherwise the status of its parent
-- transaction, or unmarked if there is no parent transaction. (Note
-- the ambiguity, unmarked can mean "posting and transaction are both
-- unmarked" or "posting is unmarked and don't know about the transaction".
postingStatus :: Posting -> Status
postingStatus Posting{pstatus=s, ptransaction=mt} = case s of
Unmarked -> maybe Unmarked tstatus mt
_ -> s
2012-05-28 04:27:55 +04:00
-- | Tags for this posting including any inherited from its parent transaction.
postingAllTags :: Posting -> [Tag]
postingAllTags p = ptags p ++ maybe [] ttags (ptransaction p)
2012-05-28 04:27:55 +04:00
-- | Tags for this transaction including any from its postings.
2012-05-28 04:27:55 +04:00
transactionAllTags :: Transaction -> [Tag]
transactionAllTags t = ttags t ++ concatMap ptags (tpostings t)
2012-05-28 04:27:55 +04:00
-- Get the other postings from this posting's transaction.
relatedPostings :: Posting -> [Posting]
relatedPostings p@Posting{ptransaction=Just t} = filter (/= p) $ tpostings t
relatedPostings _ = []
-- | Does this posting fall within the given date span ?
isPostingInDateSpan :: DateSpan -> Posting -> Bool
isPostingInDateSpan = isPostingInDateSpan' PrimaryDate
-- --date2-sensitive version, separate for now to avoid disturbing multiBalanceReport.
isPostingInDateSpan' :: WhichDate -> DateSpan -> Posting -> Bool
isPostingInDateSpan' PrimaryDate s = spanContainsDate s . postingDate
isPostingInDateSpan' SecondaryDate s = spanContainsDate s . postingDate2
isEmptyPosting :: Posting -> Bool
isEmptyPosting = mixedAmountLooksZero . pamount
-- | Apply some account aliases to the posting's account name, as described by accountNameApplyAliases.
-- This can fail due to a bad replacement pattern in a regular expression alias.
postingApplyAliases :: [AccountAlias] -> Posting -> Either RegexError Posting
postingApplyAliases aliases p@Posting{paccount} =
case accountNameApplyAliases aliases paccount of
Right a -> Right p{paccount=a}
Left e -> Left err
where
err = "problem while applying account aliases:\n" ++ pshow aliases
++ "\n to account name: "++T.unpack paccount++"\n "++e
-- | Add tags to a posting, discarding any for which the posting already has a value.
postingAddTags :: Posting -> [Tag] -> Posting
postingAddTags p@Posting{ptags} tags = p{ptags=ptags `union` tags}
-- | Apply a specified valuation to this posting's amount, using the
-- provided price oracle, commodity styles, and reference dates.
-- See amountApplyValuation.
postingApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Posting -> Posting
postingApplyValuation priceoracle styles periodlast today v p =
postingTransformAmount (mixedAmountApplyValuation priceoracle styles periodlast today (postingDate p) v) p
-- | Maybe convert this 'Posting's amount to cost.
postingToCost :: ConversionOp -> Posting -> Maybe Posting
postingToCost NoConversionOp p = Just p
postingToCost ToCost p
-- If this is a conversion posting with a matched transaction price posting, ignore it
| "_conversion-matched" `elem` map fst (ptags p) && nocosts = Nothing
| otherwise = Just $ postingTransformAmount mixedAmountCost p
where
nocosts = (not . any (isJust . acost) . amountsRaw) $ pamount p
-- | Generate inferred equity postings from a 'Posting''s costs.
-- Make sure not to duplicate them when matching ones exist already.
postingAddInferredEquityPostings :: Bool -> Text -> Posting -> [Posting]
postingAddInferredEquityPostings verbosetags equityAcct p
| "_price-matched" `elem` map fst (ptags p) = [p]
| otherwise = taggedPosting : concatMap conversionPostings costs
imp: cost: Generate totally balanced conversion postings for amounts with costs. Introduce --infer-equity option which will generate conversion postings. --cost will override --infer-equity. This means there will no longer be unbalanced transactions, but will be offsetting conversion postings to balance things out. For example. 2000-01-01 a 1 AAA @@ 2 BBB b -2 BBB When converting to cost, this is treated the same as before. When used with --infer-equity, this is now treated as: 2000-01-01 a 1 AAA equity:conversion:AAA-BBB:AAA -1 AAA equity:conversion:AAA-BBB:BBB 2 BBB b -2 BBB There is a new account type, Conversion/V, which is a subtype of Equity/E. The first account declared with this type, if any, is used as the base account for inferred equity postings in conversion transactions, overriding the default "equity:conversion". API changes: Costing has been changed to ConversionOp with three options: NoConversionOp, ToCost, and InferEquity. The first correspond to the previous NoCost and Cost options, while the third corresponds to the --infer-equity flag. This converts transactions with costs (one or more transaction prices) to transactions with equity:conversion postings. It is in ConversionOp because converting to cost with -B/--cost and inferring conversion equity postings with --infer-equity are mutually exclusive. Correspondingly, the cost_ record of ReportOpts has been changed to conversionop_. This also removes show_costs_ option in ReportOpts, as its functionality has been replaced by the richer cost_ option.
2021-05-04 04:15:55 +03:00
where
costs = filter (isJust . acost) . amountsRaw $ pamount p
imp: cost: Generate totally balanced conversion postings for amounts with costs. Introduce --infer-equity option which will generate conversion postings. --cost will override --infer-equity. This means there will no longer be unbalanced transactions, but will be offsetting conversion postings to balance things out. For example. 2000-01-01 a 1 AAA @@ 2 BBB b -2 BBB When converting to cost, this is treated the same as before. When used with --infer-equity, this is now treated as: 2000-01-01 a 1 AAA equity:conversion:AAA-BBB:AAA -1 AAA equity:conversion:AAA-BBB:BBB 2 BBB b -2 BBB There is a new account type, Conversion/V, which is a subtype of Equity/E. The first account declared with this type, if any, is used as the base account for inferred equity postings in conversion transactions, overriding the default "equity:conversion". API changes: Costing has been changed to ConversionOp with three options: NoConversionOp, ToCost, and InferEquity. The first correspond to the previous NoCost and Cost options, while the third corresponds to the --infer-equity flag. This converts transactions with costs (one or more transaction prices) to transactions with equity:conversion postings. It is in ConversionOp because converting to cost with -B/--cost and inferring conversion equity postings with --infer-equity are mutually exclusive. Correspondingly, the cost_ record of ReportOpts has been changed to conversionop_. This also removes show_costs_ option in ReportOpts, as its functionality has been replaced by the richer cost_ option.
2021-05-04 04:15:55 +03:00
taggedPosting
| null costs = p
| otherwise = p{ ptags = ("_price-matched","") : ptags p }
conversionPostings amt = case acost amt of
imp: cost: Generate totally balanced conversion postings for amounts with costs. Introduce --infer-equity option which will generate conversion postings. --cost will override --infer-equity. This means there will no longer be unbalanced transactions, but will be offsetting conversion postings to balance things out. For example. 2000-01-01 a 1 AAA @@ 2 BBB b -2 BBB When converting to cost, this is treated the same as before. When used with --infer-equity, this is now treated as: 2000-01-01 a 1 AAA equity:conversion:AAA-BBB:AAA -1 AAA equity:conversion:AAA-BBB:BBB 2 BBB b -2 BBB There is a new account type, Conversion/V, which is a subtype of Equity/E. The first account declared with this type, if any, is used as the base account for inferred equity postings in conversion transactions, overriding the default "equity:conversion". API changes: Costing has been changed to ConversionOp with three options: NoConversionOp, ToCost, and InferEquity. The first correspond to the previous NoCost and Cost options, while the third corresponds to the --infer-equity flag. This converts transactions with costs (one or more transaction prices) to transactions with equity:conversion postings. It is in ConversionOp because converting to cost with -B/--cost and inferring conversion equity postings with --infer-equity are mutually exclusive. Correspondingly, the cost_ record of ReportOpts has been changed to conversionop_. This also removes show_costs_ option in ReportOpts, as its functionality has been replaced by the richer cost_ option.
2021-05-04 04:15:55 +03:00
Nothing -> []
Just _ -> [ cp{ paccount = accountPrefix <> amtCommodity
, pamount = mixedAmount . negate $ amountStripCost amt
imp: cost: Generate totally balanced conversion postings for amounts with costs. Introduce --infer-equity option which will generate conversion postings. --cost will override --infer-equity. This means there will no longer be unbalanced transactions, but will be offsetting conversion postings to balance things out. For example. 2000-01-01 a 1 AAA @@ 2 BBB b -2 BBB When converting to cost, this is treated the same as before. When used with --infer-equity, this is now treated as: 2000-01-01 a 1 AAA equity:conversion:AAA-BBB:AAA -1 AAA equity:conversion:AAA-BBB:BBB 2 BBB b -2 BBB There is a new account type, Conversion/V, which is a subtype of Equity/E. The first account declared with this type, if any, is used as the base account for inferred equity postings in conversion transactions, overriding the default "equity:conversion". API changes: Costing has been changed to ConversionOp with three options: NoConversionOp, ToCost, and InferEquity. The first correspond to the previous NoCost and Cost options, while the third corresponds to the --infer-equity flag. This converts transactions with costs (one or more transaction prices) to transactions with equity:conversion postings. It is in ConversionOp because converting to cost with -B/--cost and inferring conversion equity postings with --infer-equity are mutually exclusive. Correspondingly, the cost_ record of ReportOpts has been changed to conversionop_. This also removes show_costs_ option in ReportOpts, as its functionality has been replaced by the richer cost_ option.
2021-05-04 04:15:55 +03:00
}
, cp{ paccount = accountPrefix <> costCommodity
, pamount = mixedAmount cost
imp: cost: Generate totally balanced conversion postings for amounts with costs. Introduce --infer-equity option which will generate conversion postings. --cost will override --infer-equity. This means there will no longer be unbalanced transactions, but will be offsetting conversion postings to balance things out. For example. 2000-01-01 a 1 AAA @@ 2 BBB b -2 BBB When converting to cost, this is treated the same as before. When used with --infer-equity, this is now treated as: 2000-01-01 a 1 AAA equity:conversion:AAA-BBB:AAA -1 AAA equity:conversion:AAA-BBB:BBB 2 BBB b -2 BBB There is a new account type, Conversion/V, which is a subtype of Equity/E. The first account declared with this type, if any, is used as the base account for inferred equity postings in conversion transactions, overriding the default "equity:conversion". API changes: Costing has been changed to ConversionOp with three options: NoConversionOp, ToCost, and InferEquity. The first correspond to the previous NoCost and Cost options, while the third corresponds to the --infer-equity flag. This converts transactions with costs (one or more transaction prices) to transactions with equity:conversion postings. It is in ConversionOp because converting to cost with -B/--cost and inferring conversion equity postings with --infer-equity are mutually exclusive. Correspondingly, the cost_ record of ReportOpts has been changed to conversionop_. This also removes show_costs_ option in ReportOpts, as its functionality has been replaced by the richer cost_ option.
2021-05-04 04:15:55 +03:00
}
]
where
cost = amountCost amt
amtCommodity = commodity amt
costCommodity = commodity cost
cp = p{ pcomment = pcomment p & (if verbosetags then (`commentAddTag` ("generated-posting","conversion")) else id)
, ptags =
("_conversion-matched","") : -- implementation-specific internal tag, not for users
("_generated-posting","conversion") :
(if verbosetags then [("generated-posting", "conversion")] else [])
imp: cost: Generate totally balanced conversion postings for amounts with costs. Introduce --infer-equity option which will generate conversion postings. --cost will override --infer-equity. This means there will no longer be unbalanced transactions, but will be offsetting conversion postings to balance things out. For example. 2000-01-01 a 1 AAA @@ 2 BBB b -2 BBB When converting to cost, this is treated the same as before. When used with --infer-equity, this is now treated as: 2000-01-01 a 1 AAA equity:conversion:AAA-BBB:AAA -1 AAA equity:conversion:AAA-BBB:BBB 2 BBB b -2 BBB There is a new account type, Conversion/V, which is a subtype of Equity/E. The first account declared with this type, if any, is used as the base account for inferred equity postings in conversion transactions, overriding the default "equity:conversion". API changes: Costing has been changed to ConversionOp with three options: NoConversionOp, ToCost, and InferEquity. The first correspond to the previous NoCost and Cost options, while the third corresponds to the --infer-equity flag. This converts transactions with costs (one or more transaction prices) to transactions with equity:conversion postings. It is in ConversionOp because converting to cost with -B/--cost and inferring conversion equity postings with --infer-equity are mutually exclusive. Correspondingly, the cost_ record of ReportOpts has been changed to conversionop_. This also removes show_costs_ option in ReportOpts, as its functionality has been replaced by the richer cost_ option.
2021-05-04 04:15:55 +03:00
, pbalanceassertion = Nothing
, poriginal = Nothing
}
accountPrefix = mconcat [ equityAcct, ":", T.intercalate "-" $ sort [amtCommodity, costCommodity], ":"]
-- Take the commodity of an amount and collapse consecutive spaces to a single space
commodity = T.unwords . filter (not . T.null) . T.words . acommodity
-- | Make a market price equivalent to this posting's amount's unit
-- price, if any.
postingPriceDirectivesFromCost :: Posting -> [PriceDirective]
postingPriceDirectivesFromCost p@Posting{pamount} =
mapMaybe (amountPriceDirectiveFromCost $ postingDate p) $ amountsRaw pamount
-- | Apply a transform function to this posting's amount.
postingTransformAmount :: (MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount f p@Posting{pamount=a} = p{pamount=f a}
-- | Join two parts of a comment, eg a tag and another tag, or a tag
-- and a non-tag, on a single line. Interpolates a comma and space
-- unless one of the parts is empty.
commentJoin :: Text -> Text -> Text
commentJoin c1 c2
| T.null c1 = c2
| T.null c2 = c1
| otherwise = c1 <> ", " <> c2
-- | Add a tag to a comment, comma-separated from any prior content.
-- A space is inserted following the colon, before the value.
commentAddTag :: Text -> Tag -> Text
commentAddTag c (t,v)
| T.null c' = tag
| otherwise = c' `commentJoin` tag
where
c' = T.stripEnd c
tag = t <> ": " <> v
-- | Like commentAddTag, but omits the space after the colon.
commentAddTagUnspaced :: Text -> Tag -> Text
commentAddTagUnspaced c (t,v)
| T.null c' = tag
| otherwise = c' `commentJoin` tag
where
c' = T.stripEnd c
tag = t <> ":" <> v
-- | Add a tag on its own line to a comment, preserving any prior content.
-- A space is inserted following the colon, before the value.
commentAddTagNextLine :: Text -> Tag -> Text
commentAddTagNextLine cmt (t,v) =
cmt <> (if "\n" `T.isSuffixOf` cmt then "" else "\n") <> t <> ": " <> v
2011-08-05 04:05:39 +04:00
2018-09-04 20:26:22 +03:00
-- tests
tests_Posting = testGroup "Posting" [
2018-09-04 20:26:22 +03:00
testCase "accountNamePostingType" $ do
accountNamePostingType "a" @?= RegularPosting
accountNamePostingType "(a)" @?= VirtualPosting
accountNamePostingType "[a]" @?= BalancedVirtualPosting
,testCase "accountNameWithoutPostingType" $ do
accountNameWithoutPostingType "(a)" @?= "a"
,testCase "accountNameWithPostingType" $ do
accountNameWithPostingType VirtualPosting "[a]" @?= "(a)"
,testCase "joinAccountNames" $ do
"a" `joinAccountNames` "b:c" @?= "a:b:c"
"a" `joinAccountNames` "(b:c)" @?= "(a:b:c)"
"[a]" `joinAccountNames` "(b:c)" @?= "[a:b:c]"
"" `joinAccountNames` "a" @?= "a"
,testCase "concatAccountNames" $ do
concatAccountNames [] @?= ""
concatAccountNames ["a","(b)","[c:d]"] @?= "(a:b:c:d)"
,testCase "commentAddTag" $ do
commentAddTag "" ("a","") @?= "a: "
commentAddTag "[1/2]" ("a","") @?= "[1/2], a: "
,testCase "commentAddTagNextLine" $ do
commentAddTagNextLine "" ("a","") @?= "\na: "
commentAddTagNextLine "[1/2]" ("a","") @?= "[1/2]\na: "
2010-12-27 23:26:22 +03:00
]