make prepareLedger use current time, not just date

This commit is contained in:
Simon Michael 2009-01-24 18:48:28 +00:00
parent b218647631
commit b0178b88cc
3 changed files with 16 additions and 14 deletions

View File

@ -458,7 +458,7 @@ balancecommand_tests = TestList [
(showBalanceReport [] [] l) (showBalanceReport [] [] l)
, ,
"balance report elides zero-balance root account(s)" ~: do "balance report elides zero-balance root account(s)" ~: do
l <- ledgerfromstringwithopts [] [] refdate l <- ledgerfromstringwithopts [] [] reftime
("2008/1/1 one\n" ++ ("2008/1/1 one\n" ++
" test:a 1\n" ++ " test:a 1\n" ++
" test:b\n" " test:b\n"
@ -564,8 +564,9 @@ registercommand_tests = TestList [
-- test data -- test data
refdate = parsedate "2008/11/26" refdate = parsedate "2008/11/26"
sampleledger = ledgerfromstringwithopts [] [] refdate sample_ledger_str reftime = dayToUTC refdate
sampleledgerwithopts opts args = ledgerfromstringwithopts opts args refdate sample_ledger_str sampleledger = ledgerfromstringwithopts [] [] reftime sample_ledger_str
sampleledgerwithopts opts args = ledgerfromstringwithopts opts args reftime sample_ledger_str
--sampleledgerwithoptsanddate opts args date = unsafePerformIO $ ledgerfromstringwithopts opts args date sample_ledger_str --sampleledgerwithoptsanddate opts args date = unsafePerformIO $ ledgerfromstringwithopts opts args date sample_ledger_str
sample_ledger_str = ( sample_ledger_str = (

View File

@ -8,6 +8,7 @@ module Utils
where where
import Control.Monad.Error import Control.Monad.Error
import qualified Data.Map as Map (lookup) import qualified Data.Map as Map (lookup)
import Data.Time.Clock
import Text.ParserCombinators.Parsec import Text.ParserCombinators.Parsec
import System.IO import System.IO
import Options import Options
@ -15,13 +16,13 @@ import Ledger
-- | Convert a RawLedger to a canonicalised, cached and filtered Ledger -- | Convert a RawLedger to a canonicalised, cached and filtered Ledger
-- based on the command-line options/arguments and today's date. -- based on the command-line options/arguments and the current date/time.
prepareLedger :: [Opt] -> [String] -> Day -> String -> RawLedger -> Ledger prepareLedger :: [Opt] -> [String] -> UTCTime -> String -> RawLedger -> Ledger
prepareLedger opts args refdate rawtext rl = l{rawledgertext=rawtext} prepareLedger opts args reftime rawtext rl = l{rawledgertext=rawtext}
where where
l = cacheLedger apats $ filterRawLedger span dpats c r $ canonicaliseAmounts cb rl l = cacheLedger apats $ filterRawLedger span dpats c r $ canonicaliseAmounts cb rl
(apats,dpats) = parseAccountDescriptionArgs [] args (apats,dpats) = parseAccountDescriptionArgs [] args
span = dateSpanFromOpts refdate opts span = dateSpanFromOpts (utctDay reftime) opts
c = Cleared `elem` opts c = Cleared `elem` opts
r = Real `elem` opts r = Real `elem` opts
cb = CostBasis `elem` opts cb = CostBasis `elem` opts
@ -31,17 +32,17 @@ rawledgerfromstring :: String -> IO RawLedger
rawledgerfromstring = liftM (either error id) . runErrorT . parseLedger "(string)" rawledgerfromstring = liftM (either error id) . runErrorT . parseLedger "(string)"
-- | Get a Ledger from the given string and options, or raise an error. -- | Get a Ledger from the given string and options, or raise an error.
ledgerfromstringwithopts :: [Opt] -> [String] -> Day -> String -> IO Ledger ledgerfromstringwithopts :: [Opt] -> [String] -> UTCTime -> String -> IO Ledger
ledgerfromstringwithopts opts args refdate s = ledgerfromstringwithopts opts args reftime s =
liftM (prepareLedger opts args refdate s) $ rawledgerfromstring s liftM (prepareLedger opts args reftime s) $ rawledgerfromstring s
-- | Get a Ledger from the given file path and options, or raise an error. -- | Get a Ledger from the given file path and options, or raise an error.
ledgerfromfilewithopts :: [Opt] -> [String] -> FilePath -> IO Ledger ledgerfromfilewithopts :: [Opt] -> [String] -> FilePath -> IO Ledger
ledgerfromfilewithopts opts args f = do ledgerfromfilewithopts opts args f = do
refdate <- today
s <- readFile f s <- readFile f
rl <- rawledgerfromstring s rl <- rawledgerfromstring s
return $ prepareLedger opts args refdate s rl reftime <- now
return $ prepareLedger opts args reftime s rl
-- | Get a Ledger from your default ledger file, or raise an error. -- | Get a Ledger from your default ledger file, or raise an error.
-- Assumes no options. -- Assumes no options.

View File

@ -92,11 +92,11 @@ main = do
-- (or report a parse error). This function makes the whole thing go. -- (or report a parse error). This function makes the whole thing go.
parseLedgerAndDo :: [Opt] -> [String] -> ([Opt] -> [String] -> Ledger -> IO ()) -> IO () parseLedgerAndDo :: [Opt] -> [String] -> ([Opt] -> [String] -> Ledger -> IO ()) -> IO ()
parseLedgerAndDo opts args cmd = do parseLedgerAndDo opts args cmd = do
refdate <- today
f <- ledgerFilePathFromOpts opts f <- ledgerFilePathFromOpts opts
-- XXX we read the file twice - inelegant -- XXX we read the file twice - inelegant
-- and, doesn't work with stdin. kludge it, stdin won't work with ui command -- and, doesn't work with stdin. kludge it, stdin won't work with ui command
let f' = if f == "-" then "/dev/null" else f let f' = if f == "-" then "/dev/null" else f
rawtext <- readFile f' rawtext <- readFile f'
let runcmd = cmd opts args . prepareLedger opts args refdate rawtext reftime <- now
let runcmd = cmd opts args . prepareLedger opts args reftime rawtext
return f >>= runErrorT . parseLedgerFile >>= either (hPutStrLn stderr) runcmd return f >>= runErrorT . parseLedgerFile >>= either (hPutStrLn stderr) runcmd