2023-01-28 19:32:56 -05:00
|
|
|
module Internal.Utils
|
|
|
|
( compareDate
|
2023-05-29 15:56:15 -04:00
|
|
|
, expandDatePat
|
|
|
|
, askDays
|
2023-05-14 19:20:10 -04:00
|
|
|
, fromWeekday
|
2023-05-29 15:56:15 -04:00
|
|
|
, inDaySpan
|
2023-01-28 19:32:56 -05:00
|
|
|
, fromGregorian'
|
2023-05-29 15:56:15 -04:00
|
|
|
, resolveDaySpan
|
|
|
|
, resolveDaySpan_
|
|
|
|
, intersectDaySpan
|
2023-07-16 19:55:33 -04:00
|
|
|
, throwAppError
|
2023-05-07 20:29:33 -04:00
|
|
|
, liftInner
|
|
|
|
, liftExceptT
|
|
|
|
, liftExcept
|
|
|
|
, liftIOExcept
|
|
|
|
, liftIOExceptT
|
|
|
|
, combineError
|
|
|
|
, combineError_
|
|
|
|
, combineError3
|
|
|
|
, combineErrors
|
|
|
|
, mapErrors
|
|
|
|
, combineErrorM
|
|
|
|
, combineErrorM3
|
|
|
|
, combineErrorIO2
|
|
|
|
, combineErrorIO3
|
|
|
|
, combineErrorIOM2
|
|
|
|
, combineErrorIOM3
|
|
|
|
, collectErrorsIO
|
|
|
|
, mapErrorsIO
|
2023-07-09 00:16:57 -04:00
|
|
|
, mapErrorsPooledIO
|
2023-01-28 19:32:56 -05:00
|
|
|
, showError
|
2023-01-28 22:55:07 -05:00
|
|
|
, lookupErr
|
2023-04-16 20:09:13 -04:00
|
|
|
, uncurry3
|
2023-02-13 19:57:39 -05:00
|
|
|
, dateMatches
|
|
|
|
, valMatches
|
2023-06-24 17:32:43 -04:00
|
|
|
, lookupAccount
|
2023-05-29 15:56:15 -04:00
|
|
|
, lookupAccountKey
|
|
|
|
, lookupAccountType
|
2023-06-24 17:32:43 -04:00
|
|
|
, lookupCurrency
|
2023-05-29 15:56:15 -04:00
|
|
|
, lookupCurrencyKey
|
|
|
|
, lookupCurrencyPrec
|
|
|
|
, lookupTag
|
2023-06-13 20:12:29 -04:00
|
|
|
, mapAdd_
|
2023-06-25 14:26:35 -04:00
|
|
|
, groupKey
|
|
|
|
, groupWith
|
2023-07-01 18:58:15 -04:00
|
|
|
, balanceTxs
|
|
|
|
, expandTransfers
|
|
|
|
, expandTransfer
|
|
|
|
, entryPair
|
2023-07-04 00:11:25 -04:00
|
|
|
, singleQuote
|
|
|
|
, keyVals
|
2023-07-16 19:55:33 -04:00
|
|
|
, realFracToDecimalP
|
2023-07-16 00:20:01 -04:00
|
|
|
, roundToP
|
2023-08-13 13:29:38 -04:00
|
|
|
, compileRegex
|
|
|
|
, matchMaybe
|
|
|
|
, matchGroupsMaybe
|
2023-01-28 19:32:56 -05:00
|
|
|
)
|
|
|
|
where
|
2022-12-11 17:51:11 -05:00
|
|
|
|
2023-05-07 20:29:33 -04:00
|
|
|
import Control.Monad.Error.Class
|
|
|
|
import Control.Monad.Except
|
2023-07-08 00:52:40 -04:00
|
|
|
import Data.Decimal
|
2023-01-25 20:52:27 -05:00
|
|
|
import Data.Time.Format.ISO8601
|
2023-07-16 19:55:33 -04:00
|
|
|
import qualified Database.Esqueleto.Experimental as E
|
2023-01-05 22:16:06 -05:00
|
|
|
import GHC.Real
|
2023-05-29 14:46:30 -04:00
|
|
|
import Internal.Types.Main
|
2023-01-05 22:16:06 -05:00
|
|
|
import RIO
|
2023-01-25 20:52:27 -05:00
|
|
|
import qualified RIO.List as L
|
2023-01-05 22:16:06 -05:00
|
|
|
import qualified RIO.Map as M
|
2023-02-25 22:56:23 -05:00
|
|
|
import qualified RIO.NonEmpty as NE
|
2023-07-01 18:58:15 -04:00
|
|
|
import RIO.State
|
2023-01-05 22:16:06 -05:00
|
|
|
import qualified RIO.Text as T
|
|
|
|
import RIO.Time
|
2023-07-01 18:58:15 -04:00
|
|
|
import qualified RIO.Vector as V
|
2023-08-13 13:29:38 -04:00
|
|
|
import Text.Regex.TDFA hiding (matchAll)
|
|
|
|
import Text.Regex.TDFA.Text
|
2022-12-11 17:51:11 -05:00
|
|
|
|
2023-05-29 15:56:15 -04:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- intervals
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
expandDatePat :: DaySpan -> DatePat -> AppExcept [Day]
|
2023-05-29 15:56:15 -04:00
|
|
|
expandDatePat b (Cron cp) = expandCronPat b cp
|
|
|
|
expandDatePat i (Mod mp) = return $ expandModPat mp i
|
|
|
|
|
|
|
|
expandModPat :: ModPat -> DaySpan -> [Day]
|
|
|
|
expandModPat ModPat {mpStart = s, mpBy = b, mpUnit = u, mpRepeats = r} bs =
|
|
|
|
takeWhile (<= upper) $
|
|
|
|
(`addFun` start) . (* b')
|
|
|
|
<$> maybe id (take . fromIntegral) r [0 ..]
|
|
|
|
where
|
|
|
|
(lower, upper) = fromDaySpan bs
|
|
|
|
start = maybe lower fromGregorian' s
|
|
|
|
b' = fromIntegral b
|
|
|
|
addFun = case u of
|
|
|
|
Day -> addDays
|
|
|
|
Week -> addDays . (* 7)
|
|
|
|
Month -> addGregorianMonthsClip
|
|
|
|
Year -> addGregorianYearsClip
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
expandCronPat :: DaySpan -> CronPat -> AppExcept [Day]
|
2023-05-29 15:56:15 -04:00
|
|
|
expandCronPat b CronPat {cpYear, cpMonth, cpDay, cpWeekly} =
|
|
|
|
combineError3 yRes mRes dRes $ \ys ms ds ->
|
|
|
|
filter validWeekday $
|
|
|
|
mapMaybe (uncurry3 toDay) $
|
|
|
|
takeWhile (\((y, _), m, d) -> (y, m, d) <= (yb1, mb1, db1)) $
|
|
|
|
dropWhile (\((y, _), m, d) -> (y, m, d) < (yb0, mb0, db0)) $
|
|
|
|
[(y, m, d) | y <- (\y -> (y, isLeapYear y)) <$> ys, m <- ms, d <- ds]
|
|
|
|
where
|
|
|
|
yRes = case cpYear of
|
|
|
|
Nothing -> return [yb0 .. yb1]
|
|
|
|
Just pat -> do
|
|
|
|
ys <- expandMDYPat (fromIntegral yb0) (fromIntegral yb1) pat
|
|
|
|
return $ dropWhile (< yb0) $ fromIntegral <$> ys
|
|
|
|
mRes = expandMD 12 cpMonth
|
|
|
|
dRes = expandMD 31 cpDay
|
|
|
|
(s, e) = fromDaySpan b
|
|
|
|
(yb0, mb0, db0) = toGregorian s
|
|
|
|
(yb1, mb1, db1) = toGregorian $ addDays (-1) e
|
|
|
|
expandMD lim =
|
|
|
|
fmap (fromIntegral <$>)
|
|
|
|
. maybe (return [1 .. lim]) (expandMDYPat 1 lim)
|
|
|
|
expandW (OnDay x) = [fromEnum x]
|
|
|
|
expandW (OnDays xs) = fromEnum <$> xs
|
|
|
|
ws = maybe [] expandW cpWeekly
|
|
|
|
validWeekday = if null ws then const True else \day -> dayToWeekday day `elem` ws
|
|
|
|
toDay (y, leap) m d
|
|
|
|
| m == 2 && (not leap && d > 28 || leap && d > 29) = Nothing
|
|
|
|
| m `elem` [4, 6, 9, 11] && d > 30 = Nothing
|
|
|
|
| otherwise = Just $ fromGregorian y m d
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
expandMDYPat :: Natural -> Natural -> MDYPat -> AppExcept [Natural]
|
2023-05-29 15:56:15 -04:00
|
|
|
expandMDYPat lower upper (Single x) = return [x | lower <= x && x <= upper]
|
|
|
|
expandMDYPat lower upper (Multi xs) = return $ dropWhile (<= lower) $ takeWhile (<= upper) xs
|
|
|
|
expandMDYPat lower upper (After x) = return [max lower x .. upper]
|
|
|
|
expandMDYPat lower upper (Before x) = return [lower .. min upper x]
|
|
|
|
expandMDYPat lower upper (Between x y) = return [max lower x .. min upper y]
|
|
|
|
expandMDYPat lower upper (Repeat RepeatPat {rpStart = s, rpBy = b, rpRepeats = r})
|
2023-07-16 19:55:33 -04:00
|
|
|
| b < 1 = throwAppError $ DatePatternError s b r ZeroLength
|
2023-05-29 15:56:15 -04:00
|
|
|
| otherwise = do
|
|
|
|
k <- limit r
|
|
|
|
return $ dropWhile (<= lower) $ takeWhile (<= k) [s + i * b | i <- [0 ..]]
|
|
|
|
where
|
|
|
|
limit Nothing = return upper
|
|
|
|
limit (Just n)
|
|
|
|
-- this guard not only produces the error for the user but also protects
|
|
|
|
-- from an underflow below it
|
2023-07-16 19:55:33 -04:00
|
|
|
| n < 1 = throwAppError $ DatePatternError s b r ZeroRepeats
|
2023-05-29 15:56:15 -04:00
|
|
|
| otherwise = return $ min (s + b * (n - 1)) upper
|
|
|
|
|
|
|
|
dayToWeekday :: Day -> Int
|
|
|
|
dayToWeekday (ModifiedJulianDay d) = mod (fromIntegral d + 2) 7
|
|
|
|
|
|
|
|
askDays
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadFinance m, MonadAppError m)
|
2023-05-29 15:56:15 -04:00
|
|
|
=> DatePat
|
|
|
|
-> Maybe Interval
|
|
|
|
-> m [Day]
|
|
|
|
askDays dp i = do
|
2023-07-20 00:25:33 -04:00
|
|
|
globalSpan <- asks (unBSpan . tsBudgetScope)
|
2023-05-29 15:56:15 -04:00
|
|
|
case i of
|
|
|
|
Just i' -> do
|
|
|
|
localSpan <- liftExcept $ resolveDaySpan i'
|
|
|
|
maybe (return []) expand $ intersectDaySpan globalSpan localSpan
|
|
|
|
Nothing -> expand globalSpan
|
|
|
|
where
|
|
|
|
expand = liftExcept . (`expandDatePat` dp)
|
|
|
|
|
2023-01-27 23:33:34 -05:00
|
|
|
--------------------------------------------------------------------------------
|
2023-01-28 19:32:56 -05:00
|
|
|
-- dates
|
|
|
|
|
2023-05-14 19:20:10 -04:00
|
|
|
-- | Lame weekday converter since day of weeks aren't in dhall (yet)
|
|
|
|
fromWeekday :: Weekday -> DayOfWeek
|
|
|
|
fromWeekday Mon = Monday
|
|
|
|
fromWeekday Tue = Tuesday
|
|
|
|
fromWeekday Wed = Wednesday
|
|
|
|
fromWeekday Thu = Thursday
|
|
|
|
fromWeekday Fri = Friday
|
|
|
|
fromWeekday Sat = Saturday
|
|
|
|
fromWeekday Sun = Sunday
|
|
|
|
|
2023-01-28 19:32:56 -05:00
|
|
|
gregTup :: Gregorian -> (Integer, Int, Int)
|
2023-02-12 16:23:32 -05:00
|
|
|
gregTup Gregorian {gYear, gMonth, gDay} =
|
2023-01-28 19:32:56 -05:00
|
|
|
( fromIntegral gYear
|
|
|
|
, fromIntegral gMonth
|
|
|
|
, fromIntegral gDay
|
|
|
|
)
|
|
|
|
|
|
|
|
gregMTup :: GregorianM -> (Integer, Int)
|
2023-02-12 16:23:32 -05:00
|
|
|
gregMTup GregorianM {gmYear, gmMonth} =
|
2023-01-28 19:32:56 -05:00
|
|
|
( fromIntegral gmYear
|
|
|
|
, fromIntegral gmMonth
|
|
|
|
)
|
|
|
|
|
2023-01-30 22:57:42 -05:00
|
|
|
data YMD_ = Y_ !Integer | YM_ !Integer !Int | YMD_ !Integer !Int !Int
|
2023-01-28 19:32:56 -05:00
|
|
|
|
2023-04-30 00:16:06 -04:00
|
|
|
fromYMDMatcher :: YMDMatcher -> YMD_
|
|
|
|
fromYMDMatcher m = case m of
|
2023-01-28 19:32:56 -05:00
|
|
|
Y y -> Y_ $ fromIntegral y
|
|
|
|
YM g -> uncurry YM_ $ gregMTup g
|
|
|
|
YMD g -> uncurry3 YMD_ $ gregTup g
|
|
|
|
|
2023-04-30 00:16:06 -04:00
|
|
|
compareDate :: DateMatcher -> Day -> Ordering
|
2023-01-28 19:32:56 -05:00
|
|
|
compareDate (On md) x =
|
2023-04-30 00:16:06 -04:00
|
|
|
case fromYMDMatcher md of
|
2023-01-25 23:04:54 -05:00
|
|
|
Y_ y' -> compare y y'
|
|
|
|
YM_ y' m' -> compare (y, m) (y', m')
|
|
|
|
YMD_ y' m' d' -> compare (y, m, d) (y', m', d')
|
2022-12-11 17:51:11 -05:00
|
|
|
where
|
2022-12-19 23:13:05 -05:00
|
|
|
(y, m, d) = toGregorian x
|
2023-01-25 23:04:54 -05:00
|
|
|
compareDate (In md offset) x = do
|
2023-04-30 00:16:06 -04:00
|
|
|
case fromYMDMatcher md of
|
2023-01-25 23:04:54 -05:00
|
|
|
Y_ y' -> compareRange y' y
|
|
|
|
YM_ y' m' -> compareRange (toMonth y' m') $ toMonth y m
|
|
|
|
YMD_ y' m' d' ->
|
|
|
|
let s = toModifiedJulianDay $ fromGregorian y' m' d'
|
|
|
|
in compareRange s $ toModifiedJulianDay x
|
2022-12-11 17:51:11 -05:00
|
|
|
where
|
2022-12-19 23:13:05 -05:00
|
|
|
(y, m, _) = toGregorian x
|
|
|
|
compareRange start z
|
2022-12-11 17:51:11 -05:00
|
|
|
| z < start = LT
|
2022-12-22 20:13:03 -05:00
|
|
|
| otherwise = if (start + fromIntegral offset - 1) < z then GT else EQ
|
2022-12-19 23:13:05 -05:00
|
|
|
toMonth year month = (year * 12) + fromIntegral month
|
2022-12-11 17:51:11 -05:00
|
|
|
|
2023-01-28 19:32:56 -05:00
|
|
|
fromGregorian' :: Gregorian -> Day
|
|
|
|
fromGregorian' = uncurry3 fromGregorian . gregTup
|
2022-12-11 17:51:11 -05:00
|
|
|
|
2023-05-29 15:56:15 -04:00
|
|
|
inDaySpan :: DaySpan -> Day -> Bool
|
|
|
|
inDaySpan bs = withinDays (fromDaySpan bs)
|
2023-05-29 13:09:17 -04:00
|
|
|
|
|
|
|
withinDays :: (Day, Day) -> Day -> Bool
|
|
|
|
withinDays (d0, d1) x = d0 <= x && x < d1
|
2023-02-05 10:34:26 -05:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
resolveDaySpan :: Interval -> AppExcept DaySpan
|
2023-05-29 15:56:15 -04:00
|
|
|
resolveDaySpan i@Interval {intStart = s} =
|
|
|
|
resolveDaySpan_ (s {gYear = gYear s + 50}) i
|
2023-03-16 23:53:57 -04:00
|
|
|
|
2023-05-29 15:56:15 -04:00
|
|
|
intersectDaySpan :: DaySpan -> DaySpan -> Maybe DaySpan
|
|
|
|
intersectDaySpan a b =
|
|
|
|
if b' > a' then Nothing else Just $ toDaySpan (a', b')
|
2023-05-29 13:09:17 -04:00
|
|
|
where
|
2023-05-29 15:56:15 -04:00
|
|
|
(a0, a1) = fromDaySpan a
|
|
|
|
(b0, b1) = fromDaySpan b
|
2023-05-29 13:09:17 -04:00
|
|
|
a' = max a0 a1
|
|
|
|
b' = min b0 b1
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
resolveDaySpan_ :: Gregorian -> Interval -> AppExcept DaySpan
|
2023-05-29 15:56:15 -04:00
|
|
|
resolveDaySpan_ def Interval {intStart = s, intEnd = e} =
|
2023-07-01 18:32:20 -04:00
|
|
|
-- TODO the default isn't checked here :/
|
2023-02-05 10:34:26 -05:00
|
|
|
case fromGregorian' <$> e of
|
2023-05-29 15:56:15 -04:00
|
|
|
Nothing -> return $ toDaySpan_ $ fromGregorian' def
|
2023-02-05 10:34:26 -05:00
|
|
|
Just e_
|
2023-05-29 15:56:15 -04:00
|
|
|
| s_ < e_ -> return $ toDaySpan_ e_
|
2023-07-16 19:55:33 -04:00
|
|
|
| otherwise -> throwAppError $ DaySpanError s e
|
2023-01-27 23:33:34 -05:00
|
|
|
where
|
2023-02-05 10:34:26 -05:00
|
|
|
s_ = fromGregorian' s
|
2023-05-29 15:56:15 -04:00
|
|
|
toDaySpan_ end = toDaySpan (s_, end)
|
|
|
|
|
|
|
|
fromDaySpan :: DaySpan -> (Day, Day)
|
|
|
|
fromDaySpan (d, n) = (d, addDays (fromIntegral n + 1) d)
|
2023-02-05 10:34:26 -05:00
|
|
|
|
2023-05-29 15:56:15 -04:00
|
|
|
-- ASSUME a < b
|
|
|
|
toDaySpan :: (Day, Day) -> DaySpan
|
|
|
|
toDaySpan (a, b) = (a, fromIntegral $ diffDays b a - 1)
|
2023-01-27 23:33:34 -05:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- matching
|
2022-12-11 17:51:11 -05:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
valMatches :: ValMatcher -> Rational -> AppExcept Bool
|
2023-04-30 23:28:16 -04:00
|
|
|
valMatches ValMatcher {vmDen, vmSign, vmNum, vmPrec} x
|
2023-07-16 19:55:33 -04:00
|
|
|
| Just d_ <- vmDen, d_ >= p = throwAppError $ MatchValPrecisionError d_ p
|
2023-01-28 20:03:58 -05:00
|
|
|
| otherwise =
|
2023-05-07 20:29:33 -04:00
|
|
|
return $
|
2023-04-30 23:28:16 -04:00
|
|
|
checkMaybe (s ==) vmSign
|
|
|
|
&& checkMaybe (n ==) vmNum
|
|
|
|
&& checkMaybe ((d * fromIntegral p ==) . fromIntegral) vmDen
|
2023-01-27 23:33:34 -05:00
|
|
|
where
|
|
|
|
(n, d) = properFraction $ abs x
|
2023-04-30 23:28:16 -04:00
|
|
|
p = 10 ^ vmPrec
|
2023-01-27 23:33:34 -05:00
|
|
|
s = signum x >= 0
|
|
|
|
checkMaybe = maybe True
|
|
|
|
|
2023-04-30 00:16:06 -04:00
|
|
|
dateMatches :: DateMatcher -> Day -> Bool
|
2023-01-28 19:32:56 -05:00
|
|
|
dateMatches md = (EQ ==) . compareDate md
|
2023-01-27 23:33:34 -05:00
|
|
|
|
2023-07-16 12:15:39 -04:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- error flow control
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
throwAppError :: MonadAppError m => AppError -> m a
|
|
|
|
throwAppError e = throwError $ AppException [e]
|
|
|
|
|
2023-05-07 20:29:33 -04:00
|
|
|
liftInner :: Monad m => ExceptT e Identity a -> ExceptT e m a
|
|
|
|
liftInner = mapExceptT (return . runIdentity)
|
|
|
|
|
|
|
|
liftExceptT :: MonadError e m => ExceptT e m a -> m a
|
|
|
|
liftExceptT x = runExceptT x >>= either throwError return
|
|
|
|
|
|
|
|
liftExcept :: MonadError e m => Except e a -> m a
|
|
|
|
liftExcept = either throwError return . runExcept
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
liftIOExceptT :: MonadIO m => AppExceptT m a -> m a
|
2023-05-07 20:29:33 -04:00
|
|
|
liftIOExceptT = fromEither <=< runExceptT
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
liftIOExcept :: MonadIO m => AppExcept a -> m a
|
2023-05-07 20:29:33 -04:00
|
|
|
liftIOExcept = fromEither . runExcept
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
combineError :: MonadAppError m => m a -> m b -> (a -> b -> c) -> m c
|
2023-05-07 20:29:33 -04:00
|
|
|
combineError a b f = combineErrorM a b (\x y -> pure $ f x y)
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
combineError_ :: MonadAppError m => m a -> m b -> m ()
|
2023-05-07 20:29:33 -04:00
|
|
|
combineError_ a b = do
|
|
|
|
_ <- catchError a $ \e ->
|
|
|
|
throwError =<< catchError (e <$ b) (return . (e <>))
|
|
|
|
_ <- b
|
|
|
|
return ()
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
combineErrorM :: MonadAppError m => m a -> m b -> (a -> b -> m c) -> m c
|
2023-05-07 20:29:33 -04:00
|
|
|
combineErrorM a b f = do
|
|
|
|
a' <- catchError a $ \e ->
|
|
|
|
throwError =<< catchError (e <$ b) (return . (e <>))
|
|
|
|
f a' =<< b
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
combineError3 :: MonadAppError m => m a -> m b -> m c -> (a -> b -> c -> d) -> m d
|
2023-05-07 20:29:33 -04:00
|
|
|
combineError3 a b c f =
|
|
|
|
combineError (combineError a b (,)) c $ \(x, y) z -> f x y z
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
combineErrorM3 :: MonadAppError m => m a -> m b -> m c -> (a -> b -> c -> m d) -> m d
|
2023-05-07 20:29:33 -04:00
|
|
|
combineErrorM3 a b c f = do
|
|
|
|
combineErrorM (combineErrorM a b (curry return)) c $ \(x, y) z -> f x y z
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
mapErrors :: (Traversable t, MonadAppError m) => (a -> m b) -> t a -> m (t b)
|
2023-06-16 22:05:28 -04:00
|
|
|
-- First, record number of each action. Then try each action. On first failure,
|
|
|
|
-- note it's position in the sequence, skip ahead to the untried actions,
|
|
|
|
-- collect failures and add to the first failure.
|
|
|
|
mapErrors f xs = mapM go $ enumTraversable xs
|
|
|
|
where
|
|
|
|
go (n, x) = catchError (f x) $ \e -> do
|
|
|
|
es <- fmap catMaybes $ mapM (err . f) $ drop (n + 1) $ toList xs
|
|
|
|
throwError $ foldr (<>) e es
|
|
|
|
err x = catchError (Nothing <$ x) (pure . Just)
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
combineErrors :: (Traversable t, MonadAppError m) => t (m a) -> m (t a)
|
2023-05-07 20:29:33 -04:00
|
|
|
combineErrors = mapErrors id
|
|
|
|
|
2023-06-16 22:05:28 -04:00
|
|
|
enumTraversable :: (Num n, Traversable t) => t a -> t (n, a)
|
|
|
|
enumTraversable = snd . L.mapAccumL go 0
|
2023-05-07 20:29:33 -04:00
|
|
|
where
|
2023-06-16 22:05:28 -04:00
|
|
|
go n x = (n + 1, (n, x))
|
2023-05-07 20:29:33 -04:00
|
|
|
|
|
|
|
combineErrorIO2 :: MonadUnliftIO m => m a -> m b -> (a -> b -> c) -> m c
|
|
|
|
combineErrorIO2 a b f = combineErrorIOM2 a b (\x y -> pure $ f x y)
|
|
|
|
|
|
|
|
combineErrorIO3 :: MonadUnliftIO m => m a -> m b -> m c -> (a -> b -> c -> d) -> m d
|
|
|
|
combineErrorIO3 a b c f = combineErrorIOM3 a b c (\x y z -> pure $ f x y z)
|
|
|
|
|
|
|
|
combineErrorIOM2 :: MonadUnliftIO m => m a -> m b -> (a -> b -> m c) -> m c
|
|
|
|
combineErrorIOM2 a b f = do
|
2023-07-16 19:55:33 -04:00
|
|
|
a' <- catch a $ \(AppException es) ->
|
|
|
|
(throwIO . AppException)
|
|
|
|
=<< catch (es <$ b) (\(AppException es') -> return (es' ++ es))
|
2023-05-07 20:29:33 -04:00
|
|
|
f a' =<< b
|
|
|
|
|
|
|
|
combineErrorIOM3 :: MonadUnliftIO m => m a -> m b -> m c -> (a -> b -> c -> m d) -> m d
|
|
|
|
combineErrorIOM3 a b c f =
|
|
|
|
combineErrorIOM2 (combineErrorIOM2 a b (curry return)) c $ \(x, y) z -> f x y z
|
|
|
|
|
2023-07-09 00:16:57 -04:00
|
|
|
mapErrorsPooledIO :: (Traversable t, MonadUnliftIO m) => Int -> (a -> m b) -> t a -> m (t b)
|
|
|
|
mapErrorsPooledIO t f xs = pooledMapConcurrentlyN t go $ enumTraversable xs
|
|
|
|
where
|
2023-07-16 19:55:33 -04:00
|
|
|
go (n, x) = catch (f x) $ \(AppException e) -> do
|
2023-07-09 00:16:57 -04:00
|
|
|
es <- fmap catMaybes $ mapM (err . f) $ drop (n + 1) $ toList xs
|
2023-07-16 19:55:33 -04:00
|
|
|
throwIO $ AppException $ foldr (<>) e es
|
|
|
|
err x = catch (Nothing <$ x) $ \(AppException es) -> pure $ Just es
|
2023-07-09 00:16:57 -04:00
|
|
|
|
2023-06-16 22:05:28 -04:00
|
|
|
mapErrorsIO :: (Traversable t, MonadUnliftIO m) => (a -> m b) -> t a -> m (t b)
|
|
|
|
mapErrorsIO f xs = mapM go $ enumTraversable xs
|
2023-05-07 20:29:33 -04:00
|
|
|
where
|
2023-07-16 19:55:33 -04:00
|
|
|
go (n, x) = catch (f x) $ \(AppException e) -> do
|
2023-06-16 22:05:28 -04:00
|
|
|
es <- fmap catMaybes $ mapM (err . f) $ drop (n + 1) $ toList xs
|
2023-07-16 19:55:33 -04:00
|
|
|
throwIO $ AppException $ foldr (<>) e es
|
|
|
|
err x = catch (Nothing <$ x) $ \(AppException es) -> pure $ Just es
|
2023-05-07 20:29:33 -04:00
|
|
|
|
2023-06-16 22:05:28 -04:00
|
|
|
collectErrorsIO :: (Traversable t, MonadUnliftIO m) => t (m a) -> m (t a)
|
2023-05-07 20:29:33 -04:00
|
|
|
collectErrorsIO = mapErrorsIO id
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
lookupErr :: (Ord k, Show k) => LookupSuberr -> k -> M.Map k v -> AppExcept v
|
2023-01-27 23:33:34 -05:00
|
|
|
lookupErr what k m = case M.lookup k m of
|
2023-05-07 20:29:33 -04:00
|
|
|
Just x -> return x
|
2023-07-16 19:55:33 -04:00
|
|
|
_ -> throwAppError $ LookupError what $ tshow k
|
2022-12-11 17:51:11 -05:00
|
|
|
|
2023-01-27 23:33:34 -05:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- error display
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
showError :: AppError -> [T.Text]
|
2023-04-16 20:09:13 -04:00
|
|
|
showError other = case other of
|
2023-07-16 19:55:33 -04:00
|
|
|
(StatementError ts ms) -> (showTx <$> ts) ++ (showMatch <$> ms)
|
2023-05-29 15:56:15 -04:00
|
|
|
(DaySpanError a b) ->
|
2023-04-16 20:09:13 -04:00
|
|
|
[T.unwords ["Could not create bounds from", showGregorian_ a, "and", showGreg b]]
|
2023-02-05 10:34:26 -05:00
|
|
|
where
|
|
|
|
showGreg (Just g) = showGregorian_ g
|
|
|
|
showGreg Nothing = "Inf"
|
2023-07-16 19:55:33 -04:00
|
|
|
(AccountTypeError a ts) ->
|
2023-04-16 20:09:13 -04:00
|
|
|
[ T.unwords
|
|
|
|
[ "account type of key"
|
2023-07-16 00:10:49 -04:00
|
|
|
, singleQuote $ unAcntID a
|
2023-04-16 20:09:13 -04:00
|
|
|
, "is not one of:"
|
|
|
|
, ts_
|
|
|
|
]
|
|
|
|
]
|
2023-02-25 22:56:23 -05:00
|
|
|
where
|
|
|
|
ts_ = T.intercalate ", " $ NE.toList $ fmap atName ts
|
2023-07-16 19:55:33 -04:00
|
|
|
(DatePatternError s b r p) -> [T.unwords [msg, "in pattern: ", pat]]
|
2023-02-05 10:34:26 -05:00
|
|
|
where
|
|
|
|
pat =
|
|
|
|
keyVals $
|
|
|
|
[ (k, v)
|
|
|
|
| (k, Just v) <-
|
2023-07-09 11:13:35 -04:00
|
|
|
[ ("start", Just $ tshow s)
|
|
|
|
, ("by", Just $ tshow b)
|
|
|
|
, ("repeats", tshow <$> r)
|
2023-02-05 10:34:26 -05:00
|
|
|
]
|
|
|
|
]
|
|
|
|
msg = case p of
|
|
|
|
ZeroLength -> "Zero repeat length"
|
|
|
|
ZeroRepeats -> "Zero repeats"
|
2023-04-16 20:09:13 -04:00
|
|
|
(RegexError re) -> [T.append "could not make regex from pattern: " re]
|
2023-07-16 19:55:33 -04:00
|
|
|
(ConversionError x isDouble) ->
|
|
|
|
[ T.unwords
|
|
|
|
[ "Could not convert to"
|
|
|
|
, if isDouble then "double" else "rational"
|
|
|
|
, "number: "
|
|
|
|
, x
|
|
|
|
]
|
|
|
|
]
|
|
|
|
(StatementIOError msg) -> [T.append "IO Error: " msg]
|
2023-04-16 20:09:13 -04:00
|
|
|
(ParseError msg) -> [T.append "Parse Error: " msg]
|
2023-01-28 20:03:58 -05:00
|
|
|
(MatchValPrecisionError d p) ->
|
2023-07-09 11:13:35 -04:00
|
|
|
[T.unwords ["Match denominator", tshow d, "must be less than", tshow p]]
|
2023-01-27 23:33:34 -05:00
|
|
|
(LookupError t f) ->
|
2023-04-16 20:09:13 -04:00
|
|
|
[T.unwords ["Could not find field", f, "when resolving", what]]
|
2023-01-27 23:33:34 -05:00
|
|
|
where
|
|
|
|
what = case t of
|
2023-05-29 16:11:19 -04:00
|
|
|
EntryIDField st -> T.unwords ["entry", idName st, "ID"]
|
|
|
|
EntryValField -> "entry value"
|
2023-01-28 22:55:07 -05:00
|
|
|
MatchField mt -> T.unwords [matchName mt, "match"]
|
|
|
|
DBKey st -> T.unwords ["database", idName st, "ID key"]
|
2023-02-26 22:53:12 -05:00
|
|
|
-- TODO this should be its own function
|
2023-01-28 22:55:07 -05:00
|
|
|
idName AcntField = "account"
|
|
|
|
idName CurField = "currency"
|
2023-02-26 22:53:12 -05:00
|
|
|
idName TagField = "tag"
|
2023-01-28 22:55:07 -05:00
|
|
|
matchName MatchNumeric = "numeric"
|
|
|
|
matchName MatchText = "text"
|
2023-05-14 19:20:10 -04:00
|
|
|
(PeriodError start next) ->
|
|
|
|
[ T.unwords
|
|
|
|
[ "First pay period on "
|
2023-07-09 11:13:35 -04:00
|
|
|
, singleQuote $ tshow start
|
2023-05-14 19:20:10 -04:00
|
|
|
, "must start before first income payment on "
|
2023-07-09 11:13:35 -04:00
|
|
|
, singleQuote $ tshow next
|
2023-04-30 00:16:06 -04:00
|
|
|
]
|
|
|
|
]
|
2023-07-16 19:55:33 -04:00
|
|
|
(LinkError i m) ->
|
2023-06-19 12:33:50 -04:00
|
|
|
[ T.unwords
|
2023-07-16 19:55:33 -04:00
|
|
|
[ "entry index"
|
|
|
|
, singleQuote $ tshow i
|
|
|
|
, "out of range: max index is"
|
|
|
|
, singleQuote $ tshow m
|
2023-06-19 12:33:50 -04:00
|
|
|
]
|
|
|
|
]
|
2023-07-16 19:55:33 -04:00
|
|
|
(DBError d) -> case d of
|
|
|
|
DBShouldBeEmpty -> ["database has no rows in 'config_state' but has other data"]
|
|
|
|
DBMultiScope -> ["database has multiple rows in 'config_state'"]
|
|
|
|
DBUpdateUnbalanced -> ["update is missing debit or credit entries"]
|
|
|
|
DBLinkError k l ->
|
|
|
|
let k' = T.append "in entry key: " $ tshow $ E.fromSqlKey k
|
|
|
|
in case l of
|
|
|
|
DBLinkNoScale -> [T.append "no link scale" k']
|
|
|
|
DBLinkNoValue -> [T.append "no link value" k']
|
|
|
|
DBLinkInvalidValue v isfixed ->
|
|
|
|
[ T.unwords
|
|
|
|
[ if isfixed
|
|
|
|
then "fixed link should not have value"
|
|
|
|
else "untyped value is ambiguous"
|
|
|
|
, singleQuote $ tshow v
|
|
|
|
, k'
|
|
|
|
]
|
|
|
|
]
|
|
|
|
DBLinkInvalidBalance -> [T.append "no value given for balance link" k']
|
|
|
|
DBLinkInvalidPercent -> [T.append "no value given for percent link" k']
|
2023-01-25 20:52:27 -05:00
|
|
|
|
2023-02-05 10:34:26 -05:00
|
|
|
showGregorian_ :: Gregorian -> T.Text
|
2023-07-09 11:13:35 -04:00
|
|
|
showGregorian_ Gregorian {gYear, gMonth, gDay} = T.intercalate "-" $ tshow <$> [gYear, gMonth, gDay]
|
2023-02-05 10:34:26 -05:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
showTx :: TxRecord -> T.Text
|
|
|
|
showTx TxRecord {trDate = d, trAmount = v, trDesc = e, trFile = f} =
|
2023-01-25 20:52:27 -05:00
|
|
|
T.append "Unmatched transaction: " $
|
|
|
|
keyVals
|
|
|
|
[ ("path", T.pack f)
|
|
|
|
, ("date", T.pack $ iso8601Show d)
|
2023-07-09 11:13:35 -04:00
|
|
|
, ("value", tshow v)
|
2023-07-16 00:39:03 -04:00
|
|
|
, ("description", doubleQuote $ unTxDesc e)
|
2023-01-25 20:52:27 -05:00
|
|
|
]
|
|
|
|
|
2023-08-13 13:29:38 -04:00
|
|
|
showMatch :: StatementParserRe -> T.Text
|
2023-04-30 23:28:16 -04:00
|
|
|
showMatch StatementParser {spDate, spVal, spDesc, spOther, spTimes, spPriority} =
|
2023-01-25 20:52:27 -05:00
|
|
|
T.append "Unused match: " $ keyVals [(x, y) | (x, Just y) <- kvs]
|
|
|
|
where
|
|
|
|
kvs =
|
2023-04-30 23:28:16 -04:00
|
|
|
[ ("date", showDateMatcher <$> spDate)
|
|
|
|
, ("val", showValMatcher spVal)
|
|
|
|
, ("desc", fst <$> spDesc)
|
2023-01-25 20:52:27 -05:00
|
|
|
, ("other", others)
|
2023-07-09 11:13:35 -04:00
|
|
|
, ("counter", Just $ maybe "Inf" tshow spTimes)
|
|
|
|
, ("priority", Just $ tshow spPriority)
|
2023-01-25 20:52:27 -05:00
|
|
|
]
|
2023-04-30 23:28:16 -04:00
|
|
|
others = case spOther of
|
2023-01-25 20:52:27 -05:00
|
|
|
[] -> Nothing
|
2023-01-28 20:03:58 -05:00
|
|
|
xs -> Just $ singleQuote $ T.concat $ showMatchOther <$> xs
|
2023-01-25 20:52:27 -05:00
|
|
|
|
2023-01-28 18:52:28 -05:00
|
|
|
-- | Convert match date to text
|
2023-01-28 19:32:56 -05:00
|
|
|
-- Single date matches will just show the single date, and ranged matches will
|
|
|
|
-- show an interval like [YY-MM-DD, YY-MM-DD)
|
2023-04-30 00:16:06 -04:00
|
|
|
showDateMatcher :: DateMatcher -> T.Text
|
|
|
|
showDateMatcher md = case md of
|
|
|
|
(On x) -> showYMDMatcher x
|
|
|
|
(In start n) -> T.concat ["[", showYMDMatcher start, " ", showYMD_ end, ")"]
|
2023-01-28 18:52:28 -05:00
|
|
|
where
|
2023-01-28 19:32:56 -05:00
|
|
|
-- TODO not DRY (this shifting thing happens during the comparison
|
|
|
|
-- function (kinda)
|
2023-04-30 00:16:06 -04:00
|
|
|
end = case fromYMDMatcher start of
|
2023-01-28 19:32:56 -05:00
|
|
|
Y_ y -> Y_ $ y + fromIntegral n
|
|
|
|
YM_ y m ->
|
|
|
|
let (y_, m_) = divMod (m + fromIntegral n - 1) 12
|
|
|
|
in YM_ (y + fromIntegral y_) (m + m_ + 1)
|
|
|
|
YMD_ y m d ->
|
|
|
|
uncurry3 YMD_ $
|
|
|
|
toGregorian $
|
|
|
|
addDays (fromIntegral n) $
|
|
|
|
fromGregorian y m d
|
2023-01-28 18:52:28 -05:00
|
|
|
|
|
|
|
-- | convert YMD match to text
|
2023-04-30 00:16:06 -04:00
|
|
|
showYMDMatcher :: YMDMatcher -> T.Text
|
|
|
|
showYMDMatcher = showYMD_ . fromYMDMatcher
|
2023-01-28 19:32:56 -05:00
|
|
|
|
|
|
|
showYMD_ :: YMD_ -> T.Text
|
|
|
|
showYMD_ md =
|
2023-07-09 11:13:35 -04:00
|
|
|
T.intercalate "-" $ L.take 3 (fmap tshow digits ++ L.repeat "*")
|
2023-01-28 18:52:28 -05:00
|
|
|
where
|
|
|
|
digits = case md of
|
2023-01-28 19:32:56 -05:00
|
|
|
Y_ y -> [fromIntegral y]
|
|
|
|
YM_ y m -> [fromIntegral y, m]
|
|
|
|
YMD_ y m d -> [fromIntegral y, m, d]
|
2023-01-25 20:52:27 -05:00
|
|
|
|
2023-04-30 00:16:06 -04:00
|
|
|
showValMatcher :: ValMatcher -> Maybe T.Text
|
2023-04-30 23:28:16 -04:00
|
|
|
showValMatcher ValMatcher {vmSign = Nothing, vmNum = Nothing, vmDen = Nothing} = Nothing
|
|
|
|
showValMatcher ValMatcher {vmNum, vmDen, vmSign, vmPrec} =
|
2023-02-12 16:23:32 -05:00
|
|
|
Just $ singleQuote $ keyVals [(k, v) | (k, Just v) <- kvs]
|
2023-01-28 18:52:28 -05:00
|
|
|
where
|
2023-01-28 20:03:58 -05:00
|
|
|
kvs =
|
2023-04-30 23:28:16 -04:00
|
|
|
[ ("sign", (\s -> if s then "+" else "-") <$> vmSign)
|
2023-07-09 11:13:35 -04:00
|
|
|
, ("numerator", tshow <$> vmNum)
|
|
|
|
, ("denominator", tshow <$> vmDen)
|
|
|
|
, ("precision", Just $ tshow vmPrec)
|
2023-01-28 20:03:58 -05:00
|
|
|
]
|
2023-01-25 20:52:27 -05:00
|
|
|
|
2023-04-30 23:28:16 -04:00
|
|
|
showMatchOther :: FieldMatcherRe -> T.Text
|
2023-02-01 23:02:07 -05:00
|
|
|
showMatchOther (Desc (Field f (re, _))) =
|
2023-01-28 20:03:58 -05:00
|
|
|
T.unwords ["desc field", singleQuote f, "with re", singleQuote re]
|
|
|
|
showMatchOther (Val (Field f mv)) =
|
|
|
|
T.unwords
|
|
|
|
[ "val field"
|
|
|
|
, singleQuote f
|
|
|
|
, "with match value"
|
2023-04-30 00:16:06 -04:00
|
|
|
, singleQuote $ fromMaybe "*" $ showValMatcher mv
|
2023-01-28 20:03:58 -05:00
|
|
|
]
|
2023-01-25 20:52:27 -05:00
|
|
|
|
|
|
|
singleQuote :: T.Text -> T.Text
|
|
|
|
singleQuote t = T.concat ["'", t, "'"]
|
|
|
|
|
|
|
|
doubleQuote :: T.Text -> T.Text
|
|
|
|
doubleQuote t = T.concat ["'", t, "'"]
|
|
|
|
|
|
|
|
keyVal :: T.Text -> T.Text -> T.Text
|
|
|
|
keyVal a b = T.concat [a, "=", b]
|
|
|
|
|
|
|
|
keyVals :: [(T.Text, T.Text)] -> T.Text
|
|
|
|
keyVals = T.intercalate "; " . fmap (uncurry keyVal)
|
2023-01-26 23:41:45 -05:00
|
|
|
|
2023-01-27 23:33:34 -05:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- random functions
|
|
|
|
|
2023-07-03 20:27:52 -04:00
|
|
|
groupKey :: Ord c => (a -> c) -> [(a, b)] -> [(a, NonEmpty b)]
|
2023-06-25 14:26:35 -04:00
|
|
|
groupKey f = fmap go . NE.groupAllWith (f . fst)
|
|
|
|
where
|
2023-07-03 20:27:52 -04:00
|
|
|
go xs@((c, _) :| _) = (c, fmap snd xs)
|
2023-06-25 14:26:35 -04:00
|
|
|
|
2023-07-15 14:14:23 -04:00
|
|
|
groupWith :: Ord b => (a -> b) -> [a] -> [(b, NonEmpty a)]
|
2023-06-25 14:26:35 -04:00
|
|
|
groupWith f = fmap go . NE.groupAllWith fst . fmap (\x -> (f x, x))
|
|
|
|
where
|
2023-07-15 14:14:23 -04:00
|
|
|
go xs@((c, _) :| _) = (c, fmap snd xs)
|
2023-06-25 14:26:35 -04:00
|
|
|
|
2023-06-13 20:12:29 -04:00
|
|
|
mapAdd_ :: (Ord k, Num v) => k -> v -> M.Map k v -> M.Map k v
|
|
|
|
mapAdd_ k v = M.alter (maybe (Just v) (Just . (+ v))) k
|
|
|
|
|
2023-01-27 23:33:34 -05:00
|
|
|
uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
|
|
|
|
uncurry3 f (a, b, c) = f a b c
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
lookupAccount :: (MonadAppError m, MonadFinance m) => AcntID -> m (AccountRId, AcntType)
|
2023-07-20 00:25:33 -04:00
|
|
|
lookupAccount = lookupFinance AcntField tsAccountMap
|
2023-05-29 15:56:15 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
lookupAccountKey :: (MonadAppError m, MonadFinance m) => AcntID -> m AccountRId
|
2023-07-09 11:13:35 -04:00
|
|
|
lookupAccountKey = fmap fst . lookupAccount
|
2023-05-29 15:56:15 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
lookupAccountType :: (MonadAppError m, MonadFinance m) => AcntID -> m AcntType
|
2023-07-09 11:13:35 -04:00
|
|
|
lookupAccountType = fmap snd . lookupAccount
|
2023-05-29 15:56:15 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
lookupCurrency :: (MonadAppError m, MonadFinance m) => CurID -> m CurrencyPrec
|
2023-07-20 00:25:33 -04:00
|
|
|
lookupCurrency = lookupFinance CurField tsCurrencyMap
|
2023-05-29 15:56:15 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
lookupCurrencyKey :: (MonadAppError m, MonadFinance m) => CurID -> m CurrencyRId
|
2023-06-29 21:32:14 -04:00
|
|
|
lookupCurrencyKey = fmap cpID . lookupCurrency
|
2023-05-29 15:56:15 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
lookupCurrencyPrec :: (MonadAppError m, MonadFinance m) => CurID -> m Precision
|
2023-06-29 21:32:14 -04:00
|
|
|
lookupCurrencyPrec = fmap cpPrec . lookupCurrency
|
2023-05-29 15:56:15 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
lookupTag :: (MonadAppError m, MonadFinance m) => TagID -> m TagRId
|
2023-07-20 00:25:33 -04:00
|
|
|
lookupTag = lookupFinance TagField tsTagMap
|
2023-05-29 15:56:15 -04:00
|
|
|
|
|
|
|
lookupFinance
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadAppError m, MonadFinance m, Ord k, Show k)
|
2023-05-29 16:11:19 -04:00
|
|
|
=> EntryIDType
|
2023-07-20 00:25:33 -04:00
|
|
|
-> (TxState -> M.Map k a)
|
2023-07-16 00:10:49 -04:00
|
|
|
-> k
|
2023-05-29 15:56:15 -04:00
|
|
|
-> m a
|
2023-07-16 12:51:39 -04:00
|
|
|
lookupFinance t f c = (liftExcept . lookupErr (DBKey t) c) =<< asks f
|
2023-07-01 18:58:15 -04:00
|
|
|
|
|
|
|
balanceTxs
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadAppError m, MonadFinance m)
|
2023-07-16 12:51:39 -04:00
|
|
|
=> [EntryCRU]
|
2023-07-01 18:58:15 -04:00
|
|
|
-> m ([UEBalanced], [InsertTx])
|
|
|
|
balanceTxs ebs =
|
|
|
|
first concat . partitionEithers . catMaybes
|
|
|
|
<$> evalStateT (mapErrors go $ L.sortOn binDate ebs) M.empty
|
|
|
|
where
|
2023-07-03 20:27:52 -04:00
|
|
|
go (ToUpdate utx) =
|
|
|
|
fmap (Just . Left) $
|
|
|
|
liftInnerS $
|
|
|
|
either rebalanceTotalEntrySet rebalanceFullEntrySet utx
|
2023-07-20 00:25:33 -04:00
|
|
|
go (ToRead ReadEntry {reCurrency, reAcnt, reValue}) = do
|
|
|
|
modify $ mapAdd_ (reAcnt, reCurrency) reValue
|
2023-07-01 18:58:15 -04:00
|
|
|
return Nothing
|
2023-07-21 19:57:54 -04:00
|
|
|
go (ToInsert Tx {txPrimary, txOther, txMeta}) = do
|
2023-07-20 00:25:33 -04:00
|
|
|
e <- either balancePrimaryEntrySet balanceSecondaryEntrySet txPrimary
|
2023-07-03 20:27:52 -04:00
|
|
|
let tot = sum $ fmap (eValue . ieEntry) $ NE.toList $ iesFromEntries e
|
2023-07-08 00:52:40 -04:00
|
|
|
es <- mapErrors (goOther tot) txOther
|
2023-07-21 19:57:54 -04:00
|
|
|
let tx = InsertTx {itxMeta = txMeta, itxEntrySets = e :| es}
|
2023-07-01 18:58:15 -04:00
|
|
|
return $ Just $ Right tx
|
2023-07-08 00:52:40 -04:00
|
|
|
where
|
|
|
|
goOther tot =
|
|
|
|
either
|
2023-07-20 00:25:33 -04:00
|
|
|
balanceSecondaryEntrySet
|
|
|
|
(balancePrimaryEntrySet . fromShadow tot)
|
2023-07-08 00:52:40 -04:00
|
|
|
fromShadow tot e@EntrySet {esTotalValue} = e {esTotalValue = tot *. esTotalValue}
|
2023-07-01 18:58:15 -04:00
|
|
|
|
2023-07-21 19:57:54 -04:00
|
|
|
-- NOTE this sorting thing is super wonky; I'm basically sorting three different
|
|
|
|
-- levels of the hierarchy directory and assuming there will be no overlaps.
|
|
|
|
-- First, sort at the transaction level by day, priority, and description as
|
|
|
|
-- tiebreaker. Anything that shares those three keys will have an unstable sort
|
|
|
|
-- order. Within the entrysets, use the index as it appears in the
|
|
|
|
-- configuration, and same with the entries. Since we assume no overlap, nothing
|
|
|
|
-- "bad" should happen if the levels above entries/entrysets sort on 'Nothing'
|
|
|
|
-- for the indices they don't have at their level.
|
|
|
|
binDate :: EntryCRU -> (TxSortKey, Maybe EntrySetIndex, Maybe EntryIndex)
|
|
|
|
binDate (ToRead ReadEntry {reSortKey, reESIndex, reIndex}) = (reSortKey, Just reESIndex, Just reIndex)
|
|
|
|
binDate (ToInsert Tx {txMeta = (TxMeta t p d _)}) = (TxSortKey t p d, Nothing, Nothing)
|
2023-07-07 00:20:18 -04:00
|
|
|
binDate (ToUpdate u) = either go go u
|
|
|
|
where
|
2023-07-21 19:57:54 -04:00
|
|
|
go UpdateEntrySet {utSortKey, utIndex} = (utSortKey, Just utIndex, Nothing)
|
2023-07-01 18:58:15 -04:00
|
|
|
|
2023-07-20 00:25:33 -04:00
|
|
|
type BCKey = CurrencyRId
|
2023-07-01 18:58:15 -04:00
|
|
|
|
2023-07-05 22:30:24 -04:00
|
|
|
type ABCKey = (AccountRId, BCKey)
|
|
|
|
|
2023-07-08 00:52:40 -04:00
|
|
|
type EntryBals = M.Map ABCKey Decimal
|
2023-07-05 22:30:24 -04:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- rebalancing
|
2023-07-01 18:58:15 -04:00
|
|
|
|
|
|
|
-- TODO make sure new values are rounded properly here
|
2023-07-03 20:27:52 -04:00
|
|
|
rebalanceTotalEntrySet :: TotalUpdateEntrySet -> State EntryBals [UEBalanced]
|
|
|
|
rebalanceTotalEntrySet
|
2023-07-01 18:58:15 -04:00
|
|
|
UpdateEntrySet
|
2023-07-05 22:30:24 -04:00
|
|
|
{ utFrom0 = (f0@UpdateEntry {ueAcnt = f0Acnt}, f0links)
|
2023-07-01 18:58:15 -04:00
|
|
|
, utTo0
|
2023-07-04 10:35:11 -04:00
|
|
|
, utFromUnk
|
2023-07-01 18:58:15 -04:00
|
|
|
, utToUnk
|
|
|
|
, utFromRO
|
|
|
|
, utToRO
|
2023-07-08 00:52:40 -04:00
|
|
|
, utCurrency
|
2023-07-04 10:35:11 -04:00
|
|
|
, utTotalValue
|
2023-07-01 18:58:15 -04:00
|
|
|
} =
|
|
|
|
do
|
2023-07-27 00:17:53 -04:00
|
|
|
(fval, fs, tpairs) <- rebalanceDebit utCurrency utFromRO utFromUnk
|
2023-07-05 22:30:24 -04:00
|
|
|
let f0val = utTotalValue - fval
|
2023-07-27 00:17:53 -04:00
|
|
|
modify $ mapAdd_ (f0Acnt, utCurrency) f0val
|
2023-07-05 22:30:24 -04:00
|
|
|
let tsLinked = tpairs ++ (unlink f0val <$> f0links)
|
2023-07-27 00:17:53 -04:00
|
|
|
ts <- rebalanceCredit utCurrency utTotalValue utTo0 utToUnk utToRO tsLinked
|
2023-07-05 22:30:24 -04:00
|
|
|
return (f0 {ueValue = StaticValue f0val} : fs ++ ts)
|
2023-07-01 18:58:15 -04:00
|
|
|
|
2023-07-03 20:27:52 -04:00
|
|
|
rebalanceFullEntrySet :: FullUpdateEntrySet -> State EntryBals [UEBalanced]
|
|
|
|
rebalanceFullEntrySet
|
|
|
|
UpdateEntrySet
|
|
|
|
{ utFrom0
|
|
|
|
, utTo0
|
2023-07-04 10:35:11 -04:00
|
|
|
, utFromUnk
|
2023-07-03 20:27:52 -04:00
|
|
|
, utToUnk
|
|
|
|
, utFromRO
|
|
|
|
, utToRO
|
2023-07-08 00:52:40 -04:00
|
|
|
, utCurrency
|
2023-07-03 20:27:52 -04:00
|
|
|
} =
|
|
|
|
do
|
2023-07-27 00:17:53 -04:00
|
|
|
(ftot, fs, tpairs) <- rebalanceDebit utCurrency rs ls
|
|
|
|
ts <- rebalanceCredit utCurrency ftot utTo0 utToUnk utToRO tpairs
|
2023-07-05 22:30:24 -04:00
|
|
|
return (fs ++ ts)
|
2023-07-03 20:27:52 -04:00
|
|
|
where
|
2023-07-05 22:30:24 -04:00
|
|
|
(rs, ls) = case utFrom0 of
|
|
|
|
Left x -> (x : utFromRO, utFromUnk)
|
|
|
|
Right x -> (utFromRO, x : utFromUnk)
|
|
|
|
|
|
|
|
rebalanceDebit
|
|
|
|
:: BCKey
|
|
|
|
-> [UE_RO]
|
|
|
|
-> [(UEUnk, [UELink])]
|
2023-07-08 00:52:40 -04:00
|
|
|
-> State EntryBals (Decimal, [UEBalanced], [UEBalanced])
|
|
|
|
rebalanceDebit k ro linked = do
|
2023-07-05 22:30:24 -04:00
|
|
|
(tot, (tpairs, fs)) <-
|
|
|
|
fmap (second (partitionEithers . concat)) $
|
|
|
|
sumM goFrom $
|
|
|
|
L.sortOn idx $
|
|
|
|
(Left <$> ro) ++ (Right <$> linked)
|
|
|
|
return (tot, fs, tpairs)
|
|
|
|
where
|
|
|
|
idx = either ueIndex (ueIndex . fst)
|
|
|
|
goFrom (Left e) = (,[]) <$> updateFixed k e
|
|
|
|
goFrom (Right (e0, es)) = do
|
2023-07-08 00:52:40 -04:00
|
|
|
v <- updateUnknown k e0
|
2023-07-05 22:30:24 -04:00
|
|
|
let e0' = Right $ e0 {ueValue = StaticValue v}
|
|
|
|
let es' = Left . unlink v <$> es
|
|
|
|
return (v, e0' : es')
|
|
|
|
|
2023-07-08 00:52:40 -04:00
|
|
|
unlink :: Decimal -> UELink -> UEBalanced
|
2023-07-16 12:51:39 -04:00
|
|
|
unlink v e = e {ueValue = StaticValue $ (-v) *. unLinkScale (ueValue e)}
|
2023-07-05 22:30:24 -04:00
|
|
|
|
|
|
|
rebalanceCredit
|
|
|
|
:: BCKey
|
2023-07-08 00:52:40 -04:00
|
|
|
-> Decimal
|
2023-07-05 22:30:24 -04:00
|
|
|
-> UEBlank
|
|
|
|
-> [UEUnk]
|
|
|
|
-> [UE_RO]
|
|
|
|
-> [UEBalanced]
|
|
|
|
-> State EntryBals [UEBalanced]
|
2023-07-27 00:17:53 -04:00
|
|
|
rebalanceCredit k tot t0@UpdateEntry {ueAcnt = t0Acnt} us rs bs = do
|
2023-07-05 22:30:24 -04:00
|
|
|
(tval, ts) <-
|
|
|
|
fmap (second catMaybes) $
|
|
|
|
sumM goTo $
|
|
|
|
L.sortOn idx $
|
|
|
|
(UETLinked <$> bs)
|
|
|
|
++ (UETUnk <$> us)
|
|
|
|
++ (UETReadOnly <$> rs)
|
2023-07-27 00:17:53 -04:00
|
|
|
let t0val = -(tot + tval)
|
|
|
|
modify $ mapAdd_ (t0Acnt, k) t0val
|
|
|
|
return (t0 {ueValue = StaticValue t0val} : ts)
|
2023-07-05 22:30:24 -04:00
|
|
|
where
|
|
|
|
idx = projectUET ueIndex ueIndex ueIndex
|
|
|
|
goTo (UETReadOnly e) = (,Nothing) <$> updateFixed k e
|
|
|
|
goTo (UETLinked e) = (,Just e) <$> updateFixed k e
|
|
|
|
goTo (UETUnk e) = do
|
2023-07-08 00:52:40 -04:00
|
|
|
v <- updateUnknown k e
|
2023-07-05 22:30:24 -04:00
|
|
|
return (v, Just $ e {ueValue = StaticValue v})
|
2023-07-03 20:27:52 -04:00
|
|
|
|
2023-07-05 22:30:24 -04:00
|
|
|
data UpdateEntryType a b
|
|
|
|
= UETReadOnly UE_RO
|
|
|
|
| UETUnk a
|
|
|
|
| UETLinked b
|
|
|
|
|
|
|
|
projectUET :: (UE_RO -> c) -> (a -> c) -> (b -> c) -> UpdateEntryType a b -> c
|
|
|
|
projectUET f _ _ (UETReadOnly e) = f e
|
|
|
|
projectUET _ f _ (UETUnk e) = f e
|
|
|
|
projectUET _ _ f (UETLinked p) = f p
|
|
|
|
|
2023-07-08 00:52:40 -04:00
|
|
|
updateFixed :: BCKey -> UpdateEntry i StaticValue -> State EntryBals Decimal
|
2023-07-05 22:30:24 -04:00
|
|
|
updateFixed k e = do
|
|
|
|
let v = unStaticValue $ ueValue e
|
|
|
|
modify $ mapAdd_ (ueAcnt e, k) v
|
|
|
|
return v
|
|
|
|
|
2023-07-08 00:52:40 -04:00
|
|
|
updateUnknown :: BCKey -> UpdateEntry i EntryValueUnk -> State EntryBals Decimal
|
|
|
|
updateUnknown k e = do
|
2023-07-05 22:30:24 -04:00
|
|
|
let key = (ueAcnt e, k)
|
|
|
|
curBal <- gets (M.findWithDefault 0 key)
|
2023-07-08 00:52:40 -04:00
|
|
|
let v = case ueValue e of
|
|
|
|
EVPercent p -> curBal *. p
|
2023-07-05 22:30:24 -04:00
|
|
|
EVBalance p -> p - curBal
|
|
|
|
modify $ mapAdd_ key v
|
|
|
|
return v
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- balancing
|
2023-07-03 20:27:52 -04:00
|
|
|
|
|
|
|
balancePrimaryEntrySet
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadAppError m, MonadFinance m)
|
2023-07-20 00:25:33 -04:00
|
|
|
=> PrimaryEntrySet
|
2023-07-03 20:27:52 -04:00
|
|
|
-> StateT EntryBals m InsertEntrySet
|
|
|
|
balancePrimaryEntrySet
|
2023-07-01 18:58:15 -04:00
|
|
|
EntrySet
|
|
|
|
{ esFrom = HalfEntrySet {hesPrimary = f0, hesOther = fs}
|
|
|
|
, esTo = HalfEntrySet {hesPrimary = t0, hesOther = ts}
|
2023-07-08 00:52:40 -04:00
|
|
|
, esCurrency
|
2023-07-01 18:58:15 -04:00
|
|
|
, esTotalValue
|
|
|
|
} =
|
|
|
|
do
|
|
|
|
let f0res = resolveAcntAndTags f0
|
|
|
|
let t0res = resolveAcntAndTags t0
|
2023-07-03 20:27:52 -04:00
|
|
|
let fsres = mapErrors resolveAcntAndTags fs
|
|
|
|
let tsres = mapErrors resolveAcntAndTags ts
|
2023-07-20 00:25:33 -04:00
|
|
|
let bc = esCurrency
|
2023-07-03 20:27:52 -04:00
|
|
|
combineErrorM (combineError f0res fsres (,)) (combineError t0res tsres (,)) $
|
|
|
|
\(f0', fs') (t0', ts') -> do
|
2023-07-08 00:52:40 -04:00
|
|
|
let balFrom = fmap liftInnerS . balanceDeferred
|
2023-07-13 23:31:27 -04:00
|
|
|
fs'' <- balanceTotalEntrySet balFrom bc esTotalValue f0' fs'
|
2023-07-08 00:52:40 -04:00
|
|
|
balanceFinal bc (-esTotalValue) fs'' t0' ts'
|
2023-07-05 22:30:24 -04:00
|
|
|
|
|
|
|
balanceSecondaryEntrySet
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadAppError m, MonadFinance m)
|
2023-07-20 00:25:33 -04:00
|
|
|
=> SecondayEntrySet
|
2023-07-05 22:30:24 -04:00
|
|
|
-> StateT EntryBals m InsertEntrySet
|
|
|
|
balanceSecondaryEntrySet
|
|
|
|
EntrySet
|
|
|
|
{ esFrom = HalfEntrySet {hesPrimary = f0, hesOther = fs}
|
|
|
|
, esTo = HalfEntrySet {hesPrimary = t0, hesOther = ts}
|
2023-07-08 00:52:40 -04:00
|
|
|
, esCurrency
|
2023-07-05 22:30:24 -04:00
|
|
|
} =
|
|
|
|
do
|
|
|
|
let fsRes = mapErrors resolveAcntAndTags (f0 :| fs)
|
|
|
|
let t0Res = resolveAcntAndTags t0
|
|
|
|
let tsRes = mapErrors resolveAcntAndTags ts
|
|
|
|
combineErrorM fsRes (combineError t0Res tsRes (,)) $ \fs' (t0', ts') -> do
|
|
|
|
fs'' <- mapErrors balFrom fs'
|
|
|
|
let tot = entrySum (NE.toList fs'')
|
2023-07-08 00:52:40 -04:00
|
|
|
balanceFinal bc (-tot) fs'' t0' ts'
|
2023-07-05 22:30:24 -04:00
|
|
|
where
|
|
|
|
entrySum = sum . fmap (eValue . ieEntry)
|
2023-07-08 00:52:40 -04:00
|
|
|
balFrom = balanceEntry (fmap liftInnerS . balanceDeferred) bc
|
2023-07-20 00:25:33 -04:00
|
|
|
bc = esCurrency
|
2023-07-05 22:30:24 -04:00
|
|
|
|
|
|
|
balanceFinal
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadAppError m)
|
2023-07-05 22:30:24 -04:00
|
|
|
=> BCKey
|
2023-07-08 00:52:40 -04:00
|
|
|
-> Decimal
|
2023-07-05 22:30:24 -04:00
|
|
|
-> NonEmpty InsertEntry
|
2023-07-09 11:13:35 -04:00
|
|
|
-> Entry AccountRId () TagRId
|
2023-07-16 12:51:39 -04:00
|
|
|
-> [Entry AccountRId EntryLink TagRId]
|
2023-07-05 22:30:24 -04:00
|
|
|
-> StateT EntryBals m InsertEntrySet
|
2023-07-20 00:25:33 -04:00
|
|
|
balanceFinal curID tot fs t0 ts = do
|
2023-07-05 22:30:24 -04:00
|
|
|
let fv = V.fromList $ NE.toList $ fmap (eValue . ieEntry) fs
|
2023-07-08 00:52:40 -04:00
|
|
|
let balTo = balanceLinked fv
|
2023-07-20 00:25:33 -04:00
|
|
|
ts' <- balanceTotalEntrySet balTo curID tot t0 ts
|
2023-07-05 22:30:24 -04:00
|
|
|
return $
|
|
|
|
InsertEntrySet
|
|
|
|
{ iesCurrency = curID
|
|
|
|
, iesFromEntries = fs
|
|
|
|
, iesToEntries = ts'
|
|
|
|
}
|
2023-07-01 18:58:15 -04:00
|
|
|
|
2023-07-13 23:31:27 -04:00
|
|
|
balanceTotalEntrySet
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadAppError m)
|
2023-07-16 12:51:39 -04:00
|
|
|
=> (ABCKey -> v -> StateT EntryBals m (Decimal, Maybe CachedEntry))
|
2023-07-05 22:30:24 -04:00
|
|
|
-> BCKey
|
2023-07-08 00:52:40 -04:00
|
|
|
-> Decimal
|
2023-07-09 11:13:35 -04:00
|
|
|
-> Entry AccountRId () TagRId
|
|
|
|
-> [Entry AccountRId v TagRId]
|
2023-07-05 22:30:24 -04:00
|
|
|
-> StateT EntryBals m (NonEmpty InsertEntry)
|
2023-07-13 23:31:27 -04:00
|
|
|
balanceTotalEntrySet f k tot e@Entry {eAcnt = acntID} es = do
|
2023-07-05 22:30:24 -04:00
|
|
|
es' <- mapErrors (balanceEntry f k) es
|
2023-07-01 18:58:15 -04:00
|
|
|
let e0val = tot - entrySum es'
|
|
|
|
-- TODO not dry
|
2023-07-05 22:30:24 -04:00
|
|
|
modify (mapAdd_ (acntID, k) e0val)
|
2023-07-01 18:58:15 -04:00
|
|
|
let e' =
|
|
|
|
InsertEntry
|
2023-07-09 11:13:35 -04:00
|
|
|
{ ieEntry = e {eValue = e0val, eAcnt = acntID}
|
2023-07-16 12:51:39 -04:00
|
|
|
, ieCached = Nothing
|
2023-07-01 18:58:15 -04:00
|
|
|
}
|
2023-07-03 20:27:52 -04:00
|
|
|
return $ e' :| es'
|
2023-07-01 18:58:15 -04:00
|
|
|
where
|
2023-07-03 20:27:52 -04:00
|
|
|
entrySum = sum . fmap (eValue . ieEntry)
|
2023-07-01 18:58:15 -04:00
|
|
|
|
|
|
|
liftInnerS :: Monad m => StateT e Identity a -> StateT e m a
|
|
|
|
liftInnerS = mapStateT (return . runIdentity)
|
|
|
|
|
|
|
|
balanceLinked
|
2023-07-16 19:55:33 -04:00
|
|
|
:: MonadAppError m
|
2023-07-08 00:52:40 -04:00
|
|
|
=> Vector Decimal
|
2023-07-05 22:30:24 -04:00
|
|
|
-> ABCKey
|
2023-07-16 12:51:39 -04:00
|
|
|
-> EntryLink
|
|
|
|
-> StateT EntryBals m (Decimal, Maybe CachedEntry)
|
2023-07-08 00:52:40 -04:00
|
|
|
balanceLinked from k lg = case lg of
|
2023-07-01 18:58:15 -04:00
|
|
|
(LinkIndex LinkedNumGetter {lngIndex, lngScale}) -> do
|
2023-07-16 19:55:33 -04:00
|
|
|
let i = fromIntegral lngIndex
|
|
|
|
upper = EntryIndex $ V.length from
|
|
|
|
res = fmap (go lngScale) $ from V.!? i
|
2023-07-01 18:58:15 -04:00
|
|
|
case res of
|
2023-07-16 12:51:39 -04:00
|
|
|
Just v -> return (v, Just $ CachedLink (EntryIndex $ fromIntegral lngIndex) (LinkScale lngScale))
|
2023-07-16 19:55:33 -04:00
|
|
|
Nothing -> throwAppError $ LinkError (EntryIndex i) upper
|
2023-07-16 12:51:39 -04:00
|
|
|
(LinkValue d) -> liftInnerS $ balanceDeferred k d
|
2023-07-01 18:58:15 -04:00
|
|
|
where
|
2023-07-08 00:52:40 -04:00
|
|
|
go s = negate . (*. s)
|
|
|
|
|
2023-07-16 12:51:39 -04:00
|
|
|
balanceDeferred :: ABCKey -> EntryValue -> State EntryBals (Decimal, Maybe CachedEntry)
|
2023-07-08 00:52:40 -04:00
|
|
|
balanceDeferred k e = do
|
|
|
|
newval <- findBalance k e
|
|
|
|
let d = case e of
|
|
|
|
EntryFixed _ -> Nothing
|
2023-07-16 12:51:39 -04:00
|
|
|
EntryBalance v -> Just $ CachedBalance v
|
|
|
|
EntryPercent v -> Just $ CachedPercent v
|
2023-07-01 18:58:15 -04:00
|
|
|
return (newval, d)
|
|
|
|
|
|
|
|
balanceEntry
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadAppError m)
|
2023-07-16 12:51:39 -04:00
|
|
|
=> (ABCKey -> v -> StateT EntryBals m (Decimal, Maybe CachedEntry))
|
2023-07-05 22:30:24 -04:00
|
|
|
-> BCKey
|
2023-07-09 11:13:35 -04:00
|
|
|
-> Entry AccountRId v TagRId
|
2023-07-05 22:30:24 -04:00
|
|
|
-> StateT EntryBals m InsertEntry
|
2023-07-09 11:13:35 -04:00
|
|
|
balanceEntry f k e@Entry {eValue, eAcnt = acntID} = do
|
2023-07-16 12:51:39 -04:00
|
|
|
(newVal, cached) <- f (acntID, k) eValue
|
2023-07-05 22:30:24 -04:00
|
|
|
modify (mapAdd_ (acntID, k) newVal)
|
2023-07-03 20:27:52 -04:00
|
|
|
return $
|
|
|
|
InsertEntry
|
2023-07-09 11:13:35 -04:00
|
|
|
{ ieEntry = e {eValue = newVal, eAcnt = acntID}
|
2023-07-16 12:51:39 -04:00
|
|
|
, ieCached = cached
|
2023-07-03 20:27:52 -04:00
|
|
|
}
|
2023-07-01 18:58:15 -04:00
|
|
|
|
|
|
|
resolveAcntAndTags
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadAppError m, MonadFinance m)
|
2023-07-01 18:58:15 -04:00
|
|
|
=> Entry AcntID v TagID
|
2023-07-09 11:13:35 -04:00
|
|
|
-> m (Entry AccountRId v TagRId)
|
2023-07-01 18:58:15 -04:00
|
|
|
resolveAcntAndTags e@Entry {eAcnt, eTags} = do
|
2023-07-09 11:13:35 -04:00
|
|
|
let acntRes = lookupAccountKey eAcnt
|
2023-07-01 18:58:15 -04:00
|
|
|
let tagRes = mapErrors lookupTag eTags
|
2023-07-09 11:13:35 -04:00
|
|
|
combineError acntRes tagRes $ \a ts -> e {eAcnt = a, eTags = ts}
|
2023-07-01 18:58:15 -04:00
|
|
|
|
2023-07-08 00:52:40 -04:00
|
|
|
findBalance :: ABCKey -> EntryValue -> State EntryBals Decimal
|
|
|
|
findBalance k e = do
|
2023-07-05 22:30:24 -04:00
|
|
|
curBal <- gets (M.findWithDefault 0 k)
|
2023-07-08 00:52:40 -04:00
|
|
|
return $ case e of
|
|
|
|
EntryBalance b -> b - curBal
|
|
|
|
EntryPercent p -> curBal *. p
|
|
|
|
EntryFixed v -> v
|
2023-07-01 18:58:15 -04:00
|
|
|
|
2023-07-05 22:30:24 -04:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- transfers
|
|
|
|
|
2023-07-01 18:58:15 -04:00
|
|
|
expandTransfers
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadAppError m, MonadFinance m)
|
2023-07-04 10:35:11 -04:00
|
|
|
=> CommitR
|
2023-07-01 18:58:15 -04:00
|
|
|
-> DaySpan
|
|
|
|
-> [PairedTransfer]
|
2023-07-04 10:35:11 -04:00
|
|
|
-> m [Tx CommitR]
|
2023-07-20 00:25:33 -04:00
|
|
|
expandTransfers tc bounds = fmap concat . mapErrors (expandTransfer tc bounds)
|
2023-07-01 18:58:15 -04:00
|
|
|
|
|
|
|
expandTransfer
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadAppError m, MonadFinance m)
|
2023-07-04 10:35:11 -04:00
|
|
|
=> CommitR
|
2023-07-01 18:58:15 -04:00
|
|
|
-> DaySpan
|
|
|
|
-> PairedTransfer
|
2023-07-04 10:35:11 -04:00
|
|
|
-> m [Tx CommitR]
|
2023-07-20 00:25:33 -04:00
|
|
|
expandTransfer tc bounds Transfer {transAmounts, transTo, transCurrency, transFrom} = do
|
2023-07-01 18:58:15 -04:00
|
|
|
txs <- mapErrors go transAmounts
|
2023-07-03 20:27:52 -04:00
|
|
|
return $ concat txs
|
2023-07-01 18:58:15 -04:00
|
|
|
where
|
|
|
|
go
|
|
|
|
Amount
|
|
|
|
{ amtWhen = pat
|
|
|
|
, amtValue = TransferValue {tvVal = v, tvType = t}
|
|
|
|
, amtDesc = desc
|
2023-07-07 00:20:18 -04:00
|
|
|
, amtPriority = pri
|
2023-07-08 00:52:40 -04:00
|
|
|
} = do
|
|
|
|
cp <- lookupCurrency transCurrency
|
|
|
|
let v' = (-v)
|
2023-07-16 19:55:33 -04:00
|
|
|
let dec = realFracToDecimalP (cpPrec cp) v'
|
2023-07-08 00:52:40 -04:00
|
|
|
let v'' = case t of
|
|
|
|
TFixed -> EntryFixed dec
|
|
|
|
TPercent -> EntryPercent v'
|
|
|
|
TBalance -> EntryBalance dec
|
|
|
|
withDates bounds pat $ \day ->
|
2023-07-01 18:58:15 -04:00
|
|
|
return
|
|
|
|
Tx
|
2023-07-21 19:57:54 -04:00
|
|
|
{ txMeta = TxMeta day (fromIntegral pri) (TxDesc desc) tc
|
2023-07-08 00:52:40 -04:00
|
|
|
, txPrimary = Right $ entryPair transFrom transTo (cpID cp) desc () v''
|
2023-07-01 18:58:15 -04:00
|
|
|
, txOther = []
|
|
|
|
}
|
|
|
|
|
|
|
|
entryPair
|
2023-07-08 00:52:40 -04:00
|
|
|
:: TaggedAcnt
|
2023-07-01 18:58:15 -04:00
|
|
|
-> TaggedAcnt
|
2023-07-08 00:52:40 -04:00
|
|
|
-> CurrencyRId
|
2023-07-01 18:58:15 -04:00
|
|
|
-> T.Text
|
2023-07-03 20:27:52 -04:00
|
|
|
-> v0
|
|
|
|
-> v1
|
2023-07-08 00:52:40 -04:00
|
|
|
-> EntrySet v0 v1 v2 v3
|
|
|
|
entryPair (TaggedAcnt fa fts) (TaggedAcnt ta tts) curid com totval val1 =
|
|
|
|
EntrySet
|
|
|
|
{ esCurrency = curid
|
|
|
|
, esTotalValue = totval
|
2023-07-16 00:10:49 -04:00
|
|
|
, esFrom = halfEntry (AcntID fa) (TagID <$> fts) val1
|
|
|
|
, esTo = halfEntry (AcntID ta) (TagID <$> tts) ()
|
2023-07-08 00:52:40 -04:00
|
|
|
}
|
2023-07-01 18:58:15 -04:00
|
|
|
where
|
2023-07-03 20:27:52 -04:00
|
|
|
halfEntry :: AcntID -> [TagID] -> v -> HalfEntrySet v v0
|
|
|
|
halfEntry a ts v =
|
2023-07-01 18:58:15 -04:00
|
|
|
HalfEntrySet
|
2023-07-03 20:27:52 -04:00
|
|
|
{ hesPrimary = Entry {eAcnt = a, eValue = v, eComment = com, eTags = ts}
|
2023-07-01 18:58:15 -04:00
|
|
|
, hesOther = []
|
|
|
|
}
|
|
|
|
|
|
|
|
withDates
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadFinance m, MonadAppError m)
|
2023-07-03 20:27:52 -04:00
|
|
|
=> DaySpan
|
|
|
|
-> DatePat
|
2023-07-01 18:58:15 -04:00
|
|
|
-> (Day -> m a)
|
|
|
|
-> m [a]
|
2023-07-03 20:27:52 -04:00
|
|
|
withDates bounds dp f = do
|
2023-07-01 18:58:15 -04:00
|
|
|
days <- liftExcept $ expandDatePat bounds dp
|
|
|
|
combineErrors $ fmap f days
|
2023-07-05 22:30:24 -04:00
|
|
|
|
|
|
|
sumM :: (Monad m, Num s) => (a -> m (s, b)) -> [a] -> m (s, [b])
|
|
|
|
sumM f = mapAccumM (\s -> fmap (first (+ s)) . f) 0
|
|
|
|
|
|
|
|
mapAccumM :: (Monad m) => (s -> a -> m (s, b)) -> s -> [a] -> m (s, [b])
|
|
|
|
mapAccumM f s = foldM (\(s', ys) -> fmap (second (: ys)) . f s') (s, [])
|
2023-07-16 00:20:01 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
realFracToDecimalP :: (Integral i, RealFrac r) => Precision -> r -> DecimalRaw i
|
|
|
|
realFracToDecimalP p = realFracToDecimal (unPrecision p)
|
2023-07-16 00:20:01 -04:00
|
|
|
|
|
|
|
roundToP :: Integral i => Precision -> DecimalRaw i -> DecimalRaw i
|
|
|
|
roundToP p = roundTo (unPrecision p)
|
2023-08-13 13:29:38 -04:00
|
|
|
|
|
|
|
compileRegex :: Bool -> T.Text -> AppExcept (Text, Regex)
|
|
|
|
compileRegex groups pat = case res of
|
|
|
|
Right re -> return (pat, re)
|
|
|
|
Left _ -> throwError $ AppException [RegexError pat]
|
|
|
|
where
|
|
|
|
res =
|
|
|
|
compile
|
|
|
|
(blankCompOpt {newSyntax = True})
|
|
|
|
(blankExecOpt {captureGroups = groups})
|
|
|
|
pat
|
|
|
|
|
|
|
|
matchMaybe :: T.Text -> Regex -> AppExcept Bool
|
|
|
|
matchMaybe q re = case execute re q of
|
|
|
|
Right res -> return $ isJust res
|
|
|
|
Left _ -> throwError $ AppException [RegexError "this should not happen"]
|
|
|
|
|
|
|
|
matchGroupsMaybe :: T.Text -> Regex -> [T.Text]
|
|
|
|
matchGroupsMaybe q re = case regexec re q of
|
|
|
|
Right Nothing -> []
|
|
|
|
Right (Just (_, _, _, xs)) -> xs
|
|
|
|
-- this should never fail as regexec always returns Right
|
|
|
|
Left _ -> []
|