diff options
Diffstat (limited to 'app/Import/Ing/CurrentAccountCsv.hs')
-rw-r--r-- | app/Import/Ing/CurrentAccountCsv.hs | 356 |
1 files changed, 356 insertions, 0 deletions
diff --git a/app/Import/Ing/CurrentAccountCsv.hs b/app/Import/Ing/CurrentAccountCsv.hs new file mode 100644 index 0000000..bf28730 --- /dev/null +++ b/app/Import/Ing/CurrentAccountCsv.hs | |||
@@ -0,0 +1,356 @@ | |||
1 | {-# LANGUAGE OverloadedLists #-} | ||
2 | {-# LANGUAGE OverloadedStrings #-} | ||
3 | |||
4 | module Import.Ing.CurrentAccountCsv where | ||
5 | |||
6 | import Control.Applicative ((<|>)) | ||
7 | import Data.ByteString.Lazy qualified as BS | ||
8 | import Data.Csv ((.:)) | ||
9 | import Data.Csv qualified as C | ||
10 | import Data.Decimal (Decimal) | ||
11 | import Data.Functor ((<&>)) | ||
12 | import Data.Iban (Iban) | ||
13 | import Data.Text qualified as T | ||
14 | import Data.Time.Calendar (Day) | ||
15 | import Data.Time.Clock (UTCTime) | ||
16 | import Data.Time.Zones (TZ, loadTZFromDB) | ||
17 | import Data.Vector qualified as V | ||
18 | import Import.Ing.Shared | ||
19 | ( DebitCredit (Credit, Debit), | ||
20 | dateCP, | ||
21 | decimalCP, | ||
22 | ibanCP, | ||
23 | maybeCP, | ||
24 | scsvOptions, | ||
25 | timestampCP, | ||
26 | ) | ||
27 | import System.IO (Handle) | ||
28 | import Text.Regex.TDFA ((=~~)) | ||
29 | |||
30 | data TransactionType | ||
31 | = AcceptGiro -- AC (acceptgiro) | ||
32 | | AtmWithdrawal -- GM (geldautomaat, Giromaat) | ||
33 | | BatchPayment -- VZ (verzamelbetaling); 'Batch payment' | ||
34 | | BranchPosting -- FL (filiaalboeking) | ||
35 | | Deposit -- ST (storting) | ||
36 | | DirectDebit -- IC (incasso); 'SEPA direct debit' | ||
37 | | Ideal -- ID (iDEAL); 'iDEAL' | ||
38 | | OnlineBanking -- GT (internetbankieren, Girotel); 'Online Banking' | ||
39 | | OfficeWithdrawal -- PK (opname kantoor, postkantoor) | ||
40 | | PaymentTerminal -- BA (betaalautomaat); 'Payment terminal' | ||
41 | | PeriodicTransfer -- PO (periodieke overschrijving) | ||
42 | | PhoneBanking -- GF (telefonisch bankieren, Girofoon) | ||
43 | | Transfer -- OV (overboeking); 'Transfer' | ||
44 | | Various -- DV (diversen) | ||
45 | deriving (Eq, Show) | ||
46 | |||
47 | parseCode :: T.Text -> C.Parser TransactionType | ||
48 | parseCode "AC" = return AcceptGiro | ||
49 | parseCode "GM" = return AtmWithdrawal | ||
50 | parseCode "VZ" = return BatchPayment | ||
51 | parseCode "FL" = return BranchPosting | ||
52 | parseCode "ST" = return Deposit | ||
53 | parseCode "IC" = return DirectDebit | ||
54 | parseCode "ID" = return Ideal | ||
55 | parseCode "GT" = return OnlineBanking | ||
56 | parseCode "PK" = return OfficeWithdrawal | ||
57 | parseCode "BA" = return PaymentTerminal | ||
58 | parseCode "PO" = return PeriodicTransfer | ||
59 | parseCode "GF" = return PhoneBanking | ||
60 | parseCode "OV" = return Transfer | ||
61 | parseCode "DV" = return Various | ||
62 | parseCode t = fail $ "Unknown transaction code '" ++ T.unpack t ++ "'" | ||
63 | |||
64 | parseType :: T.Text -> C.Parser TransactionType | ||
65 | parseType "SEPA direct debit" = return DirectDebit | ||
66 | parseType "Batch payment" = return BatchPayment | ||
67 | parseType "Online Banking" = return OnlineBanking | ||
68 | parseType "Payment terminal" = return PaymentTerminal | ||
69 | parseType "Transfer" = return Transfer | ||
70 | parseType "iDEAL" = return Ideal | ||
71 | parseType t = fail $ "Unknown transaction type '" ++ T.unpack t ++ "'" | ||
72 | |||
73 | data PrimTx = PrimTx | ||
74 | { ptDate :: !Day, | ||
75 | ptDesc :: !(Maybe T.Text), | ||
76 | ptAccount :: !Iban, | ||
77 | ptCounterparty :: !(Maybe Iban), | ||
78 | ptDebitCredit :: !DebitCredit, | ||
79 | ptAmount :: !Decimal, | ||
80 | ptResBal :: !Decimal, | ||
81 | ptTag :: !T.Text, | ||
82 | ptMoreData :: !MoreData | ||
83 | } | ||
84 | deriving (Show) | ||
85 | |||
86 | data MoreData | ||
87 | = PaymentTerminalData | ||
88 | { ptCardSequenceNo :: !T.Text, | ||
89 | ptTimestamp :: !UTCTime, | ||
90 | ptTransaction :: !T.Text, | ||
91 | ptTerminal :: !T.Text, | ||
92 | ptValueDate :: !Day, | ||
93 | ptGooglePay :: !Bool | ||
94 | } | ||
95 | | DepositTransferData | ||
96 | { dtName :: !T.Text, | ||
97 | dtDescription :: !T.Text, | ||
98 | dtIban :: !Iban, | ||
99 | dtReference :: !T.Text, | ||
100 | dtValueDate :: !Day | ||
101 | } | ||
102 | | RoundingSavingsDeposit | ||
103 | { rsdSavingsAccount :: !T.Text, | ||
104 | rsdValueDate :: !Day | ||
105 | } | ||
106 | | OnlineBankingCredit | ||
107 | { obcName :: !T.Text, | ||
108 | obcDescription :: !T.Text, | ||
109 | obcIban :: !Iban, | ||
110 | obcTimestamp :: !UTCTime, | ||
111 | obcValueDate :: !Day | ||
112 | } | ||
113 | | OnlineBankingDebit | ||
114 | { obdName :: !T.Text, | ||
115 | obdDescription :: !T.Text, | ||
116 | obdIban :: !Iban, | ||
117 | obdTimestamp :: !(Maybe UTCTime), | ||
118 | obdValueDate :: !Day | ||
119 | } | ||
120 | | RecurrentDirectDebitData | ||
121 | { rddName :: !T.Text, | ||
122 | rddDescription :: !T.Text, | ||
123 | rddIban :: !Iban, | ||
124 | rddReference :: !T.Text, | ||
125 | rddMandateId :: !T.Text, | ||
126 | rddCreditorId :: !T.Text, | ||
127 | rddOtherParty :: !(Maybe T.Text), | ||
128 | rddValueDate :: !Day | ||
129 | } | ||
130 | | IdealDebitData | ||
131 | { idName :: !T.Text, | ||
132 | idDescription :: !T.Text, | ||
133 | idIban :: !Iban, | ||
134 | idTimestamp :: !UTCTime, | ||
135 | idReference :: !T.Text, | ||
136 | idValueDate :: !Day | ||
137 | } | ||
138 | | PaymentTerminalCashbackData | ||
139 | { ptcCardSequenceNo :: !T.Text, | ||
140 | ptcTimestamp :: !UTCTime, | ||
141 | ptcTransaction :: !T.Text, | ||
142 | ptcTerminal :: !T.Text, | ||
143 | ptcValueDate :: !Day | ||
144 | } | ||
145 | | BatchPaymentData | ||
146 | { bpName :: !T.Text, | ||
147 | bpDescription :: !T.Text, | ||
148 | bpIban :: !Iban, | ||
149 | bpReference :: !T.Text, | ||
150 | bpValueDate :: !Day | ||
151 | } | ||
152 | deriving (Show) | ||
153 | |||
154 | maybeNotProvided :: T.Text -> Maybe T.Text | ||
155 | maybeNotProvided t = if t == "NOTPROVIDED" then Nothing else Just t | ||
156 | |||
157 | valueDateCP :: T.Text -> C.Parser Day | ||
158 | valueDateCP = dateCP "%d/%m/%Y" | ||
159 | |||
160 | data PartTx = PartTx !Day !TransactionType !DebitCredit | ||
161 | |||
162 | notificationsCP :: TZ -> PartTx -> T.Text -> C.Parser MoreData | ||
163 | notificationsCP _ (PartTx _ Transfer Credit) t = do | ||
164 | let regex = "^Name: (.*) Description: (.*) IBAN: ([A-Z0-9]+) Reference: (.*) Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
165 | (_, _, _, [name, desc, ibanTxt, ref, valDateTxt]) <- t =~~ regex :: C.Parser (T.Text, T.Text, T.Text, [T.Text]) | ||
166 | iban <- ibanCP ibanTxt | ||
167 | valDate <- valueDateCP valDateTxt | ||
168 | return $ | ||
169 | DepositTransferData | ||
170 | { dtName = name, | ||
171 | dtDescription = desc, | ||
172 | dtIban = iban, | ||
173 | dtReference = ref, | ||
174 | dtValueDate = valDate | ||
175 | } | ||
176 | notificationsCP _ (PartTx _ Transfer Debit) t = do | ||
177 | let regex = "^To Oranje spaarrekening ([A-Z0-9]+) Afronding Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
178 | (_, _, _, [savingsAccount, valDateTxt]) <- t =~~ regex :: C.Parser (T.Text, T.Text, T.Text, [T.Text]) | ||
179 | valDate <- valueDateCP valDateTxt | ||
180 | return $ | ||
181 | RoundingSavingsDeposit | ||
182 | { rsdSavingsAccount = savingsAccount, | ||
183 | rsdValueDate = valDate | ||
184 | } | ||
185 | notificationsCP amsTz (PartTx _ PaymentTerminal Debit) t = do | ||
186 | 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 | ||
187 | (_, _, _, [cardSeqNo, timestampTxt, transaction, _, gpayTerm, noGpayTerm, valDateTxt]) <- t =~~ regex :: C.Parser (T.Text, T.Text, T.Text, [T.Text]) | ||
188 | timestamp <- timestampCP "%d/%m/%Y %H:%M" amsTz timestampTxt | ||
189 | valDate <- valueDateCP valDateTxt | ||
190 | return $ | ||
191 | PaymentTerminalData | ||
192 | { ptCardSequenceNo = cardSeqNo, | ||
193 | ptTimestamp = timestamp, | ||
194 | ptTransaction = transaction, | ||
195 | ptTerminal = if T.null gpayTerm then noGpayTerm else gpayTerm, | ||
196 | ptValueDate = valDate, | ||
197 | ptGooglePay = T.null noGpayTerm | ||
198 | } | ||
199 | notificationsCP amsTz (PartTx _ PaymentTerminal Credit) t = do | ||
200 | 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 | ||
201 | (_, _, _, [cardSeqNo, timestampTxt, transaction, term, valDateTxt]) <- t =~~ regex :: C.Parser (T.Text, T.Text, T.Text, [T.Text]) | ||
202 | timestamp <- timestampCP "%d/%m/%Y %H:%M" amsTz timestampTxt | ||
203 | valDate <- valueDateCP valDateTxt | ||
204 | return $ | ||
205 | PaymentTerminalCashbackData | ||
206 | { ptcCardSequenceNo = cardSeqNo, | ||
207 | ptcTimestamp = timestamp, | ||
208 | ptcTransaction = transaction, | ||
209 | ptcTerminal = term, | ||
210 | ptcValueDate = valDate | ||
211 | } | ||
212 | notificationsCP amsTz (PartTx _ OnlineBanking Credit) t = do | ||
213 | 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 | ||
214 | (_, _, _, [name, desc, ibanTxt, timestampTxt, valDateTxt]) <- t =~~ regex :: C.Parser (T.Text, T.Text, T.Text, [T.Text]) | ||
215 | iban <- ibanCP ibanTxt | ||
216 | timestamp <- timestampCP "%d-%m-%Y %H:%M:%S" amsTz timestampTxt | ||
217 | valDate <- valueDateCP valDateTxt | ||
218 | return $ | ||
219 | OnlineBankingCredit | ||
220 | { obcName = name, | ||
221 | obcDescription = desc, | ||
222 | obcIban = iban, | ||
223 | obcTimestamp = timestamp, | ||
224 | obcValueDate = valDate | ||
225 | } | ||
226 | notificationsCP amsTz (PartTx _ OnlineBanking Debit) t = do | ||
227 | 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 | ||
228 | (_, _, _, [name, desc, ibanTxt, _, timestampTxt, valDateTxt]) <- t =~~ regex :: C.Parser (T.Text, T.Text, T.Text, [T.Text]) | ||
229 | iban <- ibanCP ibanTxt | ||
230 | timestamp <- | ||
231 | if T.null timestampTxt | ||
232 | then pure Nothing | ||
233 | else Just <$> timestampCP "%d-%m-%Y %H:%M:%S" amsTz timestampTxt | ||
234 | valDate <- valueDateCP valDateTxt | ||
235 | return $ | ||
236 | OnlineBankingDebit | ||
237 | { obdName = name, | ||
238 | obdDescription = desc, | ||
239 | obdIban = iban, | ||
240 | obdTimestamp = timestamp, | ||
241 | obdValueDate = valDate | ||
242 | } | ||
243 | notificationsCP _ (PartTx date DirectDebit Debit) t = normalRecurrentDirectDebit <|> ingInsurancePayment | ||
244 | where | ||
245 | normalRecurrentDirectDebit = do | ||
246 | 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 | ||
247 | (_, _, _, [name, desc, ibanTxt, ref, mandateId, creditorId, _, otherParty, valDateTxt]) <- t =~~ regex :: C.Parser (T.Text, T.Text, T.Text, [T.Text]) | ||
248 | iban <- ibanCP ibanTxt | ||
249 | valDate <- valueDateCP valDateTxt | ||
250 | return $ | ||
251 | RecurrentDirectDebitData | ||
252 | { rddName = name, | ||
253 | rddDescription = desc, | ||
254 | rddIban = iban, | ||
255 | rddReference = ref, | ||
256 | rddMandateId = mandateId, | ||
257 | rddCreditorId = creditorId, | ||
258 | rddOtherParty = if T.null otherParty then Nothing else Just otherParty, | ||
259 | rddValueDate = valDate | ||
260 | } | ||
261 | ingInsurancePayment = do | ||
262 | let regex = "^Name: (.* ING Verzekeren) Description: (.*) IBAN: ([A-Z0-9]+) Reference: (.*) Mandate ID: (.*) Creditor ID: (.*) Recurrent SEPA direct debit$" :: String | ||
263 | (_, _, _, [name, desc, ibanTxt, ref, mandateId, creditorId]) <- t =~~ regex :: C.Parser (T.Text, T.Text, T.Text, [T.Text]) | ||
264 | iban <- ibanCP ibanTxt | ||
265 | return $ | ||
266 | RecurrentDirectDebitData | ||
267 | { rddName = name, | ||
268 | rddDescription = desc, | ||
269 | rddIban = iban, | ||
270 | rddReference = ref, | ||
271 | rddMandateId = mandateId, | ||
272 | rddCreditorId = creditorId, | ||
273 | rddOtherParty = Nothing, | ||
274 | rddValueDate = date | ||
275 | } | ||
276 | notificationsCP amsTz (PartTx _ Ideal Debit) t = do | ||
277 | 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 | ||
278 | (_, _, _, [name, desc, ibanTxt, timestampTxt, ref, valDateTxt]) <- t =~~ regex :: C.Parser (T.Text, T.Text, T.Text, [T.Text]) | ||
279 | iban <- ibanCP ibanTxt | ||
280 | timestamp <- timestampCP "%d-%m-%Y %H:%M" amsTz timestampTxt | ||
281 | valDate <- valueDateCP valDateTxt | ||
282 | return $ | ||
283 | IdealDebitData | ||
284 | { idName = name, | ||
285 | idDescription = desc, | ||
286 | idIban = iban, | ||
287 | idTimestamp = timestamp, | ||
288 | idReference = ref, | ||
289 | idValueDate = valDate | ||
290 | } | ||
291 | notificationsCP _ (PartTx _ BatchPayment Credit) t = do | ||
292 | let regex = "^Name: (.*) Description: (.*) IBAN: ([A-Z0-9]+) Reference: (.*) Value date: ([0-9]{2}/[0-9]{2}/[0-9]{4})$" :: String | ||
293 | (_, _, _, [name, desc, ibanTxt, ref, valDateTxt]) <- t =~~ regex :: C.Parser (T.Text, T.Text, T.Text, [T.Text]) | ||
294 | iban <- ibanCP ibanTxt | ||
295 | valDate <- valueDateCP valDateTxt | ||
296 | return $ | ||
297 | BatchPaymentData | ||
298 | { bpName = name, | ||
299 | bpDescription = desc, | ||
300 | bpIban = iban, | ||
301 | bpReference = ref, | ||
302 | bpValueDate = valDate | ||
303 | } | ||
304 | notificationsCP _ (PartTx _ ty cd) _ = fail $ "Unmatched type and debit/credit combination (" ++ show ty ++ ", " ++ show cd ++ ")" | ||
305 | |||
306 | debitCreditCP :: T.Text -> C.Parser DebitCredit | ||
307 | debitCreditCP "Debit" = return Debit | ||
308 | debitCreditCP "Credit" = return Credit | ||
309 | debitCreditCP t = fail ("Unknown debit/credit value '" ++ T.unpack t ++ "'") | ||
310 | |||
311 | parseNamedRecord :: TZ -> C.NamedRecord -> C.Parser PrimTx | ||
312 | parseNamedRecord amsTz m = do | ||
313 | date <- m .: "Date" >>= dateCP "%0Y%m%d" | ||
314 | debitCredit <- m .: "Debit/credit" >>= debitCreditCP | ||
315 | codeText <- m .: "Code" | ||
316 | tyText <- m .: "Transaction type" | ||
317 | tyFromCode <- parseCode codeText | ||
318 | ty <- parseType tyText | ||
319 | if ty /= tyFromCode | ||
320 | then | ||
321 | fail $ "Code '" ++ T.unpack codeText ++ "' and transaction type '" ++ T.unpack tyText ++ "' do not agree" | ||
322 | else | ||
323 | PrimTx date | ||
324 | <$> (m .: "Name / Description" <&> maybeNotProvided) | ||
325 | <*> (m .: "Account" >>= ibanCP) | ||
326 | <*> (m .: "Counterparty" >>= maybeCP ibanCP) | ||
327 | <*> pure debitCredit | ||
328 | <*> (m .: "Amount (EUR)" >>= decimalCP) | ||
329 | <*> (m .: "Resulting balance" >>= decimalCP) | ||
330 | <*> m .: "Tag" | ||
331 | <*> (m .: "Notifications" >>= notificationsCP amsTz (PartTx date ty debitCredit)) | ||
332 | |||
333 | readFile :: Handle -> IO (V.Vector PrimTx) | ||
334 | readFile h = do | ||
335 | tz <- loadTZFromDB "Europe/Amsterdam" | ||
336 | contents <- BS.hGetContents h | ||
337 | case C.decodeByNameWithP (parseNamedRecord tz) scsvOptions contents of | ||
338 | Left err -> fail err | ||
339 | Right | ||
340 | ( [ "Date", | ||
341 | "Name / Description", | ||
342 | "Account", | ||
343 | "Counterparty", | ||
344 | "Code", | ||
345 | "Debit/credit", | ||
346 | "Amount (EUR)", | ||
347 | "Transaction type", | ||
348 | "Notifications", | ||
349 | "Resulting balance", | ||
350 | "Tag" | ||
351 | ], | ||
352 | txs | ||
353 | ) -> | ||
354 | return txs | ||
355 | Right _ -> | ||
356 | fail "Headers do not match expected pattern" | ||