Compare commits

...

14 Commits

9 changed files with 467 additions and 226 deletions

View File

@ -204,15 +204,12 @@ runDumpAccountKeys c = do
runSync :: Int -> FilePath -> [FilePath] -> [FilePath] -> IO () runSync :: Int -> FilePath -> [FilePath] -> [FilePath] -> IO ()
runSync threads c bs hs = do runSync threads c bs hs = do
setNumCapabilities threads setNumCapabilities threads
-- putStrLn "reading config"
config <- readConfig c config <- readConfig c
-- putStrLn "reading statements"
(bs', hs') <- (bs', hs') <-
fmap (bimap concat concat . partitionEithers) $ fmap (bimap concat concat . partitionEithers) $
pooledMapConcurrentlyN threads (bimapM readDhall readDhall) $ pooledMapConcurrentlyN threads (bimapM readDhall readDhall) $
(Left <$> bs) ++ (Right <$> hs) (Left <$> bs) ++ (Right <$> hs)
pool <- runNoLoggingT $ mkPool $ sqlConfig config pool <- runNoLoggingT $ mkPool $ sqlConfig config
putStrLn "doing other stuff"
setNumCapabilities 1 setNumCapabilities 1
handle err $ sync pool root config bs' hs' handle err $ sync pool root config bs' hs'
where where

View File

@ -278,54 +278,126 @@ let DatePat =
-} -}
< Cron : CronPat.Type | Mod : ModPat.Type > < Cron : CronPat.Type | Mod : ModPat.Type >
let TxOpts_ = let TxAmount1_ =
{- Additional metadata to use when parsing a statement -}
\(re : Type) -> \(re : Type) ->
{ Type = { a1Column : Text
{ toDate : , a1Fmt :
{- {-
Column title for date Format of the amount field. Must include three fields for the
-} sign, numerator, and denominator of the amount.
Text -}
, toAmount : re
{-
Column title for amount
-}
Text
, toDesc :
{-
Column title for description
-}
Text
, toOther :
{-
Titles of other columns to include; these will be available in
a map for use in downstream processing (see 'Field')
-}
List Text
, toDateFmt :
{-
Format of the date field as specified in the
Data.Time.Format.formattime Haskell function.
-}
Text
, toAmountFmt :
{- Format of the amount field. Must include three fields for the
sign, numerator, and denominator of the amount.
-}
re
}
, default =
{ toDate = "Date"
, toAmount = "Amount"
, toDesc = "Description"
, toOther = [] : List Text
, toDateFmt = "%0m/%0d/%Y"
, toAmountFmt = "([-+])?([0-9]+)\\.?([0-9]+)?"
}
} }
let TxOpts = TxOpts_ Text let TxAmount1 =
{ Type = TxAmount1_ Text
, default = { a1Column = "Amount", a1Fmt = "([-+])?([0-9\\.]+)" }
}
let TxAmount2_ =
\(re : Type) ->
{ a2Positive : Text
, a2Negative : Text
, a2Fmt :
{-
Format of the amount field. Must include two fields for the
numerator and denominator of the amount.
-}
re
}
let TxAmount2 =
{ Type = TxAmount2_ Text
, default =
{ a2Positive = "Deposit"
, a2Negative = "Withdraw"
, a2Fmt = "([0-9\\.]+)"
}
}
let TxAmountSpec_ =
\(re : Type) ->
< AmountSingle : TxAmount1_ re | AmountDual : TxAmount2_ re >
let TxOpts_ =
{-
Additional metadata to use when parsing a statement
-}
\(re : Type) ->
{ toDate :
{-
Column title for date
-}
Text
, toAmount :
{-
Column title for amount
-}
TxAmountSpec_ re
, toDesc :
{-
Column title for description
-}
Text
, toOther :
{-
Titles of other columns to include; these will be available in
a map for use in downstream processing (see 'Field')
-}
List Text
, toDateFmt :
{-
Format of the date field as specified in the
Data.Time.Format.formattime Haskell function.
-}
Text
, toSkipBlankDate :
{-
Skip line if date field is a blank
-}
Bool
, toSkipBlankAmount :
{-
Skip line if amount field(s) is(are) a blank
-}
Bool
, toSkipBlankDescription :
{-
Skip line if description field is a blank
-}
Bool
, toSkipBlankOther :
{-
Skip line if any arbitrary fields are blank (these fields must also
be listed in 'toOther' to be considered)
-}
List Text
, toSkipMissingFields :
{-
Skip line if any fields are missing (this is different from blank;
'missing' means there is no field with name 'X', 'blank' means that
there is a field 'X' and its value is an empty string)
-}
Bool
}
let TxAmountSpec = TxAmountSpec_ Text
let TxOpts =
{ Type = TxOpts_ Text
, default =
{ toDate = "Date"
, toAmount = TxAmountSpec.AmountSingle TxAmount1::{=}
, toDesc = "Description"
, toOther = [] : List Text
, toDateFmt = "%0m/%0d/%Y"
, toSkipBlankDate = False
, toSkipBlankAmount = False
, toSkipBlankDescription = False
, toSkipBlankOther = [] : List Text
, toSkipMissingFields = False
}
}
let Field = let Field =
{- {-
@ -984,54 +1056,40 @@ let Income =
} }
} }
let AcntSet = let AcntMatcher_ =
{- {-
A list of account IDs represented as a set. Regex pattern by which matching account ids will be identified
-} -}
{ Type = \(re : Type) ->
{ asList : List AcntID { Type = { amPat : re, amInvert : Bool }, default.amInvert = False }
, asInclude :
{-
If true, tests for account membership in this set will return
true if the account is in the set. Invert this behavior otherwise.
-}
Bool
}
, default = { asList = [] : List AcntID, asInclude = False }
}
let TransferMatcher = let AcntMatcher = AcntMatcher_ Text
let TransferMatcher_ =
{- {-
Means to match a transfer (which will be used to "clone" it in some Means to match a transfer (which will be used to "clone" it in some
fashion) fashion)
-} -}
{ Type = \(re : Type) ->
{ tmFrom : { tmFrom : Optional (AcntMatcher_ re).Type
{- , tmTo : Optional (AcntMatcher_ re).Type
List of accounts (which may be empty) to match with the , tmDate :
starting account in a transfer. {-
-} If given, means to match the date of a transfer.
AcntSet.Type -}
, tmTo : Optional DateMatcher
{- , tmVal :
List of accounts (which may be empty) to match with the {-
ending account in a transfer. If given, means to match the value of a transfer.
-} -}
AcntSet.Type ValMatcher.Type
, tmDate : }
{-
If given, means to match the date of a transfer. let TransferMatcher =
-} { Type = TransferMatcher_ Text
Optional DateMatcher
, tmVal :
{-
If given, means to match the value of a transfer.
-}
ValMatcher.Type
}
, default = , default =
{ tmFrom = AcntSet.default { tmFrom = None AcntMatcher.Type
, tmTo = AcntSet.default , tmTo = None AcntMatcher.Type
, tmDate = None DateMatcher , tmDate = None DateMatcher
, tmVal = ValMatcher.default , tmVal = ValMatcher.default
} }
@ -1148,9 +1206,9 @@ in { CurID
, Budget , Budget
, Allocation , Allocation
, Amount , Amount
, TransferMatcher_
, TransferMatcher , TransferMatcher
, ShadowTransfer , ShadowTransfer
, AcntSet
, TaggedAcnt , TaggedAcnt
, AccountTree , AccountTree
, Account , Account
@ -1177,4 +1235,13 @@ in { CurID
, TransferAmount , TransferAmount
, MultiAlloAmount , MultiAlloAmount
, SingleAlloAmount , SingleAlloAmount
, AcntMatcher_
, AcntMatcher
, TxAmountSpec
, TxAmountSpec_
, TxAmount1_
, TxAmount2_
, TxAmount1
, TxAmount2
, BudgetTransfer
} }

View File

@ -38,9 +38,8 @@ readBudget
(intAllos, _) <- combineError intAlloRes acntRes (,) (intAllos, _) <- combineError intAlloRes acntRes (,)
let res1 = mapErrors (readIncome c intAllos budgetSpan) bgtIncomes let res1 = mapErrors (readIncome c intAllos budgetSpan) bgtIncomes
let res2 = expandTransfers c budgetSpan bgtTransfers let res2 = expandTransfers c budgetSpan bgtTransfers
txs <- combineError (concat <$> res1) res2 (++) combineErrorM (concat <$> res1) res2 $ \is ts ->
shadow <- addShadowTransfers bgtShadowTransfers txs addShadowTransfers bgtShadowTransfers (is ++ ts)
return $ txs ++ shadow
where where
c = CommitR (CommitHash $ hash b) CTBudget c = CommitR (CommitHash $ hash b) CTBudget
acntRes = mapErrors isNotIncomeAcnt alloAcnts acntRes = mapErrors isNotIncomeAcnt alloAcnts
@ -146,7 +145,7 @@ readIncome
let allos = allo2Trans <$> (pre ++ tax ++ post) let allos = allo2Trans <$> (pre ++ tax ++ post)
let primary = let primary =
EntrySet EntrySet
{ esTotalValue = gross { esTotalValue = -gross
, esCurrency = cpID cp , esCurrency = cpID cp
, esFrom = HalfEntrySet {hesPrimary = src, hesOther = []} , esFrom = HalfEntrySet {hesPrimary = src, hesOther = []}
, esTo = HalfEntrySet {hesPrimary = dest, hesOther = allos} , esTo = HalfEntrySet {hesPrimary = dest, hesOther = allos}
@ -346,26 +345,31 @@ fromShadow
-> ShadowTransfer -> ShadowTransfer
-> m (Maybe ShadowEntrySet) -> m (Maybe ShadowEntrySet)
fromShadow tx ShadowTransfer {stFrom, stTo, stDesc, stRatio, stCurrency, stMatch} = fromShadow tx ShadowTransfer {stFrom, stTo, stDesc, stRatio, stCurrency, stMatch} =
combineErrorM curRes shaRes $ \cur sha -> do combineErrorM curRes mRes $ \cur compiled -> do
res <- liftExcept $ shadowMatches compiled tx
let es = entryPair stFrom stTo cur stDesc stRatio () let es = entryPair stFrom stTo cur stDesc stRatio ()
return $ if not sha then Nothing else Just es return $ if not res then Nothing else Just es
where where
curRes = lookupCurrencyKey (CurID stCurrency) curRes = lookupCurrencyKey stCurrency
shaRes = liftExcept $ shadowMatches stMatch tx mRes = liftExcept $ compileMatch stMatch
shadowMatches :: TransferMatcher -> Tx CommitR -> AppExcept Bool shadowMatches :: TransferMatcherRe -> Tx CommitR -> AppExcept Bool
shadowMatches shadowMatches
TransferMatcher {tmFrom, tmTo, tmDate, tmVal} TransferMatcher_ {tmFrom, tmTo, tmDate, tmVal}
Tx {txPrimary, txMeta = TxMeta {txmDate}} = Tx {txPrimary, txMeta = TxMeta {txmDate}} =
do do
-- ASSUME these will never fail and thus I don't need to worry about
-- stacking the errors
fromRes <- acntMatches fa tmFrom
toRes <- acntMatches ta tmTo
-- NOTE this will only match against the primary entry set since those -- NOTE this will only match against the primary entry set since those
-- are what are guaranteed to exist from a transfer -- are what are guaranteed to exist from a transfer
valRes <- case txPrimary of valRes <- case txPrimary of
Left es -> valMatches tmVal $ toRational $ esTotalValue es Left es -> valMatches tmVal $ toRational $ esTotalValue es
Right _ -> return True Right _ -> return True
return $ return $
memberMaybe fa tmFrom fromRes
&& memberMaybe ta tmTo && toRes
&& maybe True (`dateMatches` txmDate) tmDate && maybe True (`dateMatches` txmDate) tmDate
&& valRes && valRes
where where
@ -374,8 +378,22 @@ shadowMatches
getAcntFrom = getAcnt esFrom getAcntFrom = getAcnt esFrom
getAcntTo = getAcnt esTo getAcntTo = getAcnt esTo
getAcnt f = eAcnt . hesPrimary . f getAcnt f = eAcnt . hesPrimary . f
memberMaybe x AcntSet {asList, asInclude} = acntMatches (AcntID a) = maybe (return True) (match' a)
(if asInclude then id else not) $ x `elem` (AcntID <$> asList) match' a AcntMatcher_ {amPat, amInvert} =
(if amInvert then not else id) <$> matchMaybe a amPat
compileMatch :: TransferMatcher_ T.Text -> AppExcept TransferMatcherRe
compileMatch m@TransferMatcher_ {tmTo, tmFrom} =
combineError tres fres $ \t f -> m {tmTo = t, tmFrom = f}
where
go a@AcntMatcher_ {amPat} = do
(_, p) <- compileRegex False amPat
return $ a {amPat = p}
tres = mapM go tmTo
fres = mapM go tmFrom
-- memberMaybe x AcntSet {asList, asInclude} =
-- (if asInclude then id else not) $ x `elem` (AcntID <$> asList)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- random -- random

View File

@ -1,5 +1,3 @@
{-# LANGUAGE ImplicitPrelude #-}
module Internal.Database module Internal.Database
( runDB ( runDB
, readDB , readDB
@ -24,6 +22,7 @@ import Control.Monad.IO.Rerunnable
import Control.Monad.Logger import Control.Monad.Logger
import Data.Decimal import Data.Decimal
import Data.Hashable import Data.Hashable
import qualified Data.Text.IO as TI
import Database.Esqueleto.Experimental ((:&) (..), (==.), (?.), (^.)) import Database.Esqueleto.Experimental ((:&) (..), (==.), (?.), (^.))
import qualified Database.Esqueleto.Experimental as E import qualified Database.Esqueleto.Experimental as E
import Database.Esqueleto.Internal.Internal (SqlSelect) import Database.Esqueleto.Internal.Internal (SqlSelect)
@ -40,12 +39,11 @@ import Database.Persist.Sqlite hiding
, (==.) , (==.)
, (||.) , (||.)
) )
-- import GHC.Err
import Internal.Budget import Internal.Budget
import Internal.History import Internal.History
import Internal.Types.Main import Internal.Types.Main
import Internal.Utils import Internal.Utils
import RIO hiding (LogFunc, isNothing, on, (^.)) import RIO hiding (LogFunc, isNothing, logDebug, on, (^.))
import qualified RIO.List as L import qualified RIO.List as L
import qualified RIO.Map as M import qualified RIO.Map as M
import qualified RIO.NonEmpty as NE import qualified RIO.NonEmpty as NE
@ -75,15 +73,7 @@ sync pool root c bs hs = do
b <- liftIOExceptT $ readBudgetCRUD budgets b <- liftIOExceptT $ readBudgetCRUD budgets
h <- readHistoryCRUD root history h <- readHistoryCRUD root history
return (b, h) return (b, h)
-- liftIO $ print $ length $ coCreate budgets liftIO $ TI.putStr $ formatBuildPlan history budgets
liftIO $ print $ length $ fst $ coCreate history
liftIO $ print $ bimap length length $ coCreate history
liftIO $ print $ length $ coRead history
liftIO $ print $ length $ coUpdate history
liftIO $ print $ (\(DeleteTxs e a b c' d) -> (length e, length a, length b, length c', length d)) $ coDelete history
-- liftIO $ print $ length $ M.elems $ tsAccountMap txState
-- liftIO $ print $ length $ M.elems $ tsCurrencyMap txState
-- liftIO $ print $ length $ M.elems $ tsTagMap txState
-- Update the DB. -- Update the DB.
runSqlQueryT pool $ withTransaction $ flip runReaderT txState $ do runSqlQueryT pool $ withTransaction $ flip runReaderT txState $ do
@ -98,6 +88,35 @@ sync pool root c bs hs = do
-- thrown error should be caught despite possibly needing to be rerun -- thrown error should be caught despite possibly needing to be rerun
rerunnableIO $ fromEither res rerunnableIO $ fromEither res
formatBuildPlan :: PreHistoryCRUD -> PreBudgetCRUD -> T.Text
formatBuildPlan
CRUDOps {coCreate = hc, coRead = hr, coUpdate = hu, coDelete = hd}
CRUDOps {coCreate = bc, coDelete = bd} =
T.unlines $ "Build plan:" : (T.append " " <$> ht ++ [""] ++ bt)
where
ht =
[ T.append "History transfers to create: " $ tshow hCt
, T.append "History statements to create: " $ tshow hCs
, T.append "History entries to read: " $ tshow $ length hr
, T.append "History entry sets to update: " $ tshow $ length hu
]
++ formatDel "History" hd
bt =
T.append "Budgets to create: " (tshow $ bgtLabel <$> bc)
: formatDel "Budget" bd
toDel what thing n = T.unwords [what, thing, "to delete:", tshow n]
formatDel what (DeleteTxs e a b c' d) =
[ f "commits" e
, f "transactions" a
, f "entry sets" b
, f "entries" c'
, f "tag relations" d
]
where
f :: T.Text -> [a] -> T.Text
f thing = toDel what thing . length
(hCt, hCs) = bimap length length hc
runDB runDB
:: MonadUnliftIO m :: MonadUnliftIO m
=> SqlConfig => SqlConfig

View File

@ -23,7 +23,6 @@ import qualified RIO.Text as T
import RIO.Time import RIO.Time
import qualified RIO.Vector as V import qualified RIO.Vector as V
import Text.Regex.TDFA hiding (matchAll) import Text.Regex.TDFA hiding (matchAll)
import Text.Regex.TDFA.Text
readHistoryCRUD readHistoryCRUD
:: (MonadUnliftIO m, MonadFinance m) :: (MonadUnliftIO m, MonadFinance m)
@ -33,7 +32,7 @@ readHistoryCRUD
readHistoryCRUD root o@CRUDOps {coCreate = (ts, ss)} = do readHistoryCRUD root o@CRUDOps {coCreate = (ts, ss)} = do
-- TODO multithread this for some extra fun :) -- TODO multithread this for some extra fun :)
ss' <- mapM (readHistStmt root) ss ss' <- mapErrorsIO (readHistStmt root) ss
fromEitherM $ runExceptT $ do fromEitherM $ runExceptT $ do
let sRes = mapErrors (ExceptT . return) ss' let sRes = mapErrors (ExceptT . return) ss'
let tRes = mapErrors readHistTransfer ts let tRes = mapErrors readHistTransfer ts
@ -113,39 +112,93 @@ readImport_ n delim tns p = do
-- TODO handle this better, this maybe thing is a hack to skip lines with -- 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 -- blank dates but will likely want to make this more flexible
parseTxRecord :: FilePath -> TxOptsRe -> NamedRecord -> Parser (Maybe TxRecord) parseTxRecord :: FilePath -> TxOptsRe -> NamedRecord -> Parser (Maybe TxRecord)
parseTxRecord p TxOpts {toDate, toAmountFmt, toDesc, toAmount, toOther, toDateFmt} r = do parseTxRecord
d <- r .: T.encodeUtf8 toDate p
if d == "" TxOpts
then return Nothing { toDate
else do , toDesc
a <- parseDecimal toAmountFmt =<< r .: T.encodeUtf8 toAmount , toAmount
e <- r .: T.encodeUtf8 toDesc , toOther
os <- M.fromList <$> mapM (\n -> (n,) <$> r .: T.encodeUtf8 n) toOther , toDateFmt
d' <- parseTimeM True defaultTimeLocale (T.unpack toDateFmt) d , toSkipBlankDate
return $ Just $ TxRecord d' a e os p , toSkipBlankAmount
, toSkipBlankDescription
, toSkipBlankOther
, toSkipMissingFields
}
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
matchRecords :: MonadFinance m => [MatchRe] -> [TxRecord] -> AppExceptT m [Tx ()] matchRecords :: MonadFinance m => [StatementParserRe] -> [TxRecord] -> AppExceptT m [Tx ()]
matchRecords ms rs = do matchRecords ms rs = do
(matched, unmatched, notfound) <- matchAll (matchPriorities ms) rs (matched, unmatched, notfound) <- matchAll (matchPriorities ms) rs
case (matched, unmatched, notfound) of case (matched, unmatched, notfound) of
(ms_, [], []) -> return ms_ (ms_, [], []) -> return ms_
(_, us, ns) -> throwError $ AppException [StatementError us ns] (_, us, ns) -> throwError $ AppException [StatementError us ns]
matchPriorities :: [MatchRe] -> [MatchGroup] matchPriorities :: [StatementParserRe] -> [MatchGroup]
matchPriorities = matchPriorities =
fmap matchToGroup fmap matchToGroup
. L.groupBy (\a b -> spPriority a == spPriority b) . L.groupBy (\a b -> spPriority a == spPriority b)
. L.sortOn (Down . spPriority) . L.sortOn (Down . spPriority)
matchToGroup :: [MatchRe] -> MatchGroup matchToGroup :: [StatementParserRe] -> MatchGroup
matchToGroup ms = matchToGroup ms =
uncurry MatchGroup $ uncurry MatchGroup $
first (L.sortOn spDate) $ first (L.sortOn spDate) $
L.partition (isJust . spDate) ms L.partition (isJust . spDate) ms
data MatchGroup = MatchGroup data MatchGroup = MatchGroup
{ mgDate :: ![MatchRe] { mgDate :: ![StatementParserRe]
, mgNoDate :: ![MatchRe] , mgNoDate :: ![StatementParserRe]
} }
deriving (Show) deriving (Show)
@ -184,9 +237,9 @@ zipperSlice f x = go
zipperMatch zipperMatch
:: MonadFinance m :: MonadFinance m
=> Unzipped MatchRe => Unzipped StatementParserRe
-> TxRecord -> TxRecord
-> AppExceptT m (Zipped MatchRe, MatchRes (Tx ())) -> AppExceptT m (Zipped StatementParserRe, MatchRes (Tx ()))
zipperMatch (Unzipped bs cs as) x = go [] cs zipperMatch (Unzipped bs cs as) x = go [] cs
where where
go _ [] = return (Zipped bs $ cs ++ as, MatchFail) go _ [] = return (Zipped bs $ cs ++ as, MatchFail)
@ -201,9 +254,9 @@ zipperMatch (Unzipped bs cs as) x = go [] cs
zipperMatch' zipperMatch'
:: MonadFinance m :: MonadFinance m
=> Zipped MatchRe => Zipped StatementParserRe
-> TxRecord -> TxRecord
-> AppExceptT m (Zipped MatchRe, MatchRes (Tx ())) -> AppExceptT m (Zipped StatementParserRe, MatchRes (Tx ()))
zipperMatch' z x = go z zipperMatch' z x = go z
where where
go (Zipped bs (a : as)) = do go (Zipped bs (a : as)) = do
@ -214,7 +267,7 @@ zipperMatch' z x = go z
return (Zipped (maybe bs (: bs) $ matchDec a) as, skipOrPass) return (Zipped (maybe bs (: bs) $ matchDec a) as, skipOrPass)
go z' = return (z', MatchFail) go z' = return (z', MatchFail)
matchDec :: MatchRe -> Maybe MatchRe matchDec :: StatementParserRe -> Maybe StatementParserRe
matchDec m = case spTimes m of matchDec m = case spTimes m of
Just 1 -> Nothing Just 1 -> Nothing
Just n -> Just $ m {spTimes = Just $ n - 1} Just n -> Just $ m {spTimes = Just $ n - 1}
@ -224,7 +277,7 @@ matchAll
:: MonadFinance m :: MonadFinance m
=> [MatchGroup] => [MatchGroup]
-> [TxRecord] -> [TxRecord]
-> AppExceptT m ([Tx ()], [TxRecord], [MatchRe]) -> AppExceptT m ([Tx ()], [TxRecord], [StatementParserRe])
matchAll = go ([], []) matchAll = go ([], [])
where where
go (matched, unused) gs rs = case (gs, rs) of go (matched, unused) gs rs = case (gs, rs) of
@ -238,7 +291,7 @@ matchGroup
:: MonadFinance m :: MonadFinance m
=> MatchGroup => MatchGroup
-> [TxRecord] -> [TxRecord]
-> AppExceptT m ([Tx ()], [TxRecord], [MatchRe]) -> AppExceptT m ([Tx ()], [TxRecord], [StatementParserRe])
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
@ -246,9 +299,9 @@ matchGroup MatchGroup {mgDate = ds, mgNoDate = ns} rs = do
matchDates matchDates
:: MonadFinance m :: MonadFinance m
=> [MatchRe] => [StatementParserRe]
-> [TxRecord] -> [TxRecord]
-> AppExceptT m ([Tx ()], [TxRecord], [MatchRe]) -> AppExceptT m ([Tx ()], [TxRecord], [StatementParserRe])
matchDates ms = go ([], [], initZipper ms) matchDates ms = go ([], [], initZipper ms)
where where
go (matched, unmatched, z) [] = go (matched, unmatched, z) [] =
@ -271,9 +324,9 @@ matchDates ms = go ([], [], initZipper ms)
matchNonDates matchNonDates
:: MonadFinance m :: MonadFinance m
=> [MatchRe] => [StatementParserRe]
-> [TxRecord] -> [TxRecord]
-> AppExceptT m ([Tx ()], [TxRecord], [MatchRe]) -> AppExceptT m ([Tx ()], [TxRecord], [StatementParserRe])
matchNonDates ms = go ([], [], initZipper ms) matchNonDates ms = go ([], [], initZipper ms)
where where
go (matched, unmatched, z) [] = go (matched, unmatched, z) [] =
@ -290,7 +343,11 @@ 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
matches :: MonadFinance m => MatchRe -> TxRecord -> AppExceptT m (MatchRes (Tx ())) matches
:: MonadFinance m
=> StatementParserRe
-> TxRecord
-> AppExceptT m (MatchRes (Tx ()))
matches matches
StatementParser {spTx, spOther, spVal, spDate, spDesc, spPriority} StatementParser {spTx, spOther, spVal, spDate, spDesc, spPriority}
r@TxRecord {trDate, trAmount, trDesc, trOther} = do r@TxRecord {trDate, trAmount, trDesc, trOther} = do
@ -465,11 +522,17 @@ readRational s = case T.split (== '.') s of
err = throwError $ AppException [ConversionError s False] err = throwError $ AppException [ConversionError s False]
compileOptions :: TxOpts T.Text -> AppExcept TxOptsRe compileOptions :: TxOpts T.Text -> AppExcept TxOptsRe
compileOptions o@TxOpts {toAmountFmt = pat} = do compileOptions = mapM (compileRegex True)
re <- compileRegex True pat
return $ o {toAmountFmt = re}
compileMatch :: StatementParser T.Text -> AppExcept MatchRe -- 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}
compileMatch :: StatementParser T.Text -> AppExcept StatementParserRe
compileMatch m@StatementParser {spDesc, spOther} = do compileMatch m@StatementParser {spDesc, spOther} = do
combineError dres ores $ \d os -> m {spDesc = d, spOther = os} combineError dres ores $ \d os -> m {spDesc = d, spOther = os}
where where
@ -477,42 +540,15 @@ compileMatch m@StatementParser {spDesc, spOther} = do
dres = mapM go spDesc dres = mapM go spDesc
ores = combineErrors $ fmap (mapM go) spOther ores = combineErrors $ fmap (mapM go) spOther
compileRegex :: Bool -> T.Text -> AppExcept (Text, Regex) parseDecimal :: MonadFail m => Bool -> (T.Text, Regex) -> T.Text -> m Decimal
compileRegex groups pat = case res of parseDecimal wantSign (pat, re) s = case (wantSign, matchGroupsMaybe s re) of
Right re -> return (pat, re) (True, [sign, num]) -> do
Left _ -> throwError $ AppException [RegexError pat] k <- readSign sign
where x <- readNum num
res = return $ k * x
compile (False, [num]) -> readNum num
(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 _ -> []
parseDecimal :: MonadFail m => (T.Text, Regex) -> T.Text -> m Decimal
parseDecimal (pat, re) s = case matchGroupsMaybe s re of
[sign, x, ""] -> Decimal 0 . uncurry (*) <$> readWhole sign x
[sign, x, y] -> do
d <- readT "decimal" y
let p = T.length y
(k, w) <- readWhole sign x
return $ Decimal (fromIntegral p) (k * (w * (10 ^ p) + d))
_ -> msg "malformed decimal" _ -> msg "malformed decimal"
where where
readT what t = case readMaybe $ T.unpack t of
Just d -> return $ fromInteger d
_ -> msg $ T.unwords ["could not parse", what, singleQuote t]
msg :: MonadFail m => T.Text -> m a msg :: MonadFail m => T.Text -> m a
msg m = msg m =
fail $ fail $
@ -522,7 +558,10 @@ parseDecimal (pat, re) s = case matchGroupsMaybe s re of
| x == "-" = return (-1) | x == "-" = return (-1)
| x == "+" || x == "" = return 1 | x == "+" || x == "" = return 1
| otherwise = msg $ T.append "invalid sign: " x | otherwise = msg $ T.append "invalid sign: " x
readWhole sign x = do readNum x =
w <- readT "whole number" x maybe
k <- readSign sign (msg $ T.unwords ["could not parse", singleQuote x])
return (k, w) return
$ readMaybe
$ T.unpack
$ T.filter (/= ',') x

View File

@ -102,7 +102,7 @@ newtype EntryIndex = EntryIndex {unEntryIndex :: Int}
deriving newtype (Show, Eq, Ord, Num, Real, Enum, Integral, PersistField, PersistFieldSql) deriving newtype (Show, Eq, Ord, Num, Real, Enum, Integral, PersistField, PersistFieldSql)
newtype TxDesc = TxDesc {unTxDesc :: T.Text} newtype TxDesc = TxDesc {unTxDesc :: T.Text}
deriving newtype (Show, Eq, Ord, PersistField, PersistFieldSql, FromField) deriving newtype (Show, Eq, Ord, PersistField, PersistFieldSql, FromField, IsString)
newtype Precision = Precision {unPrecision :: Word8} newtype Precision = Precision {unPrecision :: Word8}
deriving newtype (Eq, Ord, Num, Show, Real, Enum, Integral, PersistField, PersistFieldSql) deriving newtype (Eq, Ord, Num, Show, Real, Enum, Integral, PersistField, PersistFieldSql)

View File

@ -49,17 +49,16 @@ makeHaskellTypesWith
, SingleConstructor "ModPat" "ModPat" "(./dhall/Types.dhall).ModPat.Type" , SingleConstructor "ModPat" "ModPat" "(./dhall/Types.dhall).ModPat.Type"
, SingleConstructor "CronPat" "CronPat" "(./dhall/Types.dhall).CronPat.Type" , SingleConstructor "CronPat" "CronPat" "(./dhall/Types.dhall).CronPat.Type"
, SingleConstructor "ValMatcher" "ValMatcher" "(./dhall/Types.dhall).ValMatcher.Type" , SingleConstructor "ValMatcher" "ValMatcher" "(./dhall/Types.dhall).ValMatcher.Type"
, SingleConstructor "TxAmount1" "TxAmount1" "(./dhall/Types.dhall).TxAmount1_"
, SingleConstructor "TxAmount2" "TxAmount2" "(./dhall/Types.dhall).TxAmount2_"
, SingleConstructor , SingleConstructor
"Amount" "Amount"
"Amount" "Amount"
"\\(w : Type) -> \\(v : Type) -> ((./dhall/Types.dhall).Amount w v).Type" "\\(w : Type) -> \\(v : Type) -> ((./dhall/Types.dhall).Amount w v).Type"
, SingleConstructor , SingleConstructor
"TxOpts" "AcntMatcher_"
"TxOpts" "AcntMatcher_"
"\\(re : Type) -> ((./dhall/Types.dhall).TxOpts_ re).Type" "\\(re : Type) -> ((./dhall/Types.dhall).AcntMatcher_ re).Type"
, SingleConstructor "AcntSet" "AcntSet" "(./dhall/Types.dhall).AcntSet.Type"
, SingleConstructor "TransferMatcher" "TransferMatcher" "(./dhall/Types.dhall).TransferMatcher.Type"
, SingleConstructor "ShadowTransfer" "ShadowTransfer" "(./dhall/Types.dhall).ShadowTransfer"
, SingleConstructor "Field" "Field" "(./dhall/Types.dhall).Field" , SingleConstructor "Field" "Field" "(./dhall/Types.dhall).Field"
, SingleConstructor "Entry" "Entry" "(./dhall/Types.dhall).Entry" , SingleConstructor "Entry" "Entry" "(./dhall/Types.dhall).Entry"
, SingleConstructor "PretaxValue" "PretaxValue" "(./dhall/Types.dhall).PretaxValue" , SingleConstructor "PretaxValue" "PretaxValue" "(./dhall/Types.dhall).PretaxValue"
@ -88,11 +87,7 @@ deriveProduct
, "CronPat" , "CronPat"
, "DatePat" , "DatePat"
, "TaggedAcnt" , "TaggedAcnt"
, "Budget"
, "Income" , "Income"
, "ShadowTransfer"
, "TransferMatcher"
, "AcntSet"
, "DateMatcher" , "DateMatcher"
, "ValMatcher" , "ValMatcher"
, "YMDMatcher" , "YMDMatcher"
@ -191,15 +186,33 @@ newtype BudgetName = BudgetName {unBudgetName :: T.Text}
deriving newtype (Show, Eq, Ord, Hashable, FromDhall, PersistField, PersistFieldSql) deriving newtype (Show, Eq, Ord, Hashable, FromDhall, PersistField, PersistFieldSql)
data Budget = Budget data Budget = Budget
{ bgtLabel :: BudgetName { bgtLabel :: !BudgetName
, bgtIncomes :: [Income] , bgtIncomes :: ![Income]
, bgtPretax :: [MultiAllocation PretaxValue] , bgtPretax :: ![MultiAllocation PretaxValue]
, bgtTax :: [MultiAllocation TaxValue] , bgtTax :: ![MultiAllocation TaxValue]
, bgtPosttax :: [MultiAllocation PosttaxValue] , bgtPosttax :: ![MultiAllocation PosttaxValue]
, bgtTransfers :: [PairedTransfer] , bgtTransfers :: ![PairedTransfer]
, bgtShadowTransfers :: [ShadowTransfer] , bgtShadowTransfers :: ![ShadowTransfer]
, bgtInterval :: !(Maybe Interval) , bgtInterval :: !(Maybe Interval)
} }
deriving (Generic, Hashable, FromDhall)
data ShadowTransfer = ShadowTransfer
{ stFrom :: !TaggedAcnt
, stTo :: !TaggedAcnt
, stCurrency :: !CurID
, stDesc :: !Text
, stMatch :: !(TransferMatcher_ Text)
, stRatio :: !Double
}
deriving (Generic, Hashable, FromDhall)
data TransferMatcher_ re = TransferMatcher_
{ tmFrom :: !(Maybe (AcntMatcher_ re))
, tmTo :: !(Maybe (AcntMatcher_ re))
, tmDate :: !(Maybe DateMatcher)
, tmVal :: !ValMatcher
}
deriving instance Hashable PretaxValue deriving instance Hashable PretaxValue
@ -213,8 +226,6 @@ deriving instance Hashable TaxValue
deriving instance Hashable PosttaxValue deriving instance Hashable PosttaxValue
deriving instance Hashable Budget
deriving instance Hashable TransferValue deriving instance Hashable TransferValue
deriving instance Hashable TransferType deriving instance Hashable TransferType
@ -314,11 +325,17 @@ data Transfer a c w v = Transfer
} }
deriving (Eq, Show) deriving (Eq, Show)
deriving instance Hashable ShadowTransfer deriving instance Generic (TransferMatcher_ Text)
deriving instance Hashable AcntSet deriving instance Hashable (TransferMatcher_ Text)
deriving instance Hashable TransferMatcher deriving instance FromDhall (TransferMatcher_ Text)
deriving instance Generic (AcntMatcher_ Text)
deriving instance Hashable (AcntMatcher_ Text)
deriving instance FromDhall (AcntMatcher_ Text)
deriving instance Hashable ValMatcher deriving instance Hashable ValMatcher
@ -449,12 +466,44 @@ deriving instance Eq a => Eq (TxOpts a)
deriving instance Generic (TxOpts a) deriving instance Generic (TxOpts a)
deriving instance Hashable a => Hashable (TxOpts a) deriving instance Hashable (TxOpts T.Text)
deriving instance FromDhall a => FromDhall (TxOpts a) deriving instance FromDhall (TxOpts T.Text)
deriving instance Show a => Show (TxOpts a) deriving instance Show a => Show (TxOpts a)
deriving instance Eq re => Eq (TxAmount1 re)
deriving instance Eq re => Eq (TxAmount2 re)
deriving instance Show re => Show (TxAmount1 re)
deriving instance Show re => Show (TxAmount2 re)
deriving instance Generic (TxAmount1 T.Text)
deriving instance Generic (TxAmount2 T.Text)
deriving instance Hashable (TxAmount1 T.Text)
deriving instance Hashable (TxAmount2 T.Text)
deriving instance FromDhall (TxAmount1 T.Text)
deriving instance FromDhall (TxAmount2 T.Text)
deriving instance Functor TxAmount1
deriving instance Functor TxAmount2
deriving instance Foldable TxAmount1
deriving instance Foldable TxAmount2
deriving instance Traversable TxAmount1
deriving instance Traversable TxAmount2
data Statement = Statement data Statement = Statement
{ stmtPaths :: ![FilePath] { stmtPaths :: ![FilePath]
, stmtParsers :: ![StatementParser T.Text] , stmtParsers :: ![StatementParser T.Text]
@ -464,6 +513,29 @@ data Statement = Statement
} }
deriving (Eq, Hashable, Generic, FromDhall, Show) deriving (Eq, Hashable, Generic, FromDhall, Show)
data TxAmountSpec re = AmountSingle (TxAmount1 re) | AmountDual (TxAmount2 re)
deriving (Eq, Show, Functor, Foldable, Traversable)
deriving instance Generic (TxAmountSpec T.Text)
deriving instance FromDhall (TxAmountSpec T.Text)
deriving instance Hashable (TxAmountSpec T.Text)
data TxOpts re = TxOpts
{ toDate :: !T.Text
, toAmount :: !(TxAmountSpec re)
, toDesc :: !T.Text
, toOther :: ![T.Text]
, toDateFmt :: !T.Text
, toSkipBlankDate :: !Bool
, toSkipBlankAmount :: !Bool
, toSkipBlankDescription :: !Bool
, toSkipBlankOther :: ![Text]
, toSkipMissingFields :: !Bool
}
deriving (Functor, Foldable, Traversable)
-- | the value of a field in entry (text version) -- | the value of a field in entry (text version)
-- can either be a raw (constant) value, a lookup from the record, or a map -- can either be a raw (constant) value, a lookup from the record, or a map
-- between the lookup and some other value -- between the lookup and some other value

View File

@ -306,7 +306,7 @@ data AppError
| LookupError !LookupSuberr !T.Text | LookupError !LookupSuberr !T.Text
| DatePatternError !Natural !Natural !(Maybe Natural) !PatternSuberr | DatePatternError !Natural !Natural !(Maybe Natural) !PatternSuberr
| DaySpanError !Gregorian !(Maybe Gregorian) | DaySpanError !Gregorian !(Maybe Gregorian)
| StatementError ![TxRecord] ![MatchRe] | StatementError ![TxRecord] ![StatementParserRe]
| PeriodError !Day !Day | PeriodError !Day !Day
| LinkError !EntryIndex !EntryIndex | LinkError !EntryIndex !EntryIndex
| DBError !DBSubError | DBError !DBSubError
@ -323,7 +323,9 @@ type AppExceptT = ExceptT AppException
type AppExcept = AppExceptT Identity type AppExcept = AppExceptT Identity
type MatchRe = StatementParser (T.Text, Regex) type StatementParserRe = StatementParser (T.Text, Regex)
type TransferMatcherRe = TransferMatcher_ Regex
type TxOptsRe = TxOpts (T.Text, Regex) type TxOptsRe = TxOpts (T.Text, Regex)

View File

@ -51,6 +51,9 @@ module Internal.Utils
, keyVals , keyVals
, realFracToDecimalP , realFracToDecimalP
, roundToP , roundToP
, compileRegex
, matchMaybe
, matchGroupsMaybe
) )
where where
@ -69,6 +72,8 @@ import RIO.State
import qualified RIO.Text as T import qualified RIO.Text as T
import RIO.Time import RIO.Time
import qualified RIO.Vector as V import qualified RIO.Vector as V
import Text.Regex.TDFA hiding (matchAll)
import Text.Regex.TDFA.Text
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- intervals -- intervals
@ -125,7 +130,7 @@ expandCronPat b CronPat {cpYear, cpMonth, cpDay, cpWeekly} =
expandMDYPat :: Natural -> Natural -> MDYPat -> AppExcept [Natural] expandMDYPat :: Natural -> Natural -> MDYPat -> AppExcept [Natural]
expandMDYPat lower upper (Single x) = return [x | lower <= x && x <= upper] 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 (Multi xs) = return $ dropWhile (< lower) $ takeWhile (<= upper) xs
expandMDYPat lower upper (After x) = return [max lower x .. upper] expandMDYPat lower upper (After x) = return [max lower x .. upper]
expandMDYPat lower upper (Before x) = return [lower .. min upper x] 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 (Between x y) = return [max lower x .. min upper y]
@ -494,7 +499,7 @@ showTx TxRecord {trDate = d, trAmount = v, trDesc = e, trFile = f} =
, ("description", doubleQuote $ unTxDesc e) , ("description", doubleQuote $ unTxDesc e)
] ]
showMatch :: MatchRe -> T.Text showMatch :: StatementParserRe -> T.Text
showMatch StatementParser {spDate, spVal, spDesc, spOther, spTimes, spPriority} = showMatch StatementParser {spDate, spVal, spDesc, spOther, spTimes, spPriority} =
T.append "Unused match: " $ keyVals [(x, y) | (x, Just y) <- kvs] T.append "Unused match: " $ keyVals [(x, y) | (x, Just y) <- kvs]
where where
@ -693,14 +698,12 @@ rebalanceTotalEntrySet
, utTotalValue , utTotalValue
} = } =
do do
(fval, fs, tpairs) <- rebalanceDebit bc utFromRO utFromUnk (fval, fs, tpairs) <- rebalanceDebit utCurrency utFromRO utFromUnk
let f0val = utTotalValue - fval let f0val = utTotalValue - fval
modify $ mapAdd_ (f0Acnt, bc) f0val modify $ mapAdd_ (f0Acnt, utCurrency) f0val
let tsLinked = tpairs ++ (unlink f0val <$> f0links) let tsLinked = tpairs ++ (unlink f0val <$> f0links)
ts <- rebalanceCredit bc utTotalValue utTo0 utToUnk utToRO tsLinked ts <- rebalanceCredit utCurrency utTotalValue utTo0 utToUnk utToRO tsLinked
return (f0 {ueValue = StaticValue f0val} : fs ++ ts) return (f0 {ueValue = StaticValue f0val} : fs ++ ts)
where
bc = utCurrency
rebalanceFullEntrySet :: FullUpdateEntrySet -> State EntryBals [UEBalanced] rebalanceFullEntrySet :: FullUpdateEntrySet -> State EntryBals [UEBalanced]
rebalanceFullEntrySet rebalanceFullEntrySet
@ -714,14 +717,13 @@ rebalanceFullEntrySet
, utCurrency , utCurrency
} = } =
do do
(ftot, fs, tpairs) <- rebalanceDebit bc rs ls (ftot, fs, tpairs) <- rebalanceDebit utCurrency rs ls
ts <- rebalanceCredit bc ftot utTo0 utToUnk utToRO tpairs ts <- rebalanceCredit utCurrency ftot utTo0 utToUnk utToRO tpairs
return (fs ++ ts) return (fs ++ ts)
where where
(rs, ls) = case utFrom0 of (rs, ls) = case utFrom0 of
Left x -> (x : utFromRO, utFromUnk) Left x -> (x : utFromRO, utFromUnk)
Right x -> (utFromRO, x : utFromUnk) Right x -> (utFromRO, x : utFromUnk)
bc = utCurrency
rebalanceDebit rebalanceDebit
:: BCKey :: BCKey
@ -755,7 +757,7 @@ rebalanceCredit
-> [UE_RO] -> [UE_RO]
-> [UEBalanced] -> [UEBalanced]
-> State EntryBals [UEBalanced] -> State EntryBals [UEBalanced]
rebalanceCredit k tot t0 us rs bs = do rebalanceCredit k tot t0@UpdateEntry {ueAcnt = t0Acnt} us rs bs = do
(tval, ts) <- (tval, ts) <-
fmap (second catMaybes) $ fmap (second catMaybes) $
sumM goTo $ sumM goTo $
@ -763,7 +765,9 @@ rebalanceCredit k tot t0 us rs bs = do
(UETLinked <$> bs) (UETLinked <$> bs)
++ (UETUnk <$> us) ++ (UETUnk <$> us)
++ (UETReadOnly <$> rs) ++ (UETReadOnly <$> rs)
return (t0 {ueValue = StaticValue (-(tot + tval))} : ts) let t0val = -(tot + tval)
modify $ mapAdd_ (t0Acnt, k) t0val
return (t0 {ueValue = StaticValue t0val} : ts)
where where
idx = projectUET ueIndex ueIndex ueIndex idx = projectUET ueIndex ueIndex ueIndex
goTo (UETReadOnly e) = (,Nothing) <$> updateFixed k e goTo (UETReadOnly e) = (,Nothing) <$> updateFixed k e
@ -1037,3 +1041,26 @@ realFracToDecimalP p = realFracToDecimal (unPrecision p)
roundToP :: Integral i => Precision -> DecimalRaw i -> DecimalRaw i roundToP :: Integral i => Precision -> DecimalRaw i -> DecimalRaw i
roundToP p = roundTo (unPrecision p) roundToP p = roundTo (unPrecision p)
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 _ -> []