Compare commits

..

No commits in common. "a22ebd18359b1c3fc62d2d5cad29ca18ee6771c1" and "7c39480c3bc185432d0014dbe78b3c0edbc52bb2" have entirely different histories.

4 changed files with 182 additions and 208 deletions

View File

@ -1,11 +1,6 @@
# TITO # TITO
Tito on Haskell-kirjasto TITO-muotoisten tiliotteiden lukemiseen. Moduuli Tito on Haskell-kirjasto TITO-muotoisten tiliotteiden lukemiseen.
`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

View File

@ -1,18 +1,2 @@
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

View File

@ -1,6 +1,5 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NamedFieldPuns #-}
module Data.TITO.Parser where module Data.TITO.Parser where
@ -94,8 +93,8 @@ transactionType = do
case n of case n of
1 -> pure Deposit 1 -> pure Deposit
2 -> pure Withdrawal 2 -> pure Withdrawal
3 -> pure DepositCorrection 3 -> pure DepositFix
4 -> pure WithdrawalCorrection 4 -> pure WithdrawalFix
9 -> pure Declined 9 -> pure Declined
_ -> P.failure Nothing mempty -- TODO: proper error message _ -> P.failure Nothing mempty -- TODO: proper error message
@ -118,9 +117,11 @@ nameSource = do
"A" -> pure Customer "A" -> pure Customer
_ -> P.failure Nothing mempty -- TODO: proper error message _ -> P.failure Nothing mempty -- TODO: proper error message
accountStatement :: Parser AccountStatement tito :: Parser TITO
accountStatement = do tito = TITO <$> titoRoot <*> P.many titoRecord <* P.eof
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
@ -139,26 +140,21 @@ accountStatement = 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 AccountStatement {events = [], ..} return TITORoot {..}
events <- P.many titoRecord <* P.eof
pure $ tito {events}
titoRecord :: Parser Event titoRecord :: Parser TITORecord
titoRecord = P.try transaction titoRecord = P.try (transaction' False)
<|> P.try (transactionDetail' False)
<|> P.try balance <|> P.try balance
<|> P.try summary <|> P.try summary
<|> P.try correctionSummary <|> P.try fixSummary
<|> P.try bankSpecific <|> P.try special
<|> P.try message <|> P.try info
<|> P.try transactionNotification <|> P.try (transaction' True)
<|> P.try (transactionDetail' True)
transaction, transactionNotification :: Parser Event transaction' :: Bool -> Parser TITORecord
transaction = BasicTransaction <$> transaction' 0 False transaction' isInformational = record (if isInformational then "80" else "10") $ do
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
@ -176,19 +172,15 @@ transaction' minimumDepth isNotification = do
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 <- fromIntegral <$> numeric 1 <|> const 0 <$> P.char 32 -- space depth <- alphaNumeric 1
guard $ depth >= minimumDepth return Transaction {date = parsedDate, ..}
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 TransactionDetail transactionDetail' :: Bool -> Parser TITORecord
transactionDetail' isNotification = transactionDetail' isInformational =
record' (if isNotification then "81" else "11") $ \recordLength -> do record' (if isInformational then "81" else "11") $ \recordLength -> do
let detailLength = recordLength - 8 let detailLength = recordLength - 8
detailType <- optional' alphaNumeric 2 detailType <- optional' alphaNumeric 2
case detailType of detail <- 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)
@ -202,7 +194,7 @@ transactionDetail' isNotification =
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" -> Correction <$> alphaNumeric 18 Just "04" -> Fix <$> alphaNumeric 18
Just "05" -> do Just "05" -> do
foreignAmount <- money foreignAmount <- money
alphaNumeric 1 alphaNumeric 1
@ -228,15 +220,16 @@ transactionDetail' isNotification =
archiveId <- optional' alphaNumeric 35 archiveId <- optional' alphaNumeric 35
pure SEPA {..} pure SEPA {..}
_ -> Unknown <$> alphaNumeric detailLength _ -> Unknown <$> alphaNumeric detailLength
pure TransactionDetail {..}
balance :: Parser Event balance :: Parser TITORecord
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 Event summary :: Parser TITORecord
summary = record "50" $ do summary = record "50" $ do
period <- period period <- period
date <- date date <- date
@ -246,22 +239,22 @@ summary = record "50" $ do
withdrawalsTotal <- money withdrawalsTotal <- money
pure Summary {..} pure Summary {..}
correctionSummary :: Parser Event fixSummary :: Parser TITORecord
correctionSummary = record "51" $ do fixSummary = record "51" $ do
period <- period period <- period
date <- date date <- date
depositCorrections <- numeric 8 depositFixes <- numeric 8
depositCorrectionsTotal <- money depositFixesTotal <- money
withdrawalCorrections <- numeric 8 withdrawalFixes <- numeric 8
withdrawalCorrectionsTotal <- money withdrawalFixesTotal <- money
pure CorrectionSummary {..} pure FixSummary {..}
bankSpecific :: Parser Event special :: Parser TITORecord
bankSpecific = record' "60" $ \recordLength -> do special = record' "60" $ \recordLength -> do
BankSpecific <$> alphaNumeric 3 <*> P.takeP Nothing (recordLength - 9) BankSpecific <$> alphaNumeric 3 <*> P.takeP Nothing (recordLength - 9)
message :: Parser Event info :: Parser TITORecord
message = record' "70" $ \recordLength -> do info = record' "70" $ \recordLength -> do
bankId <- alphaNumeric 3 bankId <- alphaNumeric 3
message <- T.unlines . T.chunksOf 80 <$> alphaNumeric (recordLength - 9) info <- T.unlines . T.chunksOf 80 <$> alphaNumeric (recordLength - 9)
pure Message {..} pure Info {..}

View File

@ -8,7 +8,14 @@ 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 AccountStatement = AccountStatement data TITO = TITO
{ 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
@ -25,46 +32,11 @@ data AccountStatement = AccountStatement
, 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)
newtype Money = Money Integer deriving (Eq, Show) data TITORecord = Transaction -- T80 if isInformational, else T10
{ isInformational :: Bool
data Event = BasicTransaction Transaction -- T10 , transactionNumber :: Integer
| 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
@ -81,9 +53,43 @@ data Transaction = Transaction
, accountChanged :: Maybe Text , accountChanged :: Maybe Text
, reference :: Maybe Integer , reference :: Maybe Integer
, formNumber :: Maybe Text , formNumber :: Maybe Text
, details :: [TransactionDetail] , depth :: Text
, itemisation :: [Transaction] }
} deriving (Show, Eq) | TransactionDetail -- T81 if isInformational, else T11
{ 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
@ -96,8 +102,8 @@ data TransactionDetail = Freeform (NonEmpty Text) -- 00
{ cardNumber :: Text { cardNumber :: Text
, merchantsReference :: Maybe Text , merchantsReference :: Maybe Text
} }
| Correction -- 04 | Fix -- 04
{ correctedTransaction :: Text} { fixedTransaction :: Text}
| ForeignCurrency -- 05 | ForeignCurrency -- 05
{ foreignAmount :: Money { foreignAmount :: Money
, currency :: Text , currency :: Text
@ -123,11 +129,7 @@ data TransactionDetail = Freeform (NonEmpty Text) -- 00
| Unknown Text -- all others | Unknown Text -- all others
deriving (Eq, Show) deriving (Eq, Show)
data TransactionType = Deposit data TransactionType = Deposit | Withdrawal | DepositFix | WithdrawalFix | Declined deriving (Show, Eq)
| 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)