cln: Rename balancingOpts to defbalancingopts, to be consistent with definputopts, defreportopts, etc.

This commit is contained in:
Stephen Morgan 2021-08-23 23:15:04 +10:00 committed by Simon Michael
parent e310ba574c
commit 13206d0b18
9 changed files with 32 additions and 32 deletions

View File

@ -723,7 +723,7 @@ journalModifyTransactions d j =
-- | Check any balance assertions in the journal and return an error message -- | Check any balance assertions in the journal and return an error message
-- if any of them fail (or if the transaction balancing they require fails). -- if any of them fail (or if the transaction balancing they require fails).
journalCheckBalanceAssertions :: Journal -> Maybe String journalCheckBalanceAssertions :: Journal -> Maybe String
journalCheckBalanceAssertions = either Just (const Nothing) . journalBalanceTransactions balancingOpts journalCheckBalanceAssertions = either Just (const Nothing) . journalBalanceTransactions defbalancingopts
-- "Transaction balancing", including: inferring missing amounts, -- "Transaction balancing", including: inferring missing amounts,
-- applying balance assignments, checking transaction balancedness, -- applying balance assignments, checking transaction balancedness,
@ -886,7 +886,7 @@ balanceTransactionAndCheckAssertionsB (Right t@Transaction{tpostings=ps}) = do
ps' <- mapM (addOrAssignAmountAndCheckAssertionB . postingStripPrices) ps ps' <- mapM (addOrAssignAmountAndCheckAssertionB . postingStripPrices) ps
-- infer any remaining missing amounts, and make sure the transaction is now fully balanced -- infer any remaining missing amounts, and make sure the transaction is now fully balanced
styles <- R.reader bsStyles styles <- R.reader bsStyles
case balanceTransactionHelper balancingOpts{commodity_styles_=styles} t{tpostings=ps'} of case balanceTransactionHelper defbalancingopts{commodity_styles_=styles} t{tpostings=ps'} of
Left err -> throwError err Left err -> throwError err
Right (t', inferredacctsandamts) -> do Right (t', inferredacctsandamts) -> do
-- for each amount just inferred, update the running balance -- for each amount just inferred, update the running balance
@ -1408,7 +1408,7 @@ journalApplyAliases aliases j =
-- liabilities:debts $1 -- liabilities:debts $1
-- assets:bank:checking -- assets:bank:checking
-- --
Right samplejournal = journalBalanceTransactions balancingOpts $ Right samplejournal = journalBalanceTransactions defbalancingopts $
nulljournal nulljournal
{jtxns = [ {jtxns = [
txnTieKnot $ Transaction { txnTieKnot $ Transaction {
@ -1551,7 +1551,7 @@ tests_Journal = tests "Journal" [
,tests "journalBalanceTransactions" [ ,tests "journalBalanceTransactions" [
test "balance-assignment" $ do test "balance-assignment" $ do
let ej = journalBalanceTransactions balancingOpts $ let ej = journalBalanceTransactions defbalancingopts $
--2019/01/01 --2019/01/01
-- (a) = 1 -- (a) = 1
nulljournal{ jtxns = [ nulljournal{ jtxns = [
@ -1562,7 +1562,7 @@ tests_Journal = tests "Journal" [
(jtxns j & head & tpostings & head & pamount & amountsRaw) @?= [num 1] (jtxns j & head & tpostings & head & pamount & amountsRaw) @?= [num 1]
,test "same-day-1" $ do ,test "same-day-1" $ do
assertRight $ journalBalanceTransactions balancingOpts $ assertRight $ journalBalanceTransactions defbalancingopts $
--2019/01/01 --2019/01/01
-- (a) = 1 -- (a) = 1
--2019/01/01 --2019/01/01
@ -1573,7 +1573,7 @@ tests_Journal = tests "Journal" [
]} ]}
,test "same-day-2" $ do ,test "same-day-2" $ do
assertRight $ journalBalanceTransactions balancingOpts $ assertRight $ journalBalanceTransactions defbalancingopts $
--2019/01/01 --2019/01/01
-- (a) 2 = 2 -- (a) 2 = 2
--2019/01/01 --2019/01/01
@ -1591,7 +1591,7 @@ tests_Journal = tests "Journal" [
]} ]}
,test "out-of-order" $ do ,test "out-of-order" $ do
assertRight $ journalBalanceTransactions balancingOpts $ assertRight $ journalBalanceTransactions defbalancingopts $
--2019/1/2 --2019/1/2
-- (a) 1 = 2 -- (a) 1 = 2
--2019/1/1 --2019/1/1

View File

@ -30,7 +30,7 @@ module Hledger.Data.Transaction (
balancedVirtualPostings, balancedVirtualPostings,
transactionsPostings, transactionsPostings,
BalancingOpts(..), BalancingOpts(..),
balancingOpts, defbalancingopts,
isTransactionBalanced, isTransactionBalanced,
balanceTransaction, balanceTransaction,
balanceTransactionHelper, balanceTransactionHelper,
@ -360,8 +360,8 @@ data BalancingOpts = BalancingOpts
, commodity_styles_ :: Maybe (M.Map CommoditySymbol AmountStyle) -- ^ commodity display styles , commodity_styles_ :: Maybe (M.Map CommoditySymbol AmountStyle) -- ^ commodity display styles
} deriving (Show) } deriving (Show)
balancingOpts :: BalancingOpts defbalancingopts :: BalancingOpts
balancingOpts = BalancingOpts defbalancingopts = BalancingOpts
{ ignore_assertions_ = False { ignore_assertions_ = False
, infer_prices_ = True , infer_prices_ = True
, commodity_styles_ = Nothing , commodity_styles_ = Nothing
@ -854,7 +854,7 @@ tests_Transaction =
, tests "balanceTransaction" [ , tests "balanceTransaction" [
test "detect unbalanced entry, sign error" $ test "detect unbalanced entry, sign error" $
assertLeft assertLeft
(balanceTransaction balancingOpts (balanceTransaction defbalancingopts
(Transaction (Transaction
0 0
"" ""
@ -869,7 +869,7 @@ tests_Transaction =
[posting {paccount = "a", pamount = mixedAmount (usd 1)}, posting {paccount = "b", pamount = mixedAmount (usd 1)}])) [posting {paccount = "a", pamount = mixedAmount (usd 1)}, posting {paccount = "b", pamount = mixedAmount (usd 1)}]))
,test "detect unbalanced entry, multiple missing amounts" $ ,test "detect unbalanced entry, multiple missing amounts" $
assertLeft $ assertLeft $
balanceTransaction balancingOpts balanceTransaction defbalancingopts
(Transaction (Transaction
0 0
"" ""
@ -886,7 +886,7 @@ tests_Transaction =
]) ])
,test "one missing amount is inferred" $ ,test "one missing amount is inferred" $
(pamount . last . tpostings <$> (pamount . last . tpostings <$>
balanceTransaction balancingOpts balanceTransaction defbalancingopts
(Transaction (Transaction
0 0
"" ""
@ -902,7 +902,7 @@ tests_Transaction =
Right (mixedAmount $ usd (-1)) Right (mixedAmount $ usd (-1))
,test "conversion price is inferred" $ ,test "conversion price is inferred" $
(pamount . head . tpostings <$> (pamount . head . tpostings <$>
balanceTransaction balancingOpts balanceTransaction defbalancingopts
(Transaction (Transaction
0 0
"" ""
@ -920,7 +920,7 @@ tests_Transaction =
Right (mixedAmount $ usd 1.35 @@ eur 1) Right (mixedAmount $ usd 1.35 @@ eur 1)
,test "balanceTransaction balances based on cost if there are unit prices" $ ,test "balanceTransaction balances based on cost if there are unit prices" $
assertRight $ assertRight $
balanceTransaction balancingOpts balanceTransaction defbalancingopts
(Transaction (Transaction
0 0
"" ""
@ -937,7 +937,7 @@ tests_Transaction =
]) ])
,test "balanceTransaction balances based on cost if there are total prices" $ ,test "balanceTransaction balances based on cost if there are total prices" $
assertRight $ assertRight $
balanceTransaction balancingOpts balanceTransaction defbalancingopts
(Transaction (Transaction
0 0
"" ""
@ -956,7 +956,7 @@ tests_Transaction =
, tests "isTransactionBalanced" [ , tests "isTransactionBalanced" [
test "detect balanced" $ test "detect balanced" $
assertBool "" $ assertBool "" $
isTransactionBalanced balancingOpts $ isTransactionBalanced defbalancingopts $
Transaction Transaction
0 0
"" ""
@ -974,7 +974,7 @@ tests_Transaction =
,test "detect unbalanced" $ ,test "detect unbalanced" $
assertBool "" $ assertBool "" $
not $ not $
isTransactionBalanced balancingOpts $ isTransactionBalanced defbalancingopts $
Transaction Transaction
0 0
"" ""
@ -992,7 +992,7 @@ tests_Transaction =
,test "detect unbalanced, one posting" $ ,test "detect unbalanced, one posting" $
assertBool "" $ assertBool "" $
not $ not $
isTransactionBalanced balancingOpts $ isTransactionBalanced defbalancingopts $
Transaction Transaction
0 0
"" ""
@ -1007,7 +1007,7 @@ tests_Transaction =
[posting {paccount = "b", pamount = mixedAmount (usd 1.00)}] [posting {paccount = "b", pamount = mixedAmount (usd 1.00)}]
,test "one zero posting is considered balanced for now" $ ,test "one zero posting is considered balanced for now" $
assertBool "" $ assertBool "" $
isTransactionBalanced balancingOpts $ isTransactionBalanced defbalancingopts $
Transaction Transaction
0 0
"" ""
@ -1022,7 +1022,7 @@ tests_Transaction =
[posting {paccount = "b", pamount = mixedAmount (usd 0)}] [posting {paccount = "b", pamount = mixedAmount (usd 0)}]
,test "virtual postings don't need to balance" $ ,test "virtual postings don't need to balance" $
assertBool "" $ assertBool "" $
isTransactionBalanced balancingOpts $ isTransactionBalanced defbalancingopts $
Transaction Transaction
0 0
"" ""
@ -1041,7 +1041,7 @@ tests_Transaction =
,test "balanced virtual postings need to balance among themselves" $ ,test "balanced virtual postings need to balance among themselves" $
assertBool "" $ assertBool "" $
not $ not $
isTransactionBalanced balancingOpts $ isTransactionBalanced defbalancingopts $
Transaction Transaction
0 0
"" ""
@ -1059,7 +1059,7 @@ tests_Transaction =
] ]
,test "balanced virtual postings need to balance among themselves (2)" $ ,test "balanced virtual postings need to balance among themselves (2)" $
assertBool "" $ assertBool "" $
isTransactionBalanced balancingOpts $ isTransactionBalanced defbalancingopts $
Transaction Transaction
0 0
"" ""

View File

@ -253,7 +253,7 @@ rawOptsToInputOpts rawopts = do
,forecast_ = forecastPeriodFromRawOpts d rawopts ,forecast_ = forecastPeriodFromRawOpts d rawopts
,reportspan_ = DateSpan (queryStartDate False datequery) (queryEndDate False datequery) ,reportspan_ = DateSpan (queryStartDate False datequery) (queryEndDate False datequery)
,auto_ = boolopt "auto" rawopts ,auto_ = boolopt "auto" rawopts
,balancingopts_ = balancingOpts{ ,balancingopts_ = defbalancingopts{
ignore_assertions_ = boolopt "ignore-assertions" rawopts ignore_assertions_ = boolopt "ignore-assertions" rawopts
, infer_prices_ = not noinferprice , infer_prices_ = not noinferprice
, commodity_styles_ = rawOptsToCommodityStylesOpts rawopts , commodity_styles_ = rawOptsToCommodityStylesOpts rawopts

View File

@ -16,7 +16,7 @@ import Control.Applicative ((<|>))
import Data.Time (Day, addDays) import Data.Time (Day, addDays)
import Hledger.Data.Types import Hledger.Data.Types
import Hledger.Data.Transaction (BalancingOpts(..), balancingOpts) import Hledger.Data.Transaction (BalancingOpts(..), defbalancingopts)
import Hledger.Data.Journal (journalEndDate) import Hledger.Data.Journal (journalEndDate)
import Hledger.Data.Dates (nulldatespan) import Hledger.Data.Dates (nulldatespan)
import Hledger.Utils import Hledger.Utils
@ -50,7 +50,7 @@ definputopts = InputOpts
, forecast_ = Nothing , forecast_ = Nothing
, reportspan_ = nulldatespan , reportspan_ = nulldatespan
, auto_ = False , auto_ = False
, balancingopts_ = balancingOpts , balancingopts_ = defbalancingopts
, strict_ = False , strict_ = False
} }

View File

@ -78,7 +78,7 @@ balanceReport rspec j = (rows, total)
-- tests -- tests
Right samplejournal2 = Right samplejournal2 =
journalBalanceTransactions balancingOpts journalBalanceTransactions defbalancingopts
nulljournal{ nulljournal{
jtxns = [ jtxns = [
txnTieKnot Transaction{ txnTieKnot Transaction{

View File

@ -116,7 +116,7 @@ validateTransaction ::
-> FormResult Transaction -> FormResult Transaction
validateTransaction dateRes descRes postingsRes = validateTransaction dateRes descRes postingsRes =
case makeTransaction <$> dateRes <*> descRes <*> postingsRes of case makeTransaction <$> dateRes <*> descRes <*> postingsRes of
FormSuccess txn -> case balanceTransaction balancingOpts txn of FormSuccess txn -> case balanceTransaction defbalancingopts txn of
Left e -> FormFailure [T.pack e] Left e -> FormFailure [T.pack e]
Right txn' -> FormSuccess txn' Right txn' -> FormSuccess txn'
x -> x x -> x

View File

@ -203,7 +203,7 @@ confirmedTransactionWizard prevInput es@EntryState{..} stack@(currentStage : _)
,tcomment=txnCmnt ,tcomment=txnCmnt
,tpostings=esPostings ,tpostings=esPostings
} }
case balanceTransaction balancingOpts t of -- imprecise balancing (?) case balanceTransaction defbalancingopts t of -- imprecise balancing (?)
Right t' -> Right t' ->
confirmedTransactionWizard prevInput es (EndStage t' : stack) confirmedTransactionWizard prevInput es (EndStage t' : stack)
Left err -> do Left err -> do
@ -292,7 +292,7 @@ descriptionAndCommentWizard PrevInput{..} EntryState{..} = do
return $ Just (desc, comment) return $ Just (desc, comment)
postingsBalanced :: [Posting] -> Bool postingsBalanced :: [Posting] -> Bool
postingsBalanced ps = isRight $ balanceTransaction balancingOpts nulltransaction{tpostings=ps} postingsBalanced ps = isRight $ balanceTransaction defbalancingopts nulltransaction{tpostings=ps}
accountWizard PrevInput{..} EntryState{..} = do accountWizard PrevInput{..} EntryState{..} = do
let pnum = length esPostings + 1 let pnum = length esPostings + 1

View File

@ -84,7 +84,7 @@ matching ppl ppr = do
readJournalFile' :: FilePath -> IO Journal readJournalFile' :: FilePath -> IO Journal
readJournalFile' fn = readJournalFile' fn =
readJournalFile definputopts{balancingopts_=balancingOpts{ignore_assertions_=True}} fn >>= either error' return -- PARTIAL: readJournalFile definputopts{balancingopts_=defbalancingopts{ignore_assertions_=True}} fn >>= either error' return -- PARTIAL:
matchingPostings :: AccountName -> Journal -> [PostingWithPath] matchingPostings :: AccountName -> Journal -> [PostingWithPath]
matchingPostings acct j = filter ((== acct) . paccount . ppposting) $ allPostingsWithPath j matchingPostings acct j = filter ((== acct) . paccount . ppposting) $ allPostingsWithPath j

View File

@ -42,7 +42,7 @@ importcmd opts@CliOpts{rawopts_=rawopts,inputopts_=iopts} j = do
Nothing -> Just inferredStyles Nothing -> Just inferredStyles
Just inputStyles -> Just $ inputStyles <> inferredStyles Just inputStyles -> Just $ inputStyles <> inferredStyles
iopts' = iopts{new_=True, new_save_=not dryrun, balancingopts_=balancingOpts{commodity_styles_= combinedStyles}} iopts' = iopts{new_=True, new_save_=not dryrun, balancingopts_=defbalancingopts{commodity_styles_= combinedStyles}}
case inputfiles of case inputfiles of
[] -> error' "please provide one or more input files as arguments" -- PARTIAL: [] -> error' "please provide one or more input files as arguments" -- PARTIAL:
fs -> do fs -> do