fix an unsafe ! in ledgerAccount; clarify that withLedgerDo does not cache the ledger

This commit is contained in:
Simon Michael 2010-02-04 20:55:12 +00:00
parent d449a64814
commit 357b27fb63
2 changed files with 8 additions and 4 deletions

View File

@ -54,10 +54,10 @@ aliases for easier interaction. Here's an example:
module Ledger.Ledger
where
import qualified Data.Map as Map
import Data.Map ((!), fromList)
import Data.Map (findWithDefault, fromList)
import Ledger.Utils
import Ledger.Types
import Ledger.Account ()
import Ledger.Account (nullacct)
import Ledger.AccountName
import Ledger.Journal
import Ledger.Posting
@ -100,9 +100,11 @@ type CachedLedger = Ledger
ledgerAccountNames :: Ledger -> [AccountName]
ledgerAccountNames = drop 1 . flatten . accountnametree
-- | Get the named account from a ledger.
-- | Get the named account from a (cached) ledger.
-- If the ledger has not been cached (with crunchJournal or
-- cacheLedger'), this returns the null account.
ledgerAccount :: Ledger -> AccountName -> Account
ledgerAccount = (!) . accountmap
ledgerAccount l a = findWithDefault nullacct a $ accountmap l
-- | List a ledger's accounts, in tree order
ledgerAccounts :: Ledger -> [Account]

View File

@ -21,6 +21,8 @@ import System.Time (ClockTime,getClockTime)
-- | Parse the user's specified ledger file and run a hledger command on
-- it, or report a parse error. This function makes the whole thing go.
-- Warning, this provides only an uncached Ledger (no accountnametree or
-- accountmap), so cmd must cacheLedger'/crunchJournal if needed.
withLedgerDo :: [Opt] -> [String] -> String -> ([Opt] -> [String] -> Ledger -> IO ()) -> IO ()
withLedgerDo opts args cmdname cmd = do
-- We kludgily read the file before parsing to grab the full text, unless