ENH clean up errors in import
This commit is contained in:
parent
ba19b7e92b
commit
95514df295
|
@ -2,6 +2,7 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
|
||||
module Internal.Statement
|
||||
( readImport
|
||||
|
@ -24,9 +25,9 @@ import qualified RIO.Vector as V
|
|||
-- TODO this probably won't scale well (pipes?)
|
||||
|
||||
readImport :: MonadUnliftIO m => Import -> MappingT m (EitherErrs [BalTx])
|
||||
readImport Import {..} =
|
||||
matchRecords impMatches . L.sort . concat
|
||||
<$> mapM (readImport_ impSkipLines impDelim impTxOpts) impPaths
|
||||
readImport Import {..} = do
|
||||
res <- mapM (readImport_ impSkipLines impDelim impTxOpts) impPaths
|
||||
return $ (matchRecords impMatches . L.sort . concat) =<< concatEitherL res
|
||||
|
||||
readImport_
|
||||
:: MonadUnliftIO m
|
||||
|
@ -34,13 +35,13 @@ readImport_
|
|||
-> Word
|
||||
-> TxOpts
|
||||
-> FilePath
|
||||
-> MappingT m [TxRecord]
|
||||
-> MappingT m (EitherErr [TxRecord])
|
||||
readImport_ n delim tns p = do
|
||||
dir <- asks kmConfigDir
|
||||
bs <- liftIO $ BL.readFile $ dir </> p
|
||||
case decodeByNameWithP (parseTxRecord p tns) opts $ skip bs of
|
||||
Left m -> liftIO $ putStrLn m >> return []
|
||||
Right (_, v) -> return $ catMaybes $ V.toList v
|
||||
Left m -> return $ Left $ ParseError $ T.pack m
|
||||
Right (_, v) -> return $ Right $ catMaybes $ V.toList v
|
||||
where
|
||||
opts = defaultDecodeOptions {decDelimiter = fromIntegral delim}
|
||||
skip = BL.intercalate "\n" . L.drop (fromIntegral n) . BL.split 10
|
||||
|
@ -145,10 +146,10 @@ zipperMatch' z x = go z
|
|||
go z' = Right (z', MatchFail)
|
||||
|
||||
matchDec :: Match -> Maybe Match
|
||||
matchDec m@Match {mTimes = t} =
|
||||
if t' == Just 0 then Nothing else Just $ m {mTimes = t'}
|
||||
where
|
||||
t' = fmap pred t
|
||||
matchDec m = case mTimes m of
|
||||
Just 0 -> Nothing
|
||||
Just n -> Just $ m {mTimes = Just $ n - 1}
|
||||
Nothing -> Just m
|
||||
|
||||
matchAll :: [MatchGroup] -> [TxRecord] -> EitherErrs ([RawTx], [TxRecord], [Match])
|
||||
matchAll = go ([], [])
|
||||
|
|
Loading…
Reference in New Issue