summaryrefslogtreecommitdiffstats
path: root/app/Import/Ing/SavingsAccountCsv.hs
diff options
context:
space:
mode:
authorRutger Broekhoff2025-03-18 15:29:27 +0100
committerRutger Broekhoff2025-03-18 15:31:11 +0100
commit86c8896ee69b068368b4ef9a4c3923285907c328 (patch)
treedc6e4f58a511c58e2910e9f7ea900165da7d47c6 /app/Import/Ing/SavingsAccountCsv.hs
downloadrdcapsis-86c8896ee69b068368b4ef9a4c3923285907c328.tar.gz
rdcapsis-86c8896ee69b068368b4ef9a4c3923285907c328.zip
Parsing ING statements (POC)
Diffstat (limited to 'app/Import/Ing/SavingsAccountCsv.hs')
-rw-r--r--app/Import/Ing/SavingsAccountCsv.hs162
1 files changed, 162 insertions, 0 deletions
diff --git a/app/Import/Ing/SavingsAccountCsv.hs b/app/Import/Ing/SavingsAccountCsv.hs
new file mode 100644
index 0000000..f6632fc
--- /dev/null
+++ b/app/Import/Ing/SavingsAccountCsv.hs
@@ -0,0 +1,162 @@
1{-# LANGUAGE OverloadedLists #-}
2{-# LANGUAGE OverloadedStrings #-}
3
4module Import.Ing.SavingsAccountCsv where
5
6import Data.ByteString.Lazy qualified as BS
7import Data.Csv ((.:))
8import Data.Csv qualified as C
9import Data.Decimal (Decimal)
10import Data.Iban (Iban, mkIban)
11import Data.Maybe (isJust)
12import Data.Text qualified as T
13import Data.Time.Calendar (Day)
14import Data.Vector qualified as V
15import Import.Ing.Shared (dateCP, decimalCP, eitherToCP, ibanCP, maybeCP, scsvOptions)
16import System.IO (Handle)
17import Text.Regex.TDFA ((=~~))
18
19data DebitCredit = Debit | Credit deriving (Show, Eq)
20
21data MutationType = DepositMutation | WithdrawalMutation | InterestMutation deriving (Show)
22
23data TxBase = TxBase
24 { txbDate :: !Day,
25 txbAccountId :: !T.Text,
26 txbAccountName :: !T.Text,
27 txbAmount :: !Decimal,
28 txbResBal :: !Decimal
29 }
30 deriving (Show)
31
32data 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
45data Tx = Tx TxBase TxSpecifics deriving (Show)
46
47instance MonadFail (Either String) where
48 fail = Left
49
50txBaseFromPrim :: PrimTx -> Either String TxBase
51txBaseFromPrim ptx@PrimTx {ptxCommodity = "EUR"} =
52 return $ TxBase (ptxDate ptx) (ptxAccountId ptx) (ptxAccountName ptx) (ptxAmount ptx) (ptxResBal ptx)
53txBaseFromPrim ptx =
54 Left $ "Unexpected commodity '" ++ T.unpack (ptxCommodity ptx) ++ "' (expected EUR)"
55
56specificsFromPrim :: PrimTx -> Either String TxSpecifics
57specificsFromPrim 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
66specificsFromPrim 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}
76specificsFromPrim 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
95processPrimTx :: PrimTx -> Either String Tx
96processPrimTx ptx = Tx <$> txBaseFromPrim ptx <*> specificsFromPrim ptx
97
98data 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
113debitCreditCP :: T.Text -> C.Parser DebitCredit
114debitCreditCP "Af" = return Debit
115debitCreditCP "Bij" = return Credit
116debitCreditCP t = fail ("Unknown debit/credit value '" ++ T.unpack t ++ "'")
117
118mutationTypeCP :: T.Text -> C.Parser MutationType
119mutationTypeCP "Inleg" = return DepositMutation
120mutationTypeCP "Opname" = return WithdrawalMutation
121mutationTypeCP "Rente" = return InterestMutation
122mutationTypeCP t = fail ("Unknown mutation type '" ++ T.unpack t ++ "'")
123
124parseNamedRecord :: C.NamedRecord -> C.Parser Tx
125parseNamedRecord m =
126 eitherToCP . processPrimTx
127 =<< PrimTx
128 <$> (m .: "Datum" >>= dateCP "%Y-%m-%d")
129 <*> m .: "Omschrijving"
130 <*> m .: "Rekening"
131 <*> m .: "Rekening naam"
132 <*> (m .: "Tegenrekening" >>= maybeCP ibanCP)
133 <*> (m .: "Af Bij" >>= debitCreditCP)
134 <*> (m .: "Bedrag" >>= decimalCP)
135 <*> m .: "Valuta"
136 <*> (m .: "Mutatiesoort" >>= mutationTypeCP)
137 <*> m .: "Mededelingen"
138 <*> (m .: "Saldo na mutatie" >>= decimalCP)
139
140readFile :: Handle -> IO (V.Vector Tx)
141readFile h = do
142 contents <- BS.hGetContents h
143 case C.decodeByNameWithP parseNamedRecord scsvOptions contents of
144 Left err -> fail err
145 Right
146 ( [ "Datum",
147 "Omschrijving",
148 "Rekening",
149 "Rekening naam",
150 "Tegenrekening",
151 "Af Bij",
152 "Bedrag",
153 "Valuta",
154 "Mutatiesoort",
155 "Mededelingen",
156 "Saldo na mutatie"
157 ],
158 txs
159 ) ->
160 return txs
161 Right _ ->
162 fail "Headers do not match expected pattern"