2023-05-29 15:56:15 -04:00
|
|
|
module Internal.History
|
2023-06-13 20:12:29 -04:00
|
|
|
( readHistStmt
|
2023-06-12 00:27:34 -04:00
|
|
|
, readHistTransfer
|
2023-06-13 20:12:29 -04:00
|
|
|
, splitHistory
|
2023-07-20 00:25:33 -04:00
|
|
|
, readHistoryCRUD
|
2023-05-29 15:56:15 -04:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Control.Monad.Except
|
2023-05-29 17:19:49 -04:00
|
|
|
import Data.Csv
|
2023-07-08 00:52:40 -04:00
|
|
|
import Data.Decimal
|
2023-06-16 22:05:28 -04:00
|
|
|
import Data.Foldable
|
2023-07-13 23:31:27 -04:00
|
|
|
import Data.Hashable
|
2023-07-04 00:11:25 -04:00
|
|
|
import GHC.Real
|
2023-05-29 15:56:15 -04:00
|
|
|
import Internal.Types.Main
|
|
|
|
import Internal.Utils
|
|
|
|
import RIO hiding (to)
|
2023-05-29 17:19:49 -04:00
|
|
|
import qualified RIO.ByteString.Lazy as BL
|
|
|
|
import RIO.FilePath
|
|
|
|
import qualified RIO.List as L
|
|
|
|
import qualified RIO.Map as M
|
2023-05-29 15:56:15 -04:00
|
|
|
import qualified RIO.Text as T
|
|
|
|
import RIO.Time
|
2023-05-29 17:19:49 -04:00
|
|
|
import qualified RIO.Vector as V
|
2023-07-04 00:11:25 -04:00
|
|
|
import Text.Regex.TDFA hiding (matchAll)
|
2023-05-29 15:56:15 -04:00
|
|
|
|
2023-07-20 00:25:33 -04:00
|
|
|
readHistoryCRUD
|
|
|
|
:: (MonadUnliftIO m, MonadFinance m)
|
|
|
|
=> FilePath
|
|
|
|
-> PreHistoryCRUD
|
|
|
|
-> m FinalHistoryCRUD
|
|
|
|
readHistoryCRUD root o@CRUDOps {coCreate = (ts, ss)} = do
|
|
|
|
-- TODO multithread this for some extra fun :)
|
|
|
|
|
2023-08-16 21:01:06 -04:00
|
|
|
ss' <- mapErrorsIO (readHistStmt root) ss
|
2023-07-20 00:25:33 -04:00
|
|
|
fromEitherM $ runExceptT $ do
|
|
|
|
let sRes = mapErrors (ExceptT . return) ss'
|
|
|
|
let tRes = mapErrors readHistTransfer ts
|
|
|
|
combineError sRes tRes $ \ss'' ts' -> o {coCreate = concat ss'' ++ concat ts'}
|
|
|
|
|
2023-07-01 18:58:15 -04:00
|
|
|
-- NOTE keep statement and transfer readers separate because the former needs
|
|
|
|
-- the IO monad, and thus will throw IO errors rather than using the ExceptT
|
|
|
|
-- thingy
|
|
|
|
splitHistory :: [History] -> ([PairedTransfer], [Statement])
|
|
|
|
splitHistory = partitionEithers . fmap go
|
|
|
|
where
|
|
|
|
go (HistTransfer x) = Left x
|
|
|
|
go (HistStatement x) = Right x
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Transfers
|
|
|
|
|
2023-06-12 00:27:34 -04:00
|
|
|
readHistTransfer
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (MonadAppError m, MonadFinance m)
|
2023-07-01 18:32:20 -04:00
|
|
|
=> PairedTransfer
|
2023-07-13 23:31:27 -04:00
|
|
|
-> m [Tx CommitR]
|
|
|
|
readHistTransfer ht = do
|
2023-07-20 00:25:33 -04:00
|
|
|
bounds <- asks (unHSpan . tsHistoryScope)
|
|
|
|
expandTransfer c bounds ht
|
2023-07-13 23:31:27 -04:00
|
|
|
where
|
2023-07-16 00:10:49 -04:00
|
|
|
c = CommitR (CommitHash $ hash ht) CTHistoryTransfer
|
2023-07-01 18:58:15 -04:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Statements
|
2023-05-29 15:56:15 -04:00
|
|
|
|
2023-05-29 18:14:43 -04:00
|
|
|
readHistStmt
|
|
|
|
:: (MonadUnliftIO m, MonadFinance m)
|
|
|
|
=> FilePath
|
|
|
|
-> Statement
|
2023-07-20 00:25:33 -04:00
|
|
|
-> m (Either AppException [Tx CommitR])
|
2023-07-13 23:31:27 -04:00
|
|
|
readHistStmt root i = do
|
2023-07-20 00:25:33 -04:00
|
|
|
bounds <- asks (unHSpan . tsHistoryScope)
|
2023-05-29 18:14:43 -04:00
|
|
|
bs <- readImport root i
|
2023-07-21 19:57:54 -04:00
|
|
|
return $ filter (inDaySpan bounds . txmDate . txMeta) . fmap go <$> bs
|
2023-07-13 23:31:27 -04:00
|
|
|
where
|
2023-07-21 19:57:54 -04:00
|
|
|
go t@Tx {txMeta = m} =
|
|
|
|
t {txMeta = m {txmCommit = CommitR (CommitHash $ hash i) CTHistoryStatement}}
|
2023-05-29 15:56:15 -04:00
|
|
|
|
2023-05-29 17:19:49 -04:00
|
|
|
-- TODO this probably won't scale well (pipes?)
|
2023-07-20 00:25:33 -04:00
|
|
|
readImport
|
|
|
|
:: (MonadUnliftIO m, MonadFinance m)
|
|
|
|
=> FilePath
|
|
|
|
-> Statement
|
|
|
|
-> m (Either AppException [Tx ()])
|
2023-05-29 18:14:43 -04:00
|
|
|
readImport root Statement {stmtTxOpts, stmtParsers, stmtSkipLines, stmtDelim, stmtPaths} = do
|
2023-05-29 17:19:49 -04:00
|
|
|
let ores = compileOptions stmtTxOpts
|
|
|
|
let cres = combineErrors $ compileMatch <$> stmtParsers
|
|
|
|
(compiledOptions, compiledMatches) <- liftIOExcept $ combineError ores cres (,)
|
|
|
|
let readStmt = readImport_ stmtSkipLines stmtDelim compiledOptions
|
2023-05-29 18:14:43 -04:00
|
|
|
records <- L.sort . concat <$> mapErrorsIO readStmt paths
|
2023-07-20 00:25:33 -04:00
|
|
|
runExceptT (matchRecords compiledMatches records)
|
2023-05-29 18:14:43 -04:00
|
|
|
where
|
|
|
|
paths = (root </>) <$> stmtPaths
|
2023-05-29 17:19:49 -04:00
|
|
|
|
|
|
|
readImport_
|
2023-05-29 18:14:43 -04:00
|
|
|
:: MonadUnliftIO m
|
2023-05-29 17:19:49 -04:00
|
|
|
=> Natural
|
|
|
|
-> Word
|
|
|
|
-> TxOptsRe
|
|
|
|
-> FilePath
|
|
|
|
-> m [TxRecord]
|
|
|
|
readImport_ n delim tns p = do
|
2023-05-29 18:14:43 -04:00
|
|
|
res <- tryIO $ BL.readFile p
|
2023-07-16 19:55:33 -04:00
|
|
|
bs <- fromEither $ first (AppException . (: []) . StatementIOError . tshow) res
|
2023-05-29 17:19:49 -04:00
|
|
|
case decodeByNameWithP (parseTxRecord p tns) opts $ skip bs of
|
2023-07-16 19:55:33 -04:00
|
|
|
Left m -> throwIO $ AppException [ParseError $ T.pack m]
|
2023-05-29 17:19:49 -04:00
|
|
|
Right (_, v) -> return $ catMaybes $ V.toList v
|
|
|
|
where
|
|
|
|
opts = defaultDecodeOptions {decDelimiter = fromIntegral delim}
|
|
|
|
skip = BL.intercalate "\n" . L.drop (fromIntegral n) . BL.split 10
|
|
|
|
|
|
|
|
-- TODO handle this better, this maybe thing is a hack to skip lines with
|
|
|
|
-- blank dates but will likely want to make this more flexible
|
|
|
|
parseTxRecord :: FilePath -> TxOptsRe -> NamedRecord -> Parser (Maybe TxRecord)
|
2023-08-16 21:01:06 -04:00
|
|
|
parseTxRecord
|
|
|
|
p
|
|
|
|
TxOpts
|
|
|
|
{ toDate
|
|
|
|
, toDesc
|
|
|
|
, toAmount
|
|
|
|
, toOther
|
|
|
|
, toDateFmt
|
|
|
|
, toSkipBlankDate
|
|
|
|
, toSkipBlankAmount
|
|
|
|
, toSkipBlankDescription
|
|
|
|
, toSkipBlankOther
|
2023-08-16 22:24:20 -04:00
|
|
|
, toSkipMissingFields
|
2023-08-16 21:01:06 -04:00
|
|
|
}
|
2023-08-16 22:24:20 -04:00
|
|
|
r =
|
|
|
|
do
|
|
|
|
-- TODO this is confusing as hell
|
|
|
|
--
|
|
|
|
-- try and parse all fields; if a parse fails, either trip an error
|
|
|
|
-- or return a Nothing if we want to deliberately skip missing fields
|
|
|
|
d <- getField toDate
|
|
|
|
e <- getField toDesc
|
|
|
|
os <-
|
|
|
|
fmap M.fromList . sequence
|
|
|
|
<$> mapM (\n -> fmap (n,) <$> getField n) toOther
|
|
|
|
(af, ax) <- case toAmount of
|
|
|
|
-- the amount column is extra confusing because it can either be one
|
|
|
|
-- or two columns, so keep track of this with a maybe
|
|
|
|
AmountSingle TxAmount1 {a1Column, a1Fmt} -> do
|
|
|
|
f <- getField a1Column
|
|
|
|
return (a1Fmt, Right <$> f)
|
|
|
|
AmountDual TxAmount2 {a2Positive, a2Negative, a2Fmt} -> do
|
|
|
|
f1 <- getField a2Positive
|
|
|
|
f2 <- getField a2Negative
|
|
|
|
return $ (a2Fmt,) $ case (f1, f2) of
|
|
|
|
(Just a, Just b) -> Just $ Left (a, b)
|
|
|
|
_ -> Nothing
|
|
|
|
case (d, e, os, ax) of
|
|
|
|
-- If all lookups were successful, check that none of the fields are
|
|
|
|
-- blank, and if they are return nothing to skip this line
|
|
|
|
(Just d', Just e', Just os', Just ax') ->
|
|
|
|
if (toSkipBlankDate && d' == "")
|
|
|
|
|| (toSkipBlankDescription && e' == "")
|
|
|
|
|| (toSkipBlankAmount && (ax' == Right "" || ax' == Left ("", "")))
|
|
|
|
|| elem "" (mapMaybe (`M.lookup` os') toSkipBlankOther)
|
|
|
|
then return Nothing
|
|
|
|
else -- if we are skipping nothing, proceed to parse the date and amount
|
|
|
|
-- columns
|
|
|
|
do
|
|
|
|
a <- case ax' of
|
|
|
|
Right a -> parseDecimal True af a
|
|
|
|
Left ("", a) -> ((-1) *) <$> parseDecimal False af a
|
|
|
|
Left (a, _) -> parseDecimal False af a
|
|
|
|
d'' <- parseTimeM True defaultTimeLocale (T.unpack toDateFmt) d'
|
|
|
|
return $ Just $ TxRecord d'' a e' os' p
|
|
|
|
-- if no lookups succeeded, return nothing to skip this line. Note that
|
|
|
|
-- a parse fail will trigger a failure error further up, so that case
|
|
|
|
-- is already dealt with implicitly
|
|
|
|
_ -> return Nothing
|
|
|
|
where
|
|
|
|
getField :: FromField a => T.Text -> Parser (Maybe a)
|
|
|
|
getField f = case runParser $ r .: T.encodeUtf8 f of
|
|
|
|
Left err -> if toSkipMissingFields then return Nothing else fail err
|
|
|
|
Right x -> return $ Just x
|
2023-05-29 17:19:49 -04:00
|
|
|
|
2023-08-13 13:29:38 -04:00
|
|
|
matchRecords :: MonadFinance m => [StatementParserRe] -> [TxRecord] -> AppExceptT m [Tx ()]
|
2023-05-29 17:19:49 -04:00
|
|
|
matchRecords ms rs = do
|
|
|
|
(matched, unmatched, notfound) <- matchAll (matchPriorities ms) rs
|
|
|
|
case (matched, unmatched, notfound) of
|
2023-06-29 21:32:14 -04:00
|
|
|
(ms_, [], []) -> return ms_
|
2023-07-16 19:55:33 -04:00
|
|
|
(_, us, ns) -> throwError $ AppException [StatementError us ns]
|
2023-05-29 17:19:49 -04:00
|
|
|
|
2023-08-13 13:29:38 -04:00
|
|
|
matchPriorities :: [StatementParserRe] -> [MatchGroup]
|
2023-05-29 17:19:49 -04:00
|
|
|
matchPriorities =
|
|
|
|
fmap matchToGroup
|
|
|
|
. L.groupBy (\a b -> spPriority a == spPriority b)
|
|
|
|
. L.sortOn (Down . spPriority)
|
|
|
|
|
2023-08-13 13:29:38 -04:00
|
|
|
matchToGroup :: [StatementParserRe] -> MatchGroup
|
2023-05-29 17:19:49 -04:00
|
|
|
matchToGroup ms =
|
|
|
|
uncurry MatchGroup $
|
|
|
|
first (L.sortOn spDate) $
|
|
|
|
L.partition (isJust . spDate) ms
|
|
|
|
|
|
|
|
data MatchGroup = MatchGroup
|
2023-08-13 13:29:38 -04:00
|
|
|
{ mgDate :: ![StatementParserRe]
|
|
|
|
, mgNoDate :: ![StatementParserRe]
|
2023-05-29 17:19:49 -04:00
|
|
|
}
|
|
|
|
deriving (Show)
|
|
|
|
|
|
|
|
data Zipped a = Zipped ![a] ![a]
|
|
|
|
|
|
|
|
data Unzipped a = Unzipped ![a] ![a] ![a]
|
|
|
|
|
|
|
|
initZipper :: [a] -> Zipped a
|
|
|
|
initZipper = Zipped []
|
|
|
|
|
|
|
|
resetZipper :: Zipped a -> Zipped a
|
|
|
|
resetZipper = initZipper . recoverZipper
|
|
|
|
|
|
|
|
recoverZipper :: Zipped a -> [a]
|
|
|
|
recoverZipper (Zipped as bs) = reverse as ++ bs
|
|
|
|
|
|
|
|
zipperSlice
|
|
|
|
:: (a -> b -> Ordering)
|
|
|
|
-> b
|
|
|
|
-> Zipped a
|
|
|
|
-> Either (Zipped a) (Unzipped a)
|
|
|
|
zipperSlice f x = go
|
|
|
|
where
|
|
|
|
go z@(Zipped _ []) = Left z
|
|
|
|
go z@(Zipped bs (a : as)) =
|
|
|
|
case f a x of
|
|
|
|
GT -> go $ Zipped (a : bs) as
|
|
|
|
EQ -> Right $ goEq (Unzipped bs [a] as)
|
|
|
|
LT -> Left z
|
|
|
|
goEq z@(Unzipped _ _ []) = z
|
|
|
|
goEq z@(Unzipped bs cs (a : as)) =
|
|
|
|
case f a x of
|
|
|
|
GT -> goEq $ Unzipped (a : bs) cs as
|
|
|
|
EQ -> goEq $ Unzipped bs (a : cs) as
|
|
|
|
LT -> z
|
|
|
|
|
|
|
|
zipperMatch
|
2023-06-29 21:32:14 -04:00
|
|
|
:: MonadFinance m
|
2023-08-13 13:29:38 -04:00
|
|
|
=> Unzipped StatementParserRe
|
2023-05-29 17:19:49 -04:00
|
|
|
-> TxRecord
|
2023-08-13 13:29:38 -04:00
|
|
|
-> AppExceptT m (Zipped StatementParserRe, MatchRes (Tx ()))
|
2023-05-29 17:19:49 -04:00
|
|
|
zipperMatch (Unzipped bs cs as) x = go [] cs
|
|
|
|
where
|
|
|
|
go _ [] = return (Zipped bs $ cs ++ as, MatchFail)
|
|
|
|
go prev (m : ms) = do
|
|
|
|
res <- matches m x
|
|
|
|
case res of
|
|
|
|
MatchFail -> go (m : prev) ms
|
|
|
|
skipOrPass ->
|
|
|
|
let ps = reverse prev
|
|
|
|
ms' = maybe ms (: ms) (matchDec m)
|
|
|
|
in return (Zipped bs $ ps ++ ms' ++ as, skipOrPass)
|
|
|
|
|
|
|
|
zipperMatch'
|
2023-06-29 21:32:14 -04:00
|
|
|
:: MonadFinance m
|
2023-08-13 13:29:38 -04:00
|
|
|
=> Zipped StatementParserRe
|
2023-05-29 17:19:49 -04:00
|
|
|
-> TxRecord
|
2023-08-13 13:29:38 -04:00
|
|
|
-> AppExceptT m (Zipped StatementParserRe, MatchRes (Tx ()))
|
2023-05-29 17:19:49 -04:00
|
|
|
zipperMatch' z x = go z
|
|
|
|
where
|
|
|
|
go (Zipped bs (a : as)) = do
|
|
|
|
res <- matches a x
|
|
|
|
case res of
|
|
|
|
MatchFail -> go (Zipped (a : bs) as)
|
|
|
|
skipOrPass ->
|
|
|
|
return (Zipped (maybe bs (: bs) $ matchDec a) as, skipOrPass)
|
|
|
|
go z' = return (z', MatchFail)
|
|
|
|
|
2023-08-13 13:29:38 -04:00
|
|
|
matchDec :: StatementParserRe -> Maybe StatementParserRe
|
2023-05-29 17:19:49 -04:00
|
|
|
matchDec m = case spTimes m of
|
|
|
|
Just 1 -> Nothing
|
|
|
|
Just n -> Just $ m {spTimes = Just $ n - 1}
|
|
|
|
Nothing -> Just m
|
|
|
|
|
2023-06-29 21:32:14 -04:00
|
|
|
matchAll
|
|
|
|
:: MonadFinance m
|
|
|
|
=> [MatchGroup]
|
|
|
|
-> [TxRecord]
|
2023-08-13 13:29:38 -04:00
|
|
|
-> AppExceptT m ([Tx ()], [TxRecord], [StatementParserRe])
|
2023-05-29 17:19:49 -04:00
|
|
|
matchAll = go ([], [])
|
|
|
|
where
|
|
|
|
go (matched, unused) gs rs = case (gs, rs) of
|
|
|
|
(_, []) -> return (matched, [], unused)
|
|
|
|
([], _) -> return (matched, rs, unused)
|
|
|
|
(g : gs', _) -> do
|
|
|
|
(ts, unmatched, us) <- matchGroup g rs
|
|
|
|
go (ts ++ matched, us ++ unused) gs' unmatched
|
|
|
|
|
2023-06-29 21:32:14 -04:00
|
|
|
matchGroup
|
|
|
|
:: MonadFinance m
|
|
|
|
=> MatchGroup
|
|
|
|
-> [TxRecord]
|
2023-08-13 13:29:38 -04:00
|
|
|
-> AppExceptT m ([Tx ()], [TxRecord], [StatementParserRe])
|
2023-05-29 17:19:49 -04:00
|
|
|
matchGroup MatchGroup {mgDate = ds, mgNoDate = ns} rs = do
|
|
|
|
(md, rest, ud) <- matchDates ds rs
|
|
|
|
(mn, unmatched, un) <- matchNonDates ns rest
|
|
|
|
return (md ++ mn, unmatched, filter ((/= Nothing) . spTimes) $ ud ++ un)
|
|
|
|
|
2023-06-29 21:32:14 -04:00
|
|
|
matchDates
|
|
|
|
:: MonadFinance m
|
2023-08-13 13:29:38 -04:00
|
|
|
=> [StatementParserRe]
|
2023-06-29 21:32:14 -04:00
|
|
|
-> [TxRecord]
|
2023-08-13 13:29:38 -04:00
|
|
|
-> AppExceptT m ([Tx ()], [TxRecord], [StatementParserRe])
|
2023-05-29 17:19:49 -04:00
|
|
|
matchDates ms = go ([], [], initZipper ms)
|
|
|
|
where
|
|
|
|
go (matched, unmatched, z) [] =
|
|
|
|
return
|
|
|
|
( catMaybes matched
|
|
|
|
, reverse unmatched
|
|
|
|
, recoverZipper z
|
|
|
|
)
|
|
|
|
go (matched, unmatched, z) (r : rs) =
|
|
|
|
case zipperSlice findDate r z of
|
|
|
|
Left zipped -> go (matched, r : unmatched, zipped) rs
|
|
|
|
Right unzipped -> do
|
|
|
|
(z', res) <- zipperMatch unzipped r
|
|
|
|
let (m, u) = case res of
|
|
|
|
(MatchPass p) -> (Just p : matched, unmatched)
|
|
|
|
MatchSkip -> (Nothing : matched, unmatched)
|
|
|
|
MatchFail -> (matched, r : unmatched)
|
|
|
|
go (m, u, z') rs
|
|
|
|
findDate m r = maybe EQ (`compareDate` trDate r) $ spDate m
|
|
|
|
|
2023-06-29 21:32:14 -04:00
|
|
|
matchNonDates
|
|
|
|
:: MonadFinance m
|
2023-08-13 13:29:38 -04:00
|
|
|
=> [StatementParserRe]
|
2023-06-29 21:32:14 -04:00
|
|
|
-> [TxRecord]
|
2023-08-13 13:29:38 -04:00
|
|
|
-> AppExceptT m ([Tx ()], [TxRecord], [StatementParserRe])
|
2023-05-29 17:19:49 -04:00
|
|
|
matchNonDates ms = go ([], [], initZipper ms)
|
|
|
|
where
|
|
|
|
go (matched, unmatched, z) [] =
|
|
|
|
return
|
|
|
|
( catMaybes matched
|
|
|
|
, reverse unmatched
|
|
|
|
, recoverZipper z
|
|
|
|
)
|
|
|
|
go (matched, unmatched, z) (r : rs) = do
|
|
|
|
(z', res) <- zipperMatch' z r
|
|
|
|
let (m, u) = case res of
|
|
|
|
MatchPass p -> (Just p : matched, unmatched)
|
|
|
|
MatchSkip -> (Nothing : matched, unmatched)
|
|
|
|
MatchFail -> (matched, r : unmatched)
|
|
|
|
in go (m, u, resetZipper z') rs
|
2023-07-04 00:11:25 -04:00
|
|
|
|
2023-08-13 13:29:38 -04:00
|
|
|
matches
|
|
|
|
:: MonadFinance m
|
|
|
|
=> StatementParserRe
|
|
|
|
-> TxRecord
|
|
|
|
-> AppExceptT m (MatchRes (Tx ()))
|
2023-07-04 00:11:25 -04:00
|
|
|
matches
|
2023-07-07 00:20:18 -04:00
|
|
|
StatementParser {spTx, spOther, spVal, spDate, spDesc, spPriority}
|
2023-07-04 00:11:25 -04:00
|
|
|
r@TxRecord {trDate, trAmount, trDesc, trOther} = do
|
|
|
|
res <- liftInner $
|
|
|
|
combineError3 val other desc $
|
|
|
|
\x y z -> x && y && z && date
|
|
|
|
if res
|
|
|
|
then maybe (return MatchSkip) convert spTx
|
|
|
|
else return MatchFail
|
|
|
|
where
|
2023-07-08 00:52:40 -04:00
|
|
|
val = valMatches spVal $ toRational trAmount
|
2023-07-04 00:11:25 -04:00
|
|
|
date = maybe True (`dateMatches` trDate) spDate
|
|
|
|
other = foldM (\a o -> (a &&) <$> otherMatches trOther o) True spOther
|
2023-07-16 00:39:03 -04:00
|
|
|
desc = maybe (return True) (matchMaybe (unTxDesc trDesc) . snd) spDesc
|
2023-07-07 00:20:18 -04:00
|
|
|
convert tg = MatchPass <$> toTx (fromIntegral spPriority) tg r
|
2023-07-04 00:11:25 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
toTx :: MonadFinance m => Int -> TxGetter -> TxRecord -> AppExceptT m (Tx ())
|
2023-07-04 00:11:25 -04:00
|
|
|
toTx
|
2023-07-07 00:20:18 -04:00
|
|
|
priority
|
2023-07-04 00:11:25 -04:00
|
|
|
TxGetter
|
|
|
|
{ tgFrom
|
|
|
|
, tgTo
|
|
|
|
, tgCurrency
|
|
|
|
, tgOtherEntries
|
|
|
|
, tgScale
|
|
|
|
}
|
|
|
|
r@TxRecord {trAmount, trDate, trDesc} = do
|
|
|
|
combineError curRes subRes $ \(cur, f, t) ss ->
|
|
|
|
Tx
|
2023-07-21 19:57:54 -04:00
|
|
|
{ txMeta = TxMeta trDate priority trDesc ()
|
2023-07-04 00:11:25 -04:00
|
|
|
, txPrimary =
|
|
|
|
Left $
|
|
|
|
EntrySet
|
2023-07-16 00:20:01 -04:00
|
|
|
{ esTotalValue = roundToP (cpPrec cur) trAmount *. tgScale
|
2023-07-08 00:52:40 -04:00
|
|
|
, esCurrency = cpID cur
|
2023-07-04 00:11:25 -04:00
|
|
|
, esFrom = f
|
|
|
|
, esTo = t
|
|
|
|
}
|
2023-07-07 00:20:18 -04:00
|
|
|
, txOther = Left <$> ss
|
2023-07-04 00:11:25 -04:00
|
|
|
}
|
|
|
|
where
|
|
|
|
curRes = do
|
2023-07-20 00:25:33 -04:00
|
|
|
m <- asks tsCurrencyMap
|
2023-07-04 00:11:25 -04:00
|
|
|
cur <- liftInner $ resolveCurrency m r tgCurrency
|
2023-07-08 00:52:40 -04:00
|
|
|
let prec = cpPrec cur
|
|
|
|
let fromRes = liftInner $ resolveHalfEntry resolveFromValue prec r () tgFrom
|
|
|
|
let toRes = liftInner $ resolveHalfEntry resolveToValue prec r () tgTo
|
2023-07-04 00:11:25 -04:00
|
|
|
combineError fromRes toRes (cur,,)
|
|
|
|
subRes = mapErrors (resolveSubGetter r) tgOtherEntries
|
|
|
|
|
|
|
|
resolveSubGetter
|
|
|
|
:: MonadFinance m
|
|
|
|
=> TxRecord
|
|
|
|
-> TxSubGetter
|
2023-07-16 19:55:33 -04:00
|
|
|
-> AppExceptT m SecondayEntrySet
|
2023-07-04 00:11:25 -04:00
|
|
|
resolveSubGetter r TxSubGetter {tsgFrom, tsgTo, tsgValue, tsgCurrency} = do
|
2023-07-20 00:25:33 -04:00
|
|
|
m <- asks tsCurrencyMap
|
2023-07-04 00:11:25 -04:00
|
|
|
cur <- liftInner $ resolveCurrency m r tsgCurrency
|
2023-07-08 00:52:40 -04:00
|
|
|
let prec = cpPrec cur
|
|
|
|
let toRes = resolveHalfEntry resolveToValue prec r () tsgTo
|
|
|
|
let valRes = liftInner $ resolveValue prec r tsgValue
|
2023-07-04 00:11:25 -04:00
|
|
|
liftInner $ combineErrorM toRes valRes $ \t v -> do
|
2023-07-08 00:52:40 -04:00
|
|
|
f <- resolveHalfEntry resolveFromValue prec r v tsgFrom
|
2023-07-04 00:11:25 -04:00
|
|
|
return $
|
|
|
|
EntrySet
|
|
|
|
{ esTotalValue = ()
|
2023-07-08 00:52:40 -04:00
|
|
|
, esCurrency = cpID cur
|
2023-07-04 00:11:25 -04:00
|
|
|
, esFrom = f
|
|
|
|
, esTo = t
|
|
|
|
}
|
|
|
|
|
|
|
|
resolveHalfEntry
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (Precision -> TxRecord -> n -> AppExcept v')
|
2023-07-08 00:52:40 -04:00
|
|
|
-> Precision
|
2023-07-04 00:11:25 -04:00
|
|
|
-> TxRecord
|
|
|
|
-> v
|
|
|
|
-> TxHalfGetter (EntryGetter n)
|
2023-07-16 19:55:33 -04:00
|
|
|
-> AppExcept (HalfEntrySet v v')
|
2023-07-08 00:52:40 -04:00
|
|
|
resolveHalfEntry f prec r v TxHalfGetter {thgAcnt, thgComment, thgTags, thgEntries} =
|
2023-07-04 00:11:25 -04:00
|
|
|
combineError acntRes esRes $ \a es ->
|
|
|
|
HalfEntrySet
|
|
|
|
{ hesPrimary =
|
|
|
|
Entry
|
|
|
|
{ eAcnt = a
|
|
|
|
, eValue = v
|
|
|
|
, eComment = thgComment
|
|
|
|
, eTags = thgTags
|
|
|
|
}
|
|
|
|
, hesOther = es
|
|
|
|
}
|
|
|
|
where
|
|
|
|
acntRes = resolveAcnt r thgAcnt
|
2023-07-08 00:52:40 -04:00
|
|
|
esRes = mapErrors (resolveEntry f prec r) thgEntries
|
2023-07-04 00:11:25 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
otherMatches :: M.Map T.Text T.Text -> FieldMatcherRe -> AppExcept Bool
|
2023-07-04 00:11:25 -04:00
|
|
|
otherMatches dict m = case m of
|
|
|
|
Val (Field n mv) -> valMatches mv =<< (readRational =<< lookup_ MatchNumeric n)
|
|
|
|
Desc (Field n (_, md)) -> (`matchMaybe` md) =<< lookup_ MatchText n
|
|
|
|
where
|
|
|
|
lookup_ t n = lookupErr (MatchField t) n dict
|
|
|
|
|
|
|
|
resolveEntry
|
2023-07-16 19:55:33 -04:00
|
|
|
:: (Precision -> TxRecord -> n -> AppExcept v)
|
2023-07-08 00:52:40 -04:00
|
|
|
-> Precision
|
2023-07-04 00:11:25 -04:00
|
|
|
-> TxRecord
|
|
|
|
-> EntryGetter n
|
2023-07-16 19:55:33 -04:00
|
|
|
-> AppExcept (Entry AcntID v TagID)
|
2023-07-08 00:52:40 -04:00
|
|
|
resolveEntry f prec r s@Entry {eAcnt, eValue} =
|
|
|
|
combineError acntRes valRes $ \a v -> s {eAcnt = a, eValue = v}
|
2023-07-04 00:11:25 -04:00
|
|
|
where
|
|
|
|
acntRes = resolveAcnt r eAcnt
|
2023-07-08 00:52:40 -04:00
|
|
|
valRes = f prec r eValue
|
2023-07-04 00:11:25 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
resolveFromValue :: Precision -> TxRecord -> EntryNumGetter -> AppExcept EntryValue
|
2023-07-04 00:11:25 -04:00
|
|
|
resolveFromValue = resolveValue
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
resolveToValue :: Precision -> TxRecord -> LinkedEntryNumGetter -> AppExcept EntryLink
|
2023-07-08 00:52:40 -04:00
|
|
|
resolveToValue _ _ (Linked l) = return $ LinkIndex l
|
2023-07-16 12:51:39 -04:00
|
|
|
resolveToValue prec r (Getter g) = LinkValue <$> resolveValue prec r g
|
2023-07-08 00:52:40 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
resolveValue :: Precision -> TxRecord -> EntryNumGetter -> AppExcept EntryValue
|
2023-07-08 00:52:40 -04:00
|
|
|
resolveValue prec TxRecord {trOther, trAmount} s = case s of
|
|
|
|
(LookupN t) -> EntryFixed . go <$> (readDouble =<< lookupErr EntryValField t trOther)
|
|
|
|
(ConstN c) -> return $ EntryFixed $ go c
|
|
|
|
AmountN m -> return $ EntryFixed $ trAmount *. m
|
|
|
|
BalanceN x -> return $ EntryBalance $ go x
|
|
|
|
PercentN x -> return $ EntryPercent x
|
|
|
|
where
|
2023-07-16 19:55:33 -04:00
|
|
|
go = realFracToDecimalP prec
|
2023-07-04 00:11:25 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
resolveAcnt :: TxRecord -> EntryAcnt -> AppExcept AcntID
|
2023-07-16 00:10:49 -04:00
|
|
|
resolveAcnt r e = AcntID <$> resolveEntryField AcntField r (unAcntID <$> e)
|
2023-07-04 00:11:25 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
resolveCurrency :: CurrencyMap -> TxRecord -> EntryCur -> AppExcept CurrencyPrec
|
2023-07-04 00:11:25 -04:00
|
|
|
resolveCurrency m r c = do
|
2023-07-16 00:10:49 -04:00
|
|
|
i <- resolveEntryField CurField r (unCurID <$> c)
|
|
|
|
case M.lookup (CurID i) m of
|
2023-07-04 00:11:25 -04:00
|
|
|
Just k -> return k
|
2023-07-16 19:55:33 -04:00
|
|
|
Nothing -> throwError $ AppException [LookupError (DBKey CurField) i]
|
2023-07-04 00:11:25 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
resolveEntryField :: EntryIDType -> TxRecord -> EntryTextGetter T.Text -> AppExcept T.Text
|
2023-07-04 00:11:25 -04:00
|
|
|
resolveEntryField t TxRecord {trOther = o} s = case s of
|
|
|
|
ConstT p -> return p
|
|
|
|
LookupT f -> lookup_ f o
|
|
|
|
MapT (Field f m) -> do
|
|
|
|
k <- lookup_ f o
|
|
|
|
lookup_ k m
|
|
|
|
Map2T (Field (f1, f2) m) -> do
|
|
|
|
(k1, k2) <- combineError (lookup_ f1 o) (lookup_ f2 o) (,)
|
|
|
|
lookup_ (k1, k2) m
|
|
|
|
where
|
2023-07-16 19:55:33 -04:00
|
|
|
lookup_ :: (Ord k, Show k) => k -> M.Map k v -> AppExcept v
|
2023-07-04 00:11:25 -04:00
|
|
|
lookup_ = lookupErr (EntryIDField t)
|
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
readDouble :: T.Text -> AppExcept Double
|
2023-07-04 00:11:25 -04:00
|
|
|
readDouble s = case readMaybe $ T.unpack s of
|
|
|
|
Just x -> return x
|
2023-07-16 19:55:33 -04:00
|
|
|
Nothing -> throwError $ AppException [ConversionError s True]
|
2023-07-04 00:11:25 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
readRational :: T.Text -> AppExcept Rational
|
2023-07-04 00:11:25 -04:00
|
|
|
readRational s = case T.split (== '.') s of
|
|
|
|
[x] -> maybe err (return . fromInteger) $ readT x
|
|
|
|
[x, y] -> case (readT x, readT y) of
|
|
|
|
(Just x', Just y') ->
|
|
|
|
let p = 10 ^ T.length y
|
|
|
|
k = if x' >= 0 then 1 else -1
|
|
|
|
in return $ fromInteger x' + k * y' % p
|
|
|
|
_ -> err
|
|
|
|
_ -> err
|
|
|
|
where
|
|
|
|
readT = readMaybe . T.unpack
|
2023-07-16 19:55:33 -04:00
|
|
|
err = throwError $ AppException [ConversionError s False]
|
2023-07-04 00:11:25 -04:00
|
|
|
|
2023-07-16 19:55:33 -04:00
|
|
|
compileOptions :: TxOpts T.Text -> AppExcept TxOptsRe
|
2023-08-16 21:01:06 -04:00
|
|
|
compileOptions = mapM (compileRegex True)
|
|
|
|
|
|
|
|
-- compileOptions o@TxOpts {toAmount = pat} = case pat of
|
|
|
|
-- AmountSingle (TxAmount1 {a1Fmt}) -> do
|
|
|
|
-- re <- compileRegex True a1Fmt
|
|
|
|
-- return $ o {toAmountFmt = re}
|
|
|
|
-- AmountDual (TxAmount2 {a2Fmt}) -> do
|
|
|
|
-- re <- compileRegex True a2Fmt
|
|
|
|
-- return $ o {toAmountFmt = re}
|
2023-07-04 00:11:25 -04:00
|
|
|
|
2023-08-13 13:29:38 -04:00
|
|
|
compileMatch :: StatementParser T.Text -> AppExcept StatementParserRe
|
2023-07-04 00:11:25 -04:00
|
|
|
compileMatch m@StatementParser {spDesc, spOther} = do
|
|
|
|
combineError dres ores $ \d os -> m {spDesc = d, spOther = os}
|
|
|
|
where
|
|
|
|
go = compileRegex False
|
|
|
|
dres = mapM go spDesc
|
|
|
|
ores = combineErrors $ fmap (mapM go) spOther
|
|
|
|
|
2023-08-16 21:01:06 -04:00
|
|
|
parseDecimal :: MonadFail m => Bool -> (T.Text, Regex) -> T.Text -> m Decimal
|
|
|
|
parseDecimal wantSign (pat, re) s = case (wantSign, matchGroupsMaybe s re) of
|
|
|
|
(True, [sign, num]) -> do
|
|
|
|
k <- readSign sign
|
|
|
|
x <- readNum num
|
|
|
|
return $ k * x
|
|
|
|
(False, [num]) -> readNum num
|
2023-07-04 00:11:25 -04:00
|
|
|
_ -> msg "malformed decimal"
|
|
|
|
where
|
|
|
|
msg :: MonadFail m => T.Text -> m a
|
|
|
|
msg m =
|
|
|
|
fail $
|
|
|
|
T.unpack $
|
|
|
|
T.unwords [m, "-", keyVals [("pattern", pat), ("query", s)]]
|
|
|
|
readSign x
|
|
|
|
| x == "-" = return (-1)
|
|
|
|
| x == "+" || x == "" = return 1
|
|
|
|
| otherwise = msg $ T.append "invalid sign: " x
|
2023-08-16 21:01:06 -04:00
|
|
|
readNum x =
|
|
|
|
maybe
|
|
|
|
(msg $ T.unwords ["could not parse", singleQuote x])
|
|
|
|
return
|
|
|
|
$ readMaybe
|
|
|
|
$ T.unpack
|
|
|
|
$ T.filter (/= ',') x
|