diff options
Diffstat (limited to 'app')
| -rw-r--r-- | app/Data/Iban.hs | 48 | ||||
| -rw-r--r-- | app/Data/Ledger.hs | 115 | ||||
| -rw-r--r-- | app/Data/Ledger/AutoFile.hs | 1 | ||||
| -rw-r--r-- | app/Data/Res.hs | 31 | ||||
| -rw-r--r-- | app/Format.hs | 3 | ||||
| -rw-r--r-- | app/Import/Ing/Convert.hs | 257 | ||||
| -rw-r--r-- | app/Import/Ing/CurrentAccountCsv.hs | 407 | ||||
| -rw-r--r-- | app/Import/Ing/SavingsAccountCsv.hs | 164 | ||||
| -rw-r--r-- | app/Import/Ing/Shared.hs | 44 | ||||
| -rw-r--r-- | app/Main.hs | 4 |
10 files changed, 0 insertions, 1074 deletions
diff --git a/app/Data/Iban.hs b/app/Data/Iban.hs deleted file mode 100644 index d9566b9..0000000 --- a/app/Data/Iban.hs +++ /dev/null | |||
| @@ -1,48 +0,0 @@ | |||
| 1 | module Data.Iban (Iban, mkIban, toText) where | ||
| 2 | |||
| 3 | import Control.Applicative ((<|>)) | ||
| 4 | import Data.Attoparsec.Text as AP | ||
| 5 | import Data.Char | ||
| 6 | ( digitToInt, | ||
| 7 | isAscii, | ||
| 8 | isDigit, | ||
| 9 | ord, | ||
| 10 | toUpper, | ||
| 11 | ) | ||
| 12 | import Data.Text qualified as T | ||
| 13 | |||
| 14 | newtype Iban = Iban T.Text deriving (Show, Eq) | ||
| 15 | |||
| 16 | mkIban :: T.Text -> Either String Iban | ||
| 17 | mkIban t = validateIban t >> return (Iban t) | ||
| 18 | |||
| 19 | validateIban :: T.Text -> Either String () | ||
| 20 | validateIban = AP.parseOnly $ do | ||
| 21 | countryCode <- AP.count 2 AP.letter | ||
| 22 | checkDigits <- AP.count 2 AP.digit | ||
| 23 | chars <- AP.many1 (AP.letter <|> AP.digit) | ||
| 24 | endOfInput | ||
| 25 | if length chars < 30 | ||
| 26 | then | ||
| 27 | if valid countryCode checkDigits chars | ||
| 28 | then return () | ||
| 29 | else fail $ "IBAN checksum does not match (" ++ countryCode ++ checkDigits ++ chars ++ ")" | ||
| 30 | else fail "IBAN has more than 34 characters" | ||
| 31 | where | ||
| 32 | letterToInt c = ord (toUpper c) - ord 'A' + 10 | ||
| 33 | charsToInteger = | ||
| 34 | foldl' | ||
| 35 | ( \acc -> \case | ||
| 36 | d | ||
| 37 | | isDigit d -> acc * 10 + toInteger (digitToInt d) | ||
| 38 | | isAscii d -> acc * 100 + toInteger (letterToInt d) | ||
| 39 | | otherwise -> error "unreachable" | ||
| 40 | ) | ||
| 41 | 0 | ||
| 42 | ibanToInteger countryCode checkDigits chars = | ||
| 43 | charsToInteger chars * 1000000 + charsToInteger countryCode * 100 + charsToInteger checkDigits | ||
| 44 | valid countryCode checkDigits chars = | ||
| 45 | ibanToInteger countryCode checkDigits chars `mod` 97 == 1 | ||
| 46 | |||
| 47 | toText :: Iban -> T.Text | ||
| 48 | toText (Iban t) = t | ||
diff --git a/app/Data/Ledger.hs b/app/Data/Ledger.hs deleted file mode 100644 index 4aa5137..0000000 --- a/app/Data/Ledger.hs +++ /dev/null | |||
| @@ -1,115 +0,0 @@ | |||
| 1 | {-# LANGUAGE TemplateHaskell #-} | ||
| 2 | {-# LANGUAGE TypeFamilies #-} | ||
| 3 | |||
| 4 | module Data.Ledger where | ||
| 5 | |||
| 6 | import Data.Constraint.Extras.TH (deriveArgDict) | ||
| 7 | import Data.Dependent.Map (DMap, fromList, singleton, union, unionWithKey) | ||
| 8 | import Data.Dependent.Sum ((==>)) | ||
| 9 | import Data.Functor.Identity | ||
| 10 | import Data.Functor.Identity (Identity (..)) | ||
| 11 | import Data.GADT.Compare.TH (deriveGCompare, deriveGEq) | ||
| 12 | import Data.GADT.Show.TH (deriveGShow) | ||
| 13 | import Data.Iban | ||
| 14 | import Data.Map qualified as M | ||
| 15 | import Data.Text qualified as T | ||
| 16 | import Data.Time.Calendar | ||
| 17 | import Data.Time.Clock | ||
| 18 | import Data.UUID | ||
| 19 | import GHC.Generics | ||
| 20 | |||
| 21 | data AccountType = Asset | Equity | Liability | Expense | Income | ||
| 22 | |||
| 23 | data TxAction = Inc | Dec | ||
| 24 | |||
| 25 | txaOpp :: TxAction -> TxAction | ||
| 26 | txaOpp Inc = Dec | ||
| 27 | txaOpp Dec = Inc | ||
| 28 | |||
| 29 | onDebit :: AccountType -> TxAction | ||
| 30 | onDebit Asset = Inc | ||
| 31 | onDebit Equity = Dec | ||
| 32 | onDebit Liability = Dec | ||
| 33 | onDebit Expense = Inc | ||
| 34 | onDebit Income = Dec | ||
| 35 | |||
| 36 | onCredit :: AccountType -> TxAction | ||
| 37 | onCredit = txaOpp . onDebit | ||
| 38 | |||
| 39 | data TxType | ||
| 40 | = InterestCtx | ||
| 41 | | OnlineBankingTx | ||
| 42 | | RecurrentDirectTx | ||
| 43 | | PaymentTerminalTx | ||
| 44 | | CashPaymentTx | ||
| 45 | | AtmTx | ||
| 46 | | AutoSaveRoundingTx | ||
| 47 | | BatchTx | ||
| 48 | | DirectDebitTx | ||
| 49 | | PeriodicTx | ||
| 50 | |||
| 51 | data IbanTag = AccountTag | CounterpartyIbanTag deriving (Eq, Enum, Ord, Show) | ||
| 52 | |||
| 53 | data UnitTag = FiledTag | GooglePayTag | AutoRoundSavingsTag deriving (Eq, Enum, Ord, Show) | ||
| 54 | |||
| 55 | data TextTag = DescTag | UserTag | CounterpartyNameTag | ReferenceTag | MandateIdTag | CreditorIdTag | OtherPartyTag | TransactionTag | TerminalTag | CardSeqNoTag | SavingsAccountTag deriving (Eq, Enum, Ord, Show) | ||
| 56 | |||
| 57 | data Label a where | ||
| 58 | TextLabel :: TextTag -> Label T.Text | ||
| 59 | IbanLabel :: IbanTag -> Label Iban | ||
| 60 | UnitLabel :: UnitTag -> Label () | ||
| 61 | TimestampLabel :: Label UTCTime | ||
| 62 | |||
| 63 | deriveGEq ''Label | ||
| 64 | deriveGCompare ''Label | ||
| 65 | deriveGShow ''Label | ||
| 66 | deriveArgDict ''Label | ||
| 67 | |||
| 68 | type Labels = DMap Label Identity | ||
| 69 | |||
| 70 | data Money = Money Integer deriving (Show) | ||
| 71 | |||
| 72 | infixl 6 +€, -€ | ||
| 73 | |||
| 74 | (+€) :: Money -> Money -> Money | ||
| 75 | Money x +€ Money y = Money (x + y) | ||
| 76 | |||
| 77 | (-€) :: Money -> Money -> Money | ||
| 78 | Money x -€ Money y = Money (x - y) | ||
| 79 | |||
| 80 | data Scalar = Amount Money | Rate Integer deriving (Show) | ||
| 81 | |||
| 82 | data AccountId = AccountId [T.Text] deriving (Show) | ||
| 83 | |||
| 84 | data CommodityId = CommodityId UUID deriving (Show) | ||
| 85 | |||
| 86 | data Account = Account | ||
| 87 | { id :: AccountId, | ||
| 88 | description :: [T.Text], | ||
| 89 | commodityId :: CommodityId, | ||
| 90 | balance :: Money | ||
| 91 | } | ||
| 92 | |||
| 93 | -- A balance assertion is only valid when all transactions before it have been | ||
| 94 | -- cleared and the balance of the account agrees with the amount in the | ||
| 95 | -- assertion. | ||
| 96 | data BalAssert = BalAssert | ||
| 97 | { account :: AccountId, | ||
| 98 | amount :: Money, | ||
| 99 | labels :: Labels | ||
| 100 | } | ||
| 101 | |||
| 102 | data Tx = Tx | ||
| 103 | { cleared :: Maybe Day, | ||
| 104 | commodityId :: CommodityId, -- the commodity w.r.t. which rates are calculated | ||
| 105 | debit :: M.Map AccountId Scalar, | ||
| 106 | credit :: M.Map AccountId Scalar, | ||
| 107 | labels :: Labels | ||
| 108 | } | ||
| 109 | deriving (Show, Generic) | ||
| 110 | |||
| 111 | -- data SeqTx = SeqTx [Integer] Tx | ||
| 112 | |||
| 113 | data Entry = TxEntry Tx | BalAssertEntry BalAssert | ||
| 114 | |||
| 115 | data Ledger = Ledger [Entry] | ||
diff --git a/app/Data/Ledger/AutoFile.hs b/app/Data/Ledger/AutoFile.hs deleted file mode 100644 index 15a1b16..0000000 --- a/app/Data/Ledger/AutoFile.hs +++ /dev/null | |||
| @@ -1 +0,0 @@ | |||
| 1 | module Data.Ledger.AutoFile where | ||
diff --git a/app/Data/Res.hs b/app/Data/Res.hs deleted file mode 100644 index 3806e5a..0000000 --- a/app/Data/Res.hs +++ /dev/null | |||
| @@ -1,31 +0,0 @@ | |||
| 1 | module Data.Res where | ||
| 2 | |||
| 3 | import Control.Applicative | ||
| 4 | import Data.String (IsString (fromString)) | ||
| 5 | |||
| 6 | data Res e r = Ok r | Err e | ||
| 7 | |||
| 8 | instance Functor (Res e) where | ||
| 9 | fmap f (Ok v) = Ok (f v) | ||
| 10 | fmap _ (Err e) = Err e | ||
| 11 | |||
| 12 | instance Applicative (Res e) where | ||
| 13 | pure = Ok | ||
| 14 | (Ok f) <*> (Ok v) = Ok (f v) | ||
| 15 | (Err e) <*> _ = Err e | ||
| 16 | _ <*> (Err e) = Err e | ||
| 17 | |||
| 18 | instance Monad (Res e) where | ||
| 19 | (Ok v) >>= f = f v | ||
| 20 | (Err e) >>= _ = Err e | ||
| 21 | |||
| 22 | instance (IsString e) => MonadFail (Res e) where | ||
| 23 | fail = Err . fromString | ||
| 24 | |||
| 25 | instance (IsString e) => Alternative (Res e) where | ||
| 26 | empty = fail "mzero" | ||
| 27 | m1@(Ok _) <|> _ = m1 | ||
| 28 | (Err _) <|> m2 = m2 | ||
| 29 | |||
| 30 | liftEither :: Either e r -> Res e r | ||
| 31 | liftEither = either Err Ok | ||
diff --git a/app/Format.hs b/app/Format.hs deleted file mode 100644 index a779d95..0000000 --- a/app/Format.hs +++ /dev/null | |||
| @@ -1,3 +0,0 @@ | |||
| 1 | module Format where | ||
| 2 | |||
| 3 | import Text.Parsec | ||
diff --git a/app/Import/Ing/Convert.hs b/app/Import/Ing/Convert.hs deleted file mode 100644 index 5dcda0b..0000000 --- a/app/Import/Ing/Convert.hs +++ /dev/null | |||
| @@ -1,257 +0,0 @@ | |||
| 1 | module Import.Ing.Convert where | ||
| 2 | |||
| 3 | import Control.Monad (when) | ||
| 4 | import Data.Decimal | ||
| 5 | import Data.Dependent.Map | ||
| 6 | import Data.Dependent.Sum ((==>)) | ||
| 7 | import Data.Functor.Identity | ||
| 8 | import Data.Iban qualified as Iban | ||
| 9 | import Data.Ledger as L | ||
| 10 | import Data.Map qualified as M | ||
| 11 | import Data.Res | ||
| 12 | import Data.Text qualified as T | ||
| 13 | import Import.Ing.CurrentAccountCsv as C | ||
| 14 | import Import.Ing.SavingsAccountCsv as S | ||
| 15 | |||
| 16 | virtCheckingAcc :: L.AccountId | ||
| 17 | virtCheckingAcc = AccountId ["Unfiled", "Checking"] | ||
| 18 | |||
| 19 | virtSavingsAcc :: L.AccountId | ||
| 20 | virtSavingsAcc = AccountId ["Unfiled", "Savings"] | ||
| 21 | |||
| 22 | virtCounterparty :: L.AccountId | ||
| 23 | virtCounterparty = AccountId ["Unfiled", "Counterparty"] | ||
| 24 | |||
| 25 | toCents :: Decimal -> Res String L.Money | ||
| 26 | toCents m | ||
| 27 | | f == 0 = | ||
| 28 | return (L.Money m') | ||
| 29 | | otherwise = | ||
| 30 | fail "Cannot convert to whole cents: amount of money is more specific" | ||
| 31 | where | ||
| 32 | (m', f) = properFraction (m * 100) | ||
| 33 | |||
| 34 | condUnitLabel :: UnitTag -> Bool -> L.Labels | ||
| 35 | condUnitLabel _ False = empty | ||
| 36 | condUnitLabel t True = singleton (UnitLabel t) (Identity ()) | ||
| 37 | |||
| 38 | lesFromCurrentAcc :: CommodityId -> C.Tx -> Res String [L.Entry] | ||
| 39 | lesFromCurrentAcc eucId tx@(C.Tx base _) = do | ||
| 40 | tx' <- txFromCurrentAcc eucId tx | ||
| 41 | ba <- baFromCurrentAccBase base | ||
| 42 | return [BalAssertEntry ba, TxEntry tx'] | ||
| 43 | |||
| 44 | baFromCurrentAccBase :: C.TxBase -> Res String L.BalAssert | ||
| 45 | baFromCurrentAccBase base = do | ||
| 46 | resBal <- toCents base.resBal | ||
| 47 | return $ | ||
| 48 | L.BalAssert | ||
| 49 | { account = virtCheckingAcc, | ||
| 50 | amount = resBal, | ||
| 51 | labels = | ||
| 52 | fromList [IbanLabel AccountTag ==> base.account] | ||
| 53 | } | ||
| 54 | |||
| 55 | baFromCurrentAcc :: C.Tx -> Res String L.BalAssert | ||
| 56 | baFromCurrentAcc (C.Tx base _) = baFromCurrentAccBase base | ||
| 57 | |||
| 58 | txFromCurrentAcc :: CommodityId -> C.Tx -> Res String L.Tx | ||
| 59 | txFromCurrentAcc eucId (C.Tx base spec) = do | ||
| 60 | when (base.amount < 0) $ | ||
| 61 | fail "Transaction amount may not be lower than zero" | ||
| 62 | amount <- L.Amount <$> toCents base.amount | ||
| 63 | case spec of | ||
| 64 | PaymentTerminalPayment | ||
| 65 | { counterpartyName, | ||
| 66 | cardSequenceNo, | ||
| 67 | timestamp, | ||
| 68 | transaction, | ||
| 69 | terminal, | ||
| 70 | googlePay | ||
| 71 | } -> | ||
| 72 | return $ | ||
| 73 | L.Tx | ||
| 74 | { cleared = Just base.date, | ||
| 75 | commodityId = eucId, | ||
| 76 | credit = M.singleton virtCheckingAcc amount, | ||
| 77 | debit = M.singleton virtCounterparty amount, | ||
| 78 | labels = | ||
| 79 | fromList | ||
| 80 | [ IbanLabel AccountTag ==> base.account, | ||
| 81 | TextLabel CounterpartyNameTag ==> counterpartyName, | ||
| 82 | TextLabel CardSeqNoTag ==> cardSequenceNo, | ||
| 83 | TextLabel TerminalTag ==> terminal, | ||
| 84 | TextLabel TransactionTag ==> transaction, | ||
| 85 | TimestampLabel ==> timestamp | ||
| 86 | ] | ||
| 87 | `union` condUnitLabel GooglePayTag googlePay | ||
| 88 | } | ||
| 89 | PaymentTerminalCashback | ||
| 90 | { counterpartyName, | ||
| 91 | cardSequenceNo, | ||
| 92 | timestamp, | ||
| 93 | transaction, | ||
| 94 | terminal | ||
| 95 | } -> | ||
| 96 | return $ | ||
| 97 | L.Tx | ||
| 98 | { cleared = Just base.date, | ||
| 99 | commodityId = eucId, | ||
| 100 | debit = M.singleton virtCheckingAcc amount, | ||
| 101 | credit = M.singleton virtCounterparty amount, | ||
| 102 | labels = | ||
| 103 | fromList | ||
| 104 | [ IbanLabel AccountTag ==> base.account, | ||
| 105 | TextLabel CounterpartyNameTag ==> counterpartyName, | ||
| 106 | TextLabel CardSeqNoTag ==> cardSequenceNo, | ||
| 107 | TextLabel TerminalTag ==> terminal, | ||
| 108 | TextLabel TransactionTag ==> transaction, | ||
| 109 | TimestampLabel ==> timestamp | ||
| 110 | ] | ||
| 111 | } | ||
| 112 | OnlineBankingCredit | ||
| 113 | { counterpartyName, | ||
| 114 | counterpartyIban, | ||
| 115 | description, | ||
| 116 | timestamp | ||
| 117 | } -> | ||
| 118 | return $ | ||
| 119 | L.Tx | ||
| 120 | { cleared = Just base.date, | ||
| 121 | commodityId = eucId, | ||
| 122 | debit = M.singleton virtCheckingAcc amount, | ||
| 123 | credit = M.singleton virtCounterparty amount, | ||
| 124 | labels = | ||
| 125 | fromList | ||
| 126 | [ IbanLabel AccountTag ==> base.account, | ||
| 127 | TextLabel CounterpartyNameTag ==> counterpartyName, | ||
| 128 | IbanLabel CounterpartyIbanTag ==> counterpartyIban, | ||
| 129 | TextLabel DescTag ==> description, | ||
| 130 | TimestampLabel ==> timestamp | ||
| 131 | ] | ||
| 132 | } | ||
| 133 | OnlineBankingDebit | ||
| 134 | { counterpartyName, | ||
| 135 | counterpartyIban, | ||
| 136 | description, | ||
| 137 | mtimestamp | ||
| 138 | } -> | ||
| 139 | return $ | ||
| 140 | L.Tx | ||
| 141 | { cleared = Just base.date, | ||
| 142 | commodityId = eucId, | ||
| 143 | debit = M.singleton virtCounterparty amount, | ||
| 144 | credit = M.singleton virtCheckingAcc amount, | ||
| 145 | labels = | ||
| 146 | fromList | ||
| 147 | [ IbanLabel AccountTag ==> base.account, | ||
| 148 | TextLabel CounterpartyNameTag ==> counterpartyName, | ||
| 149 | IbanLabel CounterpartyIbanTag ==> counterpartyIban, | ||
| 150 | TextLabel DescTag ==> description | ||
| 151 | ] | ||
| 152 | `union` (maybe empty (singleton TimestampLabel . Identity) mtimestamp) | ||
| 153 | } | ||
| 154 | RecurrentDirectDebit | ||
| 155 | { counterpartyName, | ||
| 156 | counterpartyIban, | ||
| 157 | description, | ||
| 158 | reference, | ||
| 159 | mandateId, | ||
| 160 | creditorId, | ||
| 161 | otherParty | ||
| 162 | } -> | ||
| 163 | return $ | ||
| 164 | L.Tx | ||
| 165 | { cleared = Just base.date, | ||
| 166 | commodityId = eucId, | ||
| 167 | credit = M.singleton virtCheckingAcc amount, | ||
| 168 | debit = M.singleton virtCounterparty amount, | ||
| 169 | labels = | ||
| 170 | fromList | ||
| 171 | [ IbanLabel AccountTag ==> base.account, | ||
| 172 | IbanLabel CounterpartyIbanTag ==> counterpartyIban, | ||
| 173 | TextLabel CounterpartyNameTag ==> counterpartyName, | ||
| 174 | TextLabel DescTag ==> description, | ||
| 175 | TextLabel ReferenceTag ==> reference, | ||
| 176 | TextLabel MandateIdTag ==> mandateId, | ||
| 177 | TextLabel CreditorIdTag ==> creditorId | ||
| 178 | ] | ||
| 179 | `union` (maybe empty (singleton (TextLabel OtherPartyTag) . Identity) otherParty) | ||
| 180 | } | ||
| 181 | RoundingSavingsDeposit | ||
| 182 | { savingsAccount | ||
| 183 | } -> | ||
| 184 | return $ | ||
| 185 | L.Tx | ||
| 186 | { cleared = Just base.date, | ||
| 187 | commodityId = eucId, | ||
| 188 | credit = M.singleton virtCheckingAcc amount, | ||
| 189 | debit = M.singleton virtSavingsAcc amount, | ||
| 190 | labels = | ||
| 191 | fromList | ||
| 192 | [ UnitLabel AutoRoundSavingsTag ==> (), | ||
| 193 | TextLabel SavingsAccountTag ==> savingsAccount | ||
| 194 | ] | ||
| 195 | } | ||
| 196 | DepositTransfer | ||
| 197 | { counterpartyName, | ||
| 198 | counterpartyIban, | ||
| 199 | description, | ||
| 200 | reference | ||
| 201 | } -> | ||
| 202 | return $ | ||
| 203 | L.Tx | ||
| 204 | { cleared = Just base.date, | ||
| 205 | commodityId = eucId, | ||
| 206 | debit = M.singleton virtCheckingAcc amount, | ||
| 207 | credit = M.singleton virtCounterparty amount, | ||
| 208 | labels = | ||
| 209 | fromList | ||
| 210 | [ IbanLabel CounterpartyIbanTag ==> counterpartyIban, | ||
| 211 | TextLabel CounterpartyNameTag ==> counterpartyName, | ||
| 212 | TextLabel DescTag ==> description, | ||
| 213 | TextLabel ReferenceTag ==> reference | ||
| 214 | ] | ||
| 215 | } | ||
| 216 | IdealDebit | ||
| 217 | { counterpartyName, | ||
| 218 | counterpartyIban, | ||
| 219 | description, | ||
| 220 | timestamp, | ||
| 221 | reference | ||
| 222 | } -> | ||
| 223 | return $ | ||
| 224 | L.Tx | ||
| 225 | { cleared = Just base.date, | ||
| 226 | commodityId = eucId, | ||
| 227 | debit = M.singleton virtCheckingAcc amount, | ||
| 228 | credit = M.singleton virtCounterparty amount, | ||
| 229 | labels = | ||
| 230 | fromList | ||
| 231 | [ IbanLabel CounterpartyIbanTag ==> counterpartyIban, | ||
| 232 | TextLabel CounterpartyNameTag ==> counterpartyName, | ||
| 233 | TextLabel DescTag ==> description, | ||
| 234 | TextLabel ReferenceTag ==> reference, | ||
| 235 | TimestampLabel ==> timestamp | ||
| 236 | ] | ||
| 237 | } | ||
| 238 | BatchPayment | ||
| 239 | { counterpartyName, | ||
| 240 | counterpartyIban, | ||
| 241 | description, | ||
| 242 | reference | ||
| 243 | } -> | ||
| 244 | return $ | ||
| 245 | L.Tx | ||
| 246 | { cleared = Just base.date, | ||
| 247 | commodityId = eucId, | ||
| 248 | debit = M.singleton virtCheckingAcc amount, | ||
| 249 | credit = M.singleton virtCounterparty amount, | ||
| 250 | labels = | ||
| 251 | fromList | ||
| 252 | [ IbanLabel CounterpartyIbanTag ==> counterpartyIban, | ||
| 253 | TextLabel CounterpartyNameTag ==> counterpartyName, | ||
| 254 | TextLabel DescTag ==> description, | ||
| 255 | TextLabel ReferenceTag ==> reference | ||
| 256 | ] | ||
| 257 | } | ||
diff --git a/app/Import/Ing/CurrentAccountCsv.hs b/app/Import/Ing/CurrentAccountCsv.hs deleted file mode 100644 index 21ca53d..0000000 --- a/app/Import/Ing/CurrentAccountCsv.hs +++ /dev/null | |||
| @@ -1,407 +0,0 @@ | |||
| 1 | {-# LANGUAGE OverloadedLists #-} | ||
| 2 | {-# LANGUAGE OverloadedStrings #-} | ||
| 3 | |||
| 4 | module Import.Ing.CurrentAccountCsv where | ||
| 5 | |||
| 6 | import Control.Applicative ((<|>)) | ||
| 7 | import Control.Monad (when) | ||
| 8 | import Data.ByteString.Lazy qualified as BS | ||
| 9 | import Data.Csv ((.:)) | ||
| 10 | import Data.Csv qualified as C | ||
| 11 | import Data.Decimal (Decimal) | ||
| 12 | import Data.Generics.Product.Subtype (upcast) | ||
| 13 | import Data.Iban (Iban) | ||
| 14 | import Data.Res (Res (Err, Ok)) | ||
| 15 | import Data.Text qualified as T | ||
| 16 | import Data.Time.Calendar (Day) | ||
| 17 | import Data.Time.Clock (UTCTime) | ||
| 18 | import Data.Time.Zones (TZ, loadTZFromDB) | ||
| 19 | import Data.Vector qualified as V | ||
| 20 | import GHC.Generics | ||
| 21 | import Import.Ing.Shared | ||
| 22 | ( DebitCredit (Credit, Debit), | ||
| 23 | maybeCP, | ||
| 24 | parseDateM, | ||
| 25 | parseDecimalM, | ||
| 26 | parseIbanM, | ||
| 27 | parseTimestampM, | ||
| 28 | scsvOptions, | ||
| 29 | ) | ||
| 30 | import System.IO (Handle) | ||
| 31 | import Text.Regex.TDFA ((=~~)) | ||
| 32 | |||
| 33 | data Tx = Tx TxBase TxSpecifics deriving (Show) | ||
| 34 | |||
| 35 | data TxBase = TxBase | ||
| 36 | { date :: !Day, | ||
| 37 | account :: !Iban, | ||
| 38 | amount :: !Decimal, | ||
| 39 | resBal :: !Decimal, | ||
| 40 | tag :: !T.Text | ||
| 41 | } | ||
| 42 | deriving (Show, Generic) | ||
| 43 | |||
| 44 | data TxSpecifics | ||
| 45 | = PaymentTerminalPayment | ||
| 46 | { counterpartyName :: !T.Text, | ||
| 47 | cardSequenceNo :: !T.Text, | ||
| 48 | timestamp :: !UTCTime, | ||
| 49 | transaction :: !T.Text, | ||
| 50 | terminal :: !T.Text, | ||
| 51 | googlePay :: !Bool | ||
| 52 | } | ||
| 53 | | PaymentTerminalCashback | ||
| 54 | { counterpartyName :: !T.Text, | ||
| 55 | cardSequenceNo :: !T.Text, | ||
| 56 | timestamp :: !UTCTime, | ||
| 57 | transaction :: !T.Text, | ||
| 58 | terminal :: !T.Text | ||
| 59 | } | ||
| 60 | | OnlineBankingCredit | ||
| 61 | { counterpartyName :: !T.Text, | ||
| 62 | counterpartyIban :: !Iban, | ||
| 63 | description :: !T.Text, | ||
| 64 | timestamp :: !UTCTime | ||
| 65 | } | ||
| 66 | | OnlineBankingDebit | ||
| 67 | { counterpartyName :: !T.Text, | ||
| 68 | counterpartyIban :: !Iban, | ||
| 69 | description :: T.Text, | ||
| 70 | mtimestamp :: !(Maybe UTCTime) | ||
| 71 | } | ||
| 72 | | RecurrentDirectDebit | ||
| 73 | { counterpartyName :: !T.Text, | ||
| 74 | counterpartyIban :: !Iban, | ||
| 75 | description :: !T.Text, | ||
| 76 | reference :: !T.Text, | ||
| 77 | mandateId :: !T.Text, | ||
| 78 | creditorId :: !T.Text, | ||
| 79 | otherParty :: !(Maybe T.Text) | ||
| 80 | } | ||
| 81 | | RoundingSavingsDeposit | ||
| 82 | {savingsAccount :: !T.Text} | ||
| 83 | | DepositTransfer | ||
| 84 | { counterpartyName :: !T.Text, | ||
| 85 | counterpartyIban :: !Iban, | ||
| 86 | description :: !T.Text, | ||
| 87 | reference :: !T.Text | ||
| 88 | } | ||
| 89 | | IdealDebit | ||
| 90 | { counterpartyName :: !T.Text, | ||
| 91 | counterpartyIban :: !Iban, | ||
| 92 | description :: !T.Text, | ||
| 93 | timestamp :: !UTCTime, | ||
| 94 | reference :: !T.Text | ||
| 95 | } | ||
| 96 | | BatchPayment | ||
| 97 | { counterpartyName :: !T.Text, | ||
| 98 | counterpartyIban :: !Iban, | ||
| 99 | description :: !T.Text, | ||
| 100 | reference :: !T.Text | ||
| 101 | } | ||
| 102 | deriving (Show, Generic) | ||
| 103 | |||
| 104 | data TransactionType | ||
| 105 | = AcceptGiroType -- AC (acceptgiro) | ||
| 106 | | AtmWithdrawalType -- GM (geldautomaat, Giromaat) | ||
| 107 | | BatchPaymentType -- VZ (verzamelbetaling); 'Batch payment' | ||
| 108 | | BranchPostingType -- FL (filiaalboeking) | ||
| 109 | | DepositType -- ST (storting) | ||
| 110 | | DirectDebitType -- IC (incasso); 'SEPA direct debit' | ||
| 111 | | IdealType -- ID (iDEAL); 'iDEAL' | ||
| 112 | | OnlineBankingType -- GT (internetbankieren, Girotel); 'Online Banking' | ||
| 113 | | OfficeWithdrawalType -- PK (opname kantoor, postkantoor) | ||
| 114 | | PaymentTerminalType -- BA (betaalautomaat); 'Payment terminal' | ||
| 115 | | PeriodicTransferType -- PO (periodieke overschrijving) | ||
| 116 | | PhoneBankingType -- GF (telefonisch bankieren, Girofoon) | ||
| 117 | | TransferType -- OV (overboeking); 'Transfer' | ||
| 118 | | VariousType -- DV (diversen) | ||
| 119 | deriving (Eq, Show) | ||
| 120 | |||
| 121 | parseCode :: T.Text -> C.Parser TransactionType | ||
| 122 | parseCode "AC" = return AcceptGiroType | ||
| 123 | parseCode "GM" = return AtmWithdrawalType | ||
| 124 | parseCode "VZ" = return BatchPaymentType | ||
| 125 | parseCode "FL" = return BranchPostingType | ||
| 126 | parseCode "ST" = return DepositType | ||
| 127 | parseCode "IC" = return DirectDebitType | ||
| 128 | parseCode "ID" = return IdealType | ||
| 129 | parseCode "GT" = return OnlineBankingType | ||
| 130 | parseCode "PK" = return OfficeWithdrawalType | ||
| 131 | parseCode "BA" = return PaymentTerminalType | ||
| 132 | parseCode "PO" = return PeriodicTransferType | ||
| 133 | parseCode "GF" = return PhoneBankingType | ||
| 134 | parseCode "OV" = return TransferType | ||
| 135 | parseCode "DV" = return VariousType | ||
| 136 | parseCode t = fail $ "Unknown transaction code '" ++ T.unpack t ++ "'" | ||
| 137 | |||
| 138 | parseType :: T.Text -> C.Parser TransactionType | ||
| 139 | parseType "SEPA direct debit" = return DirectDebitType | ||
| 140 | parseType "Batch payment" = return BatchPaymentType | ||
| 141 | parseType "Online Banking" = return OnlineBankingType | ||
| 142 | parseType "Payment terminal" = return PaymentTerminalType | ||
| 143 | parseType "Transfer" = return TransferType | ||
| 144 | parseType "iDEAL" = return IdealType | ||
| 145 | parseType t = fail $ "Unknown transaction type '" ++ T.unpack t ++ "'" | ||
| 146 | |||
| 147 | data PrimTx = PrimTx | ||
| 148 | { date :: !Day, | ||
| 149 | description :: !T.Text, | ||
| 150 | account :: !Iban, | ||
| 151 | counterparty :: !(Maybe Iban), | ||
| 152 | transactionType :: !TransactionType, | ||
| 153 | debitCredit :: !DebitCredit, | ||
| 154 | amount :: !Decimal, | ||
| 155 | notifications :: !T.Text, | ||
| 156 | resBal :: !Decimal, | ||
| 157 | tag :: !T.Text | ||
| 158 | } | ||
| 159 | deriving (Show, Generic) | ||
| 160 | |||
| 161 | debitCreditCP :: T.Text -> C.Parser DebitCredit | ||
| 162 | debitCreditCP "Debit" = return Debit | ||
| 163 | debitCreditCP "Credit" = return Credit | ||
| 164 | debitCreditCP t = fail ("Unknown debit/credit value '" ++ T.unpack t ++ "'") | ||
| 165 | |||
| 166 | instance C.FromNamedRecord PrimTx where | ||
| 167 | parseNamedRecord m = do | ||
| 168 | code <- m .: "Code" >>= parseCode | ||
| 169 | txType <- m .: "Transaction type" >>= parseType | ||
| 170 | if code /= txType | ||
| 171 | then fail "Expected code and transaction type to agree" | ||
| 172 | else | ||
| 173 | PrimTx | ||
| 174 | <$> (m .: "Date" >>= parseDateM "%0Y%m%d") | ||
| 175 | <*> m .: "Name / Description" | ||
| 176 | <*> (m .: "Account" >>= parseIbanM) | ||
| 177 | <*> (m .: "Counterparty" >>= maybeCP parseIbanM) | ||
| 178 | <*> return txType | ||
| 179 | <*> (m .: "Debit/credit" >>= debitCreditCP) | ||
| 180 | <*> (m .: "Amount (EUR)" >>= parseDecimalM) | ||
| 181 | <*> m .: "Notifications" | ||
| 182 | <*> (m .: "Resulting balance" >>= parseDecimalM) | ||
| 183 | <*> m .: "Tag" | ||
| 184 | |||
| 185 | processPrimTx :: TZ -> PrimTx -> Res String Tx | ||
| 186 | processPrimTx amsTz ptx = Tx (txBaseFromPrim ptx) <$> specificsFromPrim amsTz ptx | ||
| 187 | |||
| 188 | parseValueDate :: T.Text -> Res String Day | ||
| 189 | parseValueDate = parseDateM "%d/%m/%Y" | ||
| 190 | |||
| 191 | assertValueDate :: Day -> T.Text -> Res String () | ||
| 192 | assertValueDate expected t = do | ||
| 193 | valDate <- parseDateM "%d/%m/%Y" t | ||
| 194 | when (valDate /= expected) $ | ||
| 195 | fail "Expected transaction date and value date to be the same" | ||
| 196 | |||
| 197 | assertValueDatePtx :: PrimTx -> T.Text -> Res String () | ||
| 198 | assertValueDatePtx PrimTx {date = expected} = assertValueDate expected | ||
| 199 | |||
| 200 | specificsFromPrim :: TZ -> PrimTx -> Res String TxSpecifics | ||
| 201 | specificsFromPrim amsTz ptx@PrimTx {transactionType = PaymentTerminalType, debitCredit = Debit} = do | ||
| 202 | let regex = "^Card sequence no.: ([0-9]+) ? ([0-9]{2}/[0-9]{2}/[0-9]{4} [0-9]{2}:[0-9]{2}) Transaction: (.*) Term: ((.+) Google Pay|(.+)) Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
| 203 | (_, _, _, [cardSeqNo, timestampTxt, transaction, _, gpayTerm, noGpayTerm, valDateTxt]) <- | ||
| 204 | ptx.notifications =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 205 | assertValueDatePtx ptx valDateTxt | ||
| 206 | timestamp <- parseTimestampM "%d/%m/%Y %H:%M" amsTz timestampTxt | ||
| 207 | return $ | ||
| 208 | PaymentTerminalPayment | ||
| 209 | { counterpartyName = ptx.description, | ||
| 210 | cardSequenceNo = cardSeqNo, | ||
| 211 | timestamp = timestamp, | ||
| 212 | transaction = transaction, | ||
| 213 | terminal = if T.null gpayTerm then noGpayTerm else gpayTerm, | ||
| 214 | googlePay = T.null noGpayTerm | ||
| 215 | } | ||
| 216 | specificsFromPrim amsTz ptx@PrimTx {transactionType = PaymentTerminalType, debitCredit = Credit} = do | ||
| 217 | let regex = "^Card sequence no.: ([0-9]+) ? ([0-9]{2}/[0-9]{2}/[0-9]{4} [0-9]{2}:[0-9]{2}) Transaction: (.*) Term: (.*) Cashback transaction Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
| 218 | (_, _, _, [cardSeqNo, timestampTxt, transaction, term, valDateTxt]) <- | ||
| 219 | notifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 220 | assertValueDatePtx ptx valDateTxt | ||
| 221 | timestamp <- parseTimestampM "%d/%m/%Y %H:%M" amsTz timestampTxt | ||
| 222 | return $ | ||
| 223 | PaymentTerminalCashback | ||
| 224 | { counterpartyName = ptx.description, | ||
| 225 | cardSequenceNo = cardSeqNo, | ||
| 226 | timestamp = timestamp, | ||
| 227 | transaction = transaction, | ||
| 228 | terminal = term | ||
| 229 | } | ||
| 230 | specificsFromPrim amsTz ptx@PrimTx {transactionType = OnlineBankingType, debitCredit = Credit} = do | ||
| 231 | let regex = "^Name: (.*) Description: (.*) IBAN: ([A-Z0-9]+) Date/time: ([0-9]{2}-[0-9]{2}-[0-9]{4} [0-9]{2}:[0-9]{2}:[0-9]{2}) Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
| 232 | (_, _, _, [name, desc, ibanTxt, timestampTxt, valDateTxt]) <- | ||
| 233 | notifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 234 | assertValueDatePtx ptx valDateTxt | ||
| 235 | iban <- parseIbanM ibanTxt | ||
| 236 | timestamp <- parseTimestampM "%d-%m-%Y %H:%M:%S" amsTz timestampTxt | ||
| 237 | when (name /= ptx.description) $ | ||
| 238 | fail "Expected counterparty name for online banking credit to match primitive description" | ||
| 239 | when (Just iban /= ptx.counterparty) $ | ||
| 240 | fail "Expected IBAN for online banking credit to match and primitive counterparty IBAN" | ||
| 241 | return $ | ||
| 242 | OnlineBankingCredit | ||
| 243 | { counterpartyName = name, | ||
| 244 | counterpartyIban = iban, | ||
| 245 | description = desc, | ||
| 246 | timestamp = timestamp | ||
| 247 | } | ||
| 248 | specificsFromPrim amsTz ptx@PrimTx {transactionType = OnlineBankingType, debitCredit = Debit} = do | ||
| 249 | let regex = "^Name: (.*) Description: (.*) IBAN: ([A-Z0-9]+) (Date/time: ([0-9]{2}-[0-9]{2}-[0-9]{4} [0-9]{2}:[0-9]{2}:[0-9]{2}) )?Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
| 250 | (_, _, _, [name, desc, ibanTxt, _, timestampTxt, valDateTxt]) <- | ||
| 251 | notifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 252 | assertValueDatePtx ptx valDateTxt | ||
| 253 | iban <- parseIbanM ibanTxt | ||
| 254 | timestamp <- | ||
| 255 | if T.null timestampTxt | ||
| 256 | then pure Nothing | ||
| 257 | else Just <$> parseTimestampM "%d-%m-%Y %H:%M:%S" amsTz timestampTxt | ||
| 258 | when (name /= ptx.description) $ | ||
| 259 | fail "Expected counterparty name for online banking debit to match primitive description" | ||
| 260 | when (Just iban /= ptx.counterparty) $ | ||
| 261 | fail "Expected IBAN for online banking debit to match and primitive counterparty IBAN" | ||
| 262 | return $ | ||
| 263 | OnlineBankingDebit | ||
| 264 | { counterpartyIban = iban, | ||
| 265 | counterpartyName = name, | ||
| 266 | description = desc, | ||
| 267 | mtimestamp = timestamp | ||
| 268 | } | ||
| 269 | specificsFromPrim _ ptx@PrimTx {transactionType = DirectDebitType, debitCredit = Debit} = | ||
| 270 | normalRecurrentDirectDebit <|> ingInsurancePayment | ||
| 271 | where | ||
| 272 | normalRecurrentDirectDebit = do | ||
| 273 | let regex = "^Name: (.*) Description: (.*) IBAN: ([A-Z0-9]+) Reference: (.*) Mandate ID: (.*) Creditor ID: (.*) Recurrent SEPA direct debit (Other party: (.*) )?Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
| 274 | (_, _, _, [name, desc, ibanTxt, ref, mandateId, creditorId, _, otherParty, valDateTxt]) <- | ||
| 275 | notifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 276 | assertValueDatePtx ptx valDateTxt | ||
| 277 | iban <- parseIbanM ibanTxt | ||
| 278 | when (name /= ptx.description) $ | ||
| 279 | fail "Expected counterparty name for direct debit to match primitive description" | ||
| 280 | when (Just iban /= ptx.counterparty) $ | ||
| 281 | fail "Expected IBAN for direct debit to match and primitive counterparty IBAN" | ||
| 282 | return $ | ||
| 283 | RecurrentDirectDebit | ||
| 284 | { counterpartyName = name, | ||
| 285 | counterpartyIban = iban, | ||
| 286 | description = desc, | ||
| 287 | reference = ref, | ||
| 288 | mandateId = mandateId, | ||
| 289 | creditorId = creditorId, | ||
| 290 | otherParty = if T.null otherParty then Nothing else Just otherParty | ||
| 291 | } | ||
| 292 | ingInsurancePayment = do | ||
| 293 | let regex = "^Name: (.* ING Verzekeren) Description: (.*) IBAN: ([A-Z0-9]+) Reference: (.*) Mandate ID: (.*) Creditor ID: (.*) Recurrent SEPA direct debit$" :: String | ||
| 294 | (_, _, _, [name, desc, ibanTxt, ref, mandateId, creditorId]) <- | ||
| 295 | notifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 296 | iban <- parseIbanM ibanTxt | ||
| 297 | when (name /= ptx.description) $ | ||
| 298 | fail "Expected counterparty name for direct debit to match primitive description" | ||
| 299 | when (Just iban /= ptx.counterparty) $ | ||
| 300 | fail "Expected IBAN for direct debit to match and primitive counterparty IBAN" | ||
| 301 | return $ | ||
| 302 | RecurrentDirectDebit | ||
| 303 | { counterpartyName = name, | ||
| 304 | counterpartyIban = iban, | ||
| 305 | description = desc, | ||
| 306 | reference = ref, | ||
| 307 | mandateId = mandateId, | ||
| 308 | creditorId = creditorId, | ||
| 309 | otherParty = Nothing | ||
| 310 | } | ||
| 311 | specificsFromPrim _ ptx@PrimTx {transactionType = TransferType, debitCredit = Credit} = do | ||
| 312 | let regex = "^Name: (.*) Description: (.*) IBAN: ([A-Z0-9]+) Reference: (.*) Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
| 313 | (_, _, _, [name, desc, ibanTxt, ref, valDateTxt]) <- | ||
| 314 | notifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 315 | assertValueDatePtx ptx valDateTxt | ||
| 316 | iban <- parseIbanM ibanTxt | ||
| 317 | when (name /= ptx.description) $ | ||
| 318 | fail "Expected counterparty name for deposit transfer to match primitive description" | ||
| 319 | when (Just iban /= ptx.counterparty) $ | ||
| 320 | fail "Expected IBAN for deposit transfer to match and primitive counterparty IBAN" | ||
| 321 | return $ | ||
| 322 | DepositTransfer | ||
| 323 | { counterpartyName = name, | ||
| 324 | counterpartyIban = iban, | ||
| 325 | description = desc, | ||
| 326 | reference = ref | ||
| 327 | } | ||
| 328 | specificsFromPrim _ ptx@PrimTx {transactionType = TransferType, debitCredit = Debit} = do | ||
| 329 | let regex = "^To Oranje spaarrekening ([A-Z0-9]+) Afronding Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
| 330 | (_, _, _, [savingsAccount, valDateTxt]) <- | ||
| 331 | ptx.notifications =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 332 | assertValueDatePtx ptx valDateTxt | ||
| 333 | return $ RoundingSavingsDeposit {savingsAccount = savingsAccount} | ||
| 334 | specificsFromPrim amsTz ptx@PrimTx {transactionType = IdealType, debitCredit = Debit} = do | ||
| 335 | let regex = "^Name: (.*) Description: (.*) IBAN: ([A-Z0-9]+) Reference: ([0-9]{2}-[0-9]{2}-[0-9]{4} [0-9]{2}:[0-9]{2}) ([0-9]+) Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
| 336 | (_, _, _, [name, desc, ibanTxt, timestampTxt, ref, valDateTxt]) <- | ||
| 337 | notifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 338 | assertValueDatePtx ptx valDateTxt | ||
| 339 | timestamp <- parseTimestampM "%d-%m-%Y %H:%M" amsTz timestampTxt | ||
| 340 | iban <- parseIbanM ibanTxt | ||
| 341 | when (name /= ptx.description) $ | ||
| 342 | fail "Expected counterparty name for iDEAL payment to match primitive description" | ||
| 343 | when (Just iban /= ptx.counterparty) $ | ||
| 344 | fail "Expected IBAN for iDEAL payment to match and primitive counterparty IBAN" | ||
| 345 | return $ | ||
| 346 | IdealDebit | ||
| 347 | { counterpartyName = name, | ||
| 348 | counterpartyIban = iban, | ||
| 349 | description = desc, | ||
| 350 | timestamp = timestamp, | ||
| 351 | reference = ref | ||
| 352 | } | ||
| 353 | specificsFromPrim _ ptx@PrimTx {transactionType = BatchPaymentType, debitCredit = Credit} = do | ||
| 354 | let regex = "^Name: (.*) Description: (.*) IBAN: ([A-Z0-9]+) Reference: (.*) Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
| 355 | (_, _, _, [name, desc, ibanTxt, ref, valDateTxt]) <- | ||
| 356 | notifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 357 | assertValueDatePtx ptx valDateTxt | ||
| 358 | iban <- parseIbanM ibanTxt | ||
| 359 | when (name /= ptx.description) $ | ||
| 360 | fail "Expected counterparty name for batch payment to match primitive description" | ||
| 361 | when (Just iban /= ptx.counterparty) $ | ||
| 362 | fail "Expected IBAN for batch payment to match and primitive counterparty IBAN" | ||
| 363 | return $ | ||
| 364 | BatchPayment | ||
| 365 | { counterpartyName = name, | ||
| 366 | counterpartyIban = iban, | ||
| 367 | description = desc, | ||
| 368 | reference = ref | ||
| 369 | } | ||
| 370 | specificsFromPrim _ ptx = | ||
| 371 | fail $ | ||
| 372 | "Could not extract data from transaction (" | ||
| 373 | ++ show (transactionType ptx) | ||
| 374 | ++ " / " | ||
| 375 | ++ show (debitCredit ptx) | ||
| 376 | ++ ")" | ||
| 377 | |||
| 378 | txBaseFromPrim :: PrimTx -> TxBase | ||
| 379 | txBaseFromPrim = upcast | ||
| 380 | |||
| 381 | readFile :: Handle -> IO (V.Vector Tx) | ||
| 382 | readFile h = do | ||
| 383 | tz <- loadTZFromDB "Europe/Amsterdam" | ||
| 384 | contents <- BS.hGetContents h | ||
| 385 | primTxs <- case C.decodeByNameWith scsvOptions contents of | ||
| 386 | Left err -> fail err | ||
| 387 | Right | ||
| 388 | ( [ "Date", | ||
| 389 | "Name / Description", | ||
| 390 | "Account", | ||
| 391 | "Counterparty", | ||
| 392 | "Code", | ||
| 393 | "Debit/credit", | ||
| 394 | "Amount (EUR)", | ||
| 395 | "Transaction type", | ||
| 396 | "Notifications", | ||
| 397 | "Resulting balance", | ||
| 398 | "Tag" | ||
| 399 | ], | ||
| 400 | txs | ||
| 401 | ) -> | ||
| 402 | return txs | ||
| 403 | Right _ -> | ||
| 404 | fail "Headers do not match expected pattern" | ||
| 405 | case V.mapM (processPrimTx tz) primTxs of | ||
| 406 | Err err -> fail err | ||
| 407 | Ok txs -> return txs | ||
diff --git a/app/Import/Ing/SavingsAccountCsv.hs b/app/Import/Ing/SavingsAccountCsv.hs deleted file mode 100644 index 16b5f92..0000000 --- a/app/Import/Ing/SavingsAccountCsv.hs +++ /dev/null | |||
| @@ -1,164 +0,0 @@ | |||
| 1 | {-# LANGUAGE OverloadedLists #-} | ||
| 2 | {-# LANGUAGE OverloadedStrings #-} | ||
| 3 | |||
| 4 | module Import.Ing.SavingsAccountCsv where | ||
| 5 | |||
| 6 | import Data.ByteString.Lazy qualified as BS | ||
| 7 | import Data.Csv ((.:)) | ||
| 8 | import Data.Csv qualified as C | ||
| 9 | import Data.Decimal (Decimal) | ||
| 10 | import Data.Iban (Iban, mkIban) | ||
| 11 | import Data.Maybe (isJust) | ||
| 12 | import Data.Text qualified as T | ||
| 13 | import Data.Time.Calendar (Day) | ||
| 14 | import Data.Vector qualified as V | ||
| 15 | import Import.Ing.Shared (maybeCP, parseDateM, parseDecimalM, parseIbanM, scsvOptions) | ||
| 16 | import System.IO (Handle) | ||
| 17 | import Text.Regex.TDFA ((=~~)) | ||
| 18 | |||
| 19 | data DebitCredit = Debit | Credit deriving (Show, Eq) | ||
| 20 | |||
| 21 | data MutationType = DepositMutation | WithdrawalMutation | InterestMutation deriving (Show) | ||
| 22 | |||
| 23 | data TxBase = TxBase | ||
| 24 | { txbDate :: !Day, | ||
| 25 | txbAccountId :: !T.Text, | ||
| 26 | txbAccountName :: !T.Text, | ||
| 27 | txbAmount :: !Decimal, | ||
| 28 | txbResBal :: !Decimal | ||
| 29 | } | ||
| 30 | deriving (Show) | ||
| 31 | |||
| 32 | data TxSpecifics | ||
| 33 | = Interest | ||
| 34 | | Withdrawal | ||
| 35 | { wToCurrentAccountIban :: !Iban, | ||
| 36 | wDescription :: !T.Text | ||
| 37 | } | ||
| 38 | | Deposit | ||
| 39 | { dFromCurrentAccountIban :: !Iban, | ||
| 40 | dDescription :: !T.Text | ||
| 41 | } | ||
| 42 | | CurrentAccountAutoSaveRounding {caasFromCurrentAccountIban :: !Iban} | ||
| 43 | deriving (Show) | ||
| 44 | |||
| 45 | data Tx = Tx TxBase TxSpecifics deriving (Show) | ||
| 46 | |||
| 47 | instance MonadFail (Either String) where | ||
| 48 | fail = Left | ||
| 49 | |||
| 50 | txBaseFromPrim :: PrimTx -> Either String TxBase | ||
| 51 | txBaseFromPrim ptx@PrimTx {ptxCommodity = "EUR"} = | ||
| 52 | return $ TxBase <$> ptxDate <*> ptxAccountId <*> ptxAccountName <*> ptxAmount <*> ptxResBal $ ptx | ||
| 53 | txBaseFromPrim ptx = | ||
| 54 | Left $ "Unexpected commodity '" ++ T.unpack (ptxCommodity ptx) ++ "' (expected EUR)" | ||
| 55 | |||
| 56 | specificsFromPrim :: PrimTx -> Either String TxSpecifics | ||
| 57 | specificsFromPrim ptx@PrimTx {ptxMutationType = InterestMutation} | ||
| 58 | | isJust (ptxCounterparty ptx) = Left "Expected no counterparty for interest transaction" | ||
| 59 | | ptxDebitCredit ptx /= Credit = | ||
| 60 | Left "Expected interest transaction to be of credit ('Bij') type, got debit ('Af')" | ||
| 61 | | not (T.null (ptxNotifications ptx)) = | ||
| 62 | Left "Expected no notifications for interest transaction" | ||
| 63 | | ptxDescription ptx /= "Rente" = | ||
| 64 | Left $ "Expected interest transaction to have description 'Rente', got '" ++ T.unpack (ptxDescription ptx) ++ "'" | ||
| 65 | | otherwise = return Interest | ||
| 66 | specificsFromPrim ptx@PrimTx {ptxMutationType = WithdrawalMutation} = do | ||
| 67 | let regex = "Overboeking naar betaalrekening (.*)" :: String | ||
| 68 | (_, _, _, [ibanTxt]) <- ptxDescription ptx =~~ regex :: Either String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 69 | iban <- mkIban ibanTxt | ||
| 70 | case ptxCounterparty ptx of | ||
| 71 | Nothing -> Left "Expected counterparty for withdrawal transaction" | ||
| 72 | Just cpIban -> | ||
| 73 | if cpIban /= iban | ||
| 74 | then Left "Expected counterparty and IBAN in description to be equal" | ||
| 75 | else return $ Withdrawal {wToCurrentAccountIban = iban, wDescription = ptxNotifications ptx} | ||
| 76 | specificsFromPrim ptx@PrimTx {ptxMutationType = DepositMutation} = do | ||
| 77 | let regex = "(Afronding|Overboeking) van betaalrekening (.*)" :: String | ||
| 78 | (_, _, _, [ty, ibanTxt]) <- ptxDescription ptx =~~ regex :: Either String (T.Text, T.Text, T.Text, [T.Text]) | ||
| 79 | iban <- mkIban ibanTxt | ||
| 80 | case ptxCounterparty ptx of | ||
| 81 | Nothing -> Left "Expected counterparty for deposit transaction" | ||
| 82 | Just cpIban -> | ||
| 83 | if cpIban /= iban | ||
| 84 | then Left "Expected counterparty and IBAN in description to be equal" | ||
| 85 | else case ty of | ||
| 86 | "Afronding" -> | ||
| 87 | if not (T.null (ptxNotifications ptx)) | ||
| 88 | then | ||
| 89 | Left "Expected no notifications for auto-save rounding transaction" | ||
| 90 | else return $ CurrentAccountAutoSaveRounding {caasFromCurrentAccountIban = iban} | ||
| 91 | "Overboeking" -> | ||
| 92 | return $ Deposit {dFromCurrentAccountIban = iban, dDescription = ptxNotifications ptx} | ||
| 93 | _ -> error "unreachable" | ||
| 94 | |||
| 95 | processPrimTx :: PrimTx -> Either String Tx | ||
| 96 | processPrimTx ptx = Tx <$> txBaseFromPrim ptx <*> specificsFromPrim ptx | ||
| 97 | |||
| 98 | data PrimTx = PrimTx | ||
| 99 | { ptxDate :: !Day, | ||
| 100 | ptxDescription :: !T.Text, | ||
| 101 | ptxAccountId :: !T.Text, | ||
| 102 | ptxAccountName :: !T.Text, | ||
| 103 | ptxCounterparty :: !(Maybe Iban), | ||
| 104 | ptxDebitCredit :: !DebitCredit, | ||
| 105 | ptxAmount :: !Decimal, | ||
| 106 | ptxCommodity :: !T.Text, | ||
| 107 | ptxMutationType :: !MutationType, | ||
| 108 | ptxNotifications :: !T.Text, | ||
| 109 | ptxResBal :: !Decimal | ||
| 110 | } | ||
| 111 | deriving (Show) | ||
| 112 | |||
| 113 | debitCreditCP :: T.Text -> C.Parser DebitCredit | ||
| 114 | debitCreditCP "Af" = return Debit | ||
| 115 | debitCreditCP "Bij" = return Credit | ||
| 116 | debitCreditCP t = fail ("Unknown debit/credit value '" ++ T.unpack t ++ "'") | ||
| 117 | |||
| 118 | mutationTypeCP :: T.Text -> C.Parser MutationType | ||
| 119 | mutationTypeCP "Inleg" = return DepositMutation | ||
| 120 | mutationTypeCP "Opname" = return WithdrawalMutation | ||
| 121 | mutationTypeCP "Rente" = return InterestMutation | ||
| 122 | mutationTypeCP t = fail ("Unknown mutation type '" ++ T.unpack t ++ "'") | ||
| 123 | |||
| 124 | instance C.FromNamedRecord PrimTx where | ||
| 125 | parseNamedRecord m = | ||
| 126 | PrimTx | ||
| 127 | <$> (m .: "Datum" >>= parseDateM "%Y-%m-%d") | ||
| 128 | <*> m .: "Omschrijving" | ||
| 129 | <*> m .: "Rekening" | ||
| 130 | <*> m .: "Rekening naam" | ||
| 131 | <*> (m .: "Tegenrekening" >>= maybeCP parseIbanM) | ||
| 132 | <*> (m .: "Af Bij" >>= debitCreditCP) | ||
| 133 | <*> (m .: "Bedrag" >>= parseDecimalM) | ||
| 134 | <*> m .: "Valuta" | ||
| 135 | <*> (m .: "Mutatiesoort" >>= mutationTypeCP) | ||
| 136 | <*> m .: "Mededelingen" | ||
| 137 | <*> (m .: "Saldo na mutatie" >>= parseDecimalM) | ||
| 138 | |||
| 139 | readFile :: Handle -> IO (V.Vector Tx) | ||
| 140 | readFile h = do | ||
| 141 | contents <- BS.hGetContents h | ||
| 142 | primTxs <- case C.decodeByNameWith scsvOptions contents of | ||
| 143 | Left err -> fail err | ||
| 144 | Right | ||
| 145 | ( [ "Datum", | ||
| 146 | "Omschrijving", | ||
| 147 | "Rekening", | ||
| 148 | "Rekening naam", | ||
| 149 | "Tegenrekening", | ||
| 150 | "Af Bij", | ||
| 151 | "Bedrag", | ||
| 152 | "Valuta", | ||
| 153 | "Mutatiesoort", | ||
| 154 | "Mededelingen", | ||
| 155 | "Saldo na mutatie" | ||
| 156 | ], | ||
| 157 | txs | ||
| 158 | ) -> | ||
| 159 | return txs | ||
| 160 | Right _ -> | ||
| 161 | fail "Headers do not match expected pattern" | ||
| 162 | case V.mapM processPrimTx primTxs of | ||
| 163 | Left err -> fail err | ||
| 164 | Right txs -> return txs | ||
diff --git a/app/Import/Ing/Shared.hs b/app/Import/Ing/Shared.hs deleted file mode 100644 index b5d1703..0000000 --- a/app/Import/Ing/Shared.hs +++ /dev/null | |||
| @@ -1,44 +0,0 @@ | |||
| 1 | module Import.Ing.Shared where | ||
| 2 | |||
| 3 | import Data.Attoparsec.Text qualified as AP | ||
| 4 | import Data.Char (digitToInt, ord) | ||
| 5 | import Data.Csv qualified as C | ||
| 6 | import Data.Decimal (Decimal, DecimalRaw (Decimal), normalizeDecimal) | ||
| 7 | import Data.Iban (Iban, mkIban) | ||
| 8 | import Data.Text qualified as T | ||
| 9 | import Data.Time.Calendar (Day) | ||
| 10 | import Data.Time.Clock (UTCTime) | ||
| 11 | import Data.Time.Format (defaultTimeLocale, parseTimeM) | ||
| 12 | import Data.Time.Zones (TZ, localTimeToUTCTZ) | ||
| 13 | |||
| 14 | data DebitCredit = Debit | Credit deriving (Show) | ||
| 15 | |||
| 16 | scsvOptions :: C.DecodeOptions | ||
| 17 | scsvOptions = C.defaultDecodeOptions {C.decDelimiter = fromIntegral (ord ';')} | ||
| 18 | |||
| 19 | maybeCP :: (T.Text -> C.Parser a) -> T.Text -> C.Parser (Maybe a) | ||
| 20 | maybeCP p t = if T.null t then return Nothing else Just <$> p t | ||
| 21 | |||
| 22 | parseDecimalM :: (MonadFail m) => T.Text -> m Decimal | ||
| 23 | parseDecimalM = | ||
| 24 | either fail return | ||
| 25 | . AP.parseOnly | ||
| 26 | ( do | ||
| 27 | decPart <- AP.decimal | ||
| 28 | _ <- AP.char ',' | ||
| 29 | f1 <- AP.digit | ||
| 30 | f2 <- AP.digit | ||
| 31 | AP.endOfInput | ||
| 32 | let fracPart = fromIntegral $ digitToInt f1 * 10 + digitToInt f2 | ||
| 33 | return $ normalizeDecimal (Decimal 2 (decPart * 100 + fracPart)) | ||
| 34 | ) | ||
| 35 | |||
| 36 | parseIbanM :: (MonadFail m) => T.Text -> m Iban | ||
| 37 | parseIbanM = either fail return . mkIban | ||
| 38 | |||
| 39 | parseDateM :: (MonadFail m) => String -> T.Text -> m Day | ||
| 40 | parseDateM fmt = parseTimeM False defaultTimeLocale fmt . T.unpack | ||
| 41 | |||
| 42 | parseTimestampM :: (MonadFail m) => String -> TZ -> T.Text -> m UTCTime | ||
| 43 | parseTimestampM fmt amsTz t = do | ||
| 44 | localTimeToUTCTZ amsTz <$> parseTimeM False defaultTimeLocale fmt (T.unpack t) | ||
diff --git a/app/Main.hs b/app/Main.hs deleted file mode 100644 index 82505bf..0000000 --- a/app/Main.hs +++ /dev/null | |||
| @@ -1,4 +0,0 @@ | |||
| 1 | module Main where | ||
| 2 | |||
| 3 | main :: IO () | ||
| 4 | main = putStrLn "Hello!" | ||