more ledger parsing utilities, haddock

This commit is contained in:
Simon Michael 2008-11-22 20:22:59 +00:00
parent 4c97ca5514
commit 1312992000

View File

@ -7,17 +7,31 @@ Utilities for top-level modules and/or ghci. See also "Ledger.Utils".
module Utils module Utils
where where
import qualified Data.Map as Map (lookup) import qualified Data.Map as Map (lookup)
import Text.ParserCombinators.Parsec
import Options import Options
import Ledger import Ledger
-- | get a RawLedger from the given file path -- | Get a RawLedger from the given string, or raise an error.
rawledgerfromstring :: String -> RawLedger
rawledgerfromstring = fromparse . parsewith ledgerfile
-- | Get a filtered and cached Ledger from the given string, or raise an error.
ledgerfromstring :: [String] -> String -> Ledger
ledgerfromstring args s =
cacheLedger apats $ filterRawLedger Nothing Nothing dpats False False l
where
(apats,dpats) = parseAccountDescriptionArgs args
l = rawledgerfromstring s
-- | Get a RawLedger from the given file path, or a dummy one if there was an error.
rawledgerfromfile :: FilePath -> IO RawLedger rawledgerfromfile :: FilePath -> IO RawLedger
rawledgerfromfile f = do rawledgerfromfile f = do
parsed <- parseLedgerFile f parsed <- parseLedgerFile f
return $ either (\_ -> RawLedger [] [] [] "") id parsed return $ either (\_ -> RawLedger [] [] [] "") id parsed
-- | get a cached Ledger from the given file path, filtered by the patterns. -- | Get a filtered and cached Ledger from the given file path, or a dummy
-- one if there was an error.
ledgerfromfile :: [String] -> FilePath -> IO Ledger ledgerfromfile :: [String] -> FilePath -> IO Ledger
ledgerfromfile args f = do ledgerfromfile args f = do
l <- rawledgerfromfile f l <- rawledgerfromfile f
@ -25,21 +39,21 @@ ledgerfromfile args f = do
where where
(apats,dpats) = parseAccountDescriptionArgs args (apats,dpats) = parseAccountDescriptionArgs args
-- | get a RawLedger from the file your LEDGER environment variable -- | Get a RawLedger from the file your LEDGER environment variable
-- variable points to or (WARNING) an empty one if there was a problem. -- variable points to, or a dummy one if there was a problem.
myrawledger :: IO RawLedger myrawledger :: IO RawLedger
myrawledger = do myrawledger = do
parsed <- ledgerFilePathFromOpts [] >>= parseLedgerFile parsed <- ledgerFilePathFromOpts [] >>= parseLedgerFile
return $ either (\_ -> RawLedger [] [] [] "") id parsed return $ either (\_ -> RawLedger [] [] [] "") id parsed
-- | get a cached Ledger from the file your LEDGER environment variable -- | Get a cached Ledger from the file your LEDGER environment variable
-- variable points to or (WARNING) an empty one if there was a problem. -- variable points to, or a dummy one if there was a problem.
myledger :: IO Ledger myledger :: IO Ledger
myledger = do myledger = do
l <- myrawledger l <- myrawledger
return $ cacheLedger [] $ filterRawLedger Nothing Nothing [] False False l return $ cacheLedger [] $ filterRawLedger Nothing Nothing [] False False l
-- | get a named account from your ledger file -- | Get a named account from your ledger file.
myaccount :: AccountName -> IO Account myaccount :: AccountName -> IO Account
myaccount a = myledger >>= (return . fromMaybe nullacct . Map.lookup a . accountmap) myaccount a = myledger >>= (return . fromMaybe nullacct . Map.lookup a . accountmap)