lib: simpler, more consistent names for check functions
API changes: journalCheckAccountsDeclared journalCheckCommoditiesDeclared journalCheckPayeesDeclared -> journalCheckAccounts journalCheckCommodities journalCheckPayees
This commit is contained in:
		
							parent
							
								
									65e913b7c5
								
							
						
					
					
						commit
						307f723b0a
					
				| @ -8,9 +8,9 @@ others can be called only via the check command. | |||||||
| {-# LANGUAGE NamedFieldPuns #-} | {-# LANGUAGE NamedFieldPuns #-} | ||||||
| 
 | 
 | ||||||
| module Hledger.Read.Checks ( | module Hledger.Read.Checks ( | ||||||
|   journalCheckAccountsDeclared, |   journalCheckAccounts, | ||||||
|   journalCheckCommoditiesDeclared, |   journalCheckCommodities, | ||||||
|   journalCheckPayeesDeclared, |   journalCheckPayees, | ||||||
|   module Hledger.Read.Checks.Ordereddates, |   module Hledger.Read.Checks.Ordereddates, | ||||||
|   module Hledger.Read.Checks.Uniqueleafnames, |   module Hledger.Read.Checks.Uniqueleafnames, | ||||||
| ) | ) | ||||||
| @ -29,10 +29,10 @@ import Hledger.Read.Checks.Ordereddates | |||||||
| import Hledger.Read.Checks.Uniqueleafnames | import Hledger.Read.Checks.Uniqueleafnames | ||||||
| import Hledger.Read.Error | import Hledger.Read.Error | ||||||
| 
 | 
 | ||||||
| -- | Check that all the journal's postings are to accounts declared with | -- | Check that all the journal's postings are to accounts  with | ||||||
| -- account directives, returning an error message otherwise. | -- account directives, returning an error message otherwise. | ||||||
| journalCheckAccountsDeclared :: Journal -> Either String () | journalCheckAccounts :: Journal -> Either String () | ||||||
| journalCheckAccountsDeclared j = mapM_ checkacct (journalPostings j) | journalCheckAccounts j = mapM_ checkacct (journalPostings j) | ||||||
|   where |   where | ||||||
|     checkacct p@Posting{paccount=a} |     checkacct p@Posting{paccount=a} | ||||||
|       | a `elem` journalAccountNamesDeclared j = Right () |       | a `elem` journalAccountNamesDeclared j = Right () | ||||||
| @ -49,8 +49,8 @@ journalCheckAccountsDeclared j = mapM_ checkacct (journalPostings j) | |||||||
| 
 | 
 | ||||||
| -- | Check that all the commodities used in this journal's postings have been declared | -- | Check that all the commodities used in this journal's postings have been declared | ||||||
| -- by commodity directives, returning an error message otherwise. | -- by commodity directives, returning an error message otherwise. | ||||||
| journalCheckCommoditiesDeclared :: Journal -> Either String () | journalCheckCommodities :: Journal -> Either String () | ||||||
| journalCheckCommoditiesDeclared j = mapM_ checkcommodities (journalPostings j) | journalCheckCommodities j = mapM_ checkcommodities (journalPostings j) | ||||||
|   where |   where | ||||||
|     checkcommodities p = |     checkcommodities p = | ||||||
|       case findundeclaredcomm p of |       case findundeclaredcomm p of | ||||||
| @ -109,8 +109,8 @@ journalCheckCommoditiesDeclared j = mapM_ checkcommodities (journalPostings j) | |||||||
| 
 | 
 | ||||||
| -- | Check that all the journal's transactions have payees declared with | -- | Check that all the journal's transactions have payees declared with | ||||||
| -- payee directives, returning an error message otherwise. | -- payee directives, returning an error message otherwise. | ||||||
| journalCheckPayeesDeclared :: Journal -> Either String () | journalCheckPayees :: Journal -> Either String () | ||||||
| journalCheckPayeesDeclared j = mapM_ checkpayee (jtxns j) | journalCheckPayees j = mapM_ checkpayee (jtxns j) | ||||||
|   where |   where | ||||||
|     checkpayee t |     checkpayee t | ||||||
|       | payee `elem` journalPayeesDeclared j = Right () |       | payee `elem` journalPayeesDeclared j = Right () | ||||||
|  | |||||||
| @ -148,7 +148,7 @@ import Hledger.Query (Query(..), filterQuery, parseQueryTerm, queryEndDate, quer | |||||||
| import Hledger.Reports.ReportOptions (ReportOpts(..), queryFromFlags, rawOptsToReportOpts) | import Hledger.Reports.ReportOptions (ReportOpts(..), queryFromFlags, rawOptsToReportOpts) | ||||||
| import Hledger.Utils | import Hledger.Utils | ||||||
| import Hledger.Read.InputOptions | import Hledger.Read.InputOptions | ||||||
| import Hledger.Read.Checks (journalCheckAccountsDeclared, journalCheckCommoditiesDeclared) | import Hledger.Read.Checks (journalCheckAccounts, journalCheckCommodities) | ||||||
| 
 | 
 | ||||||
| --- ** doctest setup | --- ** doctest setup | ||||||
| -- $setup | -- $setup | ||||||
| @ -324,8 +324,8 @@ journalFinalise iopts@InputOpts{auto_,infer_equity_,balancingopts_,strict_,_ioDa | |||||||
|       <&> (if infer_equity_ then journalAddInferredEquityPostings else id)  -- Add inferred equity postings, after balancing transactions and generating auto postings |       <&> (if infer_equity_ then journalAddInferredEquityPostings else id)  -- Add inferred equity postings, after balancing transactions and generating auto postings | ||||||
|       <&> journalInferMarketPricesFromTransactions       -- infer market prices from commodity-exchanging transactions |       <&> journalInferMarketPricesFromTransactions       -- infer market prices from commodity-exchanging transactions | ||||||
|     when strict_ $ do |     when strict_ $ do | ||||||
|       journalCheckAccountsDeclared j                     -- If in strict mode, check all postings are to declared accounts |       journalCheckAccounts j                     -- If in strict mode, check all postings are to declared accounts | ||||||
|       journalCheckCommoditiesDeclared j                  -- and using declared commodities |       journalCheckCommodities j                  -- and using declared commodities | ||||||
|     return j |     return j | ||||||
| 
 | 
 | ||||||
| -- | Apply any auto posting rules to generate extra postings on this journal's transactions. | -- | Apply any auto posting rules to generate extra postings on this journal's transactions. | ||||||
|  | |||||||
| @ -98,10 +98,10 @@ runCheck :: CliOpts -> Journal -> (Check,[String]) -> IO () | |||||||
| runCheck CliOpts{reportspec_=ReportSpec{_rsReportOpts=ropts}} j (check,_) = do | runCheck CliOpts{reportspec_=ReportSpec{_rsReportOpts=ropts}} j (check,_) = do | ||||||
|   let |   let | ||||||
|     results = case check of |     results = case check of | ||||||
|       Accounts        -> journalCheckAccountsDeclared j |       Accounts        -> journalCheckAccounts j | ||||||
|       Commodities     -> journalCheckCommoditiesDeclared j |       Commodities     -> journalCheckCommodities j | ||||||
|       Ordereddates    -> journalCheckOrdereddates (whichDate ropts) j |       Ordereddates    -> journalCheckOrdereddates (whichDate ropts) j | ||||||
|       Payees          -> journalCheckPayeesDeclared j |       Payees          -> journalCheckPayees j | ||||||
|       Uniqueleafnames -> journalCheckUniqueleafnames j |       Uniqueleafnames -> journalCheckUniqueleafnames j | ||||||
|       -- the other checks have been done earlier during withJournalDo |       -- the other checks have been done earlier during withJournalDo | ||||||
|       _               -> Right () |       _               -> Right () | ||||||
|  | |||||||
		Loading…
	
		Reference in New Issue
	
	Block a user