{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NamedFieldPuns #-}
module Hledger.Data.Transaction (
nulltransaction,
transaction,
txnTieKnot,
txnUntieKnot,
showAccountName,
hasRealPostings,
realPostings,
assignmentPostings,
virtualPostings,
balancedVirtualPostings,
transactionsPostings,
isTransactionBalanced,
balanceTransaction,
balanceTransactionHelper,
transactionTransformPostings,
transactionApplyCostValuation,
transactionApplyValuation,
transactionToCost,
transactionApplyAliases,
transactionMapPostings,
transactionMapPostingAmounts,
transactionDate2,
transactionPayee,
transactionNote,
showTransaction,
showTransactionOneLineAmounts,
showPostingLines,
sourceFilePath,
sourceFirstLine,
showGenericSourcePos,
annotateErrorWithTransaction,
transactionFile,
tests_Transaction
)
where
import Data.Default (def)
import Data.List (intercalate, partition)
import Data.List.Extra (nubSort)
import Data.Maybe (fromMaybe, mapMaybe)
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup ((<>))
#endif
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, fromGregorian)
import qualified Data.Map as M
import Hledger.Utils
import Hledger.Data.Types
import Hledger.Data.Dates
import Hledger.Data.Posting
import Hledger.Data.Amount
import Hledger.Data.Valuation
import Text.Tabular
import Text.Tabular.AsciiWide
sourceFilePath :: GenericSourcePos -> FilePath
sourceFilePath :: GenericSourcePos -> FilePath
sourceFilePath = \case
GenericSourcePos FilePath
fp Int
_ Int
_ -> FilePath
fp
JournalSourcePos FilePath
fp (Int, Int)
_ -> FilePath
fp
sourceFirstLine :: GenericSourcePos -> Int
sourceFirstLine :: GenericSourcePos -> Int
sourceFirstLine = \case
GenericSourcePos FilePath
_ Int
line Int
_ -> Int
line
JournalSourcePos FilePath
_ (Int
line, Int
_) -> Int
line
showGenericSourcePos :: GenericSourcePos -> String
showGenericSourcePos :: GenericSourcePos -> FilePath
showGenericSourcePos = \case
GenericSourcePos FilePath
fp Int
line Int
column -> FilePath -> FilePath
forall a. Show a => a -> FilePath
show FilePath
fp FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" (line " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
line FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
", column " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
column FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
")"
JournalSourcePos FilePath
fp (Int
line, Int
line') -> FilePath -> FilePath
forall a. Show a => a -> FilePath
show FilePath
fp FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" (lines " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
line FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
line' FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
")"
nulltransaction :: Transaction
nulltransaction :: Transaction
nulltransaction = Transaction :: Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction {
tindex :: Integer
tindex=Integer
0,
tsourcepos :: GenericSourcePos
tsourcepos=GenericSourcePos
nullsourcepos,
tdate :: Day
tdate=Day
nulldate,
tdate2 :: Maybe Day
tdate2=Maybe Day
forall a. Maybe a
Nothing,
tstatus :: Status
tstatus=Status
Unmarked,
tcode :: Text
tcode=Text
"",
tdescription :: Text
tdescription=Text
"",
tcomment :: Text
tcomment=Text
"",
ttags :: [Tag]
ttags=[],
tpostings :: [Posting]
tpostings=[],
tprecedingcomment :: Text
tprecedingcomment=Text
""
}
transaction :: Day -> [Posting] -> Transaction
transaction :: Day -> [Posting] -> Transaction
transaction Day
day [Posting]
ps = Transaction -> Transaction
txnTieKnot (Transaction -> Transaction) -> Transaction -> Transaction
forall a b. (a -> b) -> a -> b
$ Transaction
nulltransaction{tdate :: Day
tdate=Day
day, tpostings :: [Posting]
tpostings=[Posting]
ps}
transactionPayee :: Transaction -> Text
transactionPayee :: Transaction -> Text
transactionPayee = Tag -> Text
forall a b. (a, b) -> a
fst (Tag -> Text) -> (Transaction -> Tag) -> Transaction -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Tag
payeeAndNoteFromDescription (Text -> Tag) -> (Transaction -> Text) -> Transaction -> Tag
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Text
tdescription
transactionNote :: Transaction -> Text
transactionNote :: Transaction -> Text
transactionNote = Tag -> Text
forall a b. (a, b) -> b
snd (Tag -> Text) -> (Transaction -> Tag) -> Transaction -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Tag
payeeAndNoteFromDescription (Text -> Tag) -> (Transaction -> Text) -> Transaction -> Tag
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> Text
tdescription
payeeAndNoteFromDescription :: Text -> (Text,Text)
payeeAndNoteFromDescription :: Text -> Tag
payeeAndNoteFromDescription Text
t
| Text -> Bool
T.null Text
n = (Text
t, Text
t)
| Bool
otherwise = (Text -> Text
T.strip Text
p, Text -> Text
T.strip (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
1 Text
n)
where
(Text
p, Text
n) = (Char -> Bool) -> Text -> Tag
T.span (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'|') Text
t
showTransaction :: Transaction -> Text
showTransaction :: Transaction -> Text
showTransaction = Text -> Text
TL.toStrict (Text -> Text) -> (Transaction -> Text) -> Transaction -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
TB.toLazyText (Builder -> Text)
-> (Transaction -> Builder) -> Transaction -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Transaction -> Builder
showTransactionHelper Bool
False
showTransactionOneLineAmounts :: Transaction -> Text
showTransactionOneLineAmounts :: Transaction -> Text
showTransactionOneLineAmounts = Text -> Text
TL.toStrict (Text -> Text) -> (Transaction -> Text) -> Transaction -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
TB.toLazyText (Builder -> Text)
-> (Transaction -> Builder) -> Transaction -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Transaction -> Builder
showTransactionHelper Bool
True
showTransactionHelper :: Bool -> Transaction -> TB.Builder
showTransactionHelper :: Bool -> Transaction -> Builder
showTransactionHelper Bool
onelineamounts Transaction
t =
Text -> Builder
TB.fromText Text
descriptionline Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
newline
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> (Text -> Builder) -> [Text] -> Builder
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
newline) (Builder -> Builder) -> (Text -> Builder) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Builder
TB.fromText) [Text]
newlinecomments
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> (Text -> Builder) -> [Text] -> Builder
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
newline) (Builder -> Builder) -> (Text -> Builder) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Builder
TB.fromText) (Bool -> [Posting] -> [Text]
postingsAsLines Bool
onelineamounts ([Posting] -> [Text]) -> [Posting] -> [Text]
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t)
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
newline
where
descriptionline :: Text
descriptionline = Text -> Text
T.stripEnd (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text
date, Text
status, Text
code, Text
desc, Text
samelinecomment]
date :: Text
date = Day -> Text
showDate (Transaction -> Day
tdate Transaction
t) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> (Day -> Text) -> Maybe Day -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" ((Text
"="Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> (Day -> Text) -> Day -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> Text
showDate) (Transaction -> Maybe Day
tdate2 Transaction
t)
status :: Text
status | Transaction -> Status
tstatus Transaction
t Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
== Status
Cleared = Text
" *"
| Transaction -> Status
tstatus Transaction
t Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
== Status
Pending = Text
" !"
| Bool
otherwise = Text
""
code :: Text
code = if Text -> Bool
T.null (Transaction -> Text
tcode Transaction
t) then Text
"" else Text -> Text -> Text -> Text
wrap Text
" (" Text
")" (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Transaction -> Text
tcode Transaction
t
desc :: Text
desc = if Text -> Bool
T.null Text
d then Text
"" else Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
d where d :: Text
d = Transaction -> Text
tdescription Transaction
t
(Text
samelinecomment, [Text]
newlinecomments) =
case Text -> [Text]
renderCommentLines (Transaction -> Text
tcomment Transaction
t) of [] -> (Text
"",[])
Text
c:[Text]
cs -> (Text
c,[Text]
cs)
newline :: Builder
newline = Char -> Builder
TB.singleton Char
'\n'
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
lineIndent (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
lineIndent (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
<>)
postingsAsLines :: Bool -> [Posting] -> [Text]
postingsAsLines :: Bool -> [Posting] -> [Text]
postingsAsLines Bool
onelineamounts [Posting]
ps = (Posting -> [Text]) -> [Posting] -> [Text]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Bool -> Bool -> [Posting] -> Posting -> [Text]
postingAsLines Bool
False Bool
onelineamounts [Posting]
ps) [Posting]
ps
postingAsLines :: Bool -> Bool -> [Posting] -> Posting -> [Text]
postingAsLines :: Bool -> Bool -> [Posting] -> Posting -> [Text]
postingAsLines Bool
elideamount Bool
onelineamounts [Posting]
pstoalignwith 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
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
amt]
, Align -> [WideBuilder] -> Cell
Cell Align
BottomLeft [WideBuilder
assertion]
, Align -> Text -> Cell
textCell Align
BottomLeft Text
samelinecomment
]
| WideBuilder
amt <- [WideBuilder]
shownAmounts]
render :: [Cell] -> Text
render = TableOpts -> Header Cell -> Text
renderRow TableOpts
forall a. Default a => a
def{tableBorders :: Bool
tableBorders=Bool
False, borderSpaces :: Bool
borderSpaces=Bool
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
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
lineIndent (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
minwidth) 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
where
minwidth :: Int
minwidth = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ (Posting -> Int) -> [Posting] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ((Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
+) (Int -> Int) -> (Posting -> Int) -> Posting -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Int
textWidth (Text -> Int) -> (Posting -> Text) -> Posting -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Posting -> Text
pacctstr) [Posting]
pstoalignwith
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
" "
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')
shownAmounts :: [WideBuilder]
shownAmounts
| Bool
elideamount Bool -> Bool -> Bool
|| [Amount] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (MixedAmount -> [Amount]
amounts (MixedAmount -> [Amount]) -> MixedAmount -> [Amount]
forall a b. (a -> b) -> a -> b
$ Posting -> MixedAmount
pamount Posting
p) = [WideBuilder
forall a. Monoid a => a
mempty]
| Bool
otherwise = AmountDisplayOpts -> MixedAmount -> [WideBuilder]
showMixedAmountLinesB AmountDisplayOpts
displayopts (MixedAmount -> [WideBuilder]) -> MixedAmount -> [WideBuilder]
forall a b. (a -> b) -> a -> b
$ Posting -> MixedAmount
pamount Posting
p
where
displayopts :: AmountDisplayOpts
displayopts = AmountDisplayOpts
noColour{displayOneLine :: Bool
displayOneLine=Bool
onelineamounts, displayMinWidth :: Maybe Int
displayMinWidth = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
amtwidth, displayNormalised :: Bool
displayNormalised=Bool
False}
amtwidth :: Int
amtwidth = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ Int
12 Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: (Posting -> Int) -> [Posting] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (WideBuilder -> Int
wbWidth (WideBuilder -> Int) -> (Posting -> WideBuilder) -> Posting -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AmountDisplayOpts -> MixedAmount -> WideBuilder
showMixedAmountB AmountDisplayOpts
displayopts{displayMinWidth :: Maybe Int
displayMinWidth=Maybe Int
forall a. Maybe a
Nothing} (MixedAmount -> WideBuilder)
-> (Posting -> MixedAmount) -> Posting -> WideBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Posting -> MixedAmount
pamount) [Posting]
pstoalignwith
(Text
samelinecomment, [Text]
newlinecomments) =
case Text -> [Text]
renderCommentLines (Posting -> Text
pcomment Posting
p) of [] -> (Text
"",[])
Text
c:[Text]
cs -> (Text
c,[Text]
cs)
showBalanceAssertion :: BalanceAssertion -> WideBuilder
showBalanceAssertion :: BalanceAssertion -> WideBuilder
showBalanceAssertion BalanceAssertion{Bool
GenericSourcePos
Amount
baposition :: BalanceAssertion -> GenericSourcePos
bainclusive :: BalanceAssertion -> Bool
batotal :: BalanceAssertion -> Bool
baamount :: BalanceAssertion -> Amount
baposition :: GenericSourcePos
bainclusive :: Bool
batotal :: Bool
baamount :: Amount
..} =
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
<> AmountDisplayOpts -> Amount -> WideBuilder
showAmountB AmountDisplayOpts
forall a. Default a => a
def{displayZeroCommodity :: Bool
displayZeroCommodity=Bool
True} Amount
baamount
where
eq :: WideBuilder
eq = if Bool
batotal then Char -> WideBuilder
singleton Char
'=' else WideBuilder
forall a. Monoid a => a
mempty
ast :: WideBuilder
ast = if Bool
bainclusive 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
showPostingLines :: Posting -> [Text]
showPostingLines :: Posting -> [Text]
showPostingLines Posting
p = Bool -> Bool -> [Posting] -> Posting -> [Text]
postingAsLines Bool
False Bool
False [Posting]
ps Posting
p where
ps :: [Posting]
ps | Just Transaction
t <- Posting -> Maybe Transaction
ptransaction Posting
p = Transaction -> [Posting]
tpostings Transaction
t
| Bool
otherwise = [Posting
p]
lineIndent :: Text -> Text
lineIndent :: Text -> Text
lineIndent = (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
<>)
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
hasRealPostings :: Transaction -> Bool
hasRealPostings :: Transaction -> Bool
hasRealPostings = Bool -> Bool
not (Bool -> Bool) -> (Transaction -> Bool) -> Transaction -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Posting] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Posting] -> Bool)
-> (Transaction -> [Posting]) -> Transaction -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> [Posting]
realPostings
realPostings :: Transaction -> [Posting]
realPostings :: Transaction -> [Posting]
realPostings = (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter Posting -> Bool
isReal ([Posting] -> [Posting])
-> (Transaction -> [Posting]) -> Transaction -> [Posting]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> [Posting]
tpostings
assignmentPostings :: Transaction -> [Posting]
assignmentPostings :: Transaction -> [Posting]
assignmentPostings = (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter Posting -> Bool
hasBalanceAssignment ([Posting] -> [Posting])
-> (Transaction -> [Posting]) -> Transaction -> [Posting]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> [Posting]
tpostings
virtualPostings :: Transaction -> [Posting]
virtualPostings :: Transaction -> [Posting]
virtualPostings = (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter Posting -> Bool
isVirtual ([Posting] -> [Posting])
-> (Transaction -> [Posting]) -> Transaction -> [Posting]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> [Posting]
tpostings
balancedVirtualPostings :: Transaction -> [Posting]
balancedVirtualPostings :: Transaction -> [Posting]
balancedVirtualPostings = (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter Posting -> Bool
isBalancedVirtual ([Posting] -> [Posting])
-> (Transaction -> [Posting]) -> Transaction -> [Posting]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> [Posting]
tpostings
transactionsPostings :: [Transaction] -> [Posting]
transactionsPostings :: [Transaction] -> [Posting]
transactionsPostings = (Transaction -> [Posting]) -> [Transaction] -> [Posting]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Transaction -> [Posting]
tpostings
transactionCheckBalanced :: Maybe (M.Map CommoditySymbol AmountStyle) -> Transaction -> [String]
transactionCheckBalanced :: Maybe (Map Text AmountStyle) -> Transaction -> [FilePath]
transactionCheckBalanced Maybe (Map Text AmountStyle)
mstyles Transaction
t = [FilePath]
errs
where
([Posting]
rps, [Posting]
bvps) = (Transaction -> [Posting]
realPostings Transaction
t, Transaction -> [Posting]
balancedVirtualPostings Transaction
t)
canonicalise :: MixedAmount -> MixedAmount
canonicalise = (MixedAmount -> MixedAmount)
-> (Map Text AmountStyle -> MixedAmount -> MixedAmount)
-> Maybe (Map Text AmountStyle)
-> MixedAmount
-> MixedAmount
forall b a. b -> (a -> b) -> Maybe a -> b
maybe MixedAmount -> MixedAmount
forall a. a -> a
id Map Text AmountStyle -> MixedAmount -> MixedAmount
canonicaliseMixedAmount Maybe (Map Text AmountStyle)
mstyles
signsOk :: [Posting] -> Bool
signsOk [Posting]
ps =
case (MixedAmount -> Bool) -> [MixedAmount] -> [MixedAmount]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not(Bool -> Bool) -> (MixedAmount -> Bool) -> MixedAmount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.MixedAmount -> Bool
mixedAmountLooksZero) ([MixedAmount] -> [MixedAmount]) -> [MixedAmount] -> [MixedAmount]
forall a b. (a -> b) -> a -> b
$ (Posting -> MixedAmount) -> [Posting] -> [MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map (MixedAmount -> MixedAmount
canonicalise(MixedAmount -> MixedAmount)
-> (Posting -> MixedAmount) -> Posting -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
.MixedAmount -> MixedAmount
mixedAmountCost(MixedAmount -> MixedAmount)
-> (Posting -> MixedAmount) -> Posting -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Posting -> MixedAmount
pamount) [Posting]
ps of
[MixedAmount]
nonzeros | [MixedAmount] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [MixedAmount]
nonzeros Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2
-> [Bool] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Bool] -> [Bool]
forall a. Ord a => [a] -> [a]
nubSort ([Bool] -> [Bool]) -> [Bool] -> [Bool]
forall a b. (a -> b) -> a -> b
$ (MixedAmount -> Maybe Bool) -> [MixedAmount] -> [Bool]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe MixedAmount -> Maybe Bool
isNegativeMixedAmount [MixedAmount]
nonzeros) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
[MixedAmount]
_ -> Bool
True
(Bool
rsignsok, Bool
bvsignsok) = ([Posting] -> Bool
signsOk [Posting]
rps, [Posting] -> Bool
signsOk [Posting]
bvps)
(MixedAmount
rsum, MixedAmount
bvsum) = ([Posting] -> MixedAmount
sumPostings [Posting]
rps, [Posting] -> MixedAmount
sumPostings [Posting]
bvps)
(MixedAmount
rsumcost, MixedAmount
bvsumcost) = (MixedAmount -> MixedAmount
mixedAmountCost MixedAmount
rsum, MixedAmount -> MixedAmount
mixedAmountCost MixedAmount
bvsum)
(MixedAmount
rsumdisplay, MixedAmount
bvsumdisplay) = (MixedAmount -> MixedAmount
canonicalise MixedAmount
rsumcost, MixedAmount -> MixedAmount
canonicalise MixedAmount
bvsumcost)
(Bool
rsumok, Bool
bvsumok) = (MixedAmount -> Bool
mixedAmountLooksZero MixedAmount
rsumdisplay, MixedAmount -> Bool
mixedAmountLooksZero MixedAmount
bvsumdisplay)
errs :: [FilePath]
errs = (FilePath -> Bool) -> [FilePath] -> [FilePath]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not(Bool -> Bool) -> (FilePath -> Bool) -> FilePath -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.FilePath -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) [FilePath
rmsg, FilePath
bvmsg]
where
rmsg :: FilePath
rmsg
| Bool -> Bool
not Bool
rsignsok = FilePath
"real postings all have the same sign"
| Bool -> Bool
not Bool
rsumok = FilePath
"real postings' sum should be 0 but is: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ MixedAmount -> FilePath
showMixedAmount MixedAmount
rsumcost
| Bool
otherwise = FilePath
""
bvmsg :: FilePath
bvmsg
| Bool -> Bool
not Bool
bvsignsok = FilePath
"balanced virtual postings all have the same sign"
| Bool -> Bool
not Bool
bvsumok = FilePath
"balanced virtual postings' sum should be 0 but is: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ MixedAmount -> FilePath
showMixedAmount MixedAmount
bvsumcost
| Bool
otherwise = FilePath
""
isTransactionBalanced :: Maybe (M.Map CommoditySymbol AmountStyle) -> Transaction -> Bool
isTransactionBalanced :: Maybe (Map Text AmountStyle) -> Transaction -> Bool
isTransactionBalanced Maybe (Map Text AmountStyle)
mstyles = [FilePath] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([FilePath] -> Bool)
-> (Transaction -> [FilePath]) -> Transaction -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Map Text AmountStyle) -> Transaction -> [FilePath]
transactionCheckBalanced Maybe (Map Text AmountStyle)
mstyles
balanceTransaction ::
Maybe (M.Map CommoditySymbol AmountStyle)
-> Transaction
-> Either String Transaction
balanceTransaction :: Maybe (Map Text AmountStyle)
-> Transaction -> Either FilePath Transaction
balanceTransaction Maybe (Map Text AmountStyle)
mstyles = ((Transaction, [(Text, MixedAmount)]) -> Transaction)
-> Either FilePath (Transaction, [(Text, MixedAmount)])
-> Either FilePath Transaction
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Transaction, [(Text, MixedAmount)]) -> Transaction
forall a b. (a, b) -> a
fst (Either FilePath (Transaction, [(Text, MixedAmount)])
-> Either FilePath Transaction)
-> (Transaction
-> Either FilePath (Transaction, [(Text, MixedAmount)]))
-> Transaction
-> Either FilePath Transaction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe (Map Text AmountStyle)
-> Transaction
-> Either FilePath (Transaction, [(Text, MixedAmount)])
balanceTransactionHelper Maybe (Map Text AmountStyle)
mstyles
balanceTransactionHelper ::
Maybe (M.Map CommoditySymbol AmountStyle)
-> Transaction
-> Either String (Transaction, [(AccountName, MixedAmount)])
balanceTransactionHelper :: Maybe (Map Text AmountStyle)
-> Transaction
-> Either FilePath (Transaction, [(Text, MixedAmount)])
balanceTransactionHelper Maybe (Map Text AmountStyle)
mstyles Transaction
t = do
(Transaction
t', [(Text, MixedAmount)]
inferredamtsandaccts) <-
Map Text AmountStyle
-> Transaction
-> Either FilePath (Transaction, [(Text, MixedAmount)])
inferBalancingAmount (Map Text AmountStyle
-> Maybe (Map Text AmountStyle) -> Map Text AmountStyle
forall a. a -> Maybe a -> a
fromMaybe Map Text AmountStyle
forall k a. Map k a
M.empty Maybe (Map Text AmountStyle)
mstyles) (Transaction
-> Either FilePath (Transaction, [(Text, MixedAmount)]))
-> Transaction
-> Either FilePath (Transaction, [(Text, MixedAmount)])
forall a b. (a -> b) -> a -> b
$ Transaction -> Transaction
inferBalancingPrices Transaction
t
case Maybe (Map Text AmountStyle) -> Transaction -> [FilePath]
transactionCheckBalanced Maybe (Map Text AmountStyle)
mstyles Transaction
t' of
[] -> (Transaction, [(Text, MixedAmount)])
-> Either FilePath (Transaction, [(Text, MixedAmount)])
forall a b. b -> Either a b
Right (Transaction -> Transaction
txnTieKnot Transaction
t', [(Text, MixedAmount)]
inferredamtsandaccts)
[FilePath]
errs -> FilePath -> Either FilePath (Transaction, [(Text, MixedAmount)])
forall a b. a -> Either a b
Left (FilePath -> Either FilePath (Transaction, [(Text, MixedAmount)]))
-> FilePath -> Either FilePath (Transaction, [(Text, MixedAmount)])
forall a b. (a -> b) -> a -> b
$ Transaction -> [FilePath] -> FilePath
transactionBalanceError Transaction
t' [FilePath]
errs
transactionBalanceError :: Transaction -> [String] -> String
transactionBalanceError :: Transaction -> [FilePath] -> FilePath
transactionBalanceError Transaction
t [FilePath]
errs =
Transaction -> FilePath -> FilePath
annotateErrorWithTransaction Transaction
t (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
"\n" ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"could not balance this transaction:" FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
: [FilePath]
errs
annotateErrorWithTransaction :: Transaction -> String -> String
annotateErrorWithTransaction :: Transaction -> FilePath -> FilePath
annotateErrorWithTransaction Transaction
t FilePath
s =
[FilePath] -> FilePath
unlines [ GenericSourcePos -> FilePath
showGenericSourcePos (GenericSourcePos -> FilePath) -> GenericSourcePos -> FilePath
forall a b. (a -> b) -> a -> b
$ Transaction -> GenericSourcePos
tsourcepos Transaction
t, FilePath
s
, Text -> FilePath
T.unpack (Text -> FilePath) -> (Text -> Text) -> Text -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.stripEnd (Text -> FilePath) -> Text -> FilePath
forall a b. (a -> b) -> a -> b
$ Transaction -> Text
showTransaction Transaction
t
]
inferBalancingAmount ::
M.Map CommoditySymbol AmountStyle
-> Transaction
-> Either String (Transaction, [(AccountName, MixedAmount)])
inferBalancingAmount :: Map Text AmountStyle
-> Transaction
-> Either FilePath (Transaction, [(Text, MixedAmount)])
inferBalancingAmount Map Text AmountStyle
styles t :: Transaction
t@Transaction{tpostings :: Transaction -> [Posting]
tpostings=[Posting]
ps}
| [Posting] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Posting]
amountlessrealps Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
= FilePath -> Either FilePath (Transaction, [(Text, MixedAmount)])
forall a b. a -> Either a b
Left (FilePath -> Either FilePath (Transaction, [(Text, MixedAmount)]))
-> FilePath -> Either FilePath (Transaction, [(Text, MixedAmount)])
forall a b. (a -> b) -> a -> b
$ Transaction -> [FilePath] -> FilePath
transactionBalanceError Transaction
t
[FilePath
"can't have more than one real posting with no amount"
,FilePath
"(remember to put two or more spaces between account and amount)"]
| [Posting] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Posting]
amountlessbvps Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
= FilePath -> Either FilePath (Transaction, [(Text, MixedAmount)])
forall a b. a -> Either a b
Left (FilePath -> Either FilePath (Transaction, [(Text, MixedAmount)]))
-> FilePath -> Either FilePath (Transaction, [(Text, MixedAmount)])
forall a b. (a -> b) -> a -> b
$ Transaction -> [FilePath] -> FilePath
transactionBalanceError Transaction
t
[FilePath
"can't have more than one balanced virtual posting with no amount"
,FilePath
"(remember to put two or more spaces between account and amount)"]
| Bool
otherwise
= let psandinferredamts :: [(Posting, Maybe MixedAmount)]
psandinferredamts = (Posting -> (Posting, Maybe MixedAmount))
-> [Posting] -> [(Posting, Maybe MixedAmount)]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> (Posting, Maybe MixedAmount)
inferamount [Posting]
ps
inferredacctsandamts :: [(Text, MixedAmount)]
inferredacctsandamts = [(Posting -> Text
paccount Posting
p, MixedAmount
amt) | (Posting
p, Just MixedAmount
amt) <- [(Posting, Maybe MixedAmount)]
psandinferredamts]
in (Transaction, [(Text, MixedAmount)])
-> Either FilePath (Transaction, [(Text, MixedAmount)])
forall a b. b -> Either a b
Right (Transaction
t{tpostings :: [Posting]
tpostings=((Posting, Maybe MixedAmount) -> Posting)
-> [(Posting, Maybe MixedAmount)] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map (Posting, Maybe MixedAmount) -> Posting
forall a b. (a, b) -> a
fst [(Posting, Maybe MixedAmount)]
psandinferredamts}, [(Text, MixedAmount)]
inferredacctsandamts)
where
([Posting]
amountfulrealps, [Posting]
amountlessrealps) = (Posting -> Bool) -> [Posting] -> ([Posting], [Posting])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Posting -> Bool
hasAmount (Transaction -> [Posting]
realPostings Transaction
t)
realsum :: MixedAmount
realsum = [MixedAmount] -> MixedAmount
forall a. Num a => [a] -> a
sumStrict ([MixedAmount] -> MixedAmount) -> [MixedAmount] -> MixedAmount
forall a b. (a -> b) -> a -> b
$ (Posting -> MixedAmount) -> [Posting] -> [MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> MixedAmount
pamount [Posting]
amountfulrealps
([Posting]
amountfulbvps, [Posting]
amountlessbvps) = (Posting -> Bool) -> [Posting] -> ([Posting], [Posting])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Posting -> Bool
hasAmount (Transaction -> [Posting]
balancedVirtualPostings Transaction
t)
bvsum :: MixedAmount
bvsum = [MixedAmount] -> MixedAmount
forall a. Num a => [a] -> a
sumStrict ([MixedAmount] -> MixedAmount) -> [MixedAmount] -> MixedAmount
forall a b. (a -> b) -> a -> b
$ (Posting -> MixedAmount) -> [Posting] -> [MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> MixedAmount
pamount [Posting]
amountfulbvps
inferamount :: Posting -> (Posting, Maybe MixedAmount)
inferamount :: Posting -> (Posting, Maybe MixedAmount)
inferamount Posting
p =
let
minferredamt :: Maybe MixedAmount
minferredamt = case Posting -> PostingType
ptype Posting
p of
PostingType
RegularPosting | Bool -> Bool
not (Posting -> Bool
hasAmount Posting
p) -> MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just MixedAmount
realsum
PostingType
BalancedVirtualPosting | Bool -> Bool
not (Posting -> Bool
hasAmount Posting
p) -> MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just MixedAmount
bvsum
PostingType
_ -> Maybe MixedAmount
forall a. Maybe a
Nothing
in
case Maybe MixedAmount
minferredamt of
Maybe MixedAmount
Nothing -> (Posting
p, Maybe MixedAmount
forall a. Maybe a
Nothing)
Just MixedAmount
a -> (Posting
p{pamount :: MixedAmount
pamount=MixedAmount
a', poriginal :: Maybe Posting
poriginal=Posting -> Maybe Posting
forall a. a -> Maybe a
Just (Posting -> Maybe Posting) -> Posting -> Maybe Posting
forall a b. (a -> b) -> a -> b
$ Posting -> Posting
originalPosting Posting
p}, MixedAmount -> Maybe MixedAmount
forall a. a -> Maybe a
Just MixedAmount
a')
where
a' :: MixedAmount
a' = Map Text AmountStyle -> MixedAmount -> MixedAmount
styleMixedAmount Map Text AmountStyle
styles (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ MixedAmount -> MixedAmount
normaliseMixedAmount (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall a b. (a -> b) -> a -> b
$ MixedAmount -> MixedAmount
mixedAmountCost (-MixedAmount
a)
inferBalancingPrices :: Transaction -> Transaction
inferBalancingPrices :: Transaction -> Transaction
inferBalancingPrices t :: Transaction
t@Transaction{tpostings :: Transaction -> [Posting]
tpostings=[Posting]
ps} = Transaction
t{tpostings :: [Posting]
tpostings=[Posting]
ps'}
where
ps' :: [Posting]
ps' = (Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map (Transaction -> PostingType -> Posting -> Posting
priceInferrerFor Transaction
t PostingType
BalancedVirtualPosting (Posting -> Posting) -> (Posting -> Posting) -> Posting -> Posting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> PostingType -> Posting -> Posting
priceInferrerFor Transaction
t PostingType
RegularPosting) [Posting]
ps
priceInferrerFor :: Transaction -> PostingType -> (Posting -> Posting)
priceInferrerFor :: Transaction -> PostingType -> Posting -> Posting
priceInferrerFor Transaction
t PostingType
pt = Posting -> Posting
inferprice
where
postings :: [Posting]
postings = (Posting -> Bool) -> [Posting] -> [Posting]
forall a. (a -> Bool) -> [a] -> [a]
filter ((PostingType -> PostingType -> Bool
forall a. Eq a => a -> a -> Bool
==PostingType
pt)(PostingType -> Bool)
-> (Posting -> PostingType) -> Posting -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Posting -> PostingType
ptype) ([Posting] -> [Posting]) -> [Posting] -> [Posting]
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t
pmixedamounts :: [MixedAmount]
pmixedamounts = (Posting -> MixedAmount) -> [Posting] -> [MixedAmount]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> MixedAmount
pamount [Posting]
postings
pamounts :: [Amount]
pamounts = (MixedAmount -> [Amount]) -> [MixedAmount] -> [Amount]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap MixedAmount -> [Amount]
amounts [MixedAmount]
pmixedamounts
pcommodities :: [Text]
pcommodities = (Amount -> Text) -> [Amount] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Amount -> Text
acommodity [Amount]
pamounts
sumamounts :: [Amount]
sumamounts = MixedAmount -> [Amount]
amounts (MixedAmount -> [Amount]) -> MixedAmount -> [Amount]
forall a b. (a -> b) -> a -> b
$ [MixedAmount] -> MixedAmount
forall a. Num a => [a] -> a
sumStrict [MixedAmount]
pmixedamounts
sumcommodities :: [Text]
sumcommodities = (Amount -> Text) -> [Amount] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Amount -> Text
acommodity [Amount]
sumamounts
sumprices :: [Maybe AmountPrice]
sumprices = (Maybe AmountPrice -> Bool)
-> [Maybe AmountPrice] -> [Maybe AmountPrice]
forall a. (a -> Bool) -> [a] -> [a]
filter (Maybe AmountPrice -> Maybe AmountPrice -> Bool
forall a. Eq a => a -> a -> Bool
/=Maybe AmountPrice
forall a. Maybe a
Nothing) ([Maybe AmountPrice] -> [Maybe AmountPrice])
-> [Maybe AmountPrice] -> [Maybe AmountPrice]
forall a b. (a -> b) -> a -> b
$ (Amount -> Maybe AmountPrice) -> [Amount] -> [Maybe AmountPrice]
forall a b. (a -> b) -> [a] -> [b]
map Amount -> Maybe AmountPrice
aprice [Amount]
sumamounts
caninferprices :: Bool
caninferprices = [Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
sumcommodities Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2 Bool -> Bool -> Bool
&& [Maybe AmountPrice] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Maybe AmountPrice]
sumprices
inferprice :: Posting -> Posting
inferprice p :: Posting
p@Posting{pamount :: Posting -> MixedAmount
pamount=Mixed [Amount
a]}
| Bool
caninferprices Bool -> Bool -> Bool
&& Posting -> PostingType
ptype Posting
p PostingType -> PostingType -> Bool
forall a. Eq a => a -> a -> Bool
== PostingType
pt Bool -> Bool -> Bool
&& Amount -> Text
acommodity Amount
a Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
fromcommodity
= Posting
p{pamount :: MixedAmount
pamount=[Amount] -> MixedAmount
Mixed [Amount
a{aprice :: Maybe AmountPrice
aprice=AmountPrice -> Maybe AmountPrice
forall a. a -> Maybe a
Just AmountPrice
conversionprice}], poriginal :: Maybe Posting
poriginal=Posting -> Maybe Posting
forall a. a -> Maybe a
Just (Posting -> Maybe Posting) -> Posting -> Maybe Posting
forall a b. (a -> b) -> a -> b
$ Posting -> Posting
originalPosting Posting
p}
where
fromcommodity :: Text
fromcommodity = [Text] -> Text
forall a. [a] -> a
head ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
sumcommodities) [Text]
pcommodities
totalpricesign :: Amount -> Amount
totalpricesign = if Amount -> Quantity
aquantity Amount
a Quantity -> Quantity -> Bool
forall a. Ord a => a -> a -> Bool
< Quantity
0 then Amount -> Amount
forall a. Num a => a -> a
negate else Amount -> Amount
forall a. a -> a
id
conversionprice :: AmountPrice
conversionprice
| Int
fromcountInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
1 = Amount -> AmountPrice
TotalPrice (Amount -> AmountPrice) -> Amount -> AmountPrice
forall a b. (a -> b) -> a -> b
$ Amount -> Amount
totalpricesign (Amount -> Amount
forall a. Num a => a -> a
abs Amount
toamount) Amount -> AmountPrecision -> Amount
`withPrecision` AmountPrecision
NaturalPrecision
| Bool
otherwise = Amount -> AmountPrice
UnitPrice (Amount -> AmountPrice) -> Amount -> AmountPrice
forall a b. (a -> b) -> a -> b
$ Amount -> Amount
forall a. Num a => a -> a
abs Amount
unitprice Amount -> AmountPrecision -> Amount
`withPrecision` AmountPrecision
unitprecision
where
fromcount :: Int
fromcount = [Amount] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Amount] -> Int) -> [Amount] -> Int
forall a b. (a -> b) -> a -> b
$ (Amount -> Bool) -> [Amount] -> [Amount]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
fromcommodity)(Text -> Bool) -> (Amount -> Text) -> Amount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Amount -> Text
acommodity) [Amount]
pamounts
fromamount :: Amount
fromamount = [Amount] -> Amount
forall a. [a] -> a
head ([Amount] -> Amount) -> [Amount] -> Amount
forall a b. (a -> b) -> a -> b
$ (Amount -> Bool) -> [Amount] -> [Amount]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
fromcommodity)(Text -> Bool) -> (Amount -> Text) -> Amount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Amount -> Text
acommodity) [Amount]
sumamounts
fromprecision :: AmountPrecision
fromprecision = AmountStyle -> AmountPrecision
asprecision (AmountStyle -> AmountPrecision) -> AmountStyle -> AmountPrecision
forall a b. (a -> b) -> a -> b
$ Amount -> AmountStyle
astyle Amount
fromamount
tocommodity :: Text
tocommodity = [Text] -> Text
forall a. [a] -> a
head ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/=Text
fromcommodity) [Text]
sumcommodities
toamount :: Amount
toamount = [Amount] -> Amount
forall a. [a] -> a
head ([Amount] -> Amount) -> [Amount] -> Amount
forall a b. (a -> b) -> a -> b
$ (Amount -> Bool) -> [Amount] -> [Amount]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
==Text
tocommodity)(Text -> Bool) -> (Amount -> Text) -> Amount -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Amount -> Text
acommodity) [Amount]
sumamounts
toprecision :: AmountPrecision
toprecision = AmountStyle -> AmountPrecision
asprecision (AmountStyle -> AmountPrecision) -> AmountStyle -> AmountPrecision
forall a b. (a -> b) -> a -> b
$ Amount -> AmountStyle
astyle Amount
toamount
unitprice :: Amount
unitprice = (Amount -> Quantity
aquantity Amount
fromamount) Quantity -> Amount -> Amount
`divideAmount` Amount
toamount
unitprecision :: AmountPrecision
unitprecision = case (AmountPrecision
fromprecision, AmountPrecision
toprecision) of
(Precision Word8
a, Precision Word8
b) -> Word8 -> AmountPrecision
Precision (Word8 -> AmountPrecision) -> Word8 -> AmountPrecision
forall a b. (a -> b) -> a -> b
$ if Word8
forall a. Bounded a => a
maxBound Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- Word8
a Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
< Word8
b then Word8
forall a. Bounded a => a
maxBound else Word8 -> Word8 -> Word8
forall a. Ord a => a -> a -> a
max Word8
2 (Word8
a Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ Word8
b)
(AmountPrecision, AmountPrecision)
_ -> AmountPrecision
NaturalPrecision
inferprice Posting
p = Posting
p
transactionDate2 :: Transaction -> Day
transactionDate2 :: Transaction -> Day
transactionDate2 Transaction
t = Day -> Maybe Day -> Day
forall a. a -> Maybe a -> a
fromMaybe (Transaction -> Day
tdate Transaction
t) (Maybe Day -> Day) -> Maybe Day -> Day
forall a b. (a -> b) -> a -> b
$ Transaction -> Maybe Day
tdate2 Transaction
t
txnTieKnot :: Transaction -> Transaction
txnTieKnot :: Transaction -> Transaction
txnTieKnot t :: Transaction
t@Transaction{tpostings :: Transaction -> [Posting]
tpostings=[Posting]
ps} = Transaction
t' where
t' :: Transaction
t' = Transaction
t{tpostings :: [Posting]
tpostings=(Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map (Transaction -> Posting -> Posting
postingSetTransaction Transaction
t') [Posting]
ps}
txnUntieKnot :: Transaction -> Transaction
txnUntieKnot :: Transaction -> Transaction
txnUntieKnot t :: Transaction
t@Transaction{tpostings :: Transaction -> [Posting]
tpostings=[Posting]
ps} = Transaction
t{tpostings :: [Posting]
tpostings=(Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map (\Posting
p -> Posting
p{ptransaction :: Maybe Transaction
ptransaction=Maybe Transaction
forall a. Maybe a
Nothing}) [Posting]
ps}
postingSetTransaction :: Transaction -> Posting -> Posting
postingSetTransaction :: Transaction -> Posting -> Posting
postingSetTransaction Transaction
t Posting
p = Posting
p{ptransaction :: Maybe Transaction
ptransaction=Transaction -> Maybe Transaction
forall a. a -> Maybe a
Just Transaction
t}
transactionTransformPostings :: (Posting -> Posting) -> Transaction -> Transaction
transactionTransformPostings :: (Posting -> Posting) -> Transaction -> Transaction
transactionTransformPostings Posting -> Posting
f t :: Transaction
t@Transaction{tpostings :: Transaction -> [Posting]
tpostings=[Posting]
ps} = Transaction
t{tpostings :: [Posting]
tpostings=(Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Posting
f [Posting]
ps}
transactionApplyCostValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> Costing -> Maybe ValuationType -> Transaction -> Transaction
transactionApplyCostValuation :: PriceOracle
-> Map Text AmountStyle
-> Day
-> Day
-> Costing
-> Maybe ValuationType
-> Transaction
-> Transaction
transactionApplyCostValuation PriceOracle
priceoracle Map Text AmountStyle
styles Day
periodlast Day
today Costing
cost Maybe ValuationType
v =
(Posting -> Posting) -> Transaction -> Transaction
transactionTransformPostings (PriceOracle
-> Map Text AmountStyle
-> Day
-> Day
-> Costing
-> Maybe ValuationType
-> Posting
-> Posting
postingApplyCostValuation PriceOracle
priceoracle Map Text AmountStyle
styles Day
periodlast Day
today Costing
cost Maybe ValuationType
v)
transactionApplyValuation :: PriceOracle -> M.Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Transaction -> Transaction
transactionApplyValuation :: PriceOracle
-> Map Text AmountStyle
-> Day
-> Day
-> ValuationType
-> Transaction
-> Transaction
transactionApplyValuation PriceOracle
priceoracle Map Text AmountStyle
styles Day
periodlast Day
today ValuationType
v =
(Posting -> Posting) -> Transaction -> Transaction
transactionTransformPostings (PriceOracle
-> Map Text AmountStyle
-> Day
-> Day
-> ValuationType
-> Posting
-> Posting
postingApplyValuation PriceOracle
priceoracle Map Text AmountStyle
styles Day
periodlast Day
today ValuationType
v)
transactionToCost :: M.Map CommoditySymbol AmountStyle -> Transaction -> Transaction
transactionToCost :: Map Text AmountStyle -> Transaction -> Transaction
transactionToCost Map Text AmountStyle
styles t :: Transaction
t@Transaction{tpostings :: Transaction -> [Posting]
tpostings=[Posting]
ps} = Transaction
t{tpostings :: [Posting]
tpostings=(Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map (Map Text AmountStyle -> Posting -> Posting
postingToCost Map Text AmountStyle
styles) [Posting]
ps}
transactionApplyAliases :: [AccountAlias] -> Transaction -> Either RegexError Transaction
transactionApplyAliases :: [AccountAlias] -> Transaction -> Either FilePath Transaction
transactionApplyAliases [AccountAlias]
aliases Transaction
t =
case (Posting -> Either FilePath Posting)
-> [Posting] -> Either FilePath [Posting]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ([AccountAlias] -> Posting -> Either FilePath Posting
postingApplyAliases [AccountAlias]
aliases) ([Posting] -> Either FilePath [Posting])
-> [Posting] -> Either FilePath [Posting]
forall a b. (a -> b) -> a -> b
$ Transaction -> [Posting]
tpostings Transaction
t of
Right [Posting]
ps -> Transaction -> Either FilePath Transaction
forall a b. b -> Either a b
Right (Transaction -> Either FilePath Transaction)
-> Transaction -> Either FilePath Transaction
forall a b. (a -> b) -> a -> b
$ Transaction -> Transaction
txnTieKnot (Transaction -> Transaction) -> Transaction -> Transaction
forall a b. (a -> b) -> a -> b
$ Transaction
t{tpostings :: [Posting]
tpostings=[Posting]
ps}
Left FilePath
err -> FilePath -> Either FilePath Transaction
forall a b. a -> Either a b
Left FilePath
err
transactionMapPostings :: (Posting -> Posting) -> Transaction -> Transaction
transactionMapPostings :: (Posting -> Posting) -> Transaction -> Transaction
transactionMapPostings Posting -> Posting
f t :: Transaction
t@Transaction{tpostings :: Transaction -> [Posting]
tpostings=[Posting]
ps} = Transaction
t{tpostings :: [Posting]
tpostings=(Posting -> Posting) -> [Posting] -> [Posting]
forall a b. (a -> b) -> [a] -> [b]
map Posting -> Posting
f [Posting]
ps}
transactionMapPostingAmounts :: (Amount -> Amount) -> Transaction -> Transaction
transactionMapPostingAmounts :: (Amount -> Amount) -> Transaction -> Transaction
transactionMapPostingAmounts Amount -> Amount
f = (Posting -> Posting) -> Transaction -> Transaction
transactionMapPostings ((MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount ((Amount -> Amount) -> MixedAmount -> MixedAmount
mapMixedAmount Amount -> Amount
f))
transactionFile :: Transaction -> FilePath
transactionFile :: Transaction -> FilePath
transactionFile Transaction{GenericSourcePos
tsourcepos :: GenericSourcePos
tsourcepos :: Transaction -> GenericSourcePos
tsourcepos} =
case GenericSourcePos
tsourcepos of
GenericSourcePos FilePath
f Int
_ Int
_ -> FilePath
f
JournalSourcePos FilePath
f (Int, Int)
_ -> FilePath
f
tests_Transaction :: TestTree
tests_Transaction :: TestTree
tests_Transaction =
FilePath -> [TestTree] -> TestTree
tests FilePath
"Transaction" [
FilePath -> [TestTree] -> TestTree
tests FilePath
"postingAsLines" [
FilePath -> Assertion -> TestTree
test FilePath
"null posting" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> [Posting] -> Posting -> [Text]
postingAsLines Bool
False Bool
False [Posting
posting] Posting
posting [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= [Text
""]
, FilePath -> Assertion -> TestTree
test FilePath
"non-null posting" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
let p :: Posting
p =
Posting
posting
{ pstatus :: Status
pstatus = Status
Cleared
, paccount :: Text
paccount = Text
"a"
, pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1, Quantity -> Amount
hrs Quantity
2]
, pcomment :: Text
pcomment = Text
"pcomment1\npcomment2\n tag3: val3 \n"
, ptype :: PostingType
ptype = PostingType
RegularPosting
, ptags :: [Tag]
ptags = [(Text
"ptag1", Text
"val1"), (Text
"ptag2", Text
"val2")]
}
in Bool -> Bool -> [Posting] -> Posting -> [Text]
postingAsLines Bool
False Bool
False [Posting
p] Posting
p [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
[ Text
" * a $1.00 ; pcomment1"
, Text
" ; pcomment2"
, Text
" ; tag3: val3 "
, Text
" * a 2.00h ; pcomment1"
, Text
" ; pcomment2"
, Text
" ; tag3: val3 "
]
]
, let
timp :: Transaction
timp = Transaction
nulltransaction {tpostings :: [Posting]
tpostings = [Text
"a" Text -> Amount -> Posting
`post` Quantity -> Amount
usd Quantity
1, Text
"b" Text -> Amount -> Posting
`post` Amount
missingamt]}
texp :: Transaction
texp = Transaction
nulltransaction {tpostings :: [Posting]
tpostings = [Text
"a" Text -> Amount -> Posting
`post` Quantity -> Amount
usd Quantity
1, Text
"b" Text -> Amount -> Posting
`post` Quantity -> Amount
usd (-Quantity
1)]}
texp1 :: Transaction
texp1 = Transaction
nulltransaction {tpostings :: [Posting]
tpostings = [Text
"(a)" Text -> Amount -> Posting
`post` Quantity -> Amount
usd Quantity
1]}
texp2 :: Transaction
texp2 = Transaction
nulltransaction {tpostings :: [Posting]
tpostings = [Text
"a" Text -> Amount -> Posting
`post` Quantity -> Amount
usd Quantity
1, Text
"b" Text -> Amount -> Posting
`post` (Quantity -> Amount
hrs (-Quantity
1) Amount -> Amount -> Amount
`at` Quantity -> Amount
usd Quantity
1)]}
texp2b :: Transaction
texp2b = Transaction
nulltransaction {tpostings :: [Posting]
tpostings = [Text
"a" Text -> Amount -> Posting
`post` Quantity -> Amount
usd Quantity
1, Text
"b" Text -> Amount -> Posting
`post` Quantity -> Amount
hrs (-Quantity
1)]}
t3 :: Transaction
t3 = Transaction
nulltransaction {tpostings :: [Posting]
tpostings = [Text
"a" Text -> Amount -> Posting
`post` Quantity -> Amount
usd Quantity
1, Text
"b" Text -> Amount -> Posting
`post` Amount
missingamt, Text
"c" Text -> Amount -> Posting
`post` Quantity -> Amount
usd (-Quantity
1)]}
in FilePath -> [TestTree] -> TestTree
tests FilePath
"postingsAsLines" [
FilePath -> Assertion -> TestTree
test FilePath
"null-transaction" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ Bool -> [Posting] -> [Text]
postingsAsLines Bool
False (Transaction -> [Posting]
tpostings Transaction
nulltransaction) [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= []
, FilePath -> Assertion -> TestTree
test FilePath
"implicit-amount" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ Bool -> [Posting] -> [Text]
postingsAsLines Bool
False (Transaction -> [Posting]
tpostings Transaction
timp) [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
[ Text
" a $1.00"
, Text
" b"
]
, FilePath -> Assertion -> TestTree
test FilePath
"explicit-amounts" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ Bool -> [Posting] -> [Text]
postingsAsLines Bool
False (Transaction -> [Posting]
tpostings Transaction
texp) [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
[ Text
" a $1.00"
, Text
" b $-1.00"
]
, FilePath -> Assertion -> TestTree
test FilePath
"one-explicit-amount" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ Bool -> [Posting] -> [Text]
postingsAsLines Bool
False (Transaction -> [Posting]
tpostings Transaction
texp1) [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
[ Text
" (a) $1.00"
]
, FilePath -> Assertion -> TestTree
test FilePath
"explicit-amounts-two-commodities" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ Bool -> [Posting] -> [Text]
postingsAsLines Bool
False (Transaction -> [Posting]
tpostings Transaction
texp2) [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
[ Text
" a $1.00"
, Text
" b -1.00h @ $1.00"
]
, FilePath -> Assertion -> TestTree
test FilePath
"explicit-amounts-not-explicitly-balanced" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ Bool -> [Posting] -> [Text]
postingsAsLines Bool
False (Transaction -> [Posting]
tpostings Transaction
texp2b) [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
[ Text
" a $1.00"
, Text
" b -1.00h"
]
, FilePath -> Assertion -> TestTree
test FilePath
"implicit-amount-not-last" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ Bool -> [Posting] -> [Text]
postingsAsLines Bool
False (Transaction -> [Posting]
tpostings Transaction
t3) [Text] -> [Text] -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
[Text
" a $1.00", Text
" b", Text
" c $-1.00"]
]
, FilePath -> Assertion -> TestTree
test FilePath
"inferBalancingAmount" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ do
((Transaction, [(Text, MixedAmount)]) -> Transaction
forall a b. (a, b) -> a
fst ((Transaction, [(Text, MixedAmount)]) -> Transaction)
-> Either FilePath (Transaction, [(Text, MixedAmount)])
-> Either FilePath Transaction
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map Text AmountStyle
-> Transaction
-> Either FilePath (Transaction, [(Text, MixedAmount)])
inferBalancingAmount Map Text AmountStyle
forall k a. Map k a
M.empty Transaction
nulltransaction) Either FilePath Transaction
-> Either FilePath Transaction -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Transaction -> Either FilePath Transaction
forall a b. b -> Either a b
Right Transaction
nulltransaction
((Transaction, [(Text, MixedAmount)]) -> Transaction
forall a b. (a, b) -> a
fst ((Transaction, [(Text, MixedAmount)]) -> Transaction)
-> Either FilePath (Transaction, [(Text, MixedAmount)])
-> Either FilePath Transaction
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map Text AmountStyle
-> Transaction
-> Either FilePath (Transaction, [(Text, MixedAmount)])
inferBalancingAmount Map Text AmountStyle
forall k a. Map k a
M.empty Transaction
nulltransaction{tpostings :: [Posting]
tpostings = [Text
"a" Text -> Amount -> Posting
`post` Quantity -> Amount
usd (-Quantity
5), Text
"b" Text -> Amount -> Posting
`post` Amount
missingamt]}) Either FilePath Transaction
-> Either FilePath Transaction -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
Transaction -> Either FilePath Transaction
forall a b. b -> Either a b
Right Transaction
nulltransaction{tpostings :: [Posting]
tpostings = [Text
"a" Text -> Amount -> Posting
`post` Quantity -> Amount
usd (-Quantity
5), Text
"b" Text -> Amount -> Posting
`post` Quantity -> Amount
usd Quantity
5]}
((Transaction, [(Text, MixedAmount)]) -> Transaction
forall a b. (a, b) -> a
fst ((Transaction, [(Text, MixedAmount)]) -> Transaction)
-> Either FilePath (Transaction, [(Text, MixedAmount)])
-> Either FilePath Transaction
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map Text AmountStyle
-> Transaction
-> Either FilePath (Transaction, [(Text, MixedAmount)])
inferBalancingAmount Map Text AmountStyle
forall k a. Map k a
M.empty Transaction
nulltransaction{tpostings :: [Posting]
tpostings = [Text
"a" Text -> Amount -> Posting
`post` Quantity -> Amount
usd (-Quantity
5), Text
"b" Text -> Amount -> Posting
`post` (Quantity -> Amount
eur Quantity
3 Amount -> Amount -> Amount
@@ Quantity -> Amount
usd Quantity
4), Text
"c" Text -> Amount -> Posting
`post` Amount
missingamt]}) Either FilePath Transaction
-> Either FilePath Transaction -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
Transaction -> Either FilePath Transaction
forall a b. b -> Either a b
Right Transaction
nulltransaction{tpostings :: [Posting]
tpostings = [Text
"a" Text -> Amount -> Posting
`post` Quantity -> Amount
usd (-Quantity
5), Text
"b" Text -> Amount -> Posting
`post` (Quantity -> Amount
eur Quantity
3 Amount -> Amount -> Amount
@@ Quantity -> Amount
usd Quantity
4), Text
"c" Text -> Amount -> Posting
`post` Quantity -> Amount
usd Quantity
1]}
, FilePath -> [TestTree] -> TestTree
tests FilePath
"showTransaction" [
FilePath -> Assertion -> TestTree
test FilePath
"null transaction" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ Transaction -> Text
showTransaction Transaction
nulltransaction Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?= Text
"0000-01-01\n\n"
, FilePath -> Assertion -> TestTree
test FilePath
"non-null transaction" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$ Transaction -> Text
showTransaction
Transaction
nulltransaction
{ tdate :: Day
tdate = Integer -> Int -> Int -> Day
fromGregorian Integer
2012 Int
05 Int
14
, tdate2 :: Maybe Day
tdate2 = Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> Day
fromGregorian Integer
2012 Int
05 Int
15
, tstatus :: Status
tstatus = Status
Unmarked
, tcode :: Text
tcode = Text
"code"
, tdescription :: Text
tdescription = Text
"desc"
, tcomment :: Text
tcomment = Text
"tcomment1\ntcomment2\n"
, ttags :: [Tag]
ttags = [(Text
"ttag1", Text
"val1")]
, tpostings :: [Posting]
tpostings =
[ Posting
nullposting
{ pstatus :: Status
pstatus = Status
Cleared
, paccount :: Text
paccount = Text
"a"
, pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1, Quantity -> Amount
hrs Quantity
2]
, pcomment :: Text
pcomment = Text
"\npcomment2\n"
, ptype :: PostingType
ptype = PostingType
RegularPosting
, ptags :: [Tag]
ptags = [(Text
"ptag1", Text
"val1"), (Text
"ptag2", Text
"val2")]
}
]
} Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
[Text] -> Text
T.unlines
[ Text
"2012-05-14=2012-05-15 (code) desc ; tcomment1"
, Text
" ; tcomment2"
, Text
" * a $1.00"
, Text
" ; pcomment2"
, Text
" * a 2.00h"
, Text
" ; pcomment2"
, Text
""
]
, FilePath -> Assertion -> TestTree
test FilePath
"show a balanced transaction" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
(let t :: Transaction
t =
Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2007 Int
01 Int
28)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"coopportunity"
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"expenses:food:groceries", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
47.18], ptransaction :: Maybe Transaction
ptransaction = Transaction -> Maybe Transaction
forall a. a -> Maybe a
Just Transaction
t}
, Posting
posting {paccount :: Text
paccount = Text
"assets:checking", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd (-Quantity
47.18)], ptransaction :: Maybe Transaction
ptransaction = Transaction -> Maybe Transaction
forall a. a -> Maybe a
Just Transaction
t}
]
in Transaction -> Text
showTransaction Transaction
t) Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
([Text] -> Text
T.unlines
[ Text
"2007-01-28 coopportunity"
, Text
" expenses:food:groceries $47.18"
, Text
" assets:checking $-47.18"
, Text
""
])
, FilePath -> Assertion -> TestTree
test FilePath
"show an unbalanced transaction, should not elide" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
(Transaction -> Text
showTransaction
(Transaction -> Transaction
txnTieKnot (Transaction -> Transaction) -> Transaction -> Transaction
forall a b. (a -> b) -> a -> b
$
Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2007 Int
01 Int
28)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"coopportunity"
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"expenses:food:groceries", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
47.18]}
, Posting
posting {paccount :: Text
paccount = Text
"assets:checking", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd (-Quantity
47.19)]}
])) Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
([Text] -> Text
T.unlines
[ Text
"2007-01-28 coopportunity"
, Text
" expenses:food:groceries $47.18"
, Text
" assets:checking $-47.19"
, Text
""
])
, FilePath -> Assertion -> TestTree
test FilePath
"show a transaction with one posting and a missing amount" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
(Transaction -> Text
showTransaction
(Transaction -> Transaction
txnTieKnot (Transaction -> Transaction) -> Transaction -> Transaction
forall a b. (a -> b) -> a -> b
$
Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2007 Int
01 Int
28)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"coopportunity"
Text
""
[]
[Posting
posting {paccount :: Text
paccount = Text
"expenses:food:groceries", pamount :: MixedAmount
pamount = MixedAmount
missingmixedamt}])) Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
([Text] -> Text
T.unlines [Text
"2007-01-28 coopportunity", Text
" expenses:food:groceries", Text
""])
, FilePath -> Assertion -> TestTree
test FilePath
"show a transaction with a priced commodityless amount" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
(Transaction -> Text
showTransaction
(Transaction -> Transaction
txnTieKnot (Transaction -> Transaction) -> Transaction -> Transaction
forall a b. (a -> b) -> a -> b
$
Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2010 Int
01 Int
01)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"x"
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"a", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
num Quantity
1 Amount -> Amount -> Amount
`at` (Quantity -> Amount
usd Quantity
2 Amount -> AmountPrecision -> Amount
`withPrecision` Word8 -> AmountPrecision
Precision Word8
0)]}
, Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = MixedAmount
missingmixedamt}
])) Text -> Text -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
([Text] -> Text
T.unlines [Text
"2010-01-01 x", Text
" a 1 @ $2", Text
" b", Text
""])
]
, FilePath -> [TestTree] -> TestTree
tests FilePath
"balanceTransaction" [
FilePath -> Assertion -> TestTree
test FilePath
"detect unbalanced entry, sign error" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
Either FilePath Transaction -> Assertion
forall b a. (HasCallStack, Eq b, Show b) => Either a b -> Assertion
assertLeft
(Maybe (Map Text AmountStyle)
-> Transaction -> Either FilePath Transaction
balanceTransaction
Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing
(Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2007 Int
01 Int
28)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"test"
Text
""
[]
[Posting
posting {paccount :: Text
paccount = Text
"a", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1]}, Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1]}]))
,FilePath -> Assertion -> TestTree
test FilePath
"detect unbalanced entry, multiple missing amounts" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
Either FilePath Transaction -> Assertion
forall b a. (HasCallStack, Eq b, Show b) => Either a b -> Assertion
assertLeft (Either FilePath Transaction -> Assertion)
-> Either FilePath Transaction -> Assertion
forall a b. (a -> b) -> a -> b
$
Maybe (Map Text AmountStyle)
-> Transaction -> Either FilePath Transaction
balanceTransaction
Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing
(Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2007 Int
01 Int
28)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"test"
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"a", pamount :: MixedAmount
pamount = MixedAmount
missingmixedamt}
, Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = MixedAmount
missingmixedamt}
])
,FilePath -> Assertion -> TestTree
test FilePath
"one missing amount is inferred" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
(Posting -> MixedAmount
pamount (Posting -> MixedAmount)
-> (Transaction -> Posting) -> Transaction -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Posting] -> Posting
forall a. [a] -> a
last ([Posting] -> Posting)
-> (Transaction -> [Posting]) -> Transaction -> Posting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> [Posting]
tpostings (Transaction -> MixedAmount)
-> Either FilePath Transaction -> Either FilePath MixedAmount
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Maybe (Map Text AmountStyle)
-> Transaction -> Either FilePath Transaction
balanceTransaction
Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing
(Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2007 Int
01 Int
28)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
""
Text
""
[]
[Posting
posting {paccount :: Text
paccount = Text
"a", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1]}, Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = MixedAmount
missingmixedamt}])) Either FilePath MixedAmount
-> Either FilePath MixedAmount -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
MixedAmount -> Either FilePath MixedAmount
forall a b. b -> Either a b
Right ([Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd (-Quantity
1)])
,FilePath -> Assertion -> TestTree
test FilePath
"conversion price is inferred" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
(Posting -> MixedAmount
pamount (Posting -> MixedAmount)
-> (Transaction -> Posting) -> Transaction -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Posting] -> Posting
forall a. [a] -> a
head ([Posting] -> Posting)
-> (Transaction -> [Posting]) -> Transaction -> Posting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Transaction -> [Posting]
tpostings (Transaction -> MixedAmount)
-> Either FilePath Transaction -> Either FilePath MixedAmount
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Maybe (Map Text AmountStyle)
-> Transaction -> Either FilePath Transaction
balanceTransaction
Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing
(Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2007 Int
01 Int
28)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
""
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"a", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1.35]}
, Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
eur (-Quantity
1)]}
])) Either FilePath MixedAmount
-> Either FilePath MixedAmount -> Assertion
forall a. (Eq a, Show a, HasCallStack) => a -> a -> Assertion
@?=
MixedAmount -> Either FilePath MixedAmount
forall a b. b -> Either a b
Right ([Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1.35 Amount -> Amount -> Amount
@@ (Quantity -> Amount
eur Quantity
1 Amount -> AmountPrecision -> Amount
`withPrecision` AmountPrecision
NaturalPrecision)])
,FilePath -> Assertion -> TestTree
test FilePath
"balanceTransaction balances based on cost if there are unit prices" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
Either FilePath Transaction -> Assertion
forall a b. (HasCallStack, Eq a, Show a) => Either a b -> Assertion
assertRight (Either FilePath Transaction -> Assertion)
-> Either FilePath Transaction -> Assertion
forall a b. (a -> b) -> a -> b
$
Maybe (Map Text AmountStyle)
-> Transaction -> Either FilePath Transaction
balanceTransaction
Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing
(Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2011 Int
01 Int
01)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
""
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"a", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1 Amount -> Amount -> Amount
`at` Quantity -> Amount
eur Quantity
2]}
, Posting
posting {paccount :: Text
paccount = Text
"a", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd (-Quantity
2) Amount -> Amount -> Amount
`at` Quantity -> Amount
eur Quantity
1]}
])
,FilePath -> Assertion -> TestTree
test FilePath
"balanceTransaction balances based on cost if there are total prices" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
Either FilePath Transaction -> Assertion
forall a b. (HasCallStack, Eq a, Show a) => Either a b -> Assertion
assertRight (Either FilePath Transaction -> Assertion)
-> Either FilePath Transaction -> Assertion
forall a b. (a -> b) -> a -> b
$
Maybe (Map Text AmountStyle)
-> Transaction -> Either FilePath Transaction
balanceTransaction
Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing
(Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2011 Int
01 Int
01)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
""
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"a", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1 Amount -> Amount -> Amount
@@ Quantity -> Amount
eur Quantity
1]}
, Posting
posting {paccount :: Text
paccount = Text
"a", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd (-Quantity
2) Amount -> Amount -> Amount
@@ Quantity -> Amount
eur (-Quantity
1)]}
])
]
, FilePath -> [TestTree] -> TestTree
tests FilePath
"isTransactionBalanced" [
FilePath -> Assertion -> TestTree
test FilePath
"detect balanced" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => FilePath -> Bool -> Assertion
FilePath -> Bool -> Assertion
assertBool FilePath
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$
Maybe (Map Text AmountStyle) -> Transaction -> Bool
isTransactionBalanced Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing (Transaction -> Bool) -> Transaction -> Bool
forall a b. (a -> b) -> a -> b
$
Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2009 Int
01 Int
01)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"a"
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1.00]}
, Posting
posting {paccount :: Text
paccount = Text
"c", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd (-Quantity
1.00)]}
]
,FilePath -> Assertion -> TestTree
test FilePath
"detect unbalanced" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => FilePath -> Bool -> Assertion
FilePath -> Bool -> Assertion
assertBool FilePath
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$
Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$
Maybe (Map Text AmountStyle) -> Transaction -> Bool
isTransactionBalanced Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing (Transaction -> Bool) -> Transaction -> Bool
forall a b. (a -> b) -> a -> b
$
Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2009 Int
01 Int
01)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"a"
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1.00]}
, Posting
posting {paccount :: Text
paccount = Text
"c", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd (-Quantity
1.01)]}
]
,FilePath -> Assertion -> TestTree
test FilePath
"detect unbalanced, one posting" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => FilePath -> Bool -> Assertion
FilePath -> Bool -> Assertion
assertBool FilePath
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$
Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$
Maybe (Map Text AmountStyle) -> Transaction -> Bool
isTransactionBalanced Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing (Transaction -> Bool) -> Transaction -> Bool
forall a b. (a -> b) -> a -> b
$
Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2009 Int
01 Int
01)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"a"
Text
""
[]
[Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1.00]}]
,FilePath -> Assertion -> TestTree
test FilePath
"one zero posting is considered balanced for now" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => FilePath -> Bool -> Assertion
FilePath -> Bool -> Assertion
assertBool FilePath
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$
Maybe (Map Text AmountStyle) -> Transaction -> Bool
isTransactionBalanced Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing (Transaction -> Bool) -> Transaction -> Bool
forall a b. (a -> b) -> a -> b
$
Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2009 Int
01 Int
01)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"a"
Text
""
[]
[Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
0]}]
,FilePath -> Assertion -> TestTree
test FilePath
"virtual postings don't need to balance" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => FilePath -> Bool -> Assertion
FilePath -> Bool -> Assertion
assertBool FilePath
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$
Maybe (Map Text AmountStyle) -> Transaction -> Bool
isTransactionBalanced Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing (Transaction -> Bool) -> Transaction -> Bool
forall a b. (a -> b) -> a -> b
$
Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2009 Int
01 Int
01)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"a"
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1.00]}
, Posting
posting {paccount :: Text
paccount = Text
"c", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd (-Quantity
1.00)]}
, Posting
posting {paccount :: Text
paccount = Text
"d", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
100], ptype :: PostingType
ptype = PostingType
VirtualPosting}
]
,FilePath -> Assertion -> TestTree
test FilePath
"balanced virtual postings need to balance among themselves" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => FilePath -> Bool -> Assertion
FilePath -> Bool -> Assertion
assertBool FilePath
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$
Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$
Maybe (Map Text AmountStyle) -> Transaction -> Bool
isTransactionBalanced Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing (Transaction -> Bool) -> Transaction -> Bool
forall a b. (a -> b) -> a -> b
$
Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2009 Int
01 Int
01)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"a"
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1.00]}
, Posting
posting {paccount :: Text
paccount = Text
"c", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd (-Quantity
1.00)]}
, Posting
posting {paccount :: Text
paccount = Text
"d", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
100], ptype :: PostingType
ptype = PostingType
BalancedVirtualPosting}
]
,FilePath -> Assertion -> TestTree
test FilePath
"balanced virtual postings need to balance among themselves (2)" (Assertion -> TestTree) -> Assertion -> TestTree
forall a b. (a -> b) -> a -> b
$
HasCallStack => FilePath -> Bool -> Assertion
FilePath -> Bool -> Assertion
assertBool FilePath
"" (Bool -> Assertion) -> Bool -> Assertion
forall a b. (a -> b) -> a -> b
$
Maybe (Map Text AmountStyle) -> Transaction -> Bool
isTransactionBalanced Maybe (Map Text AmountStyle)
forall a. Maybe a
Nothing (Transaction -> Bool) -> Transaction -> Bool
forall a b. (a -> b) -> a -> b
$
Integer
-> Text
-> GenericSourcePos
-> Day
-> Maybe Day
-> Status
-> Text
-> Text
-> Text
-> [Tag]
-> [Posting]
-> Transaction
Transaction
Integer
0
Text
""
GenericSourcePos
nullsourcepos
(Integer -> Int -> Int -> Day
fromGregorian Integer
2009 Int
01 Int
01)
Maybe Day
forall a. Maybe a
Nothing
Status
Unmarked
Text
""
Text
"a"
Text
""
[]
[ Posting
posting {paccount :: Text
paccount = Text
"b", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
1.00]}
, Posting
posting {paccount :: Text
paccount = Text
"c", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd (-Quantity
1.00)]}
, Posting
posting {paccount :: Text
paccount = Text
"d", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd Quantity
100], ptype :: PostingType
ptype = PostingType
BalancedVirtualPosting}
, Posting
posting {paccount :: Text
paccount = Text
"3", pamount :: MixedAmount
pamount = [Amount] -> MixedAmount
Mixed [Quantity -> Amount
usd (-Quantity
100)], ptype :: PostingType
ptype = PostingType
BalancedVirtualPosting}
]
]
]