{-# LANGUAGE OverloadedStrings #-} {- Rabobank - Convert Rabobank CSV exports to QIF files Copyright (C) 2012 Sander Venema This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} -- |The module Rabobank has utilities to take a Rabobank CSV export file of -- transactions, and transforming this into a QIF file ready for import into -- your accounting software. If your accounting software can't import Rabobank -- CSV files, most will be able to deal with QIF files. -- -- The QIF file generated by this module will have the bare minimum amount of -- information, namely a description, amount of money to be credited or -- debited, account number, and the transaction date. -- -- This module exports two functions namely 'toQif', which is the main function -- that will take a ByteString of Rabobank CSV data and returns a ByteString with QIF -- data, and 'baseName', which will generate a filename for the export file -- based on current date and time. module Rabobank (toQif, baseName) where import ListUtils (takeWhileIndex) import qualified Data.ByteString.Lazy.Char8 as BL import qualified Data.ByteString.Conversion as B import Data.Char (chr) import Data.List (intercalate) import Data.List.Split (splitPlaces) import Data.Maybe (fromJust, isJust) import Data.Time.Clock (getCurrentTime) import Data.Time.Format (formatTime, defaultTimeLocale) import Text.Printf (printf) -- |'Transaction' is the internal data structure used to represent a -- transaction. CSV data is turned into Transactions, and then, using the -- accessor methods converted to a QIF representation. data Transaction = Transaction { date :: BL.ByteString -- ^ The transaction date , amount :: Double -- ^ The amount of the transaction , description :: BL.ByteString -- ^ The transaction description , payee :: BL.ByteString -- ^ The payee , accountNumber :: BL.ByteString -- ^ The account number } deriving (Show) -- |'TransactionType' records whether a 'Transaction' has to be debited or -- credited. We use this data structure in the 'creditDebit' function to -- determine whether a transaction amount needs to be positive or negative. The -- 'toTransactionType' function turns a ByteString containing "D" or "C" into a -- 'TransactionType'. data TransactionType = D -- ^ Debit | C -- ^ Credit deriving (Show, Eq) -- |This function turns a string containing Rabobank CSV data to a string -- containing QIF data, ready for writing to stdout or to a file. toQif :: BL.ByteString -> BL.ByteString toQif file = BL.append qifHeader $ BL.unlines (map transactionToQif (fileToTransactions records)) where rows = BL.lines $ BL.filter (/= '"') file rawRecords = map (BL.split ',') rows records = map (takeWhileIndex [2,3,4,5,6,10,11,12,13,14,15]) (filter (\x -> length x == 19) rawRecords) -- |Turns a list of a list of list of a list of 'ByteString's into a list of -- 'Transaction's. fileToTransactions :: [[BL.ByteString]] -> [Transaction] fileToTransactions = map fromJust . filter isJust . map rowToTransaction -- |'transactionToQif' will turn a 'Transaction' into a 'ByteString' suitable -- for QIF files. We simply call the accessor methods of the 'Transaction' -- type, prefix them with the appropriate prefix letters as required by the QIF -- specification, and then intercalate then with newlines, thereby returning a -- 'ByteString' with this data, separated by newlines, just what we need. transactionToQif :: Transaction -> BL.ByteString transactionToQif t = BL.intercalate "\n" [ BL.cons 'P' (payee t), BL.cons 'M' (description t), BL.cons 'N' (accountNumber t), BL.cons 'D' (date t), BL.cons 'T' (BL.pack (printf "%.2f" (amount t)))] `BL.append` "\n^" -- |'rowToTransaction' turns a list of 'ByteString's to a 'Transaction'. It will -- apply all the necessary corrections and reformatting necessary to turn a row -- into a correct 'Transaction' for use with 'transactionToQif'. rowToTransaction :: [BL.ByteString] -> Maybe Transaction rowToTransaction (date:debitcredit:amount:accountNumber:payee:descriptionfields) = maybe Nothing (\correctAmount -> Just (Transaction correctDate correctAmount correctDescription payee accountNumber)) maybeAmount where correctDate = BL.pack $ intercalate "/" $ splitPlaces [4,2,2] $ BL.unpack date maybeAmount = maybe Nothing (\amount -> Just (creditDebit amount (toTransactionType debitcredit))) (B.fromByteString' amount :: Maybe Double) correctDescription = BL.intercalate ", " descriptionfields rowToTransaction _ = Nothing -- |Helper function to turn a 'ByteString' containing "D" or something else into a -- 'TransactionType'. This is used for 'creditDebit' to determine if an amount -- should be positive (added to the account) or negative (subtracted from the -- account. toTransactionType :: BL.ByteString -> TransactionType toTransactionType c = if c == "D" then D else C -- |'creditDebit' will make the given amount negative if 'transactiontype' == D -- (for Debet), otherwise it will leave it untouched. creditDebit :: Double -> TransactionType -> Double creditDebit amount transactiontype = if transactiontype == D then -1 * amount else amount -- |'baseName' gets the current date and time and returns an 'IO FilePath' with the -- timestamp and 'Rabobank_' as the prefix. This will be used as the filename -- (minus extension) for the exported QIF file. baseName :: IO FilePath baseName = do now <- getCurrentTime return $ "Rabobank_" ++ (formatTime defaultTimeLocale "%Y%m%d%H%M%S" now) ++ ".qif" -- |'qifHeader' returns the header at the start of the QIF file. qifHeader :: BL.ByteString qifHeader = BL.pack "!Type:Bank\n"