refactor: renames and cleanups

This commit is contained in:
Simon Michael 2010-05-22 22:05:12 +00:00
parent a3e5e7ce93
commit 11d354d426
5 changed files with 20 additions and 20 deletions

View File

@ -26,8 +26,8 @@ import System.Time (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/unfiltered ledger, so the
-- command should do further processing if needed.
-- The command will receive an uncached/unfiltered ledger, so should
-- process it further if needed.
withLedgerDo :: [Opt] -> [String] -> String -> ([Opt] -> [String] -> UncachedLedger -> IO ()) -> IO ()
withLedgerDo opts args cmdname cmd = do
-- We kludgily read the file before parsing to grab the full text, unless
@ -44,7 +44,7 @@ withLedgerDo opts args cmdname cmd = do
let runcmd = cmd opts args . makeUncachedLedger cb f tc txt
if creating
then runcmd nulljournal
else (runErrorT . parseLedgerFile t) f >>= either parseerror runcmd
else (runErrorT . parseJournalFile t) f >>= either parseerror runcmd
where parseerror e = hPutStrLn stderr e >> exitWith (ExitFailure 1)
-- | Get an uncached ledger from the given string and options, or raise an error.

View File

@ -7,7 +7,7 @@ module Hledger.Data.IO
where
import Control.Monad.Error
import Hledger.Data.Ledger (makeUncachedLedger)
import Hledger.Data.Parse (parseLedger)
import Hledger.Data.Parse (parseJournal)
import Hledger.Data.Types (FilterSpec(..),WhichDate(..),Journal(..),Ledger(..))
import Hledger.Data.Utils (getCurrentLocalTime)
import Hledger.Data.Dates (nulldatespan)
@ -84,7 +84,7 @@ readLedger f = do
journalFromString :: String -> IO Journal
journalFromString s = do
t <- getCurrentLocalTime
liftM (either error id) $ runErrorT $ parseLedger t "(string)" s
liftM (either error id) $ runErrorT $ parseJournal t "(string)" s
-- -- | Expand ~ in a file path (does not handle ~name).
-- tildeExpand :: FilePath -> IO FilePath

View File

@ -273,10 +273,10 @@ matchpats pats str =
-- | Calculate the account tree and account balances from a journal's
-- postings, and return the results for efficient lookup.
crunchJournal :: Journal -> (Tree AccountName, Map.Map AccountName Account)
crunchJournal j = (ant,amap)
journalAccountInfo :: Journal -> (Tree AccountName, Map.Map AccountName Account)
journalAccountInfo j = (ant, amap)
where
(ant,psof,_,inclbalof) = (groupPostings . journalPostings) j
(ant, psof, _, inclbalof) = (groupPostings . journalPostings) j
amap = Map.fromList [(a, acctinfo a) | a <- flatten ant]
acctinfo a = Account a (psof a) (inclbalof a)
@ -288,7 +288,7 @@ groupPostings :: [Posting] -> (Tree AccountName,
(AccountName -> [Posting]),
(AccountName -> MixedAmount),
(AccountName -> MixedAmount))
groupPostings ps = (ant,psof,exclbalof,inclbalof)
groupPostings ps = (ant, psof, exclbalof, inclbalof)
where
anames = sort $ nub $ map paccount ps
ant = accountNameTreeFrom $ expandAccountNames anames

View File

@ -84,11 +84,11 @@ makeUncachedLedger :: Bool -> FilePath -> ClockTime -> String -> Journal -> Unca
makeUncachedLedger costbasis f t s j =
nullledger{journal=canonicaliseAmounts costbasis j{filepath=f,filereadtime=t,jtext=s}}
-- | Filter a ledger's transactions according to the filter specification and generate derived data.
-- | Filter a ledger's transactions as specified and generate derived data.
filterAndCacheLedger :: FilterSpec -> UncachedLedger -> Ledger
filterAndCacheLedger filterspec l@Ledger{journal=j} = l{journal=j',accountnametree=ant,accountmap=amap}
where (ant, amap) = crunchJournal j'
j' = filterJournalPostings filterspec{depth=Nothing} j
filterAndCacheLedger filterspec l@Ledger{journal=j} = l{journal=j',accountnametree=t,accountmap=m}
where j' = filterJournalPostings filterspec{depth=Nothing} j
(t, m) = journalAccountInfo j'
-- | List a ledger's account names.
ledgerAccountNames :: Ledger -> [AccountName]

View File

@ -208,14 +208,14 @@ expandPath pos fp = liftM mkRelative (expandHome fp)
-- | Parses a ledger file or timelog file to a "Journal", or gives an
-- error. Requires the current (local) time to calculate any unfinished
-- timelog sessions, we pass it in for repeatability.
parseLedgerFile :: LocalTime -> FilePath -> ErrorT String IO Journal
parseLedgerFile t "-" = liftIO getContents >>= parseLedger t "-"
parseLedgerFile t f = liftIO (readFile f) >>= parseLedger t f
parseJournalFile :: LocalTime -> FilePath -> ErrorT String IO Journal
parseJournalFile t "-" = liftIO getContents >>= parseJournal t "-"
parseJournalFile t f = liftIO (readFile f) >>= parseJournal t f
-- | Like parseLedgerFile, but parses a string. A file path is still
-- | Like parseJournalFile, but parses a string. A file path is still
-- provided to save in the resulting journal.
parseLedger :: LocalTime -> FilePath -> String -> ErrorT String IO Journal
parseLedger reftime inname intxt =
parseJournal :: LocalTime -> FilePath -> String -> ErrorT String IO Journal
parseJournal reftime inname intxt =
case runParser ledgerFile emptyCtx inname intxt of
Right m -> liftM (journalConvertTimeLog reftime) $ m `ap` return nulljournal
Left err -> throwError $ show err -- XXX raises an uncaught exception if we have a parsec user error, eg from many ?
@ -562,7 +562,7 @@ priceamount =
many spacenonewline
char '@'
many spacenonewline
a <- someamount
a <- someamount -- XXX could parse more prices ad infinitum, shouldn't
return $ Just a
) <|> return Nothing