├── .gitignore ├── Setup.lhs ├── test-data ├── Statement-Page-1.html ├── Statement-Page-2.html └── Rules.rules ├── Finance └── Halifax │ ├── Core.hs │ ├── RulesParser.hs │ ├── Rules.hs │ ├── CSV.hs │ ├── Utilities.hs │ ├── QIF.hs │ ├── Ledger.hs │ ├── Options.hs │ ├── Main.hs │ ├── StatementParser.hs │ └── Tests.hs ├── LICENSE └── halifax-import.cabal /.gitignore: -------------------------------------------------------------------------------- 1 | # OS Junk 2 | .DS_Store 3 | Thumbs.db 4 | 5 | # Build artifacts 6 | dist/ 7 | -------------------------------------------------------------------------------- /Setup.lhs: -------------------------------------------------------------------------------- 1 | #! /usr/bin/env runhaskell 2 | 3 | > import Distribution.Simple 4 | > main = defaultMain -------------------------------------------------------------------------------- /test-data/Statement-Page-1.html: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/batterseapower/halifax-import/master/test-data/Statement-Page-1.html -------------------------------------------------------------------------------- /test-data/Statement-Page-2.html: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/batterseapower/halifax-import/master/test-data/Statement-Page-2.html -------------------------------------------------------------------------------- /test-data/Rules.rules: -------------------------------------------------------------------------------- 1 | Amazon.co.uk 2 | # A comment 3 | Expense:Books 4 | # Another comment 5 | 6 | Mozy\.Com 1111111111 US 7 | Mozy.Com 8 | Expense:Backups 9 | # Yet another comment -------------------------------------------------------------------------------- /Finance/Halifax/Core.hs: -------------------------------------------------------------------------------- 1 | module Finance.Halifax.Core where 2 | 3 | import Data.Time 4 | 5 | 6 | type Amount = Rational 7 | 8 | data Account = Account { 9 | acc_sort_code :: String, 10 | acc_number :: Int, 11 | acc_roll_number :: String 12 | } 13 | deriving (Eq, Show) 14 | 15 | data TransactionType = Debit | Credit 16 | deriving (Eq, Show) 17 | 18 | type Category = String 19 | 20 | data Transaction = Transaction { 21 | tr_time :: UTCTime, 22 | tr_comments :: [String], 23 | tr_counterparty :: String, 24 | tr_category :: Maybe Category, 25 | tr_type :: TransactionType, 26 | tr_amount :: Amount 27 | } 28 | deriving (Eq, Show) -------------------------------------------------------------------------------- /Finance/Halifax/RulesParser.hs: -------------------------------------------------------------------------------- 1 | module Finance.Halifax.RulesParser (parseRules) where 2 | 3 | import Data.Maybe 4 | import Data.List 5 | 6 | import Finance.Halifax.Rules 7 | import Finance.Halifax.Utilities 8 | 9 | 10 | parseRules :: String -> [Rule] 11 | parseRules = catMaybes . unfoldr unfold_one_rule . map trim . filter (not . ("#" `isPrefixOf`)) . lines 12 | where 13 | unfold_one_rule lines_left = case lines_left of 14 | ("":rest) 15 | -> Just (Nothing, rest) 16 | (regex_line:category_line:rest) 17 | | null rest || null (head rest) 18 | -> Just (Just (Rule regex_line Nothing category_line), drop 1 rest) 19 | (regex_line:counterparty_line:category_line:rest) 20 | -> Just (Just (Rule regex_line (Just counterparty_line) category_line), drop 1 rest) 21 | _ -> Nothing -------------------------------------------------------------------------------- /Finance/Halifax/Rules.hs: -------------------------------------------------------------------------------- 1 | module Finance.Halifax.Rules where 2 | 3 | import Data.Maybe 4 | import Data.List 5 | 6 | import Text.Regex.Posix 7 | 8 | import Finance.Halifax.Core 9 | import Finance.Halifax.Utilities 10 | 11 | 12 | data Rule = Rule { 13 | ru_regex :: String, 14 | ru_new_counterparty :: Maybe String, 15 | ru_new_category :: Category 16 | } 17 | deriving (Eq) 18 | 19 | instance Show Rule where 20 | show rule = concat $ intersperse "\r\n" $ catMaybes [Just (show (ru_regex rule)), ru_new_counterparty rule, Just (ru_new_category rule)] 21 | showList rules _ = unlines $ intersperse "" $ map show rules 22 | 23 | applyRules :: [Rule] -> Transaction -> Transaction 24 | applyRules rules transaction = fromMaybe transaction $ firstJust (map (flip applyRule transaction) rules) 25 | 26 | applyRule :: Rule -> Transaction -> Maybe Transaction 27 | applyRule rule transaction 28 | | tr_counterparty transaction =~ ru_regex rule 29 | = Just $ transaction { tr_counterparty = fromMaybe (tr_counterparty transaction) (ru_new_counterparty rule), tr_category = Just (ru_new_category rule) } 30 | | otherwise 31 | = Nothing -------------------------------------------------------------------------------- /Finance/Halifax/CSV.hs: -------------------------------------------------------------------------------- 1 | module Finance.Halifax.CSV where 2 | 3 | import Finance.Halifax.Core 4 | import Finance.Halifax.Options 5 | import Finance.Halifax.Utilities 6 | 7 | import System.Locale 8 | 9 | import Data.Time.Format 10 | import Data.List 11 | 12 | -- This CSV is designed to exactly match that you get from Halifax's front end 13 | outputCSV :: Options -> Account -> [Transaction] -> IO () 14 | outputCSV _options _account transactions = putStrLn $ unlines $ header : map transaction_line transactions 15 | where 16 | header = "Date,Amount,Description" 17 | transaction_line transaction = intercalate "," [date, amount, description] 18 | where 19 | date = formatTime defaultTimeLocale "%d/%m/%y" (tr_time transaction) 20 | amount = showFloatAsCurrencylike (fromRational ((case tr_type transaction of Debit -> negate; Credit -> id) 21 | (tr_amount transaction)) :: Double) 22 | description = tr_counterparty transaction ++ (if null (tr_comments transaction) 23 | then "" 24 | else " - " ++ unwords (tr_comments transaction)) 25 | -------------------------------------------------------------------------------- /Finance/Halifax/Utilities.hs: -------------------------------------------------------------------------------- 1 | module Finance.Halifax.Utilities where 2 | 3 | import Data.Char 4 | import Data.Maybe 5 | 6 | import Numeric 7 | 8 | 9 | trim :: String -> String 10 | trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace 11 | 12 | fragment :: (a -> Bool) -> (a -> Bool) -> [a] -> ([a], [a]) 13 | fragment start end = span (not . end) . dropWhile (not . start) 14 | 15 | firstJust :: [Maybe a] -> Maybe a 16 | firstJust = listToMaybe . catMaybes 17 | 18 | orElse :: Maybe a -> a -> a 19 | orElse = flip fromMaybe 20 | 21 | notNull :: [a] -> Bool 22 | notNull = not . null 23 | 24 | onLeft :: (a -> c) -> (a, b) -> (c, b) 25 | onLeft f (x, y) = (f x, y) 26 | 27 | onRight :: (b -> c) -> (a, b) -> (a, c) 28 | onRight f (x, y) = (x, f y) 29 | 30 | splitEithers :: [Either a b] -> ([a], [b]) 31 | splitEithers [] = ([], []) 32 | splitEithers (Left x:rest) = onLeft (x:) $ splitEithers rest 33 | splitEithers (Right y:rest) = onRight (y:) $ splitEithers rest 34 | 35 | -- | Shows the given number in a currency-like way (i.e. with two trailing zeroes). 36 | -- I wish I could look up the number of digits in the locale, but alas that is not possible! 37 | showFloatAsCurrencylike :: RealFloat a => a -> String 38 | showFloatAsCurrencylike = flip (showFFloat (Just 2)) "" -------------------------------------------------------------------------------- /LICENSE: -------------------------------------------------------------------------------- 1 | Copyright (c) 2008, Maximilian Bolingbroke 2 | All rights reserved. 3 | 4 | Redistribution and use in source and binary forms, with or without modification, are permitted 5 | provided that the following conditions are met: 6 | 7 | * Redistributions of source code must retain the above copyright notice, this list of 8 | conditions and the following disclaimer. 9 | * Redistributions in binary form must reproduce the above copyright notice, this list of 10 | conditions and the following disclaimer in the documentation and/or other materials 11 | provided with the distribution. 12 | * Neither the name of Maximilian Bolingbroke nor the names of other contributors may be used to 13 | endorse or promote products derived from this software without specific prior written permission. 14 | 15 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR 16 | IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND 17 | FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR 18 | CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL 19 | DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, 20 | DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER 21 | IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT 22 | OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -------------------------------------------------------------------------------- /Finance/Halifax/QIF.hs: -------------------------------------------------------------------------------- 1 | module Finance.Halifax.QIF where 2 | 3 | import Finance.Halifax.Core 4 | import Finance.Halifax.Options 5 | import Finance.Halifax.Utilities 6 | 7 | import System.Locale 8 | 9 | import Data.Time.Format 10 | 11 | -- http://web.intuit.com/support/quicken/docs/d_qif.html 12 | -- http://svn.gnucash.org/trac/browser/gnucash/branches/2.2/src/import-export/qif-import/file-format.txt 13 | 14 | outputQIF :: Options -> Account -> [Transaction] -> IO () 15 | outputQIF _options _account transactions = putStrLn $ unlines $ header ++ concatMap transaction_lines transactions 16 | where 17 | tab s = " " ++ s 18 | 19 | -- Each transaction must end with a symbol, indicating the end of entry. Each item 20 | -- in the transaction must display on a separate line. When Quicken exports an account 21 | -- register or list, it adds a line to the top of the file that identifies the type of 22 | -- account or list. 23 | header = 24 | [ "" 25 | , tab "!Type:Bank" -- !Type:Cash or !Type:Invst might also be useful 26 | , "" 27 | ] 28 | 29 | -- I just blindly copied this from the QIF output Halifax was giving me 30 | transaction_lines transaction = 31 | -- Date 32 | [ "D" ++ formatTime defaultTimeLocale "%d/%m/%y" (tr_time transaction) 33 | , "" 34 | -- Amount 35 | , tab $ tab $ "T" ++ showFloatAsCurrencylike (fromRational ((case tr_type transaction of Debit -> negate; Credit -> id) 36 | (tr_amount transaction)) :: Double) 37 | -- Payee 38 | , "P" ++ tr_counterparty transaction ++ (if null (tr_comments transaction) 39 | then "" 40 | else " - " ++ unwords (tr_comments transaction)) 41 | -- End of entry 42 | , "^" 43 | , "" 44 | ] 45 | -------------------------------------------------------------------------------- /Finance/Halifax/Ledger.hs: -------------------------------------------------------------------------------- 1 | module Finance.Halifax.Ledger (outputLedger) where 2 | 3 | import Finance.Halifax.Core 4 | import Finance.Halifax.Options 5 | import Finance.Halifax.Utilities 6 | 7 | import System.IO 8 | import System.Locale 9 | 10 | import Control.Monad 11 | 12 | import Data.List 13 | import Data.Maybe 14 | import Data.Time.Format 15 | 16 | 17 | outputLedger :: Options -> Account -> [Transaction] -> IO () 18 | outputLedger options _account transactions = do 19 | putStrLn (unlines ok_entries) 20 | when (notNull bad_entries) $ do 21 | hPutStrLn stderr "Some entries in the input to the Ledger formatter did not have any category assigned. Add rules to fix these:" 22 | hPutStrLn stderr (unlines $ nub bad_entries) 23 | where 24 | account_category = fromMaybe "Assets:Bank:Current" (opt_ledger_account_category options) 25 | (bad_entries, ok_entries) = splitEithers $ map (showLedgerTransaction account_category) transactions 26 | 27 | -- Output something like this: 28 | -- 29 | -- 2004/05/27 Book Store 30 | -- Expenses:Books $20.00 31 | -- Assets:Bank:Current 32 | showLedgerTransaction :: Category -> Transaction -> Either String String 33 | showLedgerTransaction account_category transaction 34 | | isJust mb_category = Right $ unlines [ 35 | unwords [date, who], 36 | " " ++ to ++ amount_padding ++ amount, 37 | " " ++ from 38 | ] 39 | | otherwise = Left who 40 | where 41 | date = formatTime defaultTimeLocale "%Y/%m/%d" (tr_time transaction) 42 | who = tr_counterparty transaction 43 | mb_category = tr_category transaction 44 | category = fromJust mb_category 45 | (from, to) = case tr_type transaction of 46 | Debit -> (account_category, category) 47 | Credit -> (category, account_category) 48 | amount_padding = replicate (31 - length to) ' ' 49 | amount = "£" ++ showFloatAsCurrencylike (fromRational (tr_amount transaction) :: Double) 50 | -------------------------------------------------------------------------------- /Finance/Halifax/Options.hs: -------------------------------------------------------------------------------- 1 | module Finance.Halifax.Options where 2 | 3 | import Finance.Halifax.Core (Category) 4 | 5 | import System.Console.GetOpt 6 | 7 | import Control.Monad (mplus) 8 | 9 | import Data.Char 10 | import Data.List 11 | import Data.Monoid 12 | 13 | 14 | data OutputMethod = Ledger 15 | | QIF 16 | | CSV 17 | 18 | instance Show OutputMethod where 19 | show Ledger = "ledger" 20 | show QIF = "qif" 21 | show CSV = "csv" 22 | 23 | instance Read OutputMethod where 24 | readsPrec _ s | "ledger" `isPrefixOf` lower_s = [(Ledger, drop 6 s)] 25 | | "qif" `isPrefixOf` lower_s = [(QIF, drop 3 s)] 26 | | "csv" `isPrefixOf` lower_s = [(CSV, drop 3 s)] 27 | | otherwise = [] 28 | where lower_s = map toLower s 29 | 30 | 31 | data Options = Options { 32 | opt_rules_file :: Maybe FilePath, 33 | opt_ledger_account_category :: Maybe Category, 34 | opt_output_method :: Maybe OutputMethod 35 | } 36 | 37 | instance Monoid Options where 38 | mempty = Options { 39 | opt_rules_file = Nothing, 40 | opt_ledger_account_category = Nothing, 41 | opt_output_method = Nothing 42 | } 43 | mappend o1 o2 = Options { 44 | opt_rules_file = opt_rules_file o1 `mplus` opt_rules_file o2, 45 | opt_ledger_account_category = opt_ledger_account_category o1 `mplus` opt_ledger_account_category o2, 46 | opt_output_method = opt_output_method o1 `mplus` opt_output_method o2 47 | } 48 | 49 | option_descriptions :: [OptDescr Options] 50 | option_descriptions = [ 51 | Option ['f'] ["output-format"] (ReqArg (\s -> mempty { opt_output_method = Just (read s) }) "ledger|qif|csv") 52 | "Format to output the parsed file in", 53 | Option ['r'] ["rules"] (ReqArg (\s -> mempty { opt_rules_file = Just s }) "filename") 54 | "Rules file to use for processing transactions", 55 | Option ['c'] ["ledger-category"] (ReqArg (\s -> mempty { opt_ledger_account_category = Just s }) "category") 56 | "Category to attribute this account to in Ledger output" 57 | ] -------------------------------------------------------------------------------- /Finance/Halifax/Main.hs: -------------------------------------------------------------------------------- 1 | module Main where 2 | 3 | import Data.Monoid 4 | 5 | import System.Console.GetOpt 6 | import System.Environment (getArgs) 7 | import System.Exit 8 | import System.IO 9 | 10 | import Finance.Halifax.CSV 11 | import Finance.Halifax.Ledger 12 | import Finance.Halifax.QIF 13 | import Finance.Halifax.Options 14 | import Finance.Halifax.Rules 15 | import Finance.Halifax.RulesParser (parseRules) 16 | import Finance.Halifax.StatementParser (parseStatement) 17 | import Finance.Halifax.Utilities 18 | 19 | 20 | main :: IO () 21 | main = do 22 | args <- getArgs 23 | let (optionss, page_paths, errors) = getOpt Permute option_descriptions args 24 | if notNull errors 25 | then do 26 | mapM_ putStrLn errors 27 | putStrLn $ usageInfo "halifax-ledger" option_descriptions 28 | exitWith (ExitFailure 1) 29 | else do 30 | let options = mconcat optionss 31 | 32 | -- Read the page files and the statement they contain. 33 | -- For some reason, the Halifax files contain character 0xA0 (160). 34 | -- This terminates the file reading process in text mode for some reason, 35 | -- so let's just read in binary mode for now. 36 | pages <- mapM readBinaryFile page_paths 37 | let (account, transactions) = parseStatement pages 38 | --hPutStrLn stderr (show transactions) 39 | 40 | -- Read the rules (if any) and apply them to the transactions from the pages 41 | rules <- maybe (return []) (fmap parseRules . readFile) $ opt_rules_file options 42 | let transactions' = map (applyRules rules) transactions 43 | 44 | -- Output the data in the appropriate format 45 | let output_method = case opt_output_method options `orElse` QIF of 46 | QIF -> outputQIF 47 | Ledger -> outputLedger 48 | CSV -> outputCSV 49 | output_method options account transactions' 50 | 51 | readBinaryFile :: FilePath -> IO String 52 | readBinaryFile fp = withBinaryFile fp ReadMode $ \h -> do 53 | res <- hGetContents h 54 | length res `seq` return res 55 | -------------------------------------------------------------------------------- /halifax-import.cabal: -------------------------------------------------------------------------------- 1 | Name: halifax-import 2 | Version: 0.1 3 | Cabal-Version: >= 1.2 4 | Category: Finance 5 | Synopsis: Halifax statement conversion into QIF and Ledger formats 6 | Description: Recover your data from uncooperative banks by parsing out your transaction information. 7 | License: BSD3 8 | License-File: LICENSE 9 | Extra-Source-Files: README.textile 10 | Author: Max Bolingbroke 11 | Maintainer: batterseapower@hotmail.com 12 | Homepage: http://github.com/batterseapower/halifax-import 13 | Build-Type: Simple 14 | 15 | Data-Dir: test-data 16 | Data-Files: 17 | Rules.rules 18 | Statement-Page-1.html 19 | Statement-Page-2.html 20 | 21 | Flag Tests 22 | Description: Enable building the tests 23 | Default: False 24 | 25 | Flag SplitBase 26 | Description: Choose the new smaller, split-up base package 27 | Default: True 28 | 29 | 30 | Executable halifax-import 31 | Main-Is: Finance/Halifax/Main.hs 32 | 33 | Build-Depends: time >= 1.1, old-locale >= 1.0, tagsoup >= 0.6, 34 | regex-posix >= 0.72 35 | if flag(splitBase) 36 | Build-Depends: base >= 3, containers >= 0.1.0.1 37 | else 38 | Build-Depends: base < 3 39 | 40 | Extensions: PatternGuards, PatternSignatures 41 | Ghc-Options: -Wall 42 | 43 | Executable halifax-import-tests 44 | Main-Is: Finance/Halifax/Tests.hs 45 | 46 | Build-Depends: time >= 1.1, old-locale >= 1.0, tagsoup >= 0.6, 47 | regex-posix >= 0.72 48 | if flag(splitBase) 49 | Build-Depends: base >= 3, containers >= 0.1.0.1 50 | else 51 | Build-Depends: base < 3 52 | 53 | Extensions: PatternGuards, PatternSignatures 54 | Ghc-Options: -Wall 55 | 56 | if !flag(tests) 57 | Buildable: False 58 | else 59 | Build-Depends: test-framework >= 0.1.1, test-framework-hunit >= 0.1.1, HUnit >= 1.2 60 | 61 | -------------------------------------------------------------------------------- /Finance/Halifax/StatementParser.hs: -------------------------------------------------------------------------------- 1 | module Finance.Halifax.StatementParser (Transaction(..), parseStatement) where 2 | 3 | import Data.Char 4 | import Data.List 5 | import Data.Maybe 6 | import Data.Time 7 | 8 | import System.Locale 9 | 10 | import Text.HTML.TagSoup 11 | 12 | import Finance.Halifax.Core 13 | import Finance.Halifax.Utilities 14 | 15 | parseStatement :: [String] -> (Account, [Transaction]) 16 | parseStatement pages = (parseAccountInfo account_info, transactions) 17 | where 18 | -- Halifax seems to include stray non-ASCII characters in the files, for some reason (these are the ones that mean we have to read in binary mode). 19 | tagss = map (parseTags . map (\c -> if isAscii c then c else ' ')) pages 20 | account_info = fst $ fragment (~== "