module Hledger.Data.AutoTransaction
(
runModifierTransaction
, runPeriodicTransaction
, mtvaluequery
, jdatespan
)
where
import Data.Maybe
import Data.Monoid ((<>))
import Data.Time.Calendar
import qualified Data.Text as T
import Hledger.Data.Types
import Hledger.Data.Dates
import Hledger.Data.Amount
import Hledger.Data.Transaction
import Hledger.Utils.Parse
import Hledger.Utils.UTF8IOCompat (error')
import Hledger.Query
runModifierTransaction :: Query -> ModifierTransaction -> (Transaction -> Transaction)
runModifierTransaction q mt = modifier where
q' = simplifyQuery $ And [q, mtvaluequery mt (error "query cannot depend on current time")]
mods = map runModifierPosting $ mtpostings mt
generatePostings ps = [m p | p <- ps, q' `matchesPosting` p, m <- mods]
modifier t@(tpostings -> ps) = t { tpostings = ps ++ generatePostings ps }
mtvaluequery :: ModifierTransaction -> (Day -> Query)
mtvaluequery mt = fst . flip parseQuery (mtvalueexpr mt)
jdatespan :: Journal -> DateSpan
jdatespan j
| null dates = nulldatespan
| otherwise = DateSpan (Just $ minimum dates) (Just $ 1 `addDays` maximum dates)
where
dates = concatMap tdates $ jtxns j
tdates :: Transaction -> [Day]
tdates t = tdate t : concatMap pdates (tpostings t) ++ maybeToList (tdate2 t) where
pdates p = catMaybes [pdate p, pdate2 p]
postingScale :: Posting -> Maybe Quantity
postingScale p =
case amounts $ pamount p of
[a] | amultiplier a -> Just $ aquantity a
_ -> Nothing
runModifierPosting :: Posting -> (Posting -> Posting)
runModifierPosting p' = modifier where
modifier p = renderPostingCommentDates $ p'
{ pdate = pdate p
, pdate2 = pdate2 p
, pamount = amount' p
}
amount' = case postingScale p' of
Nothing -> const $ pamount p'
Just n -> \p -> withAmountType (head $ amounts $ pamount p') $ pamount p `divideMixedAmount` (1/n)
withAmountType amount (Mixed as) = case acommodity amount of
"" -> Mixed as
c -> Mixed [a{acommodity = c, astyle = astyle amount, aprice = aprice amount} | a <- as]
renderPostingCommentDates :: Posting -> Posting
renderPostingCommentDates p = p { pcomment = comment' }
where
datesComment = T.concat $ catMaybes [T.pack . showDate <$> pdate p, ("=" <>) . T.pack . showDate <$> pdate2 p]
comment'
| T.null datesComment = pcomment p
| otherwise = T.intercalate "\n" $ filter (not . T.null) [T.strip $ pcomment p, "[" <> datesComment <> "]"]
runPeriodicTransaction :: PeriodicTransaction -> (DateSpan -> [Transaction])
runPeriodicTransaction pt = generate where
base = nulltransaction { tpostings = ptpostings pt }
periodExpr = ptperiodicexpr pt
errCurrent = error' $ "Current date cannot be referenced in " ++ show (T.unpack periodExpr)
(interval, effectspan) =
case parsePeriodExpr errCurrent periodExpr of
Left e -> error' $ "Failed to parse " ++ show (T.unpack periodExpr) ++ ": " ++ showDateParseError e
Right x -> x
generate jspan = [base {tdate=date} | span <- interval `splitSpan` spanIntersect effectspan jspan, let Just date = spanStart span]