From 30fe7ac225fff064e41eddaadfd80aec48c60d14 Mon Sep 17 00:00:00 2001 From: Simon Michael Date: Sat, 10 Feb 2007 17:36:50 +0000 Subject: [PATCH] cleanup --- Options.hs | 4 +++- Parse.hs | 20 ++++++++++---------- TODO | 12 ++++++------ Tests.hs | 16 +++++----------- Types.hs | 14 ++++++-------- hledger.hs | 33 ++++++++++++++++++++++++++------- 6 files changed, 56 insertions(+), 43 deletions(-) diff --git a/Options.hs b/Options.hs index 10b7b212d..3bdfe19a3 100644 --- a/Options.hs +++ b/Options.hs @@ -1,4 +1,6 @@ -module Options where + +module Options +where import System.Console.GetOpt import Data.Maybe ( fromMaybe ) diff --git a/Parse.hs b/Parse.hs index 1a1b75044..767a92067 100644 --- a/Parse.hs +++ b/Parse.hs @@ -1,3 +1,13 @@ + +module Parse +where + +import Text.ParserCombinators.Parsec +import Text.ParserCombinators.Parsec.Language +import qualified Text.ParserCombinators.Parsec.Token as P + +import Types + {- Here's the ledger 2.5 grammar: "The ledger file format is quite simple, but also very flexible. It supports @@ -98,14 +108,6 @@ i, o, b, h -- parsec example: http://pandoc.googlecode.com/svn/trunk/src/Text/Pandoc/Readers/RST.hs -- sample data in Tests.hs -module Parse where - -import Text.ParserCombinators.Parsec -import Text.ParserCombinators.Parsec.Language -import qualified Text.ParserCombinators.Parsec.Token as P - -import Types - -- set up token parsing, though we're not yet using these much ledgerLanguageDef = LanguageDef { commentStart = "" @@ -241,5 +243,3 @@ printParseResult r = case r of parseError e = do putStr "ledger parse error at "; print e -parseLedgerFile :: IO String -> IO (Either ParseError Ledger) -parseLedgerFile f = f >>= parseFromFile ledger diff --git a/TODO b/TODO index c7bc3c05a..4b9b49e35 100644 --- a/TODO +++ b/TODO @@ -1,11 +1,6 @@ -testing - get quickcheck working - consider hunit dsl - ledger regression/compatibility tests - features balance - show final balance + show top-level acct balance show per-account balances print matching by account/description regexp @@ -18,6 +13,11 @@ features auto entry generation read gnucash files +testing + get quickcheck working + consider hunit dsl + ledger regression/compatibility tests + environment cleaner option processing smart ledger file finding diff --git a/Tests.hs b/Tests.hs index 8c2136c8b..eba1dc987 100644 --- a/Tests.hs +++ b/Tests.hs @@ -1,8 +1,10 @@ -module Tests where -import Text.ParserCombinators.Parsec -import Test.QuickCheck +module Tests +where + import Test.HUnit +import Test.QuickCheck +import Text.ParserCombinators.Parsec import Options import Types @@ -262,11 +264,3 @@ prop1 = 1 == 1 -- (parse' ledgertransaction sample_transaction)) -- how ? --- commands - -test :: IO () -test = do - runTestTT hunittests --- runTestTT hunittests2 --- quickCheck prop1 - return () diff --git a/Types.hs b/Types.hs index 9e3d8060f..183d4ec9f 100644 --- a/Types.hs +++ b/Types.hs @@ -1,5 +1,6 @@ --- a data model -module Types where + +module Types -- data model & methods +where import Text.Printf import List @@ -130,9 +131,6 @@ showRegisterEntries (e:es) b = showEntryWithBalances e b ++ (showRegisterEntries es b') where b' = b + (sumTransactions (transactions e)) -printRegister :: Ledger -> IO () -printRegister l = putStr $ showRegisterEntries (entries l) 0 - -- misc -- fill in missing amounts etc., as far as possible @@ -156,12 +154,12 @@ normalAndAutoTransactions ts = sumTransactions :: [Transaction] -> Amount sumTransactions ts = sum [amount t | t <- ts] - transactionsFrom :: [Entry] -> [Transaction] transactionsFrom es = concat $ map transactions es accountsFrom :: [Transaction] -> [Account] accountsFrom ts = nub $ map account ts -accountList :: Ledger -> [Account] -accountList l = accountsFrom $ transactionsFrom $ entries l +accountsUsed :: Ledger -> [Account] +accountsUsed l = accountsFrom $ transactionsFrom $ entries l + diff --git a/hledger.hs b/hledger.hs index 6041b886c..0957cf6de 100644 --- a/hledger.hs +++ b/hledger.hs @@ -1,10 +1,14 @@ #!/usr/bin/runhaskell --- hledger - ledger-compatible money management utilities (& haskell workout) +-- hledger - ledger-compatible money management utilities (& haskell study) -- GPLv3, (c) Simon Michael & contributors, -- John Wiegley's ledger is at http://newartisans.com/ledger.html . +module Main where + import System (getArgs) import Data.List (isPrefixOf) +import Test.HUnit (runTestTT) +import Text.ParserCombinators.Parsec (parseFromFile, ParseError) import Options import Types @@ -25,17 +29,32 @@ main = do -- commands +test :: IO () +test = do + runTestTT hunittests +-- quickCheck prop1 + return () + register :: [String] -> IO () register args = do p <- parseLedgerFile ledgerFilePath - case p of - Left e -> do putStr "ledger parse error at "; print e - Right l -> printRegister l + case p of Left e -> parseError e + Right l -> printRegister l balance :: [String] -> IO () balance args = do p <- parseLedgerFile ledgerFilePath - case p of - Left e -> do putStr "ledger parse error at "; print e - Right l -> printRegister l + case p of Left e -> parseError e + Right l -> printBalances l + +-- utils + +parseLedgerFile :: IO String -> IO (Either ParseError Ledger) +parseLedgerFile f = f >>= parseFromFile ledger + +printRegister :: Ledger -> IO () +printRegister l = putStr $ showRegisterEntries (entries l) 0 + +printBalances :: Ledger -> IO () +printBalances l = putStr $ showRegisterEntries (entries l) 0