refactor journalModifyTransactions, modifyTransactions

API changes:

Hledger.Data.TransactionModifier
-transactionModifierToFunction
+modifyTransactions

Hledger.Read.Common.applyTransactionModifiers -> Hledger.Data.Journal.journalModifyTransactions
This commit is contained in:
Simon Michael 2019-02-01 11:31:04 -08:00
parent 4a9fa5cd38
commit d6e075dacd
5 changed files with 19 additions and 17 deletions

View File

@ -69,6 +69,7 @@ module Hledger.Data.Journal (
journalCheckBalanceAssertions, journalCheckBalanceAssertions,
journalNumberAndTieTransactions, journalNumberAndTieTransactions,
journalUntieTransactions, journalUntieTransactions,
journalModifyTransactions,
-- * Tests -- * Tests
samplejournal, samplejournal,
tests_Journal, tests_Journal,
@ -107,6 +108,7 @@ import Hledger.Data.AccountName
import Hledger.Data.Amount import Hledger.Data.Amount
import Hledger.Data.Dates import Hledger.Data.Dates
import Hledger.Data.Transaction import Hledger.Data.Transaction
import Hledger.Data.TransactionModifier
import Hledger.Data.Posting import Hledger.Data.Posting
import Hledger.Query import Hledger.Query
@ -557,6 +559,11 @@ journalTieTransactions j@Journal{jtxns=ts} = j{jtxns=map txnTieKnot ts}
journalUntieTransactions :: Transaction -> Transaction journalUntieTransactions :: Transaction -> Transaction
journalUntieTransactions t@Transaction{tpostings=ps} = t{tpostings=map (\p -> p{ptransaction=Nothing}) ps} journalUntieTransactions t@Transaction{tpostings=ps} = t{tpostings=map (\p -> p{ptransaction=Nothing}) ps}
-- | Apply any transaction modifier rules in the journal
-- (adding automated postings to transactions, eg).
journalModifyTransactions :: Journal -> Journal
journalModifyTransactions j = j{ jtxns = modifyTransactions (jtxnmodifiers j) (jtxns j) }
-- | Check any balance assertions in the journal and return an error -- | Check any balance assertions in the journal and return an error
-- message if any of them fail. -- message if any of them fail.
journalCheckBalanceAssertions :: Journal -> Either String Journal journalCheckBalanceAssertions :: Journal -> Either String Journal

View File

@ -8,7 +8,7 @@ typically adding automated postings to them.
-} -}
module Hledger.Data.TransactionModifier ( module Hledger.Data.TransactionModifier (
transactionModifierToFunction modifyTransactions
) )
where where
@ -32,6 +32,12 @@ import Hledger.Utils.Debug
-- >>> import Hledger.Data.Transaction -- >>> import Hledger.Data.Transaction
-- >>> import Hledger.Data.Journal -- >>> import Hledger.Data.Journal
-- | Apply all the given transaction modifiers, in turn, to each transaction.
modifyTransactions :: [TransactionModifier] -> [Transaction] -> [Transaction]
modifyTransactions tmods ts = map applymods ts
where
applymods = foldr (flip (.) . transactionModifierToFunction) id tmods
-- | Converts a 'TransactionModifier' to a 'Transaction'-transforming function, -- | Converts a 'TransactionModifier' to a 'Transaction'-transforming function,
-- which applies the modification(s) specified by the TransactionModifier. -- which applies the modification(s) specified by the TransactionModifier.
-- Currently this means adding automated postings when certain other postings are present. -- Currently this means adding automated postings when certain other postings are present.

View File

@ -33,7 +33,6 @@ module Hledger.Read.Common (
rejp, rejp,
genericSourcePos, genericSourcePos,
journalSourcePos, journalSourcePos,
applyTransactionModifiers,
parseAndFinaliseJournal, parseAndFinaliseJournal,
parseAndFinaliseJournal', parseAndFinaliseJournal',
setYear, setYear,
@ -228,14 +227,6 @@ journalSourcePos p p' = JournalSourcePos (sourceName p) (fromIntegral . unPos $
| otherwise = unPos $ sourceLine p' -- might be at end of file withat last new-line | otherwise = unPos $ sourceLine p' -- might be at end of file withat last new-line
-- | Apply any transaction modifier rules in the journal
-- (adding automated postings to transactions, eg).
applyTransactionModifiers :: Journal -> Journal
applyTransactionModifiers j = j { jtxns = map applyallmodifiers $ jtxns j }
where
applyallmodifiers =
foldr (flip (.) . transactionModifierToFunction) id (jtxnmodifiers j)
-- | Given a megaparsec ParsedJournal parser, input options, file -- | Given a megaparsec ParsedJournal parser, input options, file
-- path and file content: parse and post-process a Journal, or give an error. -- path and file content: parse and post-process a Journal, or give an error.
parseAndFinaliseJournal :: ErroringJournalParser IO ParsedJournal -> InputOpts parseAndFinaliseJournal :: ErroringJournalParser IO ParsedJournal -> InputOpts
@ -267,7 +258,7 @@ parseAndFinaliseJournal parser iopts f txt = do
-- with transaction modifiers -- with transaction modifiers
then then
-- first pass -- first pass
applyTransactionModifiers <$> journalModifyTransactions <$>
(journalBalanceTransactions False $ (journalBalanceTransactions False $
journalReverse $ journalReverse $
journalAddFile (f, txt) $ journalAddFile (f, txt) $
@ -312,7 +303,7 @@ parseAndFinaliseJournal' parser iopts f txt = do
-- time. If we are only running once, we reorder and follow the -- time. If we are only running once, we reorder and follow the
-- options for checking assertions. -- options for checking assertions.
let fj = if auto_ iopts && (not . null . jtxnmodifiers) pj let fj = if auto_ iopts && (not . null . jtxnmodifiers) pj
then applyTransactionModifiers <$> then journalModifyTransactions <$>
(journalBalanceTransactions False $ (journalBalanceTransactions False $
journalReverse $ journalReverse $
journalApplyCommodityStyles pj) >>= journalApplyCommodityStyles pj) >>=

View File

@ -37,11 +37,9 @@ rewritemode = hledgerCommandMode
-- TODO allow using this on unbalanced entries, eg to rewrite while editing -- TODO allow using this on unbalanced entries, eg to rewrite while editing
rewrite opts@CliOpts{rawopts_=rawopts,reportopts_=ropts} j@Journal{jtxns=ts} = do rewrite opts@CliOpts{rawopts_=rawopts,reportopts_=ropts} j@Journal{jtxns=ts} = do
-- create re-writer
let modifiers = transactionModifierFromOpts opts : jtxnmodifiers j
applyallmodifiers = foldr (flip (.) . transactionModifierToFunction) id modifiers
-- rewrite matched transactions -- rewrite matched transactions
let j' = j{jtxns=map applyallmodifiers ts} let modifiers = transactionModifierFromOpts opts : jtxnmodifiers j
let j' = j{jtxns=modifyTransactions modifiers ts}
-- run the print command, showing all transactions, or show diffs -- run the print command, showing all transactions, or show diffs
printOrDiff rawopts opts{reportopts_=ropts{query_=""}} j j' printOrDiff rawopts opts{reportopts_=ropts{query_=""}} j j'

View File

@ -154,7 +154,7 @@ journalAddForecast opts@CliOpts{reportopts_=ropts} j = do
let forecastspan = DateSpan (Just forecaststart) (Just forecastend) let forecastspan = DateSpan (Just forecaststart) (Just forecastend)
forecasttxns = forecasttxns =
-- If there are forecast transaction, lets apply transaction modifiers to them -- If there are forecast transaction, lets apply transaction modifiers to them
map (foldr (flip (.) . transactionModifierToFunction) id (jtxnmodifiers j)) $ modifyTransactions (jtxnmodifiers j) $
[ txnTieKnot t | pt <- jperiodictxns j [ txnTieKnot t | pt <- jperiodictxns j
, t <- runPeriodicTransaction pt forecastspan , t <- runPeriodicTransaction pt forecastspan
, spanContainsDate forecastspan (tdate t) , spanContainsDate forecastspan (tdate t)