Compare commits
3 Commits
7c39480c3b
...
a22ebd1835
Author | SHA1 | Date | |
---|---|---|---|
a22ebd1835 | |||
f9fc39fe8e | |||
9d3e6400b9 |
@ -1,6 +1,11 @@
|
|||||||
# TITO
|
# TITO
|
||||||
|
|
||||||
Tito on Haskell-kirjasto TITO-muotoisten tiliotteiden lukemiseen.
|
Tito on Haskell-kirjasto TITO-muotoisten tiliotteiden lukemiseen. Moduuli
|
||||||
|
`Data.TITO` sisältää ylätason funktiot tiliotteen tulkitsemiseen,
|
||||||
|
`Data.TITO.Types` määrittää tiliotteen tietorakenteen ja `Data.TITO.Parser`
|
||||||
|
ohjeet sen tekstimuodon tulkitsemisen. Kaikki moduulien nimet on suunniteltu
|
||||||
|
tuotavaksi omaan nimiavaruuteensa, mutta vain `Data.TITO.readFile` menee
|
||||||
|
päällekkäin `Prelude`:n nimen kanssa.
|
||||||
|
|
||||||
## Asentaminen
|
## Asentaminen
|
||||||
|
|
||||||
|
@ -1,2 +1,18 @@
|
|||||||
module Data.TITO where
|
module Data.TITO where
|
||||||
|
|
||||||
|
import Control.Exception
|
||||||
|
|
||||||
|
import qualified Data.ByteString as BS
|
||||||
|
import qualified Text.Megaparsec as P
|
||||||
|
|
||||||
|
import Data.TITO.Parser
|
||||||
|
import Data.TITO.Types
|
||||||
|
|
||||||
|
decode :: BS.ByteString -> Either ParseErrors AccountStatement
|
||||||
|
decode = P.parse accountStatement ""
|
||||||
|
|
||||||
|
readFile :: FilePath -> IO AccountStatement
|
||||||
|
readFile fp =
|
||||||
|
BS.readFile fp
|
||||||
|
>>= either (throwIO . ErrorCall . P.errorBundlePretty) pure
|
||||||
|
. P.parse accountStatement fp
|
||||||
|
@ -1,5 +1,6 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
|
{-# LANGUAGE NamedFieldPuns #-}
|
||||||
|
|
||||||
module Data.TITO.Parser where
|
module Data.TITO.Parser where
|
||||||
|
|
||||||
@ -93,8 +94,8 @@ transactionType = do
|
|||||||
case n of
|
case n of
|
||||||
1 -> pure Deposit
|
1 -> pure Deposit
|
||||||
2 -> pure Withdrawal
|
2 -> pure Withdrawal
|
||||||
3 -> pure DepositFix
|
3 -> pure DepositCorrection
|
||||||
4 -> pure WithdrawalFix
|
4 -> pure WithdrawalCorrection
|
||||||
9 -> pure Declined
|
9 -> pure Declined
|
||||||
_ -> P.failure Nothing mempty -- TODO: proper error message
|
_ -> P.failure Nothing mempty -- TODO: proper error message
|
||||||
|
|
||||||
@ -117,11 +118,9 @@ nameSource = do
|
|||||||
"A" -> pure Customer
|
"A" -> pure Customer
|
||||||
_ -> P.failure Nothing mempty -- TODO: proper error message
|
_ -> P.failure Nothing mempty -- TODO: proper error message
|
||||||
|
|
||||||
tito :: Parser TITO
|
accountStatement :: Parser AccountStatement
|
||||||
tito = TITO <$> titoRoot <*> P.many titoRecord <* P.eof
|
accountStatement = do
|
||||||
|
tito <- record "00" $ do
|
||||||
titoRoot :: Parser TITORoot
|
|
||||||
titoRoot = record "00" $ do
|
|
||||||
P.string "100" -- version number
|
P.string "100" -- version number
|
||||||
account <- alphaNumeric 14
|
account <- alphaNumeric 14
|
||||||
statementNumber <- alphaNumeric 3
|
statementNumber <- alphaNumeric 3
|
||||||
@ -140,21 +139,26 @@ titoRoot = record "00" $ do
|
|||||||
contactInformation <- optional' alphaNumeric 40
|
contactInformation <- optional' alphaNumeric 40
|
||||||
bankSpecific <- optional' alphaNumeric 30
|
bankSpecific <- optional' alphaNumeric 30
|
||||||
ibanAndBic <- fmap (fmap $ T.break isSpace) $ optional' alphaNumeric 30 -- FI1234567 XXXXX
|
ibanAndBic <- fmap (fmap $ T.break isSpace) $ optional' alphaNumeric 30 -- FI1234567 XXXXX
|
||||||
return TITORoot {..}
|
return AccountStatement {events = [], ..}
|
||||||
|
events <- P.many titoRecord <* P.eof
|
||||||
|
pure $ tito {events}
|
||||||
|
|
||||||
titoRecord :: Parser TITORecord
|
titoRecord :: Parser Event
|
||||||
titoRecord = P.try (transaction' False)
|
titoRecord = P.try transaction
|
||||||
<|> P.try (transactionDetail' False)
|
|
||||||
<|> P.try balance
|
<|> P.try balance
|
||||||
<|> P.try summary
|
<|> P.try summary
|
||||||
<|> P.try fixSummary
|
<|> P.try correctionSummary
|
||||||
<|> P.try special
|
<|> P.try bankSpecific
|
||||||
<|> P.try info
|
<|> P.try message
|
||||||
<|> P.try (transaction' True)
|
<|> P.try transactionNotification
|
||||||
<|> P.try (transactionDetail' True)
|
|
||||||
|
|
||||||
transaction' :: Bool -> Parser TITORecord
|
transaction, transactionNotification :: Parser Event
|
||||||
transaction' isInformational = record (if isInformational then "80" else "10") $ do
|
transaction = BasicTransaction <$> transaction' 0 False
|
||||||
|
transactionNotification = TransactionNotification <$> transaction' 0 True
|
||||||
|
|
||||||
|
transaction' :: Int -> Bool -> Parser Transaction
|
||||||
|
transaction' minimumDepth isNotification = do
|
||||||
|
(depth, transaction) <- record (if isNotification then "80" else "10") $ do
|
||||||
transactionNumber <- numeric 6
|
transactionNumber <- numeric 6
|
||||||
archiveId <- optional' alphaNumeric 18
|
archiveId <- optional' alphaNumeric 18
|
||||||
parsedDate <- date
|
parsedDate <- date
|
||||||
@ -172,15 +176,19 @@ transaction' isInformational = record (if isInformational then "80" else "10") $
|
|||||||
accountChanged <- optional' alphaNumeric 1
|
accountChanged <- optional' alphaNumeric 1
|
||||||
reference <- optional' numeric 20
|
reference <- optional' numeric 20
|
||||||
formNumber <- optional' alphaNumeric 8
|
formNumber <- optional' alphaNumeric 8
|
||||||
depth <- alphaNumeric 1
|
depth <- fromIntegral <$> numeric 1 <|> const 0 <$> P.char 32 -- space
|
||||||
return Transaction {date = parsedDate, ..}
|
guard $ depth >= minimumDepth
|
||||||
|
return (depth, Transaction {details = [], itemisation = [], date = parsedDate, ..})
|
||||||
|
details <- P.many $ P.try $ transactionDetail' isNotification
|
||||||
|
itemisation <- P.many $ P.try $ transaction' (depth + 1) isNotification
|
||||||
|
pure $ transaction {details, itemisation}
|
||||||
|
|
||||||
transactionDetail' :: Bool -> Parser TITORecord
|
transactionDetail' :: Bool -> Parser TransactionDetail
|
||||||
transactionDetail' isInformational =
|
transactionDetail' isNotification =
|
||||||
record' (if isInformational then "81" else "11") $ \recordLength -> do
|
record' (if isNotification then "81" else "11") $ \recordLength -> do
|
||||||
let detailLength = recordLength - 8
|
let detailLength = recordLength - 8
|
||||||
detailType <- optional' alphaNumeric 2
|
detailType <- optional' alphaNumeric 2
|
||||||
detail <- case detailType of
|
case detailType of
|
||||||
Just "00" -> do
|
Just "00" -> do
|
||||||
first <- alphaNumeric 35
|
first <- alphaNumeric 35
|
||||||
rest <- P.count' 0 11 (optional' alphaNumeric 35)
|
rest <- P.count' 0 11 (optional' alphaNumeric 35)
|
||||||
@ -194,7 +202,7 @@ transactionDetail' isInformational =
|
|||||||
date <- date
|
date <- date
|
||||||
pure Invoice {..}
|
pure Invoice {..}
|
||||||
Just "03" -> Card <$> alphaNumeric 19 <* alphaNumeric 1 <*> optional' alphaNumeric 14
|
Just "03" -> Card <$> alphaNumeric 19 <* alphaNumeric 1 <*> optional' alphaNumeric 14
|
||||||
Just "04" -> Fix <$> alphaNumeric 18
|
Just "04" -> Correction <$> alphaNumeric 18
|
||||||
Just "05" -> do
|
Just "05" -> do
|
||||||
foreignAmount <- money
|
foreignAmount <- money
|
||||||
alphaNumeric 1
|
alphaNumeric 1
|
||||||
@ -220,16 +228,15 @@ transactionDetail' isInformational =
|
|||||||
archiveId <- optional' alphaNumeric 35
|
archiveId <- optional' alphaNumeric 35
|
||||||
pure SEPA {..}
|
pure SEPA {..}
|
||||||
_ -> Unknown <$> alphaNumeric detailLength
|
_ -> Unknown <$> alphaNumeric detailLength
|
||||||
pure TransactionDetail {..}
|
|
||||||
|
|
||||||
balance :: Parser TITORecord
|
balance :: Parser Event
|
||||||
balance = record "40" $ do
|
balance = record "40" $ do
|
||||||
date <- date
|
date <- date
|
||||||
endBalance <- money
|
endBalance <- money
|
||||||
usableBalance <- optional 19 money
|
usableBalance <- optional 19 money
|
||||||
pure Balance {..}
|
pure Balance {..}
|
||||||
|
|
||||||
summary :: Parser TITORecord
|
summary :: Parser Event
|
||||||
summary = record "50" $ do
|
summary = record "50" $ do
|
||||||
period <- period
|
period <- period
|
||||||
date <- date
|
date <- date
|
||||||
@ -239,22 +246,22 @@ summary = record "50" $ do
|
|||||||
withdrawalsTotal <- money
|
withdrawalsTotal <- money
|
||||||
pure Summary {..}
|
pure Summary {..}
|
||||||
|
|
||||||
fixSummary :: Parser TITORecord
|
correctionSummary :: Parser Event
|
||||||
fixSummary = record "51" $ do
|
correctionSummary = record "51" $ do
|
||||||
period <- period
|
period <- period
|
||||||
date <- date
|
date <- date
|
||||||
depositFixes <- numeric 8
|
depositCorrections <- numeric 8
|
||||||
depositFixesTotal <- money
|
depositCorrectionsTotal <- money
|
||||||
withdrawalFixes <- numeric 8
|
withdrawalCorrections <- numeric 8
|
||||||
withdrawalFixesTotal <- money
|
withdrawalCorrectionsTotal <- money
|
||||||
pure FixSummary {..}
|
pure CorrectionSummary {..}
|
||||||
|
|
||||||
special :: Parser TITORecord
|
bankSpecific :: Parser Event
|
||||||
special = record' "60" $ \recordLength -> do
|
bankSpecific = record' "60" $ \recordLength -> do
|
||||||
BankSpecific <$> alphaNumeric 3 <*> P.takeP Nothing (recordLength - 9)
|
BankSpecific <$> alphaNumeric 3 <*> P.takeP Nothing (recordLength - 9)
|
||||||
|
|
||||||
info :: Parser TITORecord
|
message :: Parser Event
|
||||||
info = record' "70" $ \recordLength -> do
|
message = record' "70" $ \recordLength -> do
|
||||||
bankId <- alphaNumeric 3
|
bankId <- alphaNumeric 3
|
||||||
info <- T.unlines . T.chunksOf 80 <$> alphaNumeric (recordLength - 9)
|
message <- T.unlines . T.chunksOf 80 <$> alphaNumeric (recordLength - 9)
|
||||||
pure Info {..}
|
pure Message {..}
|
||||||
|
@ -8,14 +8,7 @@ import Data.Text (Text)
|
|||||||
import Data.Time (Day, LocalTime)
|
import Data.Time (Day, LocalTime)
|
||||||
import Data.List.NonEmpty (NonEmpty)
|
import Data.List.NonEmpty (NonEmpty)
|
||||||
|
|
||||||
data TITO = TITO
|
data AccountStatement = AccountStatement
|
||||||
{ root :: TITORoot
|
|
||||||
, records :: [TITORecord]
|
|
||||||
} deriving (Show, Eq)
|
|
||||||
|
|
||||||
newtype Money = Money Integer deriving (Eq, Show)
|
|
||||||
|
|
||||||
data TITORoot = TITORoot -- T00
|
|
||||||
{ account :: Text
|
{ account :: Text
|
||||||
, statementNumber :: Text
|
, statementNumber :: Text
|
||||||
, startDate :: Day
|
, startDate :: Day
|
||||||
@ -32,11 +25,46 @@ data TITORoot = TITORoot -- T00
|
|||||||
, contactInformation :: Maybe Text
|
, contactInformation :: Maybe Text
|
||||||
, bankSpecific :: Maybe Text
|
, bankSpecific :: Maybe Text
|
||||||
, ibanAndBic :: Maybe (Text, Text)
|
, ibanAndBic :: Maybe (Text, Text)
|
||||||
|
, events :: [Event]
|
||||||
} deriving (Show, Eq)
|
} deriving (Show, Eq)
|
||||||
|
|
||||||
data TITORecord = Transaction -- T80 if isInformational, else T10
|
newtype Money = Money Integer deriving (Eq, Show)
|
||||||
{ isInformational :: Bool
|
|
||||||
, transactionNumber :: Integer
|
data Event = BasicTransaction Transaction -- T10
|
||||||
|
| TransactionNotification Transaction -- T80
|
||||||
|
| Balance -- T40
|
||||||
|
{ date :: Day
|
||||||
|
, endBalance :: Money
|
||||||
|
, usableBalance :: Maybe Money
|
||||||
|
}
|
||||||
|
| Summary -- T50
|
||||||
|
{ period :: Period
|
||||||
|
, date :: Day
|
||||||
|
, deposits :: Integer
|
||||||
|
, depositsTotal :: Money
|
||||||
|
, withdrawals :: Integer
|
||||||
|
, withdrawalsTotal :: Money
|
||||||
|
}
|
||||||
|
| CorrectionSummary -- T51
|
||||||
|
{ period :: Period
|
||||||
|
, date :: Day
|
||||||
|
, depositCorrections :: Integer
|
||||||
|
, depositCorrectionsTotal :: Money
|
||||||
|
, withdrawalCorrections :: Integer
|
||||||
|
, withdrawalCorrectionsTotal :: Money
|
||||||
|
}
|
||||||
|
| BankSpecific -- T60
|
||||||
|
{ bankId :: Text
|
||||||
|
, rawData :: ByteString
|
||||||
|
}
|
||||||
|
| Message -- T70
|
||||||
|
{ bankId :: Text
|
||||||
|
, message :: Text
|
||||||
|
}
|
||||||
|
deriving (Show, Eq)
|
||||||
|
|
||||||
|
data Transaction = Transaction
|
||||||
|
{ transactionNumber :: Integer
|
||||||
, archiveId :: Maybe Text
|
, archiveId :: Maybe Text
|
||||||
, date :: Day
|
, date :: Day
|
||||||
, valueDate :: Maybe Day
|
, valueDate :: Maybe Day
|
||||||
@ -53,43 +81,9 @@ data TITORecord = Transaction -- T80 if isInformational, else T10
|
|||||||
, accountChanged :: Maybe Text
|
, accountChanged :: Maybe Text
|
||||||
, reference :: Maybe Integer
|
, reference :: Maybe Integer
|
||||||
, formNumber :: Maybe Text
|
, formNumber :: Maybe Text
|
||||||
, depth :: Text
|
, details :: [TransactionDetail]
|
||||||
}
|
, itemisation :: [Transaction]
|
||||||
| TransactionDetail -- T81 if isInformational, else T11
|
} deriving (Show, Eq)
|
||||||
{ isInformational :: Bool
|
|
||||||
, detailType :: Maybe Text
|
|
||||||
, detail :: TransactionDetail
|
|
||||||
}
|
|
||||||
| Balance -- T40
|
|
||||||
{ date :: Day
|
|
||||||
, endBalance :: Money
|
|
||||||
, usableBalance :: Maybe Money
|
|
||||||
}
|
|
||||||
| Summary -- T50
|
|
||||||
{ period :: Period
|
|
||||||
, date :: Day
|
|
||||||
, deposits :: Integer
|
|
||||||
, depositsTotal :: Money
|
|
||||||
, withdrawals :: Integer
|
|
||||||
, withdrawalsTotal :: Money
|
|
||||||
}
|
|
||||||
| FixSummary -- T51
|
|
||||||
{ period :: Period
|
|
||||||
, date :: Day
|
|
||||||
, depositFixes :: Integer
|
|
||||||
, depositFixesTotal :: Money
|
|
||||||
, withdrawalFixes :: Integer
|
|
||||||
, withdrawalFixesTotal :: Money
|
|
||||||
}
|
|
||||||
| BankSpecific -- T60
|
|
||||||
{ bankId :: Text
|
|
||||||
, rawData :: ByteString
|
|
||||||
}
|
|
||||||
| Info -- T70
|
|
||||||
{ bankId :: Text
|
|
||||||
, info :: Text
|
|
||||||
}
|
|
||||||
deriving (Show, Eq)
|
|
||||||
|
|
||||||
data TransactionDetail = Freeform (NonEmpty Text) -- 00
|
data TransactionDetail = Freeform (NonEmpty Text) -- 00
|
||||||
| Number Integer -- 01
|
| Number Integer -- 01
|
||||||
@ -102,8 +96,8 @@ data TransactionDetail = Freeform (NonEmpty Text) -- 00
|
|||||||
{ cardNumber :: Text
|
{ cardNumber :: Text
|
||||||
, merchantsReference :: Maybe Text
|
, merchantsReference :: Maybe Text
|
||||||
}
|
}
|
||||||
| Fix -- 04
|
| Correction -- 04
|
||||||
{ fixedTransaction :: Text}
|
{ correctedTransaction :: Text}
|
||||||
| ForeignCurrency -- 05
|
| ForeignCurrency -- 05
|
||||||
{ foreignAmount :: Money
|
{ foreignAmount :: Money
|
||||||
, currency :: Text
|
, currency :: Text
|
||||||
@ -129,7 +123,11 @@ data TransactionDetail = Freeform (NonEmpty Text) -- 00
|
|||||||
| Unknown Text -- all others
|
| Unknown Text -- all others
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
|
||||||
data TransactionType = Deposit | Withdrawal | DepositFix | WithdrawalFix | Declined deriving (Show, Eq)
|
data TransactionType = Deposit
|
||||||
|
| Withdrawal
|
||||||
|
| DepositCorrection
|
||||||
|
| WithdrawalCorrection
|
||||||
|
| Declined deriving (Show, Eq)
|
||||||
|
|
||||||
data Period = Day | Statement | Month | Year deriving (Show, Eq)
|
data Period = Day | Statement | Month | Year deriving (Show, Eq)
|
||||||
|
|
||||||
|
Loading…
Reference in New Issue
Block a user