summaryrefslogtreecommitdiffstats
path: root/app/Import/Ing/CurrentAccountCsv2.hs
diff options
context:
space:
mode:
Diffstat (limited to 'app/Import/Ing/CurrentAccountCsv2.hs')
-rw-r--r--app/Import/Ing/CurrentAccountCsv2.hs411
1 files changed, 0 insertions, 411 deletions
diff --git a/app/Import/Ing/CurrentAccountCsv2.hs b/app/Import/Ing/CurrentAccountCsv2.hs
deleted file mode 100644
index 0a5f8af..0000000
--- a/app/Import/Ing/CurrentAccountCsv2.hs
+++ /dev/null
@@ -1,411 +0,0 @@
1{-# LANGUAGE OverloadedLists #-}
2{-# LANGUAGE OverloadedStrings #-}
3
4module Import.Ing.CurrentAccountCsv2 where
5
6import Control.Applicative ((<|>))
7import Control.Monad (when)
8import Data.ByteString.Lazy qualified as BS
9import Data.Csv ((.:))
10import Data.Csv qualified as C
11import Data.Decimal (Decimal)
12import Data.Iban (Iban)
13import Data.Res (Res (Err, Ok))
14import Data.Text qualified as T
15import Data.Time.Calendar (Day)
16import Data.Time.Clock (UTCTime)
17import Data.Time.Zones (TZ, loadTZFromDB)
18import Data.Vector qualified as V
19import Import.Ing.Shared
20 ( DebitCredit (Credit, Debit),
21 maybeCP,
22 parseDateM,
23 parseDecimalM,
24 parseIbanM,
25 parseTimestampM,
26 scsvOptions,
27 )
28import System.IO (Handle)
29import Text.Regex.TDFA ((=~~))
30
31data TransactionType
32 = AcceptGiroType -- AC (acceptgiro)
33 | AtmWithdrawalType -- GM (geldautomaat, Giromaat)
34 | BatchPaymentType -- VZ (verzamelbetaling); 'Batch payment'
35 | BranchPostingType -- FL (filiaalboeking)
36 | DepositType -- ST (storting)
37 | DirectDebitType -- IC (incasso); 'SEPA direct debit'
38 | IdealType -- ID (iDEAL); 'iDEAL'
39 | OnlineBankingType -- GT (internetbankieren, Girotel); 'Online Banking'
40 | OfficeWithdrawalType -- PK (opname kantoor, postkantoor)
41 | PaymentTerminalType -- BA (betaalautomaat); 'Payment terminal'
42 | PeriodicTransferType -- PO (periodieke overschrijving)
43 | PhoneBankingType -- GF (telefonisch bankieren, Girofoon)
44 | TransferType -- OV (overboeking); 'Transfer'
45 | VariousType -- DV (diversen)
46 deriving (Eq, Show)
47
48parseCode :: T.Text -> C.Parser TransactionType
49parseCode "AC" = return AcceptGiroType
50parseCode "GM" = return AtmWithdrawalType
51parseCode "VZ" = return BatchPaymentType
52parseCode "FL" = return BranchPostingType
53parseCode "ST" = return DepositType
54parseCode "IC" = return DirectDebitType
55parseCode "ID" = return IdealType
56parseCode "GT" = return OnlineBankingType
57parseCode "PK" = return OfficeWithdrawalType
58parseCode "BA" = return PaymentTerminalType
59parseCode "PO" = return PeriodicTransferType
60parseCode "GF" = return PhoneBankingType
61parseCode "OV" = return TransferType
62parseCode "DV" = return VariousType
63parseCode t = fail $ "Unknown transaction code '" ++ T.unpack t ++ "'"
64
65parseType :: T.Text -> C.Parser TransactionType
66parseType "SEPA direct debit" = return DirectDebitType
67parseType "Batch payment" = return BatchPaymentType
68parseType "Online Banking" = return OnlineBankingType
69parseType "Payment terminal" = return PaymentTerminalType
70parseType "Transfer" = return TransferType
71parseType "iDEAL" = return IdealType
72parseType t = fail $ "Unknown transaction type '" ++ T.unpack t ++ "'"
73
74data PrimTx = PrimTx
75 { ptxDate :: !Day,
76 ptxDescription :: !T.Text,
77 ptxAccount :: !Iban,
78 ptxCounterparty :: !(Maybe Iban),
79 ptxTransactionType :: !TransactionType,
80 ptxDebitCredit :: !DebitCredit,
81 ptxAmount :: !Decimal,
82 ptxNotifications :: !T.Text,
83 ptxResBal :: !Decimal,
84 ptxTag :: !T.Text
85 }
86 deriving (Show)
87
88debitCreditCP :: T.Text -> C.Parser DebitCredit
89debitCreditCP "Debit" = return Debit
90debitCreditCP "Credit" = return Credit
91debitCreditCP t = fail ("Unknown debit/credit value '" ++ T.unpack t ++ "'")
92
93instance C.FromNamedRecord PrimTx where
94 parseNamedRecord m = do
95 code <- m .: "Code" >>= parseCode
96 txType <- m .: "Transaction type" >>= parseType
97 if code /= txType
98 then fail "Expected code and transaction type to agree"
99 else
100 PrimTx
101 <$> (m .: "Date" >>= parseDateM "%0Y%m%d")
102 <*> m .: "Name / Description"
103 <*> (m .: "Account" >>= parseIbanM)
104 <*> (m .: "Counterparty" >>= maybeCP parseIbanM)
105 <*> return txType
106 <*> (m .: "Debit/credit" >>= debitCreditCP)
107 <*> (m .: "Amount (EUR)" >>= parseDecimalM)
108 <*> m .: "Notifications"
109 <*> (m .: "Resulting balance" >>= parseDecimalM)
110 <*> m .: "Tag"
111
112processPrimTx :: TZ -> PrimTx -> Res String Tx
113processPrimTx amsTz ptx = Tx (txBaseFromPrim ptx) <$> specificsFromPrim amsTz ptx
114
115parseValueDate :: T.Text -> Res String Day
116parseValueDate = parseDateM "%d/%m/%Y"
117
118assertValueDate :: Day -> T.Text -> Res String ()
119assertValueDate expected t = do
120 valDate <- parseDateM "%d/%m/%Y" t
121 when (valDate /= expected) $
122 fail "Expected transaction date and value date to be the same"
123
124assertValueDatePtx :: PrimTx -> T.Text -> Res String ()
125assertValueDatePtx PrimTx {ptxDate = expected} = assertValueDate expected
126
127specificsFromPrim :: TZ -> PrimTx -> Res String TxSpecifics
128specificsFromPrim amsTz ptx@PrimTx {ptxTransactionType = PaymentTerminalType, ptxDebitCredit = Debit} = do
129 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
130 (_, _, _, [cardSeqNo, timestampTxt, transaction, _, gpayTerm, noGpayTerm, valDateTxt]) <-
131 ptxNotifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text])
132 assertValueDatePtx ptx valDateTxt
133 timestamp <- parseTimestampM "%d/%m/%Y %H:%M" amsTz timestampTxt
134 return $
135 PaymentTerminalPayment
136 { ptpCounterpartyName = ptxDescription ptx,
137 ptpCardSequenceNo = cardSeqNo,
138 ptpTimestamp = timestamp,
139 ptpTransaction = transaction,
140 ptpTerminal = if T.null gpayTerm then noGpayTerm else gpayTerm,
141 ptpGooglePay = T.null noGpayTerm
142 }
143specificsFromPrim amsTz ptx@PrimTx {ptxTransactionType = PaymentTerminalType, ptxDebitCredit = Credit} = do
144 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
145 (_, _, _, [cardSeqNo, timestampTxt, transaction, term, valDateTxt]) <-
146 ptxNotifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text])
147 assertValueDatePtx ptx valDateTxt
148 timestamp <- parseTimestampM "%d/%m/%Y %H:%M" amsTz timestampTxt
149 return $
150 PaymentTerminalCashback
151 { ptcCounterpartyName = ptxDescription ptx,
152 ptcCardSequenceNo = cardSeqNo,
153 ptcTimestamp = timestamp,
154 ptcTransaction = transaction,
155 ptcTerminal = term
156 }
157specificsFromPrim amsTz ptx@PrimTx {ptxTransactionType = OnlineBankingType, ptxDebitCredit = Credit} = do
158 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
159 (_, _, _, [name, desc, ibanTxt, timestampTxt, valDateTxt]) <-
160 ptxNotifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text])
161 assertValueDatePtx ptx valDateTxt
162 iban <- parseIbanM ibanTxt
163 timestamp <- parseTimestampM "%d-%m-%Y %H:%M:%S" amsTz timestampTxt
164 when (name /= ptxDescription ptx) $
165 fail "Expected counterparty name for online banking credit to match primitive description"
166 when (Just iban /= ptxCounterparty ptx) $
167 fail "Expected IBAN for online banking credit to match and primitive counterparty IBAN"
168 return $
169 OnlineBankingCredit
170 { obcCounterpartyName = name,
171 obcCounterpartyIban = iban,
172 obcDescription = desc,
173 obcTimestamp = timestamp
174 }
175specificsFromPrim amsTz ptx@PrimTx {ptxTransactionType = OnlineBankingType, ptxDebitCredit = Debit} = do
176 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
177 (_, _, _, [name, desc, ibanTxt, _, timestampTxt, valDateTxt]) <-
178 ptxNotifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text])
179 assertValueDatePtx ptx valDateTxt
180 iban <- parseIbanM ibanTxt
181 timestamp <-
182 if T.null timestampTxt
183 then pure Nothing
184 else Just <$> parseTimestampM "%d-%m-%Y %H:%M:%S" amsTz timestampTxt
185 when (name /= ptxDescription ptx) $
186 fail "Expected counterparty name for online banking debit to match primitive description"
187 when (Just iban /= ptxCounterparty ptx) $
188 fail "Expected IBAN for online banking debit to match and primitive counterparty IBAN"
189 return $
190 OnlineBankingDebit
191 { obdCounterpartyIban = iban,
192 obdCounterpartyName = name,
193 obdDescription = desc,
194 obdTimestamp = timestamp
195 }
196specificsFromPrim _ ptx@PrimTx {ptxTransactionType = DirectDebitType, ptxDebitCredit = Debit} =
197 normalRecurrentDirectDebit <|> ingInsurancePayment
198 where
199 normalRecurrentDirectDebit = do
200 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
201 (_, _, _, [name, desc, ibanTxt, ref, mandateId, creditorId, _, otherParty, valDateTxt]) <-
202 ptxNotifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text])
203 assertValueDatePtx ptx valDateTxt
204 iban <- parseIbanM ibanTxt
205 when (name /= ptxDescription ptx) $
206 fail "Expected counterparty name for direct debit to match primitive description"
207 when (Just iban /= ptxCounterparty ptx) $
208 fail "Expected IBAN for direct debit to match and primitive counterparty IBAN"
209 return $
210 RecurrentDirectDebit
211 { rddCounterpartyName = name,
212 rddCounterpartyIban = iban,
213 rddDescription = desc,
214 rddReference = ref,
215 rddMandateId = mandateId,
216 rddCreditorId = creditorId,
217 rddOtherParty = if T.null otherParty then Nothing else Just otherParty
218 }
219 ingInsurancePayment = do
220 let regex = "^Name: (.* ING Verzekeren) Description: (.*) IBAN: ([A-Z0-9]+) Reference: (.*) Mandate ID: (.*) Creditor ID: (.*) Recurrent SEPA direct debit$" :: String
221 (_, _, _, [name, desc, ibanTxt, ref, mandateId, creditorId]) <-
222 ptxNotifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text])
223 iban <- parseIbanM ibanTxt
224 when (name /= ptxDescription ptx) $
225 fail "Expected counterparty name for direct debit to match primitive description"
226 when (Just iban /= ptxCounterparty ptx) $
227 fail "Expected IBAN for direct debit to match and primitive counterparty IBAN"
228 return $
229 RecurrentDirectDebit
230 { rddCounterpartyName = name,
231 rddCounterpartyIban = iban,
232 rddDescription = desc,
233 rddReference = ref,
234 rddMandateId = mandateId,
235 rddCreditorId = creditorId,
236 rddOtherParty = Nothing
237 }
238specificsFromPrim _ ptx@PrimTx {ptxTransactionType = TransferType, ptxDebitCredit = Credit} = do
239 let regex = "^Name: (.*) Description: (.*) IBAN: ([A-Z0-9]+) Reference: (.*) Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String
240 (_, _, _, [name, desc, ibanTxt, ref, valDateTxt]) <-
241 ptxNotifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text])
242 assertValueDatePtx ptx valDateTxt
243 iban <- parseIbanM ibanTxt
244 when (name /= ptxDescription ptx) $
245 fail "Expected counterparty name for deposit transfer to match primitive description"
246 when (Just iban /= ptxCounterparty ptx) $
247 fail "Expected IBAN for deposit transfer to match and primitive counterparty IBAN"
248 return $
249 DepositTransfer
250 { dtCounterpartyName = name,
251 dtCounterpartyIban = iban,
252 dtDescription = desc,
253 dtReference = ref
254 }
255specificsFromPrim _ ptx@PrimTx {ptxTransactionType = TransferType, ptxDebitCredit = Debit} = do
256 let regex = "^To Oranje spaarrekening ([A-Z0-9]+) Afronding Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String
257 (_, _, _, [savingsAccount, valDateTxt]) <-
258 ptxNotifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text])
259 assertValueDatePtx ptx valDateTxt
260 return $ RoundingSavingsDeposit {rsdSavingsAccount = savingsAccount}
261specificsFromPrim amsTz ptx@PrimTx {ptxTransactionType = IdealType, ptxDebitCredit = Debit} = do
262 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
263 (_, _, _, [name, desc, ibanTxt, timestampTxt, ref, valDateTxt]) <-
264 ptxNotifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text])
265 assertValueDatePtx ptx valDateTxt
266 timestamp <- parseTimestampM "%d-%m-%Y %H:%M" amsTz timestampTxt
267 iban <- parseIbanM ibanTxt
268 when (name /= ptxDescription ptx) $
269 fail "Expected counterparty name for iDEAL payment to match primitive description"
270 when (Just iban /= ptxCounterparty ptx) $
271 fail "Expected IBAN for iDEAL payment to match and primitive counterparty IBAN"
272 return $
273 IdealDebit
274 { idCounterpartyName = name,
275 idCounterpartyIban = iban,
276 idDescription = desc,
277 idTimestamp = timestamp,
278 idReference = ref
279 }
280specificsFromPrim _ ptx@PrimTx {ptxTransactionType = BatchPaymentType, ptxDebitCredit = Credit} = do
281 let regex = "^Name: (.*) Description: (.*) IBAN: ([A-Z0-9]+) Reference: (.*) Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String
282 (_, _, _, [name, desc, ibanTxt, ref, valDateTxt]) <-
283 ptxNotifications ptx =~~ regex :: Res String (T.Text, T.Text, T.Text, [T.Text])
284 assertValueDatePtx ptx valDateTxt
285 iban <- parseIbanM ibanTxt
286 when (name /= ptxDescription ptx) $
287 fail "Expected counterparty name for batch payment to match primitive description"
288 when (Just iban /= ptxCounterparty ptx) $
289 fail "Expected IBAN for batch payment to match and primitive counterparty IBAN"
290 return $
291 BatchPayment
292 { bpCounterpartyName = name,
293 bpCounterpartyIban = iban,
294 bpDescription = desc,
295 bpReference = ref
296 }
297specificsFromPrim _ ptx =
298 fail $
299 "Could not extract data from transaction ("
300 ++ show (ptxTransactionType ptx)
301 ++ " / "
302 ++ show (ptxDebitCredit ptx)
303 ++ ")"
304
305txBaseFromPrim :: PrimTx -> TxBase
306txBaseFromPrim =
307 TxBase
308 <$> ptxDate
309 <*> ptxAccount
310 <*> ptxAmount
311 <*> ptxResBal
312 <*> ptxTag
313
314data Tx = Tx TxBase TxSpecifics deriving (Show)
315
316data TxBase = TxBase
317 { txbDate :: !Day,
318 txbAccount :: !Iban,
319 txbAmount :: !Decimal,
320 txbResBal :: !Decimal,
321 txbTag :: !T.Text
322 }
323 deriving (Show)
324
325data TxSpecifics
326 = PaymentTerminalPayment
327 { ptpCounterpartyName :: !T.Text,
328 ptpCardSequenceNo :: !T.Text,
329 ptpTimestamp :: !UTCTime,
330 ptpTransaction :: !T.Text,
331 ptpTerminal :: !T.Text,
332 ptpGooglePay :: !Bool
333 }
334 | PaymentTerminalCashback
335 { ptcCounterpartyName :: !T.Text,
336 ptcCardSequenceNo :: !T.Text,
337 ptcTimestamp :: !UTCTime,
338 ptcTransaction :: !T.Text,
339 ptcTerminal :: !T.Text
340 }
341 | OnlineBankingCredit
342 { obcCounterpartyName :: !T.Text,
343 obcCounterpartyIban :: !Iban,
344 obcDescription :: !T.Text,
345 obcTimestamp :: !UTCTime
346 }
347 | OnlineBankingDebit
348 { obdCounterpartyName :: !T.Text,
349 obdCounterpartyIban :: !Iban,
350 obdDescription :: T.Text,
351 obdTimestamp :: !(Maybe UTCTime)
352 }
353 | RecurrentDirectDebit
354 { rddCounterpartyName :: !T.Text,
355 rddCounterpartyIban :: !Iban,
356 rddDescription :: !T.Text,
357 rddReference :: !T.Text,
358 rddMandateId :: !T.Text,
359 rddCreditorId :: !T.Text,
360 rddOtherParty :: !(Maybe T.Text)
361 }
362 | RoundingSavingsDeposit
363 {rsdSavingsAccount :: !T.Text}
364 | DepositTransfer
365 { dtCounterpartyName :: !T.Text,
366 dtCounterpartyIban :: !Iban,
367 dtDescription :: !T.Text,
368 dtReference :: !T.Text
369 }
370 | IdealDebit
371 { idCounterpartyName :: !T.Text,
372 idCounterpartyIban :: !Iban,
373 idDescription :: !T.Text,
374 idTimestamp :: !UTCTime,
375 idReference :: !T.Text
376 }
377 | BatchPayment
378 { bpCounterpartyName :: !T.Text,
379 bpCounterpartyIban :: !Iban,
380 bpDescription :: !T.Text,
381 bpReference :: !T.Text
382 }
383 deriving (Show)
384
385readFile :: Handle -> IO (V.Vector Tx)
386readFile h = do
387 tz <- loadTZFromDB "Europe/Amsterdam"
388 contents <- BS.hGetContents h
389 primTxs <- case C.decodeByNameWith scsvOptions contents of
390 Left err -> fail err
391 Right
392 ( [ "Date",
393 "Name / Description",
394 "Account",
395 "Counterparty",
396 "Code",
397 "Debit/credit",
398 "Amount (EUR)",
399 "Transaction type",
400 "Notifications",
401 "Resulting balance",
402 "Tag"
403 ],
404 txs
405 ) ->
406 return txs
407 Right _ ->
408 fail "Headers do not match expected pattern"
409 case V.mapM (processPrimTx tz) primTxs of
410 Err err -> fail err
411 Ok txs -> return txs