pwncash/lib/Internal/Utils.hs

389 lines
12 KiB
Haskell
Raw Normal View History

{-# LANGUAGE FlexibleContexts #-}
2022-12-11 17:51:11 -05:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
2022-12-11 17:51:11 -05:00
module Internal.Utils where
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
import qualified RIO.Text as T
import RIO.Time
import Text.Regex.TDFA
2022-12-11 17:51:11 -05:00
-- when bifunctor fails...
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-25 20:52:27 -05:00
-- TODO get rid of these errors
2023-01-25 23:04:54 -05:00
gregTup :: Gregorian -> EitherErr (Integer, Int, Int)
gregTup Gregorian {..}
| gYear > 99 = Left $ YearError gYear
| otherwise =
2023-01-25 23:04:54 -05:00
return
( fromIntegral gYear + 2000
, fromIntegral gMonth
, fromIntegral gDay
)
gregMTup :: GregorianM -> EitherErr (Integer, Int)
gregMTup GregorianM {..}
| gmYear > 99 = Left $ YearError gmYear
| otherwise =
2023-01-25 23:04:54 -05:00
return
( fromIntegral gmYear + 2000
, fromIntegral gmMonth
)
data MDY_ = Y_ Integer | YM_ Integer Int | YMD_ Integer Int Int
2023-01-25 23:04:54 -05:00
fromMatchYMD :: MatchYMD -> EitherErr MDY_
fromMatchYMD m = case m of
Y y
2023-01-25 23:04:54 -05:00
| y > 99 -> Left $ YearError y
| otherwise -> Right $ Y_ $ fromIntegral y + 2000
YM g -> uncurry YM_ <$> gregMTup g
YMD g -> uncurry3 YMD_ <$> gregTup g
compareDate :: MatchDate -> Day -> EitherErr Ordering
compareDate (On md) x = do
res <- fromMatchYMD md
return $ case res of
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
res <- fromMatchYMD md
return $ case res of
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-25 23:04:54 -05:00
dateMatches :: MatchDate -> Day -> EitherErr Bool
dateMatches md = fmap (EQ ==) . compareDate md
2022-12-11 17:51:11 -05:00
valMatches :: MatchVal -> Rational -> Bool
valMatches MatchVal {..} x =
checkMaybe (s ==) mvSign
&& checkMaybe (n ==) mvNum
&& checkMaybe ((d * p ==) . fromIntegral) mvDen
2022-12-11 17:51:11 -05:00
where
(n, d) = properFraction $ abs x
p = 10 ^ mvPrec
s = signum x >= 0
2023-01-25 23:04:54 -05:00
evalSplit :: TxRecord -> ExpSplit -> EitherErr RawSplit
evalSplit r s@Split {sAcnt = a, sValue = v, sCurrency = c} = do
a_ <- evalAcnt r a
v_ <- mapM (evalExp r) v
c_ <- evalCurrency r c
return (s {sAcnt = a_, sValue = v_, sCurrency = c_})
2022-12-11 17:51:11 -05:00
2023-01-25 23:04:54 -05:00
evalAcnt :: TxRecord -> SplitAcnt -> EitherErr T.Text
evalAcnt TxRecord {trOther = o} s = case s of
2023-01-25 23:04:54 -05:00
ConstT p -> Right p
LookupT f -> lookupErr AccountField f o
MapT (Field f m) -> do
k <- lookupErr AccountField f o
lookupErr AccountField k m
Map2T (Field (f1, f2) m) -> do
k1 <- lookupErr AccountField f1 o
k2 <- lookupErr AccountField f2 o
lookupErr AccountField (k1, k2) m
evalCurrency :: TxRecord -> SplitCur -> EitherErr T.Text
evalCurrency TxRecord {trOther = o} s = case s of
2023-01-25 23:04:54 -05:00
ConstT p -> Right p
LookupT f -> lookupErr CurrencyField f o
MapT (Field f m) -> do
k <- lookupErr CurrencyField f o
lookupErr CurrencyField k m
Map2T (Field (f1, f2) m) -> do
k1 <- lookupErr CurrencyField f1 o
k2 <- lookupErr CurrencyField f2 o
lookupErr CurrencyField (k1, k2) m
2022-12-11 17:51:11 -05:00
errorT :: T.Text -> a
errorT = error . T.unpack
2023-01-25 23:04:54 -05:00
-- lookupField :: (Ord k, Show k) => k -> M.Map k v -> v
-- lookupField = lookupErr "field"
2022-12-11 17:51:11 -05:00
2023-01-25 23:04:54 -05:00
lookupErr :: (Ord k, Show k) => LookupField -> k -> M.Map k v -> EitherErr v
2022-12-11 17:51:11 -05:00
lookupErr what k m = case M.lookup k m of
2023-01-25 23:04:54 -05:00
Just x -> Right x
_ -> Left $ LookupError what $ showT k
2022-12-11 17:51:11 -05:00
2023-01-24 23:24:41 -05:00
matches :: Match -> TxRecord -> EitherErr (MatchRes RawTx)
matches Match {..} r@TxRecord {..} = do
2023-01-25 23:04:54 -05:00
date <- maybe (Right True) (`dateMatches` trDate) mDate
let val = valMatches mVal trAmount
other <- foldM (\a o -> (a &&) <$> fieldMatches trOther o) True mOther
desc <- maybe (return True) (matchMaybe trDesc) mDesc
2023-01-25 23:04:54 -05:00
if date && val && desc && other
then maybe (Right MatchSkip) (fmap MatchPass . eval) mTx
else Right MatchFail
2022-12-11 17:51:11 -05:00
where
eval (ToTx cur a ss) = toTx cur a ss r
2023-01-24 23:24:41 -05:00
matchMaybe :: RegexContext Regex query b => query -> T.Text -> EitherErr b
matchMaybe q re = first (const $ RegexError re) $ pureTry $ q =~ re
2023-01-24 23:24:41 -05:00
fieldMatches :: M.Map T.Text T.Text -> MatchOther -> EitherErr Bool
2022-12-11 17:51:11 -05:00
fieldMatches dict m = case m of
2023-01-25 23:04:54 -05:00
Val (Field n mv) -> valMatches mv <$> (readRational =<< lookup_ n)
Desc (Field n md) -> (`matchMaybe` md) =<< lookup_ n
where
lookup_ n = case M.lookup n dict of
Just r -> Right r
2023-01-25 23:04:54 -05:00
Nothing -> Left $ LookupError OtherField n
2022-12-11 17:51:11 -05:00
checkMaybe :: (a -> Bool) -> Maybe a -> Bool
checkMaybe = maybe True
2023-01-25 23:04:54 -05:00
toTx :: SplitCur -> SplitAcnt -> [ExpSplit] -> TxRecord -> EitherErr RawTx
toTx sc sa toSplits r@TxRecord {..} = do
a_ <- evalAcnt r sa
c_ <- evalCurrency r sc
ss_ <- mapM (evalSplit r) toSplits
let fromSplit =
Split
{ sAcnt = a_
, sCurrency = c_
, sValue = Just trAmount
, sComment = ""
}
return $
Tx
{ txTags = []
, txDate = trDate
, txDescr = trDesc
, txSplits = fromSplit : ss_
}
2022-12-11 17:51:11 -05:00
parseRational :: MonadFail m => T.Text -> T.Text -> m Rational
parseRational pat s = case ms of
[sign, x, ""] -> uncurry (*) <$> readWhole sign x
[sign, x, y] -> do
d <- readT "decimal" y
let p = 10 ^ T.length y
(k, w) <- readWhole sign x
return $ k * (w + d % p)
_ -> msg "malformed decimal"
2022-12-11 17:51:11 -05:00
where
(_, _, _, ms) = (s =~ pat) :: (T.Text, T.Text, T.Text, [T.Text])
readT what t = case readMaybe $ T.unpack t of
Just d -> return $ fromInteger d
_ -> msg $ T.unwords ["could not parse", what, t]
msg m =
fail $
T.unpack $
T.concat
[ m
, "; 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
readWhole sign x = do
w <- readT "whole number" x
k <- readSign sign
return (k, w)
2023-01-25 23:04:54 -05:00
-- readRationalMsg :: T.Text -> EitherErr Rational
-- readRationalMsg t = maybe (Left $ ConversionError t) Right $ readRational t
readRational :: T.Text -> EitherErr Rational
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
2022-12-11 17:51:11 -05:00
where
2023-01-25 23:04:54 -05:00
readT = readMaybe . T.unpack
err = Left $ ConversionError s
2022-12-11 17:51:11 -05:00
-- TODO smells like a lens
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
2023-01-25 23:04:54 -05:00
boundsFromGregorian :: (Gregorian, Gregorian) -> EitherErr Bounds
boundsFromGregorian (a, b) = do
a_ <- fromGregorian' a
b_ <- fromGregorian' b
return (a_, b_)
2022-12-11 17:51:11 -05:00
2023-01-25 23:04:54 -05:00
fromGregorian' :: Gregorian -> EitherErr Day
fromGregorian' = fmap (uncurry3 fromGregorian) . gregTup
2022-12-11 17:51:11 -05:00
inBounds :: Bounds -> Day -> Bool
inBounds (d0, d1) x = d0 <= x && x <= d1
inMaybeBounds :: MaybeBounds -> Day -> Bool
inMaybeBounds (d0, d1) x = maybe True (x >=) d0 && maybe True (x <=) d1
2023-01-25 23:04:54 -05:00
intervalMaybeBounds :: Interval -> EitherErr MaybeBounds
intervalMaybeBounds Interval {intStart = s, intEnd = e} = do
s_ <- mapM fromGregorian' s
e_ <- mapM fromGregorian' e
return (s_, e_)
2022-12-11 17:51:11 -05:00
2023-01-05 22:23:22 -05:00
resolveBounds :: MonadUnliftIO m => MaybeBounds -> m Bounds
2022-12-11 17:51:11 -05:00
resolveBounds (s, e) = do
s' <- maybe getDay return s
e' <- maybe (addGregorianYearsClip 50 <$> getDay) return e
return (s', e')
where
getDay = utctDay <$> getCurrentTime
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
uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 f (a, b, c) = f a b c
lpad :: a -> Int -> [a] -> [a]
lpad c n s = replicate (n - length s) c ++ s
rpad :: a -> Int -> [a] -> [a]
rpad c n s = s ++ replicate (n - length s) c
2023-01-25 23:04:54 -05:00
evalExp :: TxRecord -> SplitNum -> EitherErr Rational
2022-12-11 17:51:11 -05:00
evalExp r s = case s of
2023-01-25 23:04:54 -05:00
(LookupN t) -> readRational =<< lookupErr OtherField t (trOther r)
(ConstN c) -> Right $ dec2Rat c
AmountN -> Right $ trAmount r
2022-12-11 17:51:11 -05:00
dec2Rat :: Decimal -> Rational
2022-12-14 23:59:23 -05:00
dec2Rat D {..} =
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
showError :: InsertError -> [T.Text]
showError (StatementError ts ms) = (showTx <$> ts) ++ (showMatch <$> ms)
showError other = (: []) $ case other of
2023-01-25 23:04:54 -05:00
(YearError y) -> T.append "Year must be two digits: " $ showT y
2023-01-24 23:24:41 -05:00
(RegexError re) -> T.append "could not make regex from pattern: " re
(ConversionError x) -> T.append "Could not convert to rational number: " x
2023-01-25 23:04:54 -05:00
-- TODO use the field indicator
(LookupError _ f) -> T.append "Could not find field: " f
2023-01-25 20:52:27 -05:00
(BalanceError t cur rss) ->
T.concat
[ msg
, " for currency "
, singleQuote cur
, " and for splits "
, splits
]
where
msg = case t of
TooFewSplits -> "Need at least two splits to balance"
NotOneBlank -> "Exactly one split must be blank"
splits = T.intercalate ", " $ fmap showSplit rss
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)
]
showMatch :: Match -> T.Text
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", showMatchDate <$> d)
, ("val", showMatchVal v)
, ("desc", e)
, ("other", others)
, -- TODO it might be best to always show this
("counter", showT <$> n)
, ("priority", Just $ showT p)
]
others = case o of
[] -> Nothing
xs -> Just $ T.concat $ showMatchOther <$> xs
showMatchDate :: MatchDate -> T.Text
showMatchDate md = case md of
(On x) ->
let ys = case x of
Y y -> [y]
YM (GregorianM {..}) -> [gmYear, gmMonth]
YMD (Gregorian {..}) -> [gYear, gMonth, gDay]
in T.intercalate "-" $ L.take 3 (fmap showT ys ++ L.repeat "*")
(In _ _) -> undefined
-- let ys = case x of
-- Y y -> [y]
-- YM (GregorianM {..}) -> [gmYear, gmMonth]
-- YMD (Gregorian {..}) -> [gYear, gMonth, gDay]
-- in T.intercalate "-" $ L.take 3 (fmap showT ys ++ L.repeat "*")
showT :: Show a => a -> T.Text
showT = T.pack . show
showMatchVal :: MatchVal -> Maybe T.Text
showMatchVal = undefined
showMatchOther :: MatchOther -> T.Text
showMatchOther = undefined
showSplit :: RawSplit -> T.Text
showSplit Split {sAcnt = a, sValue = v, sComment = c} =
singleQuote $
keyVals
[ ("account", a)
, ("value", T.pack $ show ((fromRational <$> v) :: Maybe Float))
, ("comment", doubleQuote c)
]
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)