{- Rabobank - Convert Rabobank CSV exports to QIF files
   Copyright (C) 2012 Sander Venema <sander.venema@gmail.com>

   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 <http://www.gnu.org/licenses/>. -}

-- |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 String of Rabobank CSV data and returns a String 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 Data.Char (chr)
import Data.List (intercalate)
import Data.List.Split (splitOn, splitPlaces)
import Data.Maybe (fromJust, isJust)
import Data.Time.Clock (getCurrentTime)
import Data.Time.Format (formatTime)
import System.Locale (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 :: String          -- ^ The transaction date
                               , amount :: Double        -- ^ The amount of the transaction
                               , description :: String   -- ^ The transaction description
                               , accountNumber :: String -- ^ 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 String 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 :: String -> String
toQif file = qifHeader ++ unlines (map transactionToQif (fileToTransactions records))
    where rows       = lines $ filter (/= '"') file
          rawRecords = map (splitOn ",") rows
          records    = map (takeWhileIndex [2,3,4,5,6,10]) 
                            (filter (\x -> length x == 16) rawRecords)

-- |Turns a list of a list of list of a list of 'String's into a list of
-- 'Transaction's.
fileToTransactions :: [[String]] -> [Transaction]
fileToTransactions = map fromJust . filter isJust . map rowToTransaction

-- |'transactionToQif' will turn a 'Transaction' into a 'String' 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
-- 'String' with this data, separated by newlines, just what we need.
transactionToQif :: Transaction -> String
transactionToQif t = intercalate "\n" ['P':description t, 'N':accountNumber t, 
                                  'D':date t, 'T':printf "%.2f" (amount t)] ++ "\n^"

-- |'rowToTransaction' turns a list of 'String'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 :: [String] -> Maybe Transaction
rowToTransaction
    [date, debitcredit, amount, accountNumber, description, acctDesc] =
        Just (Transaction correctDate correctAmount correctDescription accountNumber)
  where correctDate         = intercalate "/" $ splitPlaces [4,2,2] date
        correctAmount       = creditDebit (read amount :: Double) (toTransactionType debitcredit)
        correctDescription  = description ++ ", " ++ acctDesc
rowToTransaction _ = Nothing

-- |Helper function to turn a 'String' 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 :: String -> 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 String' with the
-- timestamp and 'Rabobank_' as the prefix. This will be used as the filename
-- (minus extension) for the exported QIF file.
baseName :: IO String
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 :: String
qifHeader = "!Type:Bank\n"