{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Hledger.Data.Posting (
nullposting,
posting,
post,
vpost,
post',
vpost',
nullsourcepos,
nullassertion,
balassert,
balassertTot,
balassertParInc,
balassertTotInc,
originalPosting,
postingStatus,
isReal,
isVirtual,
isBalancedVirtual,
isEmptyPosting,
hasBalanceAssignment,
hasAmount,
postingAllTags,
transactionAllTags,
relatedPostings,
removePrices,
postingApplyAliases,
postingDate,
postingDate2,
isPostingInDateSpan,
isPostingInDateSpan',
accountNamesFromPostings,
accountNamePostingType,
accountNameWithoutPostingType,
accountNameWithPostingType,
joinAccountNames,
concatAccountNames,
accountNameApplyAliases,
accountNameApplyAliasesMemo,
commentJoin,
commentAddTag,
commentAddTagNextLine,
sumPostings,
showPosting,
showComment,
postingTransformAmount,
postingApplyCostValuation,
postingApplyValuation,
postingToCost,
tests_Posting
)
where
import Control.Monad (foldM)
import Data.Foldable (asum)
import Data.List.Extra (nubSort)
import qualified Data.Map as M
import Data.Maybe
import Data.MemoUgly (memo)
#if !(MIN_VERSION_base(4,11,0))
import Data.Monoid
#endif
import Data.Text (Text)
import qualified Data.Text as T
import Data.Time.Calendar
import Safe
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
nullposting, posting :: Posting
nullposting :: Posting
nullposting = Posting :: Maybe Day
-> Maybe Day
-> Status
-> AccountName
-> MixedAmount
-> AccountName
-> PostingType
-> [Tag]
-> Maybe BalanceAssertion
-> Maybe Transaction
-> Maybe Posting
-> Posting
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 :: AccountName
paccount=AccountName
""
,pamount :: MixedAmount
pamount=MixedAmount
nullmixedamt
,pcomment :: AccountName
pcomment=AccountName
""
,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 :: AccountName -> Amount -> Posting
post AccountName
acc Amount
amt = Posting
posting {paccount :: AccountName
paccount=AccountName
acc, pamount :: MixedAmount
pamount=[Amount] -> MixedAmount
Mixed [Amount
amt]}
vpost :: AccountName -> Amount -> Posting
vpost :: AccountName -> Amount -> Posting
vpost AccountName
acc Amount
amt = (AccountName -> Amount -> Posting
post AccountName
acc Amount
amt){ptype :: PostingType
ptype=PostingType
VirtualPosting}
post' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
post' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
post' AccountName
acc Amount
amt Maybe BalanceAssertion
ass = Posting
posting {paccount :: AccountName
paccount=AccountName
acc, pamount :: MixedAmount
pamount=[Amount] -> MixedAmount
Mixed [Amount
amt], pbalanceassertion :: Maybe BalanceAssertion
pbalanceassertion=Maybe BalanceAssertion
ass}
vpost' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
vpost' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
vpost' AccountName
acc Amount
amt Maybe BalanceAssertion
ass = (AccountName -> Amount -> Maybe BalanceAssertion -> Posting
post' AccountName
acc Amount
amt Maybe BalanceAssertion
ass){ptype :: PostingType
ptype=PostingType
VirtualPosting, pbalanceassertion :: Maybe BalanceAssertion
pbalanceassertion=Maybe BalanceAssertion
ass}
nullsourcepos :: GenericSourcePos
nullsourcepos :: GenericSourcePos
nullsourcepos = FilePath -> (Int, Int) -> GenericSourcePos
JournalSourcePos FilePath
"" (Int
1,Int
1)
nullassertion :: BalanceAssertion
nullassertion :: BalanceAssertion
nullassertion = BalanceAssertion :: Amount -> Bool -> Bool -> GenericSourcePos -> BalanceAssertion
BalanceAssertion
{baamount :: Amount
baamount=Amount
nullamt
,batotal :: Bool
batotal=Bool
False
,bainclusive :: Bool
bainclusive=Bool
False
,baposition :: GenericSourcePos
baposition=GenericSourcePos
nullsourcepos
}
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 :: Amount
baamount=Amount
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 :: Amount
baamount=Amount
amt, batotal :: Bool
batotal=Bool
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 :: Amount
baamount=Amount
amt, bainclusive :: Bool
bainclusive=Bool
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 :: Amount
baamount=Amount
amt, batotal :: Bool
batotal=Bool
True, bainclusive :: Bool
bainclusive=Bool
True}
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 p :: Posting
p@Posting{paccount :: Posting -> AccountName
paccount=AccountName
a,pamount :: Posting -> MixedAmount
pamount=MixedAmount
amt,ptype :: Posting -> PostingType
ptype=PostingType
t} =
[FilePath] -> FilePath
unlines ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ [[FilePath] -> FilePath
concatTopPadded [Day -> FilePath
forall a. Show a => a -> FilePath
show (Posting -> Day
postingDate Posting
p) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" ", AccountName -> FilePath
showaccountname AccountName
a FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" ", MixedAmount -> FilePath
showamount MixedAmount
amt, AccountName -> FilePath
T.unpack (AccountName -> FilePath)
-> (AccountName -> AccountName) -> AccountName -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AccountName -> AccountName
showComment (AccountName -> FilePath) -> AccountName -> FilePath
forall a b. (a -> b) -> a -> b
$ Posting -> AccountName
pcomment Posting
p]]
where
ledger3ishlayout :: Bool
ledger3ishlayout = Bool
False
acctnamewidth :: Int
acctnamewidth = if Bool
ledger3ishlayout then Int
25 else Int
22
showaccountname :: AccountName -> FilePath
showaccountname = AccountName -> FilePath
T.unpack (AccountName -> FilePath)
-> (AccountName -> AccountName) -> AccountName -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Int
-> Maybe Int -> Bool -> Bool -> AccountName -> AccountName
fitText (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
acctnamewidth) Maybe Int
forall a. Maybe a
Nothing Bool
False Bool
False (AccountName -> AccountName)
-> (AccountName -> AccountName) -> AccountName -> AccountName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AccountName -> AccountName
bracket (AccountName -> AccountName)
-> (AccountName -> AccountName) -> AccountName -> AccountName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> AccountName -> AccountName
elideAccountName Int
width
(AccountName -> AccountName
bracket,Int
width) = case PostingType
t of
PostingType
BalancedVirtualPosting -> (AccountName -> AccountName -> AccountName -> AccountName
wrap AccountName
"[" AccountName
"]", Int
acctnamewidthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2)
PostingType
VirtualPosting -> (AccountName -> AccountName -> AccountName -> AccountName
wrap AccountName
"(" AccountName
")", Int
acctnamewidthInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
2)
PostingType
_ -> (AccountName -> AccountName
forall a. a -> a
id,Int
acctnamewidth)
showamount :: MixedAmount -> FilePath
showamount = WideBuilder -> FilePath
wbUnpack (WideBuilder -> FilePath)
-> (MixedAmount -> WideBuilder) -> MixedAmount -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AmountDisplayOpts -> MixedAmount -> WideBuilder
showMixedAmountB AmountDisplayOpts
noColour{displayMinWidth :: Maybe Int
displayMinWidth=Int -> Maybe Int
forall a. a -> Maybe a
Just Int
12}
showComment :: Text -> Text
AccountName
t = if AccountName -> Bool
T.null AccountName
t then AccountName
"" else AccountName
" ;" AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
t
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 = (MixedAmount -> MixedAmount -> Bool
forall a. Eq a => a -> a -> Bool
/= MixedAmount
missingmixedamt) (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] -> [AccountName]
accountNamesFromPostings = [AccountName] -> [AccountName]
forall a. Ord a => [a] -> [a]
nubSort ([AccountName] -> [AccountName])
-> ([Posting] -> [AccountName]) -> [Posting] -> [AccountName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Posting -> AccountName) -> [Posting] -> [AccountName]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> AccountName
paccount
sumPostings :: [Posting] -> MixedAmount
sumPostings :: [Posting] -> MixedAmount
sumPostings = [MixedAmount] -> MixedAmount
forall a. Num a => [a] -> a
sumStrict ([MixedAmount] -> MixedAmount)
-> ([Posting] -> [MixedAmount]) -> [Posting] -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Posting -> MixedAmount) -> [Posting] -> [MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> MixedAmount
pamount
removePrices :: Posting -> Posting
removePrices :: Posting -> Posting
removePrices Posting
p = Posting
p{ pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed ([Amount] -> MixedAmount) -> [Amount] -> MixedAmount
forall a b. (a -> b) -> a -> b
$ Amount -> Amount
remove (Amount -> Amount) -> [Amount] -> [Amount]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MixedAmount -> [Amount]
amounts (Posting -> MixedAmount
pamount Posting
p) }
where remove :: Amount -> Amount
remove Amount
a = Amount
a { aprice :: Maybe AmountPrice
aprice = Maybe AmountPrice
forall a. Maybe a
Nothing }
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
]
postingStatus :: Posting -> Status
postingStatus :: Posting -> Status
postingStatus Posting{pstatus :: Posting -> Status
pstatus=Status
s, ptransaction :: Posting -> Maybe Transaction
ptransaction=Maybe Transaction
mt}
| Status
s Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
== Status
Unmarked = case Maybe Transaction
mt of Just Transaction
t -> Transaction -> Status
tstatus Transaction
t
Maybe Transaction
Nothing -> Status
Unmarked
| Bool
otherwise = 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
accountNamePostingType :: AccountName -> PostingType
accountNamePostingType :: AccountName -> PostingType
accountNamePostingType AccountName
a
| AccountName -> Bool
T.null AccountName
a = PostingType
RegularPosting
| AccountName -> Char
T.head AccountName
a Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'[' Bool -> Bool -> Bool
&& AccountName -> Char
T.last AccountName
a Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
']' = PostingType
BalancedVirtualPosting
| AccountName -> Char
T.head AccountName
a Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'(' Bool -> Bool -> Bool
&& AccountName -> Char
T.last AccountName
a Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
')' = PostingType
VirtualPosting
| Bool
otherwise = PostingType
RegularPosting
accountNameWithoutPostingType :: AccountName -> AccountName
accountNameWithoutPostingType :: AccountName -> AccountName
accountNameWithoutPostingType AccountName
a = case AccountName -> PostingType
accountNamePostingType AccountName
a of
PostingType
BalancedVirtualPosting -> AccountName -> AccountName
T.init (AccountName -> AccountName) -> AccountName -> AccountName
forall a b. (a -> b) -> a -> b
$ AccountName -> AccountName
T.tail AccountName
a
PostingType
VirtualPosting -> AccountName -> AccountName
T.init (AccountName -> AccountName) -> AccountName -> AccountName
forall a b. (a -> b) -> a -> b
$ AccountName -> AccountName
T.tail AccountName
a
PostingType
RegularPosting -> AccountName
a
accountNameWithPostingType :: PostingType -> AccountName -> AccountName
accountNameWithPostingType :: PostingType -> AccountName -> AccountName
accountNameWithPostingType PostingType
BalancedVirtualPosting = AccountName -> AccountName -> AccountName -> AccountName
wrap AccountName
"[" AccountName
"]" (AccountName -> AccountName)
-> (AccountName -> AccountName) -> AccountName -> AccountName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AccountName -> AccountName
accountNameWithoutPostingType
accountNameWithPostingType PostingType
VirtualPosting = AccountName -> AccountName -> AccountName -> AccountName
wrap AccountName
"(" AccountName
")" (AccountName -> AccountName)
-> (AccountName -> AccountName) -> AccountName -> AccountName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AccountName -> AccountName
accountNameWithoutPostingType
accountNameWithPostingType PostingType
RegularPosting = AccountName -> AccountName
accountNameWithoutPostingType
joinAccountNames :: AccountName -> AccountName -> AccountName
joinAccountNames :: AccountName -> AccountName -> AccountName
joinAccountNames AccountName
a AccountName
b = [AccountName] -> AccountName
concatAccountNames ([AccountName] -> AccountName) -> [AccountName] -> AccountName
forall a b. (a -> b) -> a -> b
$ (AccountName -> Bool) -> [AccountName] -> [AccountName]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (AccountName -> Bool) -> AccountName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AccountName -> Bool
T.null) [AccountName
a,AccountName
b]
concatAccountNames :: [AccountName] -> AccountName
concatAccountNames :: [AccountName] -> AccountName
concatAccountNames [AccountName]
as = PostingType -> AccountName -> AccountName
accountNameWithPostingType PostingType
t (AccountName -> AccountName) -> AccountName -> AccountName
forall a b. (a -> b) -> a -> b
$ AccountName -> [AccountName] -> AccountName
T.intercalate AccountName
":" ([AccountName] -> AccountName) -> [AccountName] -> AccountName
forall a b. (a -> b) -> a -> b
$ (AccountName -> AccountName) -> [AccountName] -> [AccountName]
forall a b. (a -> b) -> [a] -> [b]
map AccountName -> AccountName
accountNameWithoutPostingType [AccountName]
as
where t :: PostingType
t = PostingType -> [PostingType] -> PostingType
forall a. a -> [a] -> a
headDef PostingType
RegularPosting ([PostingType] -> PostingType) -> [PostingType] -> PostingType
forall a b. (a -> b) -> a -> b
$ (PostingType -> Bool) -> [PostingType] -> [PostingType]
forall a. (a -> Bool) -> [a] -> [a]
filter (PostingType -> PostingType -> Bool
forall a. Eq a => a -> a -> Bool
/= PostingType
RegularPosting) ([PostingType] -> [PostingType]) -> [PostingType] -> [PostingType]
forall a b. (a -> b) -> a -> b
$ (AccountName -> PostingType) -> [AccountName] -> [PostingType]
forall a b. (a -> b) -> [a] -> [b]
map AccountName -> PostingType
accountNamePostingType [AccountName]
as
postingApplyAliases :: [AccountAlias] -> Posting -> Either RegexError Posting
postingApplyAliases :: [AccountAlias] -> Posting -> Either FilePath Posting
postingApplyAliases [AccountAlias]
aliases p :: Posting
p@Posting{AccountName
paccount :: AccountName
paccount :: Posting -> AccountName
paccount} =
case [AccountAlias] -> AccountName -> Either FilePath AccountName
accountNameApplyAliases [AccountAlias]
aliases AccountName
paccount of
Right AccountName
a -> Posting -> Either FilePath Posting
forall a b. b -> Either a b
Right Posting
p{paccount :: AccountName
paccount=AccountName
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]
++AccountName -> FilePath
T.unpack AccountName
paccountFilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++FilePath
"\n "FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++FilePath
e
accountNameApplyAliases :: [AccountAlias] -> AccountName -> Either RegexError AccountName
accountNameApplyAliases :: [AccountAlias] -> AccountName -> Either FilePath AccountName
accountNameApplyAliases [AccountAlias]
aliases AccountName
a =
let (AccountName
aname,PostingType
atype) = (AccountName -> AccountName
accountNameWithoutPostingType AccountName
a, AccountName -> PostingType
accountNamePostingType AccountName
a)
in (AccountName -> AccountAlias -> Either FilePath AccountName)
-> AccountName -> [AccountAlias] -> Either FilePath AccountName
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM
(\AccountName
acct AccountAlias
alias -> FilePath
-> Either FilePath AccountName -> Either FilePath AccountName
forall a. Show a => FilePath -> a -> a
dbg6 FilePath
"result" (Either FilePath AccountName -> Either FilePath AccountName)
-> Either FilePath AccountName -> Either FilePath AccountName
forall a b. (a -> b) -> a -> b
$ AccountAlias -> AccountName -> Either FilePath AccountName
aliasReplace (FilePath -> AccountAlias -> AccountAlias
forall a. Show a => FilePath -> a -> a
dbg6 FilePath
"alias" AccountAlias
alias) (FilePath -> AccountName -> AccountName
forall a. Show a => FilePath -> a -> a
dbg6 FilePath
"account" AccountName
acct))
AccountName
aname
[AccountAlias]
aliases
Either FilePath AccountName
-> (AccountName -> Either FilePath AccountName)
-> Either FilePath AccountName
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= AccountName -> Either FilePath AccountName
forall a b. b -> Either a b
Right (AccountName -> Either FilePath AccountName)
-> (AccountName -> AccountName)
-> AccountName
-> Either FilePath AccountName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PostingType -> AccountName -> AccountName
accountNameWithPostingType PostingType
atype
accountNameApplyAliasesMemo :: [AccountAlias] -> AccountName -> Either RegexError AccountName
accountNameApplyAliasesMemo :: [AccountAlias] -> AccountName -> Either FilePath AccountName
accountNameApplyAliasesMemo [AccountAlias]
aliases = (AccountName -> Either FilePath AccountName)
-> AccountName -> Either FilePath AccountName
forall a b. Ord a => (a -> b) -> a -> b
memo ([AccountAlias] -> AccountName -> Either FilePath AccountName
accountNameApplyAliases [AccountAlias]
aliases)
aliasReplace :: AccountAlias -> AccountName -> Either RegexError AccountName
aliasReplace :: AccountAlias -> AccountName -> Either FilePath AccountName
aliasReplace (BasicAlias AccountName
old AccountName
new) AccountName
a
| AccountName
old AccountName -> AccountName -> Bool
`isAccountNamePrefixOf` AccountName
a Bool -> Bool -> Bool
|| AccountName
old AccountName -> AccountName -> Bool
forall a. Eq a => a -> a -> Bool
== AccountName
a =
AccountName -> Either FilePath AccountName
forall a b. b -> Either a b
Right (AccountName -> Either FilePath AccountName)
-> AccountName -> Either FilePath AccountName
forall a b. (a -> b) -> a -> b
$ AccountName
new AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> Int -> AccountName -> AccountName
T.drop (AccountName -> Int
T.length AccountName
old) AccountName
a
| Bool
otherwise = AccountName -> Either FilePath AccountName
forall a b. b -> Either a b
Right AccountName
a
aliasReplace (RegexAlias Regexp
re FilePath
repl) AccountName
a =
(FilePath -> AccountName)
-> Either FilePath FilePath -> Either FilePath AccountName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> AccountName
T.pack (Either FilePath FilePath -> Either FilePath AccountName)
-> (FilePath -> Either FilePath FilePath)
-> FilePath
-> Either FilePath AccountName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Regexp -> FilePath -> FilePath -> Either FilePath FilePath
regexReplace Regexp
re FilePath
repl (FilePath -> Either FilePath AccountName)
-> FilePath -> Either FilePath AccountName
forall a b. (a -> b) -> a -> b
$ AccountName -> FilePath
T.unpack AccountName
a
postingApplyCostValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Costing -> Maybe ValuationType -> Posting -> Posting
postingApplyCostValuation :: PriceOracle
-> Map AccountName AmountStyle
-> Day
-> Day
-> Costing
-> Maybe ValuationType
-> Posting
-> Posting
postingApplyCostValuation PriceOracle
priceoracle Map AccountName AmountStyle
styles Day
periodlast Day
today Costing
cost Maybe ValuationType
v Posting
p =
(MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount (PriceOracle
-> Map AccountName AmountStyle
-> Day
-> Day
-> Day
-> Costing
-> Maybe ValuationType
-> MixedAmount
-> MixedAmount
mixedAmountApplyCostValuation PriceOracle
priceoracle Map AccountName AmountStyle
styles Day
periodlast Day
today (Posting -> Day
postingDate Posting
p) Costing
cost Maybe ValuationType
v) Posting
p
postingApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Posting -> Posting
postingApplyValuation :: PriceOracle
-> Map AccountName AmountStyle
-> Day
-> Day
-> ValuationType
-> Posting
-> Posting
postingApplyValuation PriceOracle
priceoracle Map AccountName AmountStyle
styles Day
periodlast Day
today ValuationType
v Posting
p =
(MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount (PriceOracle
-> Map AccountName AmountStyle
-> Day
-> Day
-> Day
-> ValuationType
-> MixedAmount
-> MixedAmount
mixedAmountApplyValuation PriceOracle
priceoracle Map AccountName AmountStyle
styles Day
periodlast Day
today (Posting -> Day
postingDate Posting
p) ValuationType
v) Posting
p
postingToCost :: M.Map CommoditySymbol AmountStyle -> Posting -> Posting
postingToCost :: Map AccountName AmountStyle -> Posting -> Posting
postingToCost Map AccountName AmountStyle
styles = (MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount (Map AccountName AmountStyle -> MixedAmount -> MixedAmount
styleMixedAmount Map AccountName AmountStyle
styles (MixedAmount -> MixedAmount)
-> (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MixedAmount -> MixedAmount
mixedAmountCost)
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 :: MixedAmount
pamount=MixedAmount -> MixedAmount
f MixedAmount
a}
commentJoin :: Text -> Text -> Text
AccountName
c1 AccountName
c2
| AccountName -> Bool
T.null AccountName
c1 = AccountName
c2
| AccountName -> Bool
T.null AccountName
c2 = AccountName
c1
| Bool
otherwise = AccountName
c1 AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
", " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
c2
commentAddTag :: Text -> Tag -> Text
AccountName
c (AccountName
t,AccountName
v)
| AccountName -> Bool
T.null AccountName
c' = AccountName
tag
| Bool
otherwise = AccountName
c' AccountName -> AccountName -> AccountName
`commentJoin` AccountName
tag
where
c' :: AccountName
c' = AccountName -> AccountName
T.stripEnd AccountName
c
tag :: AccountName
tag = AccountName
t AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
": " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
v
commentAddTagNextLine :: Text -> Tag -> Text
AccountName
cmt (AccountName
t,AccountName
v) =
AccountName
cmt AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> (if AccountName
"\n" AccountName -> AccountName -> Bool
`T.isSuffixOf` AccountName
cmt then AccountName
"" else AccountName
"\n") AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
t AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
": " AccountName -> AccountName -> AccountName
forall a. Semigroup a => a -> a -> a
<> AccountName
v
tests_Posting :: TestTree
tests_Posting = FilePath -> [TestTree] -> TestTree
tests FilePath
"Posting" [
FilePath -> Assertion -> TestTree
test FilePath
"accountNamePostingType" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
AccountName -> PostingType
accountNamePostingType AccountName
"a" PostingType -> PostingType -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= PostingType
RegularPosting
AccountName -> PostingType
accountNamePostingType AccountName
"(a)" PostingType -> PostingType -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= PostingType
VirtualPosting
AccountName -> PostingType
accountNamePostingType AccountName
"[a]" PostingType -> PostingType -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= PostingType
BalancedVirtualPosting
,FilePath -> Assertion -> TestTree
test FilePath
"accountNameWithoutPostingType" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
AccountName -> AccountName
accountNameWithoutPostingType AccountName
"(a)" AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
"a"
,FilePath -> Assertion -> TestTree
test FilePath
"accountNameWithPostingType" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
PostingType -> AccountName -> AccountName
accountNameWithPostingType PostingType
VirtualPosting AccountName
"[a]" AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
"(a)"
,FilePath -> Assertion -> TestTree
test FilePath
"joinAccountNames" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
AccountName
"a" AccountName -> AccountName -> AccountName
`joinAccountNames` AccountName
"b:c" AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
"a:b:c"
AccountName
"a" AccountName -> AccountName -> AccountName
`joinAccountNames` AccountName
"(b:c)" AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
"(a:b:c)"
AccountName
"[a]" AccountName -> AccountName -> AccountName
`joinAccountNames` AccountName
"(b:c)" AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
"[a:b:c]"
AccountName
"" AccountName -> AccountName -> AccountName
`joinAccountNames` AccountName
"a" AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
"a"
,FilePath -> Assertion -> TestTree
test FilePath
"concatAccountNames" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
[AccountName] -> AccountName
concatAccountNames [] AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
""
[AccountName] -> AccountName
concatAccountNames [AccountName
"a",AccountName
"(b)",AccountName
"[c:d]"] AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
"(a:b:c:d)"
,FilePath -> Assertion -> TestTree
test FilePath
"commentAddTag" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
AccountName -> Tag -> AccountName
commentAddTag AccountName
"" (AccountName
"a",AccountName
"") AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
"a: "
AccountName -> Tag -> AccountName
commentAddTag AccountName
"[1/2]" (AccountName
"a",AccountName
"") AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
"[1/2], a: "
,FilePath -> Assertion -> TestTree
test FilePath
"commentAddTagNextLine" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
AccountName -> Tag -> AccountName
commentAddTagNextLine AccountName
"" (AccountName
"a",AccountName
"") AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
"\na: "
AccountName -> Tag -> AccountName
commentAddTagNextLine AccountName
"[1/2]" (AccountName
"a",AccountName
"") AccountName -> AccountName -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= AccountName
"[1/2]\na: "
]