pwncash/lib/Internal/Utils.hs

654 lines
21 KiB
Haskell
Raw Normal View History

2023-01-28 19:32:56 -05:00
module Internal.Utils
( compareDate
, inBounds
, expandBounds
2023-01-28 19:32:56 -05:00
, fmtRational
, matches
, fromGregorian'
, resolveBounds
, resolveBounds_
2023-01-28 19:32:56 -05:00
, leftToMaybe
, dec2Rat
, concatEithers2
2023-02-12 21:52:41 -05:00
, concatEithers3
2023-01-28 22:55:07 -05:00
, concatEither3
2023-01-28 19:32:56 -05:00
, concatEither2
2023-01-28 22:55:07 -05:00
, concatEitherL
, concatEithersL
2023-02-12 21:52:41 -05:00
, concatEither2M
, concatEithers2M
2023-01-28 19:32:56 -05:00
, parseRational
, showError
2023-01-28 22:55:07 -05:00
, unlessLeft_
, unlessLefts_
2023-01-28 19:32:56 -05:00
, unlessLeft
, unlessLefts
, acntPath2Text
, showT
2023-01-28 22:55:07 -05:00
, lookupErr
, gregorians
2023-04-16 20:09:13 -04:00
, uncurry3
, fstOf3
, sndOf3
, thdOf3
, xGregToDay
2023-02-01 23:02:07 -05:00
, plural
, compileMatch
, compileOptions
2023-02-13 19:57:39 -05:00
, dateMatches
, valMatches
2023-01-28 19:32:56 -05:00
)
where
2022-12-11 17:51:11 -05:00
2023-01-25 20:52:27 -05:00
import Data.Time.Format.ISO8601
import GHC.Real
import Internal.Types
import RIO
2023-01-25 20:52:27 -05:00
import qualified RIO.List as L
import qualified RIO.Map as M
2023-02-25 22:56:23 -05:00
import qualified RIO.NonEmpty as NE
import qualified RIO.Text as T
import RIO.Time
import Text.Regex.TDFA
import Text.Regex.TDFA.Text
2022-12-11 17:51:11 -05:00
2023-01-27 23:33:34 -05:00
--------------------------------------------------------------------------------
2023-01-28 19:32:56 -05:00
-- dates
-- | find the next date
-- this is meant to go in a very tight loop and be very fast (hence no
-- complex date functions, most of which heavily use 'mod' and friends)
nextXGreg :: XGregorian -> XGregorian
nextXGreg XGregorian {xgYear = y, xgMonth = m, xgDay = d, xgDayOfWeek = w}
| m == 12 && d == 31 = XGregorian (y + 1) 1 1 w_
| (m == 2 && (not leap && d == 28 || (leap && d == 29)))
|| (m `elem` [4, 6, 9, 11] && d == 30)
|| (d == 31) =
XGregorian y (m + 1) 1 w_
| otherwise = XGregorian y m (d + 1) w_
where
-- don't use DayOfWeek from Data.Time since this uses mod (which uses a
-- division opcode) and thus will be slower than just checking for equality
-- and adding
w_ = if w == 6 then 0 else w + 1
leap = isLeapYear $ fromIntegral y
gregorians :: Day -> [XGregorian]
gregorians x = L.iterate nextXGreg $ XGregorian (fromIntegral y) m d w
where
(y, m, d) = toGregorian x
w = fromEnum $ dayOfWeek x
xGregToDay :: XGregorian -> Day
xGregToDay XGregorian {xgYear = y, xgMonth = m, xgDay = d} = fromGregorian (fromIntegral y) m d
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
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
compareDate :: DateMatcher -> Day -> Ordering
2023-01-28 19:32:56 -05:00
compareDate (On md) x =
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
(y, m, d) = toGregorian x
2023-01-25 23:04:54 -05:00
compareDate (In md offset) x = do
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
(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
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
-- TODO misleading name
inBounds :: (Day, Day) -> Day -> Bool
inBounds (d0, d1) x = d0 <= x && x < d1
resolveBounds :: Interval -> EitherErr Bounds
resolveBounds i@Interval {intStart = s} =
resolveBounds_ (s {gYear = gYear s + 50}) i
resolveBounds_ :: Gregorian -> Interval -> EitherErr Bounds
resolveBounds_ def Interval {intStart = s, intEnd = e} =
case fromGregorian' <$> e of
Nothing -> Right $ toBounds $ fromGregorian' def
Just e_
| s_ < e_ -> Right $ toBounds e_
| otherwise -> Left $ BoundsError s e
2023-01-27 23:33:34 -05:00
where
s_ = fromGregorian' s
toBounds end = (s_, fromIntegral $ diffDays end s_ - 1)
expandBounds :: Bounds -> (Day, Day)
expandBounds (d, n) = (d, addDays (fromIntegral n + 1) d)
2023-01-27 23:33:34 -05:00
--------------------------------------------------------------------------------
-- matching
2022-12-11 17:51:11 -05:00
2023-02-01 23:02:07 -05:00
matches :: MatchRe -> TxRecord -> EitherErrs (MatchRes RawTx)
2023-02-12 16:23:32 -05:00
matches
Match {mTx, mOther, mVal, mDate, mDesc}
r@TxRecord {trDate, trAmount, trDesc, trOther} = do
res <- concatEither3 val other desc $ \x y z -> x && y && z
if date && res
then maybe (Right MatchSkip) (fmap MatchPass . convert) mTx
else Right MatchFail
where
val = valMatches mVal trAmount
date = maybe True (`dateMatches` trDate) mDate
other = foldM (\a o -> (a &&) <$> otherMatches trOther o) True mOther
desc = maybe (return True) (matchMaybe trDesc . snd) mDesc
convert (ToTx cur a ss) = toTx cur a ss r
2022-12-11 17:51:11 -05:00
2023-01-26 23:41:45 -05:00
toTx :: SplitCur -> SplitAcnt -> [ExpSplit] -> TxRecord -> EitherErrs RawTx
2023-02-12 16:23:32 -05:00
toTx sc sa toSplits r@TxRecord {trAmount, trDate, trDesc} =
2023-01-26 23:41:45 -05:00
concatEithers2 acRes ssRes $ \(a_, c_) ss_ ->
let fromSplit =
Entry
2023-01-26 23:41:45 -05:00
{ sAcnt = a_
, sCurrency = c_
, sValue = Just trAmount
, sComment = ""
2023-02-26 22:53:12 -05:00
, sTags = [] -- TODO what goes here?
2023-01-26 23:41:45 -05:00
}
in Tx
2023-02-26 22:56:32 -05:00
{ txDate = trDate
, txDescr = trDesc
2023-01-26 23:41:45 -05:00
, txSplits = fromSplit : ss_
2023-01-25 23:04:54 -05:00
}
2023-01-26 23:41:45 -05:00
where
2023-01-27 23:33:34 -05:00
acRes = concatEithers2 (resolveAcnt r sa) (resolveCurrency r sc) (,)
ssRes = concatEithersL $ fmap (resolveSplit r) toSplits
valMatches :: ValMatcher -> Rational -> EitherErr Bool
valMatches ValMatcher {mvDen, mvSign, mvNum, mvPrec} x
2023-01-28 20:03:58 -05:00
| Just d_ <- mvDen, d_ >= p = Left $ MatchValPrecisionError d_ p
| otherwise =
Right $
checkMaybe (s ==) mvSign
&& checkMaybe (n ==) mvNum
&& checkMaybe ((d * fromIntegral p ==) . fromIntegral) mvDen
2023-01-27 23:33:34 -05:00
where
(n, d) = properFraction $ abs x
p = 10 ^ mvPrec
s = signum x >= 0
checkMaybe = maybe True
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
otherMatches :: M.Map T.Text T.Text -> MatchOtherRe -> EitherErr Bool
2023-01-27 23:33:34 -05:00
otherMatches dict m = case m of
2023-01-28 20:03:58 -05:00
Val (Field n mv) -> valMatches mv =<< (readRational =<< lookup_ MatchNumeric n)
2023-02-01 23:02:07 -05:00
Desc (Field n (_, md)) -> (`matchMaybe` md) =<< lookup_ MatchText n
2023-01-27 23:33:34 -05:00
where
lookup_ t n = lookupErr (MatchField t) n dict
resolveSplit :: TxRecord -> ExpSplit -> EitherErrs RawSplit
resolveSplit r s@Entry {sAcnt = a, sValue = v, sCurrency = c} =
2023-01-27 23:33:34 -05:00
concatEithers2 acRes valRes $
\(a_, c_) v_ -> (s {sAcnt = a_, sValue = v_, sCurrency = c_})
where
acRes = concatEithers2 (resolveAcnt r a) (resolveCurrency r c) (,)
valRes = plural $ mapM (resolveValue r) v
resolveValue :: TxRecord -> EntryNumGetter -> EitherErr Rational
2023-01-27 23:33:34 -05:00
resolveValue r s = case s of
(LookupN t) -> readRational =<< lookupErr SplitValField t (trOther r)
(ConstN c) -> Right $ dec2Rat c
AmountN -> Right $ trAmount r
resolveAcnt :: TxRecord -> SplitAcnt -> EitherErrs T.Text
resolveAcnt = resolveSplitField AcntField
resolveCurrency :: TxRecord -> SplitCur -> EitherErrs T.Text
resolveCurrency = resolveSplitField CurField
resolveSplitField :: SplitIDType -> TxRecord -> SplitAcnt -> EitherErrs T.Text
resolveSplitField t TxRecord {trOther = o} s = case s of
ConstT p -> Right p
LookupT f -> plural $ lookup_ f o
2023-01-27 23:33:34 -05:00
MapT (Field f m) -> plural $ do
k <- lookup_ f o
lookup_ k m
2023-01-27 23:33:34 -05:00
Map2T (Field (f1, f2) m) -> do
(k1, k2) <- concatEither2 (lookup_ f1 o) (lookup_ f2 o) (,)
plural $ lookup_ (k1, k2) m
2023-01-27 23:33:34 -05:00
where
lookup_ :: (Ord k, Show k) => k -> M.Map k v -> EitherErr v
lookup_ = lookupErr (SplitIDField t)
lookupErr :: (Ord k, Show k) => LookupSuberr -> k -> M.Map k v -> EitherErr v
lookupErr what k m = case M.lookup k m of
Just x -> Right x
_ -> Left $ LookupError what $ showT k
2022-12-11 17:51:11 -05:00
parseRational :: MonadFail m => (T.Text, Regex) -> T.Text -> m Rational
parseRational (pat, re) s = case matchGroupsMaybe s re of
2022-12-11 17:51:11 -05:00
[sign, x, ""] -> uncurry (*) <$> readWhole sign x
[sign, x, y] -> do
d <- readT "decimal" y
let p = 10 ^ T.length y
2022-12-11 17:51:11 -05:00
(k, w) <- readWhole sign x
return $ k * (w + d % p)
_ -> msg "malformed decimal"
2022-12-11 17:51:11 -05:00
where
readT what t = case readMaybe $ T.unpack t of
2023-02-13 18:49:41 -05:00
Just d -> return $ fromInteger d
_ -> msg $ T.unwords ["could not parse", what, singleQuote t]
2023-02-12 16:23:32 -05:00
msg :: MonadFail m => T.Text -> m a
msg m =
fail $
T.unpack $
T.unwords [m, "-", keyVals [("pattern", pat), ("query", s)]]
2022-12-11 17:51:11 -05:00
readSign x
| x == "-" = return (-1)
| x == "+" || x == "" = return 1
| otherwise = msg $ T.append "invalid sign: " x
2022-12-11 17:51:11 -05:00
readWhole sign x = do
w <- readT "whole number" x
k <- readSign sign
return (k, w)
readRational :: T.Text -> EitherErr Rational
readRational s = case T.split (== '.') s of
2023-01-25 23:04:54 -05:00
[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
2023-01-25 23:04:54 -05:00
k = if x' >= 0 then 1 else -1
in return $ fromInteger x' + k * y' % p
_ -> err
_ -> err
2022-12-11 17:51:11 -05:00
where
readT = readMaybe . T.unpack
2023-01-25 23:04:54 -05:00
err = Left $ ConversionError s
2022-12-11 17:51:11 -05:00
-- TODO smells like a lens
2023-01-28 19:32:56 -05:00
-- mapTxSplits :: (a -> b) -> Tx a -> Tx b
-- mapTxSplits f t@Tx {txSplits = ss} = t {txSplits = fmap f ss}
2022-12-11 17:51:11 -05:00
fmtRational :: Natural -> Rational -> T.Text
fmtRational precision x = T.concat [s, txt n', ".", pad 2 "0" $ txt d']
where
s = if x >= 0 then "" else "-"
x'@(n :% d) = abs x
2022-12-11 17:51:11 -05:00
p = 10 ^ precision
n' = div n d
d' = (\(a :% b) -> div a b) ((x' - fromIntegral n') * p)
2022-12-11 17:51:11 -05:00
txt = T.pack . show
pad i c z = T.append (T.replicate (i - T.length z) c) z
dec2Rat :: Decimal -> Rational
2023-02-12 16:23:32 -05:00
dec2Rat D {sign, whole, decimal, precision} =
2022-12-14 23:59:23 -05:00
k * (fromIntegral whole + (fromIntegral decimal % (10 ^ precision)))
2022-12-11 17:51:11 -05:00
where
2022-12-14 23:59:23 -05:00
k = if sign then 1 else -1
2022-12-11 17:51:11 -05:00
acntPath2Text :: AcntPath -> T.Text
acntPath2Text (AcntPath t cs) = T.intercalate "/" (atName t : cs)
2023-01-24 23:24:41 -05:00
2023-01-27 23:33:34 -05:00
--------------------------------------------------------------------------------
-- error display
2023-01-24 23:24:41 -05:00
showError :: InsertError -> [T.Text]
2023-04-16 20:09:13 -04:00
showError other = case other of
(StatementError ts ms) -> (showTx <$> ts) ++ (showMatch <$> ms)
(BoundsError a b) ->
2023-04-16 20:09:13 -04:00
[T.unwords ["Could not create bounds from", showGregorian_ a, "and", showGreg b]]
where
showGreg (Just g) = showGregorian_ g
showGreg Nothing = "Inf"
2023-02-25 22:56:23 -05:00
(AccountError a ts) ->
2023-04-16 20:09:13 -04:00
[ T.unwords
[ "account type of key"
, singleQuote a
, "is not one of:"
, ts_
]
]
2023-02-25 22:56:23 -05:00
where
ts_ = T.intercalate ", " $ NE.toList $ fmap atName ts
2023-04-16 20:09:13 -04:00
(PatternError s b r p) -> [T.unwords [msg, "in pattern: ", pat]]
where
pat =
keyVals $
[ (k, v)
| (k, Just v) <-
[ ("start", Just $ showT s)
, ("by", Just $ showT b)
, ("repeats", showT <$> r)
]
]
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]
(ConversionError x) -> [T.append "Could not convert to rational number: " x]
(InsertIOError msg) -> [T.append "IO Error: " msg]
(ParseError msg) -> [T.append "Parse Error: " msg]
2023-01-28 20:03:58 -05:00
(MatchValPrecisionError d p) ->
2023-04-16 20:09:13 -04:00
[T.unwords ["Match denominator", showT d, "must be less than", showT 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-01-28 22:55:07 -05:00
SplitIDField st -> T.unwords ["split", idName st, "ID"]
2023-01-27 23:33:34 -05:00
SplitValField -> "split 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"
(IncomeError day name balance) ->
[ T.unwords
[ "Income allocations for budget"
, singleQuote name
, "exceed total on day"
, showT day
, "where balance is"
, showT balance
]
]
2023-01-25 20:52:27 -05:00
(BalanceError t cur rss) ->
2023-04-16 20:09:13 -04:00
[ T.unwords
[ msg
, "for currency"
, singleQuote cur
, "and for splits"
, splits
]
]
2023-01-25 20:52:27 -05:00
where
msg = case t of
TooFewSplits -> "Need at least two splits to balance"
NotOneBlank -> "Exactly one split must be blank"
2023-01-28 20:03:58 -05:00
splits = T.intercalate ", " $ fmap (singleQuote . showSplit) rss
2023-01-25 20:52:27 -05:00
showGregorian_ :: Gregorian -> T.Text
2023-02-12 16:23:32 -05:00
showGregorian_ Gregorian {gYear, gMonth, gDay} = T.intercalate "-" $ showT <$> [gYear, gMonth, gDay]
2023-01-25 20:52:27 -05:00
showTx :: TxRecord -> T.Text
showTx TxRecord {trDate = d, trAmount = v, trDesc = e, trFile = f} =
T.append "Unmatched transaction: " $
keyVals
[ ("path", T.pack f)
, ("date", T.pack $ iso8601Show d)
, ("value", showT (fromRational v :: Float))
, ("description", doubleQuote e)
2023-01-25 20:52:27 -05:00
]
2023-02-01 23:02:07 -05:00
showMatch :: MatchRe -> T.Text
2023-01-25 20:52:27 -05:00
showMatch Match {mDate = d, mVal = v, mDesc = e, mOther = o, mTimes = n, mPriority = p} =
T.append "Unused match: " $ keyVals [(x, y) | (x, Just y) <- kvs]
where
kvs =
[ ("date", showDateMatcher <$> d)
, ("val", showValMatcher v)
2023-02-01 23:02:07 -05:00
, ("desc", fst <$> e)
2023-01-25 20:52:27 -05:00
, ("other", others)
2023-01-28 20:05:26 -05:00
, ("counter", Just $ maybe "Inf" showT n)
2023-01-25 20:52:27 -05:00
, ("priority", Just $ showT p)
]
others = case o of
[] -> 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)
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)
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
showYMDMatcher :: YMDMatcher -> T.Text
showYMDMatcher = showYMD_ . fromYMDMatcher
2023-01-28 19:32:56 -05:00
showYMD_ :: YMD_ -> T.Text
showYMD_ md =
2023-01-28 18:52:28 -05:00
T.intercalate "-" $ L.take 3 (fmap showT digits ++ L.repeat "*")
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
showValMatcher :: ValMatcher -> Maybe T.Text
showValMatcher ValMatcher {mvSign = Nothing, mvNum = Nothing, mvDen = Nothing} = Nothing
showValMatcher ValMatcher {mvNum, mvDen, mvSign, mvPrec} =
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 =
[ ("sign", (\s -> if s then "+" else "-") <$> mvSign)
, ("numerator", showT <$> mvNum)
, ("denominator", showT <$> mvDen)
, ("precision", Just $ showT mvPrec)
]
2023-01-25 20:52:27 -05:00
2023-02-01 23:02:07 -05:00
showMatchOther :: MatchOtherRe -> T.Text
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"
, singleQuote $ fromMaybe "*" $ showValMatcher mv
2023-01-28 20:03:58 -05:00
]
2023-01-25 20:52:27 -05:00
showSplit :: RawSplit -> T.Text
showSplit Entry {sAcnt = a, sValue = v, sComment = c} =
2023-01-28 20:03:58 -05:00
keyVals
[ ("account", a)
, ("value", T.pack $ show ((fromRational <$> v) :: Maybe Float))
, ("comment", doubleQuote c)
]
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
showT :: Show a => a -> T.Text
showT = T.pack . show
--------------------------------------------------------------------------------
-- pure error processing
2023-01-26 23:41:45 -05:00
concatEither2 :: Either x a -> Either x b -> (a -> b -> c) -> Either [x] c
concatEither2 a b fun = case (a, b) of
(Right a_, Right b_) -> Right $ fun a_ b_
_ -> Left $ catMaybes [leftToMaybe a, leftToMaybe b]
2023-02-12 21:52:41 -05:00
concatEither2M :: Monad m => Either x a -> Either x b -> (a -> b -> m c) -> m (Either [x] c)
concatEither2M a b fun = case (a, b) of
(Right a_, Right b_) -> Right <$> fun a_ b_
_ -> return $ Left $ catMaybes [leftToMaybe a, leftToMaybe b]
2023-01-28 20:03:58 -05:00
concatEither3 :: Either x a -> Either x b -> Either x c -> (a -> b -> c -> d) -> Either [x] d
concatEither3 a b c fun = case (a, b, c) of
(Right a_, Right b_, Right c_) -> Right $ fun a_ b_ c_
_ -> Left $ catMaybes [leftToMaybe a, leftToMaybe b, leftToMaybe c]
2023-01-26 23:41:45 -05:00
concatEithers2 :: Either [x] a -> Either [x] b -> (a -> b -> c) -> Either [x] c
2023-01-27 23:33:34 -05:00
concatEithers2 a b = merge . concatEither2 a b
2023-01-26 23:41:45 -05:00
2023-02-12 21:52:41 -05:00
concatEithers2M
:: Monad m
=> Either [x] a
-> Either [x] b
-> (a -> b -> m c)
-> m (Either [x] c)
concatEithers2M a b = fmap merge . concatEither2M a b
concatEithers3
:: Either [x] a
-> Either [x] b
-> Either [x] c
-> (a -> b -> c -> d)
-> Either [x] d
concatEithers3 a b c = merge . concatEither3 a b c
2023-01-26 23:41:45 -05:00
concatEitherL :: [Either x a] -> Either [x] [a]
concatEitherL as = case partitionEithers as of
([], bs) -> Right bs
(es, _) -> Left es
concatEithersL :: [Either [x] a] -> Either [x] [a]
2023-01-27 23:33:34 -05:00
concatEithersL = merge . concatEitherL
2023-01-26 23:41:45 -05:00
leftToMaybe :: Either a b -> Maybe a
leftToMaybe (Left a) = Just a
leftToMaybe _ = Nothing
2023-01-27 20:31:13 -05:00
2023-01-28 22:55:07 -05:00
unlessLeft :: (Monad m, MonadPlus n) => Either a b -> (b -> m (n a)) -> m (n a)
2023-01-27 20:31:13 -05:00
unlessLeft (Left es) _ = return (return es)
2023-01-28 22:55:07 -05:00
unlessLeft (Right rs) f = f rs
2023-01-27 20:31:13 -05:00
2023-01-28 22:55:07 -05:00
unlessLefts :: (Monad m) => Either (n a) b -> (b -> m (n a)) -> m (n a)
2023-01-27 20:31:13 -05:00
unlessLefts (Left es) _ = return es
2023-01-28 22:55:07 -05:00
unlessLefts (Right rs) f = f rs
unlessLeft_ :: (Monad m, MonadPlus n) => Either a b -> (b -> m ()) -> m (n a)
unlessLeft_ e f = unlessLeft e (\x -> void (f x) >> return mzero)
unlessLefts_ :: (Monad m, MonadPlus n) => Either (n a) b -> (b -> m ()) -> m (n a)
unlessLefts_ e f = unlessLefts e (\x -> void (f x) >> return mzero)
2023-01-27 23:33:34 -05:00
plural :: Either a b -> Either [a] b
plural = first (: [])
merge :: Either [[a]] b -> Either [a] b
merge = first concat
--------------------------------------------------------------------------------
-- random functions
-- when bifunctor fails...
2023-01-28 19:32:56 -05:00
-- thrice :: (a -> d) -> (b -> e) -> (c -> f) -> (a, b, c) -> (d, e, f)
-- thrice f1 f2 f3 (x, y, z) = (f1 x, f2 y, f3 z)
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-04-16 20:09:13 -04:00
fstOf3 :: (a, b, c) -> a
fstOf3 (a, _, _) = a
sndOf3 :: (a, b, c) -> b
sndOf3 (_, b, _) = b
thdOf3 :: (a, b, c) -> c
thdOf3 (_, _, c) = c
2023-01-28 19:32:56 -05:00
-- lpad :: a -> Int -> [a] -> [a]
-- lpad c n s = replicate (n - length s) c ++ s
2023-01-27 23:33:34 -05:00
2023-01-28 19:32:56 -05:00
-- rpad :: a -> Int -> [a] -> [a]
-- rpad c n s = s ++ replicate (n - length s) c
2023-01-27 23:33:34 -05:00
2023-01-28 20:03:58 -05:00
-- lpadT :: Char -> Int -> T.Text -> T.Text
-- lpadT c n s = T.append (T.replicate (n - T.length s) (T.singleton c)) s
2023-01-28 18:52:28 -05:00
-- TODO this regular expression appears to be compiled each time, which is
-- super slow
-- NOTE: see https://github.com/haskell-hvr/regex-tdfa/issues/9 - performance
-- is likely not going to be optimal for text
2023-02-01 23:02:07 -05:00
-- matchMaybe :: T.Text -> T.Text -> EitherErr Bool
-- matchMaybe q pat = case compres of
-- Right re -> case execute re q of
-- Right res -> Right $ isJust res
-- Left _ -> Left $ RegexError "this should not happen"
-- Left _ -> Left $ RegexError pat
-- where
-- -- these options barely do anything in terms of performance
-- compres = compile (blankCompOpt {newSyntax = True}) (blankExecOpt {captureGroups = False}) pat
compileOptions :: TxOpts T.Text -> EitherErr TxOptsRe
compileOptions o@TxOpts {toAmountFmt = pat} = do
re <- compileRegex True pat
return $ o {toAmountFmt = re}
2023-02-01 23:02:07 -05:00
compileMatch :: Match T.Text -> EitherErrs MatchRe
compileMatch m@Match {mDesc = d, mOther = os} = do
let dres = plural $ mapM go d
let ores = concatEitherL $ fmap (mapM go) os
2023-02-01 23:02:07 -05:00
concatEithers2 dres ores $ \d_ os_ -> m {mDesc = d_, mOther = os_}
where
go = compileRegex False
2023-02-01 23:02:07 -05:00
compileRegex :: Bool -> T.Text -> EitherErr (Text, Regex)
compileRegex groups pat = case res of
2023-02-01 23:02:07 -05:00
Right re -> Right (pat, re)
Left _ -> Left $ RegexError pat
where
res =
compile
(blankCompOpt {newSyntax = True})
(blankExecOpt {captureGroups = groups})
pat
2023-02-01 23:02:07 -05:00
matchMaybe :: T.Text -> Regex -> EitherErr Bool
2023-02-01 23:02:07 -05:00
matchMaybe q re = case execute re q of
Right res -> Right $ isJust res
Left _ -> Left $ 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 _ -> []