-
-
Notifications
You must be signed in to change notification settings - Fork 322
/
Copy pathPosting.hs
616 lines (532 loc) · 25.5 KB
/
Posting.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
{-|
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 #-}
{-# LANGUAGE OverloadedStrings #-}
module Hledger.Data.Posting (
-- * Posting
nullposting,
posting,
post,
vpost,
post',
vpost',
nullassertion,
balassert,
balassertTot,
balassertParInc,
balassertTotInc,
-- * operations
originalPosting,
postingStatus,
isReal,
isVirtual,
isBalancedVirtual,
isEmptyPosting,
hasBalanceAssignment,
hasAmount,
postingAllTags,
transactionAllTags,
relatedPostings,
postingStripCosts,
postingApplyAliases,
postingApplyCommodityStyles,
postingStyleAmounts,
postingAddTags,
postingAddHiddenAndMaybeVisibleTag,
-- * date operations
postingDate,
postingDate2,
postingDateOrDate2,
isPostingInDateSpan,
isPostingInDateSpan',
-- * account name operations
accountNamesFromPostings,
-- * comment/tag operations
commentJoin,
commentAddTag,
commentAddTagUnspaced,
commentAddTagNextLine,
generatedTransactionTagName,
modifiedTransactionTagName,
generatedPostingTagName,
costPostingTagName,
conversionPostingTagName,
-- * arithmetic
sumPostings,
postingNegate,
postingNegateMainAmount,
-- * rendering
showPosting,
showPostingLines,
postingAsLines,
postingsAsLines,
postingIndent,
showAccountName,
renderCommentLines,
showBalanceAssertion,
-- * misc.
postingTransformAmount,
postingApplyValuation,
postingToCost,
postingAddInferredEquityPostings,
postingPriceDirectivesFromCost,
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
import Data.Text (Text)
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)
import Hledger.Utils
import Hledger.Data.Types
import Hledger.Data.Amount
import Hledger.Data.AccountName
import Hledger.Data.Dates (nulldate, spanContainsDate)
import Hledger.Data.Valuation
-- | Special tags hledger sometimes adds to mark various things.
-- These should be hidden tag names, beginning with _.
-- With --verbose-tags, the equivalent visible tags will also be added.
-- These tag names are mentioned in docs and can be matched by user queries, so consider the impact before changing them.
generatedTransactionTagName, modifiedTransactionTagName, costPostingTagName, conversionPostingTagName, generatedPostingTagName :: TagName
generatedTransactionTagName = "_generated-transaction" -- ^ transactions generated by a periodic txn rule
modifiedTransactionTagName = "_modified-transaction" -- ^ transactions modified by an auto posting rule
generatedPostingTagName = "_generated-posting" -- ^ postings generated by hledger for one reason or another
costPostingTagName = "_cost-posting" -- ^ postings which have or could have a cost that's equivalent to nearby conversion postings
conversionPostingTagName = "_conversion-posting" -- ^ postings to an equity account of Conversion type which have an amount that's equivalent to a nearby costful or potentially costful posting
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
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
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}
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
-- | Render a transaction's postings as indented lines, suitable for `print` output.
--
-- Normally these will be in valid journal syntax which hledger can reparse
-- (though they may include no-longer-valid balance assertions).
-- Explicit amounts are shown, 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.
--
-- Posting amounts will be aligned with each other, starting about 4 columns
-- beyond the widest account name (see postingAsLines for details).
-- The postings will appear balanced (amounts summing to zero).
-- Amounts' display precisions, which may have been limited by commodity directives,
-- will be increased if necessary to ensure this.
--
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.
-- Also returns the widths calculated for the account and amount fields.
--
-- 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.
--
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 = postingIndent . 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
-- | 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 (postingIndent . comment) ls -- multi-line comment with empty first line
(l:ls) -> commentSpace (comment l) : map (postingIndent . comment) ls
where
comment = ("; "<>)
-- | Prepend a suitable indent for a posting (or transaction/posting comment) line.
postingIndent :: Text -> Text
postingIndent = (" "<>)
-- | 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
-- | Sum all amounts from a list of postings.
sumPostings :: [Posting] -> MixedAmount
sumPostings = foldl' (\amt p -> maPlus amt $ pamount p) nullmixedamt
-- | Negate the posting's main amount and balance assertion amount if any.
postingNegate :: Posting -> Posting
postingNegate p@Posting{pamount=a, pbalanceassertion=mb} =
p{pamount=negate a, pbalanceassertion=fmap balanceAssertionNegate mb}
where
balanceAssertionNegate b@BalanceAssertion{baamount=ba} = b{baamount=negate ba}
-- | Negate the posting's main amount but not the balance assertion amount.
postingNegateMainAmount :: Posting -> Posting
postingNegateMainAmount p@Posting{pamount=a} = p{pamount=negate a}
-- | 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
-- | Tags for this posting including any inherited from its parent transaction.
postingAllTags :: Posting -> [Tag]
postingAllTags p = ptags p ++ maybe [] ttags (ptransaction p)
-- | Tags for this transaction including any from its postings.
transactionAllTags :: Transaction -> [Tag]
transactionAllTags t = ttags t ++ concatMap ptags (tpostings t)
-- 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.
-- Note this does not add tags to the posting's comment.
postingAddTags :: Posting -> [Tag] -> Posting
postingAddTags p@Posting{ptags} tags = p{ptags=ptags `union` tags}
-- | Add the given hidden tag to a posting; and with a true argument,
-- also add the equivalent visible tag to the posting's tags and comment fields.
-- If the posting already has these tags (with any value), do nothing.
postingAddHiddenAndMaybeVisibleTag :: Bool -> HiddenTag -> Posting -> Posting
postingAddHiddenAndMaybeVisibleTag verbosetags ht p@Posting{pcomment=c, ptags} =
(p `postingAddTags` ([ht] <> [vt|verbosetags]))
{pcomment=if verbosetags && not hadtag then c `commentAddTag` vt else c}
where
vt@(vname,_) = toVisibleTag ht
hadtag = any ((== (T.toLower vname)) . T.toLower . fst) ptags -- XXX should regex-quote vname
-- | 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 an equity conversion posting with an associated cost nearby, ignore it
| conversionPostingTagName `elem` map fst (ptags p) && nocosts = Nothing
| otherwise = Just $ postingTransformAmount mixedAmountCost p
where
nocosts = (not . any (isJust . acost) . amountsRaw) $ pamount p
-- | Generate equity conversion postings corresponding to a 'Posting''s cost(s)
-- (one pair of conversion postings per cost), wherever they don't already exist.
postingAddInferredEquityPostings :: Bool -> Text -> Posting -> [Posting]
postingAddInferredEquityPostings verbosetags equityAcct p
-- this posting has no costs
| null costs = [p]
-- this posting is already tagged as having associated conversion postings
| costPostingTagName `elem` map fst (ptags p) = [p]
-- tag the posting, and for each of its costs, add an equivalent pair of conversion postings after it
| otherwise =
postingAddHiddenAndMaybeVisibleTag verbosetags (costPostingTagName,"") p :
concatMap makeConversionPostings costs
where
costs = filter (isJust . acost) . amountsRaw $ pamount p
makeConversionPostings amt = case acost amt of
Nothing -> []
Just _ -> [ convp{ paccount = accountPrefix <> amtCommodity
, pamount = mixedAmount . negate $ amountStripCost amt
}
, convp{ paccount = accountPrefix <> costCommodity
, pamount = mixedAmount cost
}
]
where
cost = amountCost amt
amtCommodity = commodity amt
costCommodity = commodity cost
convp = p{pbalanceassertion=Nothing, poriginal=Nothing}
& postingAddHiddenAndMaybeVisibleTag verbosetags (conversionPostingTagName,"")
& postingAddHiddenAndMaybeVisibleTag verbosetags (generatedPostingTagName, "")
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 main amount (but not its balance assertion 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
-- tests
tests_Posting = testGroup "Posting" [
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: "
]