top-level Utils module

This commit is contained in:
Simon Michael 2008-10-10 10:04:26 +00:00
parent 37e75d610e
commit 220417ce48
2 changed files with 60 additions and 42 deletions

59
Utils.hs Normal file
View File

@ -0,0 +1,59 @@
{-|
Utilities for top-level modules. See also "Ledger.Utils".
There are some helpers here for working with your ledger in ghci. Examples:
> $ rm -f *.o Ledger/*.o
> $ ghci hledger.hs
> *Main> l <- myledger
> Ledger with 696 entries, 132 accounts:
> ...
> *Main> printbalance [] [] l
> ...
> *Main> printregister [] [] l
> ...
> *Main> accounts l
> ...
> *Main> myaccount "expenses:food:groceries"
> Account expenses:food:groceries with 60 transactions
-}
module Utils
where
import qualified Data.Map as Map (lookup)
import Options
import Ledger
-- | get a RawLedger from the given file path
rawledgerfromfile :: FilePath -> IO RawLedger
rawledgerfromfile f = do
parsed <- parseLedgerFile f
return $ either (\_ -> RawLedger [] [] [] "") id parsed
-- | get a cached Ledger from the given file path
ledgerfromfile :: FilePath -> IO Ledger
ledgerfromfile f = do
l <- rawledgerfromfile f
return $ cacheLedger wildcard $ filterRawLedgerEntries "" "" wildcard l
-- | get a RawLedger from the file your LEDGER environment variable
-- variable points to or (WARNING) an empty one if there was a problem.
myrawledger :: IO RawLedger
myrawledger = do
parsed <- ledgerFilePathFromOpts [] >>= parseLedgerFile
return $ either (\_ -> RawLedger [] [] [] "") id parsed
-- | get a cached Ledger from the file your LEDGER environment variable
-- variable points to or (WARNING) an empty one if there was a problem.
myledger :: IO Ledger
myledger = do
l <- myrawledger
return $ cacheLedger wildcard $ filterRawLedgerEntries "" "" wildcard l
-- | get a named account from your ledger file
myaccount :: AccountName -> IO Account
myaccount a = myledger >>= (return . fromMaybe nullacct . Map.lookup a . accounts)

View File

@ -22,6 +22,7 @@ import BalanceCommand
import PrintCommand
import RegisterCommand
import Tests
import Utils
main :: IO ()
@ -51,45 +52,3 @@ parseLedgerAndDo opts args cmd =
descpat = regexFor descpats
(acctpats,descpats) = parseAccountDescriptionArgs args
-- | get a RawLedger from the file your LEDGER environment
-- variable points to or (WARNING) an empty one if there was a problem.
myrawledger :: IO RawLedger
myrawledger = do
parsed <- ledgerFilePathFromOpts [] >>= parseLedgerFile
return $ either (\_ -> RawLedger [] [] [] "") id parsed
-- | as above, and convert it to a cached Ledger
myledger :: IO Ledger
myledger = do
l <- myrawledger
return $ cacheLedger wildcard $ filterRawLedgerEntries "" "" wildcard l
-- | get a Ledger from the given file path
rawledgerfromfile :: String -> IO RawLedger
rawledgerfromfile f = do
parsed <- ledgerFilePathFromOpts [File f] >>= parseLedgerFile
return $ either (\_ -> RawLedger [] [] [] "") id parsed
-- | get a named account from your ledger file
{-|
The above are helpers for working with your ledger in ghci. Examples:
> $ rm -f hledger.o
> $ ghci hledger.hs
> *Main> l <- myledger
> Ledger with 696 entries, 132 accounts
> *Main> putStr $ drawTree $ treemap show $ accountnametree l
> ...
> *Main> putStr $ showLedgerAccountBalances l 1
> ...
> *Main> printregister l
> ...
> *Main> accounts l
> ...
> *Main> accountnamed "expenses:food:groceries"
> Account expenses:food:groceries with 60 transactions
-}
accountnamed :: AccountName -> IO Account
accountnamed a = myledger >>= (return . fromMaybe nullacct . Map.lookup a . accounts)