hledger/Utils.hs

61 lines
2.3 KiB
Haskell
Raw Normal View History

2008-10-10 14:04:26 +04:00
{-|
2008-10-12 13:17:21 +04:00
Utilities for top-level modules and/or ghci. See also "Ledger.Utils".
2008-10-10 14:04:26 +04:00
-}
module Utils
where
2008-12-08 04:49:31 +03:00
import Control.Monad.Error
2008-10-10 14:04:26 +04:00
import qualified Data.Map as Map (lookup)
import Data.Time.Clock
2008-11-22 23:22:59 +03:00
import Text.ParserCombinators.Parsec
2008-11-29 23:00:21 +03:00
import System.IO
2008-10-10 14:04:26 +04:00
import Options
import Ledger
2008-11-29 23:00:21 +03:00
-- | Convert a RawLedger to a canonicalised, cached and filtered Ledger
-- based on the command-line options/arguments and the current date/time.
prepareLedger :: [Opt] -> [String] -> LocalTime -> String -> RawLedger -> Ledger
prepareLedger opts args reftime rawtext rl = l{rawledgertext=rawtext}
2008-11-29 23:00:21 +03:00
where
l = cacheLedger apats $ filterRawLedger span dpats c r $ canonicaliseAmounts cb rl
2008-11-29 23:00:21 +03:00
(apats,dpats) = parseAccountDescriptionArgs [] args
span = dateSpanFromOpts (localDay reftime) opts
2008-11-29 23:00:21 +03:00
r = Real `elem` opts
cb = CostBasis `elem` opts
2009-04-03 15:45:56 +04:00
c = clearedValueFromOpts opts
where clearedValueFromOpts opts | null os = Nothing
| last os == Cleared = Just True
| otherwise = Just False
where os = optsWithConstructors [Cleared,UnCleared] opts
2008-11-29 23:00:21 +03:00
2008-11-22 23:22:59 +03:00
-- | Get a RawLedger from the given string, or raise an error.
-- This uses the current local time as the reference time (for closing
-- open timelog entries).
2008-12-08 04:49:31 +03:00
rawledgerfromstring :: String -> IO RawLedger
rawledgerfromstring s = do
t <- getCurrentLocalTime
liftM (either error id) $ runErrorT $ parseLedger t "(string)" s
2008-11-22 23:22:59 +03:00
2008-12-05 11:51:14 +03:00
-- | Get a Ledger from the given string and options, or raise an error.
ledgerfromstringwithopts :: [Opt] -> [String] -> LocalTime -> String -> IO Ledger
ledgerfromstringwithopts opts args reftime s =
liftM (prepareLedger opts args reftime s) $ rawledgerfromstring s
2008-10-10 14:04:26 +04:00
2008-12-05 11:51:14 +03:00
-- | Get a Ledger from the given file path and options, or raise an error.
ledgerfromfilewithopts :: [Opt] -> [String] -> FilePath -> IO Ledger
ledgerfromfilewithopts opts args f = do
s <- readFile f
rl <- rawledgerfromstring s
reftime <- getCurrentLocalTime
return $ prepareLedger opts args reftime s rl
2008-12-05 11:51:14 +03:00
-- | Get a Ledger from your default ledger file, or raise an error.
-- Assumes no options.
2008-10-10 14:04:26 +04:00
myledger :: IO Ledger
2008-12-05 11:51:14 +03:00
myledger = ledgerFilePathFromOpts [] >>= ledgerfromfilewithopts [] []
2008-12-08 04:49:31 +03:00
parseWithCtx :: GenParser Char LedgerFileCtx a -> String -> Either ParseError a
parseWithCtx p ts = runParser p emptyCtx "" ts