WIP cancel transactions on error

This commit is contained in:
Nathan Dwarshuis 2023-01-07 23:42:04 -05:00
parent 28291e72c7
commit eb79b325eb
2 changed files with 44 additions and 31 deletions

View File

@ -23,18 +23,12 @@ import qualified RIO.Vector as V
-- TODO this probably won't scale well (pipes?) -- TODO this probably won't scale well (pipes?)
readImport :: MonadUnliftIO m => Import -> MappingT m [BalTx] readImport :: MonadUnliftIO m => Import -> MappingT m StatementRes
readImport Import {..} = do readImport Import {..} = do
rs <- L.sort . concat <$> mapM (readImport_ impSkipLines impDelim impTxOpts) impPaths rs <- L.sort . concat <$> mapM (readImport_ impSkipLines impDelim impTxOpts) impPaths
case matchRecords impMatches rs of -- TODO show more useful information here (eg which file emitted this
Right (ts, es, notfound) -> do -- error and possibly where)
liftIO $ mapM_ putStrLn $ reverse es return $ matchRecords impMatches rs
liftIO $ mapM_ print notfound
return ts
Left e -> do
liftIO $ print e
-- TODO make sure that a blank list results in a cache reset in the db
return []
readImport_ readImport_
:: MonadUnliftIO m :: MonadUnliftIO m
@ -67,19 +61,15 @@ parseTxRecord TxOpts {..} r = do
d' <- parseTimeM True defaultTimeLocale (T.unpack toDateFmt) d d' <- parseTimeM True defaultTimeLocale (T.unpack toDateFmt) d
return $ Just $ TxRecord d' a e os return $ Just $ TxRecord d' a e os
matchRecords :: [Match] -> [TxRecord] -> PureErr ([BalTx], [String], [Match]) matchRecords :: [Match] -> [TxRecord] -> StatementRes
matchRecords ms rs = do matchRecords ms rs = case matchAll (matchPriorities ms) rs of
(matched, unmatched, notfound) <- matchAll (matchPriorities ms) rs Left e -> StatementFail $ StatementErrors [] [] [e]
let (es, ts) = Right (matched, unmatched, notfound) ->
partitionEithers $ -- TODO record number of times each match hits for debugging
fmap Just . balanceTx <$> catMaybes matched let (errors, matched_) = partitionEithers $ balanceTx <$> matched
let bu = fmap (\x -> T.pack $ "unmatched: " ++ show x) unmatched in case (matched_, unmatched, notfound, errors) of
return (xs, [], [], []) -> StatementPass xs
( catMaybes ts (_, us, ns, es) -> StatementFail $ StatementErrors us ns es
, T.unpack <$> (es ++ bu)
, -- TODO record number of times each match hits for debugging
notfound
)
matchPriorities :: [Match] -> [MatchGroup] matchPriorities :: [Match] -> [MatchGroup]
matchPriorities = matchPriorities =
@ -156,7 +146,7 @@ matchDec m@Match {mTimes = t} =
where where
t' = fmap pred t t' = fmap pred t
matchAll :: [MatchGroup] -> [TxRecord] -> PureErr ([Maybe RawTx], [TxRecord], [Match]) matchAll :: [MatchGroup] -> [TxRecord] -> PureErr ([RawTx], [TxRecord], [Match])
matchAll = go ([], []) matchAll = go ([], [])
where where
go (matched, unused) gs rs = case (gs, rs) of go (matched, unused) gs rs = case (gs, rs) of
@ -166,16 +156,21 @@ matchAll = go ([], [])
(ts, unmatched, us) <- matchGroup g rs (ts, unmatched, us) <- matchGroup g rs
go (ts ++ matched, us ++ unused) gs' unmatched go (ts ++ matched, us ++ unused) gs' unmatched
matchGroup :: MatchGroup -> [TxRecord] -> PureErr ([Maybe RawTx], [TxRecord], [Match]) matchGroup :: MatchGroup -> [TxRecord] -> PureErr ([RawTx], [TxRecord], [Match])
matchGroup MatchGroup {mgDate = ds, mgNoDate = ns} rs = do matchGroup MatchGroup {mgDate = ds, mgNoDate = ns} rs = do
(md, rest, ud) <- matchDates ds rs (md, rest, ud) <- matchDates ds rs
(mn, unmatched, un) <- matchNonDates ns rest (mn, unmatched, un) <- matchNonDates ns rest
return (md ++ mn, unmatched, filter ((/= Nothing) . mTimes) $ ud ++ un) return (md ++ mn, unmatched, filter ((/= Nothing) . mTimes) $ ud ++ un)
matchDates :: [Match] -> [TxRecord] -> PureErr ([Maybe RawTx], [TxRecord], [Match]) matchDates :: [Match] -> [TxRecord] -> PureErr ([RawTx], [TxRecord], [Match])
matchDates ms = go ([], [], initZipper ms) matchDates ms = go ([], [], initZipper ms)
where where
go (matched, unmatched, z) [] = Right (matched, reverse unmatched, recoverZipper z) go (matched, unmatched, z) [] =
Right
( catMaybes matched
, reverse unmatched
, recoverZipper z
)
go (matched, unmatched, z) (r : rs) = case zipperSlice findDate r z of go (matched, unmatched, z) (r : rs) = case zipperSlice findDate r z of
Left zipped -> go (matched, r : unmatched, zipped) rs Left zipped -> go (matched, r : unmatched, zipped) rs
Right unzipped -> do Right unzipped -> do
@ -187,10 +182,15 @@ matchDates ms = go ([], [], initZipper ms)
go (m, u, z') rs go (m, u, z') rs
findDate m r = maybe EQ (`compareDate` trDate r) $ mDate m findDate m r = maybe EQ (`compareDate` trDate r) $ mDate m
matchNonDates :: [Match] -> [TxRecord] -> PureErr ([Maybe RawTx], [TxRecord], [Match]) matchNonDates :: [Match] -> [TxRecord] -> PureErr ([RawTx], [TxRecord], [Match])
matchNonDates ms = go ([], [], initZipper ms) matchNonDates ms = go ([], [], initZipper ms)
where where
go (matched, unmatched, z) [] = Right (matched, reverse unmatched, recoverZipper z) go (matched, unmatched, z) [] =
Right
( catMaybes matched
, reverse unmatched
, recoverZipper z
)
go (matched, unmatched, z) (r : rs) = do go (matched, unmatched, z) (r : rs) = do
(z', res) <- zipperMatch' z r (z', res) <- zipperMatch' z r
let (m, u) = case res of let (m, u) = case res of
@ -199,12 +199,12 @@ matchNonDates ms = go ([], [], initZipper ms)
MatchFail -> (matched, r : unmatched) MatchFail -> (matched, r : unmatched)
in go (m, u, resetZipper z') rs in go (m, u, resetZipper z') rs
balanceTx :: RawTx -> Either T.Text BalTx balanceTx :: RawTx -> PureErr BalTx
balanceTx t@Tx {txSplits = ss} = do balanceTx t@Tx {txSplits = ss} = do
bs <- balanceSplits ss bs <- balanceSplits ss
return $ t {txSplits = bs} return $ t {txSplits = bs}
balanceSplits :: [RawSplit] -> Either T.Text [BalSplit] balanceSplits :: [RawSplit] -> PureErr [BalSplit]
balanceSplits ss = balanceSplits ss =
fmap concat fmap concat
<$> mapM (uncurry bal) <$> mapM (uncurry bal)

View File

@ -506,3 +506,16 @@ type BalTx = Tx BalSplit
type PureErr a = Either T.Text a type PureErr a = Either T.Text a
data MatchRes a = MatchPass a | MatchFail | MatchSkip data MatchRes a = MatchPass a | MatchFail | MatchSkip
data InsertException = MatchException | RegexException deriving (Show)
-- TODO retain file information here for clearer printing purposes
data StatementErrors = StatementErrors
{ seUnmatched :: [TxRecord]
, seNotFound :: [Match]
, seErrors :: [T.Text]
}
data StatementRes = StatementPass [BalTx] | StatementFail StatementErrors
instance Exception InsertException