{-# LANGUAGE CPP #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
module Hledger.Data.Posting (
nullposting,
posting,
post,
vpost,
post',
vpost',
nullassertion,
balassert,
balassertTot,
balassertParInc,
balassertTotInc,
originalPosting,
postingStatus,
isReal,
isVirtual,
isBalancedVirtual,
isEmptyPosting,
hasBalanceAssignment,
hasAmount,
postingAllTags,
transactionAllTags,
relatedPostings,
postingStripCosts,
postingApplyAliases,
postingApplyCommodityStyles,
postingStyleAmounts,
postingAddTags,
postingAddHiddenAndMaybeVisibleTag,
postingDate,
postingDate2,
postingDateOrDate2,
isPostingInDateSpan,
isPostingInDateSpan',
accountNamesFromPostings,
commentJoin,
commentAddTag,
commentAddTagUnspaced,
commentAddTagNextLine,
generatedTransactionTagName,
modifiedTransactionTagName,
generatedPostingTagName,
costPostingTagName,
conversionPostingTagName,
sumPostings,
postingNegate,
postingNegateMainAmount,
showPosting,
showPostingLines,
postingAsLines,
postingsAsLines,
postingIndent,
showAccountName,
renderCommentLines,
showBalanceAssertion,
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
generatedTransactionTagName, modifiedTransactionTagName, costPostingTagName, conversionPostingTagName, generatedPostingTagName :: TagName
generatedTransactionTagName :: Text
generatedTransactionTagName = Text
"_generated-transaction"
modifiedTransactionTagName :: Text
modifiedTransactionTagName = Text
"_modified-transaction"
generatedPostingTagName :: Text
generatedPostingTagName = Text
"_generated-posting"
costPostingTagName :: Text
costPostingTagName = Text
"_cost-posting"
conversionPostingTagName :: Text
conversionPostingTagName = Text
"_conversion-posting"
instance HasAmounts BalanceAssertion where
styleAmounts :: Map Text AmountStyle -> BalanceAssertion -> BalanceAssertion
styleAmounts Map Text AmountStyle
styles ba :: BalanceAssertion
ba@BalanceAssertion{Amount
baamount :: Amount
baamount :: BalanceAssertion -> Amount
baamount} = BalanceAssertion
ba{baamount=styleAmounts styles baamount}
instance HasAmounts Posting where
styleAmounts :: Map Text AmountStyle -> Posting -> Posting
styleAmounts Map Text AmountStyle
styles p :: Posting
p@Posting{MixedAmount
pamount :: MixedAmount
pamount :: Posting -> MixedAmount
pamount, Maybe BalanceAssertion
pbalanceassertion :: Maybe BalanceAssertion
pbalanceassertion :: Posting -> Maybe BalanceAssertion
pbalanceassertion} =
Posting
p{ pamount=styleAmounts styles pamount
,pbalanceassertion=styleAmounts styles pbalanceassertion
}
{-# DEPRECATED postingApplyCommodityStyles "please use styleAmounts instead" #-}
postingApplyCommodityStyles :: M.Map CommoditySymbol AmountStyle -> Posting -> Posting
postingApplyCommodityStyles :: Map Text AmountStyle -> Posting -> Posting
postingApplyCommodityStyles = Map Text AmountStyle -> Posting -> Posting
forall a. HasAmounts a => Map Text AmountStyle -> a -> a
styleAmounts
{-# DEPRECATED postingStyleAmounts "please use styleAmounts instead" #-}
postingStyleAmounts :: M.Map CommoditySymbol AmountStyle -> Posting -> Posting
postingStyleAmounts :: Map Text AmountStyle -> Posting -> Posting
postingStyleAmounts = Map Text AmountStyle -> Posting -> Posting
forall a. HasAmounts a => Map Text AmountStyle -> a -> a
styleAmounts
nullposting, posting :: Posting
nullposting :: Posting
nullposting = Posting
{pdate :: Maybe Day
pdate=Maybe Day
forall a. Maybe a
Nothing
,pdate2 :: Maybe Day
pdate2=Maybe Day
forall a. Maybe a
Nothing
,pstatus :: Status
pstatus=Status
Unmarked
,paccount :: Text
paccount=Text
""
,pamount :: MixedAmount
pamount=MixedAmount
nullmixedamt
,pcomment :: Text
pcomment=Text
""
,ptype :: PostingType
ptype=PostingType
RegularPosting
,ptags :: [Tag]
ptags=[]
,pbalanceassertion :: Maybe BalanceAssertion
pbalanceassertion=Maybe BalanceAssertion
forall a. Maybe a
Nothing
,ptransaction :: Maybe Transaction
ptransaction=Maybe Transaction
forall a. Maybe a
Nothing
,poriginal :: Maybe Posting
poriginal=Maybe Posting
forall a. Maybe a
Nothing
}
posting :: Posting
posting = Posting
nullposting
post :: AccountName -> Amount -> Posting
post :: Text -> Amount -> Posting
post Text
acc Amount
amt = Posting
posting {paccount=acc, pamount=mixedAmount amt}
vpost :: AccountName -> Amount -> Posting
vpost :: Text -> Amount -> Posting
vpost Text
acc Amount
amt = (Text -> Amount -> Posting
post Text
acc Amount
amt){ptype=VirtualPosting}
post' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
post' :: Text -> Amount -> Maybe BalanceAssertion -> Posting
post' Text
acc Amount
amt Maybe BalanceAssertion
ass = Posting
posting {paccount=acc, pamount=mixedAmount amt, pbalanceassertion=ass}
vpost' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
vpost' :: Text -> Amount -> Maybe BalanceAssertion -> Posting
vpost' Text
acc Amount
amt Maybe BalanceAssertion
ass = (Text -> Amount -> Maybe BalanceAssertion -> Posting
post' Text
acc Amount
amt Maybe BalanceAssertion
ass){ptype=VirtualPosting, pbalanceassertion=ass}
nullassertion :: BalanceAssertion
nullassertion :: BalanceAssertion
nullassertion = BalanceAssertion
{baamount :: Amount
baamount=Amount
nullamt
,batotal :: Bool
batotal=Bool
False
,bainclusive :: Bool
bainclusive=Bool
False
,baposition :: SourcePos
baposition=FilePath -> SourcePos
initialPos FilePath
""
}
balassert :: Amount -> Maybe BalanceAssertion
balassert :: Amount -> Maybe BalanceAssertion
balassert Amount
amt = BalanceAssertion -> Maybe BalanceAssertion
forall a. a -> Maybe a
Just (BalanceAssertion -> Maybe BalanceAssertion)
-> BalanceAssertion -> Maybe BalanceAssertion
forall a b. (a -> b) -> a -> b
$ BalanceAssertion
nullassertion{baamount=amt}
balassertTot :: Amount -> Maybe BalanceAssertion
balassertTot :: Amount -> Maybe BalanceAssertion
balassertTot Amount
amt = BalanceAssertion -> Maybe BalanceAssertion
forall a. a -> Maybe a
Just (BalanceAssertion -> Maybe BalanceAssertion)
-> BalanceAssertion -> Maybe BalanceAssertion
forall a b. (a -> b) -> a -> b
$ BalanceAssertion
nullassertion{baamount=amt, batotal=True}
balassertParInc :: Amount -> Maybe BalanceAssertion
balassertParInc :: Amount -> Maybe BalanceAssertion
balassertParInc Amount
amt = BalanceAssertion -> Maybe BalanceAssertion
forall a. a -> Maybe a
Just (BalanceAssertion -> Maybe BalanceAssertion)
-> BalanceAssertion -> Maybe BalanceAssertion
forall a b. (a -> b) -> a -> b
$ BalanceAssertion
nullassertion{baamount=amt, bainclusive=True}
balassertTotInc :: Amount -> Maybe BalanceAssertion
balassertTotInc :: Amount -> Maybe BalanceAssertion
balassertTotInc Amount
amt = BalanceAssertion -> Maybe BalanceAssertion
forall a. a -> Maybe a
Just (BalanceAssertion -> Maybe BalanceAssertion)
-> BalanceAssertion -> Maybe BalanceAssertion
forall a b. (a -> b) -> a -> b
$ BalanceAssertion
nullassertion{baamount=amt, batotal=True, bainclusive=True}
showBalanceAssertion :: BalanceAssertion -> WideBuilder
showBalanceAssertion :: BalanceAssertion -> WideBuilder
showBalanceAssertion BalanceAssertion
ba =
Char -> WideBuilder
singleton Char
'=' WideBuilder -> WideBuilder -> WideBuilder
forall a. Semigroup a => a -> a -> a
<> WideBuilder
eq WideBuilder -> WideBuilder -> WideBuilder
forall a. Semigroup a => a -> a -> a
<> WideBuilder
ast WideBuilder -> WideBuilder -> WideBuilder
forall a. Semigroup a => a -> a -> a
<> Char -> WideBuilder
singleton Char
' ' WideBuilder -> WideBuilder -> WideBuilder
forall a. Semigroup a => a -> a -> a
<> AmountFormat -> Amount -> WideBuilder
showAmountB AmountFormat
forall a. Default a => a
def{displayZeroCommodity=True, displayForceDecimalMark=True} (BalanceAssertion -> Amount
baamount BalanceAssertion
ba)
where
eq :: WideBuilder
eq = if BalanceAssertion -> Bool
batotal BalanceAssertion
ba then Char -> WideBuilder
singleton Char
'=' else WideBuilder
forall a. Monoid a => a
mempty
ast :: WideBuilder
ast = if BalanceAssertion -> Bool
bainclusive BalanceAssertion
ba then Char -> WideBuilder
singleton Char
'*' else WideBuilder
forall a. Monoid a => a
mempty
singleton :: Char -> WideBuilder
singleton Char
c = Builder -> Int -> WideBuilder
WideBuilder (Char -> Builder
TB.singleton Char
c) Int
1
originalPosting :: Posting -> Posting
originalPosting :: Posting -> Posting
originalPosting Posting
p = Posting -> Maybe Posting -> Posting
forall a. a -> Maybe a -> a
fromMaybe Posting
p (Maybe Posting -> Posting) -> Maybe Posting -> Posting
forall a b. (a -> b) -> a -> b
$ Posting -> Maybe Posting
poriginal Posting
p
showPosting :: Posting -> String
showPosting :: Posting -> FilePath
showPosting Posting
p = Text -> FilePath
T.unpack (Text -> FilePath) -> ([Text] -> Text) -> [Text] -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.unlines ([Text] -> FilePath) -> [Text] -> FilePath
forall a b. (a -> b) -> a -> b
$ Bool -> [Posting] -> [Text]
postingsAsLines Bool
False [Posting
p]
showPostingLines :: Posting -> [Text]
showPostingLines :: Posting -> [Text]
showPostingLines Posting
p = ([Text], Int, Int) -> [Text]
forall {a} {b} {c}. (a, b, c) -> a
first3 (([Text], Int, Int) -> [Text]) -> ([Text], Int, Int) -> [Text]
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> Int -> Int -> Posting -> ([Text], Int, Int)
postingAsLines Bool
False Bool
False Int
maxacctwidth Int
maxamtwidth Posting
p
where
linesWithWidths :: [([Text], Int, Int)]
linesWithWidths = (Posting -> ([Text], Int, Int))
-> [Posting] -> [([Text], Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Bool -> Int -> Int -> Posting -> ([Text], Int, Int)
postingAsLines Bool
False Bool
False Int
maxacctwidth Int
maxamtwidth) ([Posting] -> [([Text], Int, Int)])
-> (Maybe Transaction -> [Posting])
-> Maybe Transaction
-> [([Text], Int, Int)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Posting]
-> (Transaction -> [Posting]) -> Maybe Transaction -> [Posting]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Posting
p] Transaction -> [Posting]
tpostings (Maybe Transaction -> [([Text], Int, Int)])
-> Maybe Transaction -> [([Text], Int, Int)]
forall a b. (a -> b) -> a -> b
$ Posting -> Maybe Transaction
ptransaction Posting
p
maxacctwidth :: Int
maxacctwidth = Int -> [Int] -> Int
forall a. Ord a => a -> [a] -> a
maximumBound Int
0 ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (([Text], Int, Int) -> Int) -> [([Text], Int, Int)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Text], Int, Int) -> Int
forall {a} {b} {c}. (a, b, c) -> b
second3 [([Text], Int, Int)]
linesWithWidths
maxamtwidth :: Int
maxamtwidth = Int -> [Int] -> Int
forall a. Ord a => a -> [a] -> a
maximumBound Int
0 ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (([Text], Int, Int) -> Int) -> [([Text], Int, Int)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Text], Int, Int) -> Int
forall {a} {b} {c}. (a, b, c) -> c
third3 [([Text], Int, Int)]
linesWithWidths
postingsAsLines :: Bool -> [Posting] -> [Text]
postingsAsLines :: Bool -> [Posting] -> [Text]
postingsAsLines Bool
onelineamounts [Posting]
ps = (([Text], Int, Int) -> [Text]) -> [([Text], Int, Int)] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([Text], Int, Int) -> [Text]
forall {a} {b} {c}. (a, b, c) -> a
first3 [([Text], Int, Int)]
linesWithWidths
where
linesWithWidths :: [([Text], Int, Int)]
linesWithWidths = (Posting -> ([Text], Int, Int))
-> [Posting] -> [([Text], Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (Bool -> Bool -> Int -> Int -> Posting -> ([Text], Int, Int)
postingAsLines Bool
False Bool
onelineamounts Int
maxacctwidth Int
maxamtwidth) [Posting]
ps
maxacctwidth :: Int
maxacctwidth = Int -> [Int] -> Int
forall a. Ord a => a -> [a] -> a
maximumBound Int
0 ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (([Text], Int, Int) -> Int) -> [([Text], Int, Int)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Text], Int, Int) -> Int
forall {a} {b} {c}. (a, b, c) -> b
second3 [([Text], Int, Int)]
linesWithWidths
maxamtwidth :: Int
maxamtwidth = Int -> [Int] -> Int
forall a. Ord a => a -> [a] -> a
maximumBound Int
0 ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (([Text], Int, Int) -> Int) -> [([Text], Int, Int)] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Text], Int, Int) -> Int
forall {a} {b} {c}. (a, b, c) -> c
third3 [([Text], Int, Int)]
linesWithWidths
postingAsLines :: Bool -> Bool -> Int -> Int -> Posting -> ([Text], Int, Int)
postingAsLines :: Bool -> Bool -> Int -> Int -> Posting -> ([Text], Int, Int)
postingAsLines Bool
elideamount Bool
onelineamounts Int
acctwidth Int
amtwidth Posting
p =
(([Text] -> [Text]) -> [[Text]] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text]
newlinecomments) [[Text]]
postingblocks, Int
thisacctwidth, Int
thisamtwidth)
where
postingblocks :: [[Text]]
postingblocks = [(Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
T.stripEnd ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.lines (Text -> [Text]) -> (Text -> Text) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
TL.toStrict (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$
[Cell] -> Text
render [ Align -> Text -> Cell
textCell Align
BottomLeft Text
statusandaccount
, Align -> Text -> Cell
textCell Align
BottomLeft Text
" "
, Align -> [WideBuilder] -> Cell
Cell Align
BottomLeft [WideBuilder -> WideBuilder
pad WideBuilder
amt]
, Align -> [WideBuilder] -> Cell
Cell Align
BottomLeft [WideBuilder
assertion]
, Align -> Text -> Cell
textCell Align
BottomLeft Text
samelinecomment
]
| (WideBuilder
amt,WideBuilder
assertion) <- [(WideBuilder, WideBuilder)]
shownAmountsAssertions]
render :: [Cell] -> Text
render = TableOpts -> Header Cell -> Text
renderRow TableOpts
forall a. Default a => a
def{tableBorders=False, borderSpaces=False} (Header Cell -> Text) -> ([Cell] -> Header Cell) -> [Cell] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Properties -> [Header Cell] -> Header Cell
forall h. Properties -> [Header h] -> Header h
Group Properties
NoLine ([Header Cell] -> Header Cell)
-> ([Cell] -> [Header Cell]) -> [Cell] -> Header Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Cell -> Header Cell) -> [Cell] -> [Header Cell]
forall a b. (a -> b) -> [a] -> [b]
map Cell -> Header Cell
forall h. h -> Header h
Header
pad :: WideBuilder -> WideBuilder
pad WideBuilder
amt = Builder -> Int -> WideBuilder
WideBuilder (Text -> Builder
TB.fromText (Text -> Builder) -> Text -> Builder
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.replicate Int
w Text
" ") Int
w WideBuilder -> WideBuilder -> WideBuilder
forall a. Semigroup a => a -> a -> a
<> WideBuilder
amt
where w :: Int
w = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
12 Int
amtwidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- WideBuilder -> Int
wbWidth WideBuilder
amt
pacctstr :: Posting -> Text
pacctstr Posting
p' = Maybe Int -> PostingType -> Text -> Text
showAccountName Maybe Int
forall a. Maybe a
Nothing (Posting -> PostingType
ptype Posting
p') (Posting -> Text
paccount Posting
p')
pstatusandacct :: Posting -> Text
pstatusandacct Posting
p' = Posting -> Text
pstatusprefix Posting
p' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Posting -> Text
pacctstr Posting
p'
pstatusprefix :: Posting -> Text
pstatusprefix Posting
p' = case Posting -> Status
pstatus Posting
p' of
Status
Unmarked -> Text
""
Status
s -> FilePath -> Text
T.pack (Status -> FilePath
forall a. Show a => a -> FilePath
show Status
s) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" "
shownAmounts :: [WideBuilder]
shownAmounts
| Bool
elideamount = [WideBuilder
forall a. Monoid a => a
mempty]
| Bool
otherwise = AmountFormat -> MixedAmount -> [WideBuilder]
showMixedAmountLinesB AmountFormat
displayopts (MixedAmount -> [WideBuilder]) -> MixedAmount -> [WideBuilder]
forall a b. (a -> b) -> a -> b
$ Posting -> MixedAmount
pamount Posting
p
where displayopts :: AmountFormat
displayopts = AmountFormat
defaultFmt{
displayZeroCommodity=True, displayForceDecimalMark=True, displayOneLine=onelineamounts
}
thisamtwidth :: Int
thisamtwidth = Int -> [Int] -> Int
forall a. Ord a => a -> [a] -> a
maximumBound Int
0 ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (WideBuilder -> Int) -> [WideBuilder] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map WideBuilder -> Int
wbWidth [WideBuilder]
shownAmounts
shownAmountsAssertions :: [(WideBuilder, WideBuilder)]
shownAmountsAssertions = [WideBuilder] -> [WideBuilder] -> [(WideBuilder, WideBuilder)]
forall a b. [a] -> [b] -> [(a, b)]
zip [WideBuilder]
shownAmounts [WideBuilder]
shownAssertions
where
shownAssertions :: [WideBuilder]
shownAssertions = Int -> WideBuilder -> [WideBuilder]
forall a. Int -> a -> [a]
replicate ([WideBuilder] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [WideBuilder]
shownAmounts Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) WideBuilder
forall a. Monoid a => a
mempty [WideBuilder] -> [WideBuilder] -> [WideBuilder]
forall a. [a] -> [a] -> [a]
++ [WideBuilder
assertion]
where
assertion :: WideBuilder
assertion = WideBuilder
-> (BalanceAssertion -> WideBuilder)
-> Maybe BalanceAssertion
-> WideBuilder
forall b a. b -> (a -> b) -> Maybe a -> b
maybe WideBuilder
forall a. Monoid a => a
mempty ((Builder -> Int -> WideBuilder
WideBuilder (Char -> Builder
TB.singleton Char
' ') Int
1 WideBuilder -> WideBuilder -> WideBuilder
forall a. Semigroup a => a -> a -> a
<>)(WideBuilder -> WideBuilder)
-> (BalanceAssertion -> WideBuilder)
-> BalanceAssertion
-> WideBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
.BalanceAssertion -> WideBuilder
showBalanceAssertion) (Maybe BalanceAssertion -> WideBuilder)
-> Maybe BalanceAssertion -> WideBuilder
forall a b. (a -> b) -> a -> b
$ Posting -> Maybe BalanceAssertion
pbalanceassertion Posting
p
statusandaccount :: Text
statusandaccount = Text -> Text
postingIndent (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Int -> Maybe Int -> Bool -> Bool -> Text -> Text
fitText (Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
acctwidth) Maybe Int
forall a. Maybe a
Nothing Bool
False Bool
True (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Posting -> Text
pstatusandacct Posting
p
thisacctwidth :: Int
thisacctwidth = Text -> Int
forall a. HasChars a => a -> Int
realLength (Text -> Int) -> Text -> Int
forall a b. (a -> b) -> a -> b
$ Posting -> Text
pacctstr Posting
p
(Text
samelinecomment, [Text]
newlinecomments) =
case Text -> [Text]
renderCommentLines (Posting -> Text
pcomment Posting
p) of [] -> (Text
"",[])
Text
c:[Text]
cs -> (Text
c,[Text]
cs)
showAccountName :: Maybe Int -> PostingType -> AccountName -> Text
showAccountName :: Maybe Int -> PostingType -> Text -> Text
showAccountName Maybe Int
w = PostingType -> Text -> Text
fmt
where
fmt :: PostingType -> Text -> Text
fmt PostingType
RegularPosting = (Text -> Text)
-> (Int -> Text -> Text) -> Maybe Int -> Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text -> Text
forall a. a -> a
id Int -> Text -> Text
T.take Maybe Int
w
fmt PostingType
VirtualPosting = Text -> Text -> Text -> Text
wrap Text
"(" Text
")" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text)
-> (Int -> Text -> Text) -> Maybe Int -> Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text -> Text
forall a. a -> a
id (Int -> Text -> Text
T.takeEnd (Int -> Text -> Text) -> (Int -> Int) -> Int -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
2) Maybe Int
w
fmt PostingType
BalancedVirtualPosting = Text -> Text -> Text -> Text
wrap Text
"[" Text
"]" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text)
-> (Int -> Text -> Text) -> Maybe Int -> Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text -> Text
forall a. a -> a
id (Int -> Text -> Text
T.takeEnd (Int -> Text -> Text) -> (Int -> Int) -> Int -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
2) Maybe Int
w
renderCommentLines :: Text -> [Text]
Text
t =
case Text -> [Text]
T.lines Text
t of
[] -> []
[Text
l] -> [Text -> Text
commentSpace (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
comment Text
l]
(Text
"":[Text]
ls) -> Text
"" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Text
postingIndent (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
comment) [Text]
ls
(Text
l:[Text]
ls) -> Text -> Text
commentSpace (Text -> Text
comment Text
l) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Text
postingIndent (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
comment) [Text]
ls
where
comment :: Text -> Text
comment = (Text
"; "Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>)
postingIndent :: Text -> Text
postingIndent :: Text -> Text
postingIndent = (Text
" "Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>)
commentSpace :: Text -> Text
= (Text
" "Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>)
isReal :: Posting -> Bool
isReal :: Posting -> Bool
isReal Posting
p = Posting -> PostingType
ptype Posting
p PostingType -> PostingType -> Bool
forall a. Eq a => a -> a -> Bool
== PostingType
RegularPosting
isVirtual :: Posting -> Bool
isVirtual :: Posting -> Bool
isVirtual Posting
p = Posting -> PostingType
ptype Posting
p PostingType -> PostingType -> Bool
forall a. Eq a => a -> a -> Bool
== PostingType
VirtualPosting
isBalancedVirtual :: Posting -> Bool
isBalancedVirtual :: Posting -> Bool
isBalancedVirtual Posting
p = Posting -> PostingType
ptype Posting
p PostingType -> PostingType -> Bool
forall a. Eq a => a -> a -> Bool
== PostingType
BalancedVirtualPosting
hasAmount :: Posting -> Bool
hasAmount :: Posting -> Bool
hasAmount = Bool -> Bool
not (Bool -> Bool) -> (Posting -> Bool) -> Posting -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MixedAmount -> Bool
isMissingMixedAmount (MixedAmount -> Bool)
-> (Posting -> MixedAmount) -> Posting -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Posting -> MixedAmount
pamount
hasBalanceAssignment :: Posting -> Bool
hasBalanceAssignment :: Posting -> Bool
hasBalanceAssignment Posting
p = Bool -> Bool
not (Posting -> Bool
hasAmount Posting
p) Bool -> Bool -> Bool
&& Maybe BalanceAssertion -> Bool
forall a. Maybe a -> Bool
isJust (Posting -> Maybe BalanceAssertion
pbalanceassertion Posting
p)
accountNamesFromPostings :: [Posting] -> [AccountName]
accountNamesFromPostings :: [Posting] -> [Text]
accountNamesFromPostings = Set Text -> [Text]
forall a. Set a -> [a]
S.toList (Set Text -> [Text])
-> ([Posting] -> Set Text) -> [Posting] -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Set Text
forall a. Ord a => [a] -> Set a
S.fromList ([Text] -> Set Text)
-> ([Posting] -> [Text]) -> [Posting] -> Set Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Posting -> Text) -> [Posting] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Text
paccount
sumPostings :: [Posting] -> MixedAmount
sumPostings :: [Posting] -> MixedAmount
sumPostings = (MixedAmount -> Posting -> MixedAmount)
-> MixedAmount -> [Posting] -> MixedAmount
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\MixedAmount
amt Posting
p -> MixedAmount -> MixedAmount -> MixedAmount
maPlus MixedAmount
amt (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ Posting -> MixedAmount
pamount Posting
p) MixedAmount
nullmixedamt
postingNegate :: Posting -> Posting
postingNegate :: Posting -> Posting
postingNegate p :: Posting
p@Posting{pamount :: Posting -> MixedAmount
pamount=MixedAmount
a, pbalanceassertion :: Posting -> Maybe BalanceAssertion
pbalanceassertion=Maybe BalanceAssertion
mb} =
Posting
p{pamount=negate a, pbalanceassertion=fmap balanceAssertionNegate mb}
where
balanceAssertionNegate :: BalanceAssertion -> BalanceAssertion
balanceAssertionNegate b :: BalanceAssertion
b@BalanceAssertion{baamount :: BalanceAssertion -> Amount
baamount=Amount
ba} = BalanceAssertion
b{baamount=negate ba}
postingNegateMainAmount :: Posting -> Posting
postingNegateMainAmount :: Posting -> Posting
postingNegateMainAmount p :: Posting
p@Posting{pamount :: Posting -> MixedAmount
pamount=MixedAmount
a} = Posting
p{pamount=negate a}
postingStripCosts :: Posting -> Posting
postingStripCosts :: Posting -> Posting
postingStripCosts = (MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount MixedAmount -> MixedAmount
mixedAmountStripCosts
postingDate :: Posting -> Day
postingDate :: Posting -> Day
postingDate Posting
p = Day -> Maybe Day -> Day
forall a. a -> Maybe a -> a
fromMaybe Day
nulldate (Maybe Day -> Day) -> Maybe Day -> Day
forall a b. (a -> b) -> a -> b
$ [Maybe Day] -> Maybe Day
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum [Maybe Day]
dates
where dates :: [Maybe Day]
dates = [ Posting -> Maybe Day
pdate Posting
p, Transaction -> Day
tdate (Transaction -> Day) -> Maybe Transaction -> Maybe Day
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Posting -> Maybe Transaction
ptransaction Posting
p ]
postingDate2 :: Posting -> Day
postingDate2 :: Posting -> Day
postingDate2 Posting
p = Day -> Maybe Day -> Day
forall a. a -> Maybe a -> a
fromMaybe Day
nulldate (Maybe Day -> Day) -> Maybe Day -> Day
forall a b. (a -> b) -> a -> b
$ [Maybe Day] -> Maybe Day
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum [Maybe Day]
dates
where dates :: [Maybe Day]
dates = [ Posting -> Maybe Day
pdate2 Posting
p
, Transaction -> Maybe Day
tdate2 (Transaction -> Maybe Day) -> Maybe Transaction -> Maybe Day
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Posting -> Maybe Transaction
ptransaction Posting
p
, Posting -> Maybe Day
pdate Posting
p
, Transaction -> Day
tdate (Transaction -> Day) -> Maybe Transaction -> Maybe Day
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Posting -> Maybe Transaction
ptransaction Posting
p
]
postingDateOrDate2 :: WhichDate -> Posting -> Day
postingDateOrDate2 :: WhichDate -> Posting -> Day
postingDateOrDate2 WhichDate
PrimaryDate = Posting -> Day
postingDate
postingDateOrDate2 WhichDate
SecondaryDate = Posting -> Day
postingDate2
postingStatus :: Posting -> Status
postingStatus :: Posting -> Status
postingStatus Posting{pstatus :: Posting -> Status
pstatus=Status
s, ptransaction :: Posting -> Maybe Transaction
ptransaction=Maybe Transaction
mt} = case Status
s of
Status
Unmarked -> Status -> (Transaction -> Status) -> Maybe Transaction -> Status
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Status
Unmarked Transaction -> Status
tstatus Maybe Transaction
mt
Status
_ -> Status
s
postingAllTags :: Posting -> [Tag]
postingAllTags :: Posting -> [Tag]
postingAllTags Posting
p = Posting -> [Tag]
ptags Posting
p [Tag] -> [Tag] -> [Tag]
forall a. [a] -> [a] -> [a]
++ [Tag] -> (Transaction -> [Tag]) -> Maybe Transaction -> [Tag]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Transaction -> [Tag]
ttags (Posting -> Maybe Transaction
ptransaction Posting
p)
transactionAllTags :: Transaction -> [Tag]
transactionAllTags :: Transaction -> [Tag]
transactionAllTags Transaction
t = Transaction -> [Tag]
ttags Transaction
t [Tag] -> [Tag] -> [Tag]
forall a. [a] -> [a] -> [a]
++ (Posting -> [Tag]) -> [Posting] -> [Tag]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Posting -> [Tag]
ptags (Transaction -> [Posting]
tpostings Transaction
t)
relatedPostings :: Posting -> [Posting]
relatedPostings :: Posting -> [Posting]
relatedPostings p :: Posting
p@Posting{ptransaction :: Posting -> Maybe Transaction
ptransaction=Just Transaction
t} = (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter (Posting -> Posting -> Bool
forall a. Eq a => a -> a -> Bool
/= Posting
p) ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t
relatedPostings Posting
_ = []
isPostingInDateSpan :: DateSpan -> Posting -> Bool
isPostingInDateSpan :: DateSpan -> Posting -> Bool
isPostingInDateSpan = WhichDate -> DateSpan -> Posting -> Bool
isPostingInDateSpan' WhichDate
PrimaryDate
isPostingInDateSpan' :: WhichDate -> DateSpan -> Posting -> Bool
isPostingInDateSpan' :: WhichDate -> DateSpan -> Posting -> Bool
isPostingInDateSpan' WhichDate
PrimaryDate DateSpan
s = DateSpan -> Day -> Bool
spanContainsDate DateSpan
s (Day -> Bool) -> (Posting -> Day) -> Posting -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Posting -> Day
postingDate
isPostingInDateSpan' WhichDate
SecondaryDate DateSpan
s = DateSpan -> Day -> Bool
spanContainsDate DateSpan
s (Day -> Bool) -> (Posting -> Day) -> Posting -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Posting -> Day
postingDate2
isEmptyPosting :: Posting -> Bool
isEmptyPosting :: Posting -> Bool
isEmptyPosting = MixedAmount -> Bool
mixedAmountLooksZero (MixedAmount -> Bool)
-> (Posting -> MixedAmount) -> Posting -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Posting -> MixedAmount
pamount
postingApplyAliases :: [AccountAlias] -> Posting -> Either RegexError Posting
postingApplyAliases :: [AccountAlias] -> Posting -> Either FilePath Posting
postingApplyAliases [AccountAlias]
aliases p :: Posting
p@Posting{Text
paccount :: Posting -> Text
paccount :: Text
paccount} =
case [AccountAlias] -> Text -> Either FilePath Text
accountNameApplyAliases [AccountAlias]
aliases Text
paccount of
Right Text
a -> Posting -> Either FilePath Posting
forall a b. b -> Either a b
Right Posting
p{paccount=a}
Left FilePath
e -> FilePath -> Either FilePath Posting
forall a b. a -> Either a b
Left FilePath
err
where
err :: FilePath
err = FilePath
"problem while applying account aliases:\n" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [AccountAlias] -> FilePath
forall a. Show a => a -> FilePath
pshow [AccountAlias]
aliases
FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n to account name: "FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++Text -> FilePath
T.unpack Text
paccountFilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++FilePath
"\n "FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++FilePath
e
postingAddTags :: Posting -> [Tag] -> Posting
postingAddTags :: Posting -> [Tag] -> Posting
postingAddTags p :: Posting
p@Posting{[Tag]
ptags :: Posting -> [Tag]
ptags :: [Tag]
ptags} [Tag]
tags = Posting
p{ptags=ptags `union` tags}
postingAddHiddenAndMaybeVisibleTag :: Bool -> HiddenTag -> Posting -> Posting
postingAddHiddenAndMaybeVisibleTag :: Bool -> Tag -> Posting -> Posting
postingAddHiddenAndMaybeVisibleTag Bool
verbosetags Tag
ht p :: Posting
p@Posting{pcomment :: Posting -> Text
pcomment=Text
c, [Tag]
ptags :: Posting -> [Tag]
ptags :: [Tag]
ptags} =
(Posting
p Posting -> [Tag] -> Posting
`postingAddTags` ([Tag
ht] [Tag] -> [Tag] -> [Tag]
forall a. Semigroup a => a -> a -> a
<> [Tag
vt|Bool
verbosetags]))
{pcomment=if verbosetags && not hadtag then c `commentAddTag` vt else c}
where
vt :: Tag
vt@(Text
vname,Text
_) = Tag -> Tag
toVisibleTag Tag
ht
hadtag :: Bool
hadtag = (Tag -> Bool) -> [Tag] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== (Text -> Text
T.toLower Text
vname)) (Text -> Bool) -> (Tag -> Text) -> Tag -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.toLower (Text -> Text) -> (Tag -> Text) -> Tag -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tag -> Text
forall a b. (a, b) -> a
fst) [Tag]
ptags
postingApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Posting -> Posting
postingApplyValuation :: PriceOracle
-> Map Text AmountStyle
-> Day
-> Day
-> ValuationType
-> Posting
-> Posting
postingApplyValuation PriceOracle
priceoracle Map Text AmountStyle
styles Day
periodlast Day
today ValuationType
v Posting
p =
(MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount (PriceOracle
-> Map Text AmountStyle
-> Day
-> Day
-> Day
-> ValuationType
-> MixedAmount
-> MixedAmount
mixedAmountApplyValuation PriceOracle
priceoracle Map Text AmountStyle
styles Day
periodlast Day
today (Posting -> Day
postingDate Posting
p) ValuationType
v) Posting
p
postingToCost :: ConversionOp -> Posting -> Maybe Posting
postingToCost :: ConversionOp -> Posting -> Maybe Posting
postingToCost ConversionOp
NoConversionOp Posting
p = Posting -> Maybe Posting
forall a. a -> Maybe a
Just Posting
p
postingToCost ConversionOp
ToCost Posting
p
| Text
conversionPostingTagName Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Tag -> Text) -> [Tag] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Tag -> Text
forall a b. (a, b) -> a
fst (Posting -> [Tag]
ptags Posting
p) Bool -> Bool -> Bool
&& Bool
nocosts = Maybe Posting
forall a. Maybe a
Nothing
| Bool
otherwise = Posting -> Maybe Posting
forall a. a -> Maybe a
Just (Posting -> Maybe Posting) -> Posting -> Maybe Posting
forall a b. (a -> b) -> a -> b
$ (MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount MixedAmount -> MixedAmount
mixedAmountCost Posting
p
where
nocosts :: Bool
nocosts = (Bool -> Bool
not (Bool -> Bool) -> (MixedAmount -> Bool) -> MixedAmount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Amount -> Bool) -> [Amount] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Maybe AmountCost -> Bool
forall a. Maybe a -> Bool
isJust (Maybe AmountCost -> Bool)
-> (Amount -> Maybe AmountCost) -> Amount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Amount -> Maybe AmountCost
acost) ([Amount] -> Bool)
-> (MixedAmount -> [Amount]) -> MixedAmount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MixedAmount -> [Amount]
amountsRaw) (MixedAmount -> Bool) -> MixedAmount -> Bool
forall a b. (a -> b) -> a -> b
$ Posting -> MixedAmount
pamount Posting
p
postingAddInferredEquityPostings :: Bool -> Text -> Posting -> [Posting]
postingAddInferredEquityPostings :: Bool -> Text -> Posting -> [Posting]
postingAddInferredEquityPostings Bool
verbosetags Text
equityAcct Posting
p
| [Amount] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Amount]
costs = [Posting
p]
| Text
costPostingTagName Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Tag -> Text) -> [Tag] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Tag -> Text
forall a b. (a, b) -> a
fst (Posting -> [Tag]
ptags Posting
p) = [Posting
p]
| Bool
otherwise =
Bool -> Tag -> Posting -> Posting
postingAddHiddenAndMaybeVisibleTag Bool
verbosetags (Text
costPostingTagName,Text
"") Posting
p Posting -> [Posting] -> [Posting]
forall a. a -> [a] -> [a]
:
(Amount -> [Posting]) -> [Amount] -> [Posting]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Amount -> [Posting]
makeConversionPostings [Amount]
costs
where
costs :: [Amount]
costs = (Amount -> Bool) -> [Amount] -> [Amount]
forall a. (a -> Bool) -> [a] -> [a]
filter (Maybe AmountCost -> Bool
forall a. Maybe a -> Bool
isJust (Maybe AmountCost -> Bool)
-> (Amount -> Maybe AmountCost) -> Amount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Amount -> Maybe AmountCost
acost) ([Amount] -> [Amount])
-> (MixedAmount -> [Amount]) -> MixedAmount -> [Amount]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MixedAmount -> [Amount]
amountsRaw (MixedAmount -> [Amount]) -> MixedAmount -> [Amount]
forall a b. (a -> b) -> a -> b
$ Posting -> MixedAmount
pamount Posting
p
makeConversionPostings :: Amount -> [Posting]
makeConversionPostings Amount
amt = case Amount -> Maybe AmountCost
acost Amount
amt of
Maybe AmountCost
Nothing -> []
Just AmountCost
_ -> [ Posting
convp{ paccount = accountPrefix <> amtCommodity
, pamount = mixedAmount . negate $ amountStripCost amt
}
, Posting
convp{ paccount = accountPrefix <> costCommodity
, pamount = mixedAmount cost
}
]
where
cost :: Amount
cost = Amount -> Amount
amountCost Amount
amt
amtCommodity :: Text
amtCommodity = Amount -> Text
commodity Amount
amt
costCommodity :: Text
costCommodity = Amount -> Text
commodity Amount
cost
convp :: Posting
convp = Posting
p{pbalanceassertion=Nothing, poriginal=Nothing}
Posting -> (Posting -> Posting) -> Posting
forall a b. a -> (a -> b) -> b
& Bool -> Tag -> Posting -> Posting
postingAddHiddenAndMaybeVisibleTag Bool
verbosetags (Text
conversionPostingTagName,Text
"")
Posting -> (Posting -> Posting) -> Posting
forall a b. a -> (a -> b) -> b
& Bool -> Tag -> Posting -> Posting
postingAddHiddenAndMaybeVisibleTag Bool
verbosetags (Text
generatedPostingTagName, Text
"")
accountPrefix :: Text
accountPrefix = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
equityAcct, Text
":", Text -> [Text] -> Text
T.intercalate Text
"-" ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. Ord a => [a] -> [a]
sort [Text
amtCommodity, Text
costCommodity], Text
":"]
commodity :: Amount -> Text
commodity = [Text] -> Text
T.unwords ([Text] -> Text) -> (Amount -> [Text]) -> Amount -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) ([Text] -> [Text]) -> (Amount -> [Text]) -> Amount -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
T.words (Text -> [Text]) -> (Amount -> Text) -> Amount -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Amount -> Text
acommodity
postingPriceDirectivesFromCost :: Posting -> [PriceDirective]
postingPriceDirectivesFromCost :: Posting -> [PriceDirective]
postingPriceDirectivesFromCost p :: Posting
p@Posting{MixedAmount
pamount :: Posting -> MixedAmount
pamount :: MixedAmount
pamount} =
(Amount -> Maybe PriceDirective) -> [Amount] -> [PriceDirective]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Day -> Amount -> Maybe PriceDirective
amountPriceDirectiveFromCost (Day -> Amount -> Maybe PriceDirective)
-> Day -> Amount -> Maybe PriceDirective
forall a b. (a -> b) -> a -> b
$ Posting -> Day
postingDate Posting
p) ([Amount] -> [PriceDirective]) -> [Amount] -> [PriceDirective]
forall a b. (a -> b) -> a -> b
$ MixedAmount -> [Amount]
amountsRaw MixedAmount
pamount
postingTransformAmount :: (MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount :: (MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount MixedAmount -> MixedAmount
f p :: Posting
p@Posting{pamount :: Posting -> MixedAmount
pamount=MixedAmount
a} = Posting
p{pamount=f a}
commentJoin :: Text -> Text -> Text
Text
c1 Text
c2
| Text -> Bool
T.null Text
c1 = Text
c2
| Text -> Bool
T.null Text
c2 = Text
c1
| Bool
otherwise = Text
c1 Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
", " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
c2
commentAddTag :: Text -> Tag -> Text
Text
c (Text
t,Text
v)
| Text -> Bool
T.null Text
c' = Text
tag
| Bool
otherwise = Text
c' Text -> Text -> Text
`commentJoin` Text
tag
where
c' :: Text
c' = Text -> Text
T.stripEnd Text
c
tag :: Text
tag = Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
": " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
v
commentAddTagUnspaced :: Text -> Tag -> Text
Text
c (Text
t,Text
v)
| Text -> Bool
T.null Text
c' = Text
tag
| Bool
otherwise = Text
c' Text -> Text -> Text
`commentJoin` Text
tag
where
c' :: Text
c' = Text -> Text
T.stripEnd Text
c
tag :: Text
tag = Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
v
commentAddTagNextLine :: Text -> Tag -> Text
Text
cmt (Text
t,Text
v) =
Text
cmt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (if Text
"\n" Text -> Text -> Bool
`T.isSuffixOf` Text
cmt then Text
"" else Text
"\n") Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
": " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
v
tests_Posting :: TestTree
tests_Posting = FilePath -> [TestTree] -> TestTree
testGroup FilePath
"Posting" [
FilePath -> Assertion -> TestTree
testCase FilePath
"accountNamePostingType" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
Text -> PostingType
accountNamePostingType Text
"a" PostingType -> PostingType -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= PostingType
RegularPosting
Text -> PostingType
accountNamePostingType Text
"(a)" PostingType -> PostingType -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= PostingType
VirtualPosting
Text -> PostingType
accountNamePostingType Text
"[a]" PostingType -> PostingType -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= PostingType
BalancedVirtualPosting
,FilePath -> Assertion -> TestTree
testCase FilePath
"accountNameWithoutPostingType" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
Text -> Text
accountNameWithoutPostingType Text
"(a)" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"a"
,FilePath -> Assertion -> TestTree
testCase FilePath
"accountNameWithPostingType" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
PostingType -> Text -> Text
accountNameWithPostingType PostingType
VirtualPosting Text
"[a]" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"(a)"
,FilePath -> Assertion -> TestTree
testCase FilePath
"joinAccountNames" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
Text
"a" Text -> Text -> Text
`joinAccountNames` Text
"b:c" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"a:b:c"
Text
"a" Text -> Text -> Text
`joinAccountNames` Text
"(b:c)" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"(a:b:c)"
Text
"[a]" Text -> Text -> Text
`joinAccountNames` Text
"(b:c)" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"[a:b:c]"
Text
"" Text -> Text -> Text
`joinAccountNames` Text
"a" Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"a"
,FilePath -> Assertion -> TestTree
testCase FilePath
"concatAccountNames" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
[Text] -> Text
concatAccountNames [] Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
""
[Text] -> Text
concatAccountNames [Text
"a",Text
"(b)",Text
"[c:d]"] Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"(a:b:c:d)"
,FilePath -> Assertion -> TestTree
testCase FilePath
"commentAddTag" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
Text -> Tag -> Text
commentAddTag Text
"" (Text
"a",Text
"") Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"a: "
Text -> Tag -> Text
commentAddTag Text
"[1/2]" (Text
"a",Text
"") Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"[1/2], a: "
,FilePath -> Assertion -> TestTree
testCase FilePath
"commentAddTagNextLine" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
Text -> Tag -> Text
commentAddTagNextLine Text
"" (Text
"a",Text
"") Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"\na: "
Text -> Tag -> Text
commentAddTagNextLine Text
"[1/2]" (Text
"a",Text
"") Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"[1/2]\na: "
]