2015-08-28 21:17:49 +03:00
|
|
|
{-# LANGUAGE CPP, RecordWildCards, DeriveDataTypeable #-}
|
2014-03-20 04:11:48 +04:00
|
|
|
{-|
|
|
|
|
|
2014-03-26 04:10:30 +04:00
|
|
|
Options common to most hledger reports.
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Hledger.Reports.ReportOptions (
|
|
|
|
ReportOpts(..),
|
|
|
|
BalanceType(..),
|
2014-12-05 23:56:33 +03:00
|
|
|
AccountListMode(..),
|
2014-03-20 04:11:48 +04:00
|
|
|
FormatStr,
|
|
|
|
defreportopts,
|
2014-03-26 04:10:30 +04:00
|
|
|
rawOptsToReportOpts,
|
2015-08-28 19:57:01 +03:00
|
|
|
checkReportOpts,
|
2014-12-05 23:56:33 +03:00
|
|
|
flat_,
|
|
|
|
tree_,
|
2014-03-20 04:11:48 +04:00
|
|
|
whichDateFromOpts,
|
|
|
|
journalSelectingAmountFromOpts,
|
|
|
|
queryFromOpts,
|
|
|
|
queryFromOptsOnly,
|
|
|
|
queryOptsFromOpts,
|
|
|
|
transactionDateFn,
|
|
|
|
postingDateFn,
|
2016-12-30 22:44:01 +03:00
|
|
|
reportStartDate,
|
|
|
|
reportEndDate,
|
|
|
|
reportStartEndDates,
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
tests_Hledger_Reports_ReportOptions
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
2014-03-26 04:10:30 +04:00
|
|
|
import Data.Data (Data)
|
2015-08-28 21:17:49 +03:00
|
|
|
#if !MIN_VERSION_base(4,8,0)
|
|
|
|
import Data.Functor.Compat ((<$>))
|
|
|
|
#endif
|
2016-07-30 05:19:44 +03:00
|
|
|
import Data.Maybe
|
2016-07-29 18:57:10 +03:00
|
|
|
import qualified Data.Text as T
|
2014-03-26 04:10:30 +04:00
|
|
|
import Data.Typeable (Typeable)
|
2014-03-20 04:11:48 +04:00
|
|
|
import Data.Time.Calendar
|
2016-07-29 20:15:48 +03:00
|
|
|
import Data.Default
|
2016-07-30 05:19:44 +03:00
|
|
|
import Safe
|
2014-03-20 04:11:48 +04:00
|
|
|
import Test.HUnit
|
2017-01-14 00:10:11 +03:00
|
|
|
import Text.Megaparsec.Error
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
import Hledger.Data
|
|
|
|
import Hledger.Query
|
|
|
|
import Hledger.Utils
|
|
|
|
|
|
|
|
|
2014-03-26 04:10:30 +04:00
|
|
|
type FormatStr = String
|
|
|
|
|
2016-08-12 19:44:31 +03:00
|
|
|
-- | Which "balance" is being shown in a balance report.
|
|
|
|
data BalanceType = PeriodChange -- ^ The change of balance in each period.
|
|
|
|
| CumulativeChange -- ^ The accumulated change across multiple periods.
|
|
|
|
| HistoricalBalance -- ^ The historical ending balance, including the effect of
|
|
|
|
-- all postings before the report period. Unless altered by,
|
|
|
|
-- a query, this is what you would see on a bank statement.
|
2014-03-26 04:10:30 +04:00
|
|
|
deriving (Eq,Show,Data,Typeable)
|
|
|
|
|
2016-08-12 19:44:31 +03:00
|
|
|
instance Default BalanceType where def = PeriodChange
|
2014-03-26 04:10:30 +04:00
|
|
|
|
2014-12-05 23:56:33 +03:00
|
|
|
-- | Should accounts be displayed: in the command's default style, hierarchically, or as a flat list ?
|
|
|
|
data AccountListMode = ALDefault | ALTree | ALFlat deriving (Eq, Show, Data, Typeable)
|
|
|
|
|
|
|
|
instance Default AccountListMode where def = ALDefault
|
|
|
|
|
2014-03-20 04:11:48 +04:00
|
|
|
-- | Standard options for customising report filtering and output,
|
|
|
|
-- corresponding to hledger's command-line options and query language
|
|
|
|
-- arguments. Used in hledger-lib and above.
|
|
|
|
data ReportOpts = ReportOpts {
|
2016-07-30 05:19:44 +03:00
|
|
|
period_ :: Period
|
|
|
|
,interval_ :: Interval
|
|
|
|
,clearedstatus_ :: Maybe ClearedStatus
|
2014-03-20 04:11:48 +04:00
|
|
|
,cost_ :: Bool
|
|
|
|
,depth_ :: Maybe Int
|
|
|
|
,display_ :: Maybe DisplayExp
|
|
|
|
,date2_ :: Bool
|
|
|
|
,empty_ :: Bool
|
|
|
|
,no_elide_ :: Bool
|
|
|
|
,real_ :: Bool
|
|
|
|
,format_ :: Maybe FormatStr
|
|
|
|
,query_ :: String -- all arguments, as a string
|
2016-07-30 05:19:44 +03:00
|
|
|
-- register only
|
2014-03-26 04:10:30 +04:00
|
|
|
,average_ :: Bool
|
|
|
|
,related_ :: Bool
|
2016-07-30 05:19:44 +03:00
|
|
|
-- balance only
|
2014-03-26 04:10:30 +04:00
|
|
|
,balancetype_ :: BalanceType
|
2016-07-30 05:19:44 +03:00
|
|
|
,accountlistmode_ :: AccountListMode
|
2014-03-26 04:10:30 +04:00
|
|
|
,drop_ :: Int
|
2014-12-28 02:16:36 +03:00
|
|
|
,row_total_ :: Bool
|
2014-03-26 04:10:30 +04:00
|
|
|
,no_total_ :: Bool
|
2015-08-10 01:15:01 +03:00
|
|
|
,value_ :: Bool
|
2014-03-20 04:11:48 +04:00
|
|
|
} deriving (Show, Data, Typeable)
|
|
|
|
|
2014-03-26 04:10:30 +04:00
|
|
|
instance Default ReportOpts where def = defreportopts
|
2016-07-29 20:15:48 +03:00
|
|
|
instance Default Bool where def = False
|
2014-03-20 04:11:48 +04:00
|
|
|
|
2014-03-26 04:10:30 +04:00
|
|
|
defreportopts :: ReportOpts
|
2014-03-20 04:11:48 +04:00
|
|
|
defreportopts = ReportOpts
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
def
|
|
|
|
|
2014-03-26 04:10:30 +04:00
|
|
|
rawOptsToReportOpts :: RawOpts -> IO ReportOpts
|
2015-08-28 19:57:01 +03:00
|
|
|
rawOptsToReportOpts rawopts = checkReportOpts <$> do
|
2014-03-26 04:10:30 +04:00
|
|
|
d <- getCurrentDay
|
2016-08-12 19:44:31 +03:00
|
|
|
let rawopts' = checkRawOpts rawopts
|
2014-03-26 04:10:30 +04:00
|
|
|
return defreportopts{
|
2016-08-12 19:44:31 +03:00
|
|
|
period_ = periodFromRawOpts d rawopts'
|
|
|
|
,interval_ = intervalFromRawOpts rawopts'
|
|
|
|
,clearedstatus_ = clearedStatusFromRawOpts rawopts'
|
|
|
|
,cost_ = boolopt "cost" rawopts'
|
|
|
|
,depth_ = maybeintopt "depth" rawopts'
|
|
|
|
,display_ = maybedisplayopt d rawopts'
|
|
|
|
,date2_ = boolopt "date2" rawopts'
|
|
|
|
,empty_ = boolopt "empty" rawopts'
|
|
|
|
,no_elide_ = boolopt "no-elide" rawopts'
|
|
|
|
,real_ = boolopt "real" rawopts'
|
|
|
|
,format_ = maybestringopt "format" rawopts' -- XXX move to CliOpts or move validation from Cli.CliOptions to here
|
|
|
|
,query_ = unwords $ listofstringopt "args" rawopts' -- doesn't handle an arg like "" right
|
|
|
|
,average_ = boolopt "average" rawopts'
|
|
|
|
,related_ = boolopt "related" rawopts'
|
|
|
|
,balancetype_ = balancetypeopt rawopts'
|
|
|
|
,accountlistmode_ = accountlistmodeopt rawopts'
|
|
|
|
,drop_ = intopt "drop" rawopts'
|
|
|
|
,row_total_ = boolopt "row-total" rawopts'
|
|
|
|
,no_total_ = boolopt "no-total" rawopts'
|
|
|
|
,value_ = boolopt "value" rawopts'
|
2014-03-26 04:10:30 +04:00
|
|
|
}
|
|
|
|
|
2016-08-12 19:44:31 +03:00
|
|
|
-- | Do extra validation of raw option values, raising an error if there's a problem.
|
|
|
|
checkRawOpts :: RawOpts -> RawOpts
|
|
|
|
checkRawOpts rawopts
|
|
|
|
-- our standard behaviour is to accept conflicting options actually,
|
|
|
|
-- using the last one - more forgiving for overriding command-line aliases
|
|
|
|
-- | countopts ["change","cumulative","historical"] > 1
|
2017-03-29 18:00:30 +03:00
|
|
|
-- = usageError "please specify at most one of --change, --cumulative, --historical"
|
2016-08-12 19:44:31 +03:00
|
|
|
-- | countopts ["flat","tree"] > 1
|
2017-03-29 18:00:30 +03:00
|
|
|
-- = usageError "please specify at most one of --flat, --tree"
|
2016-08-12 19:44:31 +03:00
|
|
|
-- | countopts ["daily","weekly","monthly","quarterly","yearly"] > 1
|
2017-03-29 18:00:30 +03:00
|
|
|
-- = usageError "please specify at most one of --daily, "
|
2016-08-12 19:44:31 +03:00
|
|
|
| otherwise = rawopts
|
|
|
|
-- where
|
|
|
|
-- countopts = length . filter (`boolopt` rawopts)
|
|
|
|
|
|
|
|
-- | Do extra validation of report options, raising an error if there's a problem.
|
2015-08-28 19:57:01 +03:00
|
|
|
checkReportOpts :: ReportOpts -> ReportOpts
|
|
|
|
checkReportOpts ropts@ReportOpts{..} =
|
2017-03-29 18:00:30 +03:00
|
|
|
either usageError (const ropts) $ do
|
2015-08-28 19:57:30 +03:00
|
|
|
case depth_ of
|
|
|
|
Just d | d < 0 -> Left "--depth should have a positive number"
|
|
|
|
_ -> Right ()
|
2015-08-28 19:57:01 +03:00
|
|
|
|
2014-12-05 23:56:33 +03:00
|
|
|
accountlistmodeopt :: RawOpts -> AccountListMode
|
|
|
|
accountlistmodeopt rawopts =
|
|
|
|
case reverse $ filter (`elem` ["tree","flat"]) $ map fst rawopts of
|
|
|
|
("tree":_) -> ALTree
|
|
|
|
("flat":_) -> ALFlat
|
|
|
|
_ -> ALDefault
|
|
|
|
|
2014-03-26 04:10:30 +04:00
|
|
|
balancetypeopt :: RawOpts -> BalanceType
|
2016-08-12 19:44:31 +03:00
|
|
|
balancetypeopt rawopts =
|
|
|
|
case reverse $ filter (`elem` ["change","cumulative","historical"]) $ map fst rawopts of
|
|
|
|
("historical":_) -> HistoricalBalance
|
|
|
|
("cumulative":_) -> CumulativeChange
|
|
|
|
_ -> PeriodChange
|
2014-03-26 04:10:30 +04:00
|
|
|
|
2016-07-30 05:19:44 +03:00
|
|
|
-- Get the period specified by the intersection of -b/--begin, -e/--end and/or
|
|
|
|
-- -p/--period options, using the given date to interpret relative date expressions.
|
|
|
|
periodFromRawOpts :: Day -> RawOpts -> Period
|
|
|
|
periodFromRawOpts d rawopts =
|
|
|
|
case (mearliestb, mlateste) of
|
|
|
|
(Nothing, Nothing) -> PeriodAll
|
|
|
|
(Just b, Nothing) -> PeriodFrom b
|
|
|
|
(Nothing, Just e) -> PeriodTo e
|
|
|
|
(Just b, Just e) -> simplifyPeriod $
|
|
|
|
PeriodBetween b e
|
|
|
|
where
|
|
|
|
mearliestb = case beginDatesFromRawOpts d rawopts of
|
|
|
|
[] -> Nothing
|
|
|
|
bs -> Just $ minimum bs
|
|
|
|
mlateste = case endDatesFromRawOpts d rawopts of
|
|
|
|
[] -> Nothing
|
|
|
|
es -> Just $ maximum es
|
|
|
|
|
|
|
|
-- Get all begin dates specified by -b/--begin or -p/--period options, in order,
|
|
|
|
-- using the given date to interpret relative date expressions.
|
|
|
|
beginDatesFromRawOpts :: Day -> RawOpts -> [Day]
|
|
|
|
beginDatesFromRawOpts d = catMaybes . map (begindatefromrawopt d)
|
|
|
|
where
|
|
|
|
begindatefromrawopt d (n,v)
|
|
|
|
| n == "begin" =
|
2017-03-29 18:00:30 +03:00
|
|
|
either (\e -> usageError $ "could not parse "++n++" date: "++parseErrorPretty e) Just $
|
2016-07-30 05:19:44 +03:00
|
|
|
fixSmartDateStrEither' d (T.pack v)
|
|
|
|
| n == "period" =
|
|
|
|
case
|
2017-03-29 18:00:30 +03:00
|
|
|
either (\e -> usageError $ "could not parse period option: "++parseErrorPretty e) id $
|
2016-07-30 05:19:44 +03:00
|
|
|
parsePeriodExpr d (stripquotes $ T.pack v)
|
|
|
|
of
|
|
|
|
(_, DateSpan (Just b) _) -> Just b
|
|
|
|
_ -> Nothing
|
|
|
|
| otherwise = Nothing
|
|
|
|
|
|
|
|
-- Get all end dates specified by -e/--end or -p/--period options, in order,
|
|
|
|
-- using the given date to interpret relative date expressions.
|
|
|
|
endDatesFromRawOpts :: Day -> RawOpts -> [Day]
|
|
|
|
endDatesFromRawOpts d = catMaybes . map (enddatefromrawopt d)
|
|
|
|
where
|
|
|
|
enddatefromrawopt d (n,v)
|
|
|
|
| n == "end" =
|
2017-03-29 18:00:30 +03:00
|
|
|
either (\e -> usageError $ "could not parse "++n++" date: "++parseErrorPretty e) Just $
|
2016-07-30 05:19:44 +03:00
|
|
|
fixSmartDateStrEither' d (T.pack v)
|
|
|
|
| n == "period" =
|
|
|
|
case
|
2017-03-29 18:00:30 +03:00
|
|
|
either (\e -> usageError $ "could not parse period option: "++parseErrorPretty e) id $
|
2016-07-30 05:19:44 +03:00
|
|
|
parsePeriodExpr d (stripquotes $ T.pack v)
|
|
|
|
of
|
|
|
|
(_, DateSpan _ (Just e)) -> Just e
|
|
|
|
_ -> Nothing
|
|
|
|
| otherwise = Nothing
|
|
|
|
|
|
|
|
-- | Get the report interval, if any, specified by the last of -p/--period,
|
|
|
|
-- -D/--daily, -W/--weekly, -M/--monthly etc. options.
|
|
|
|
intervalFromRawOpts :: RawOpts -> Interval
|
|
|
|
intervalFromRawOpts = lastDef NoInterval . catMaybes . map intervalfromrawopt
|
|
|
|
where
|
|
|
|
intervalfromrawopt (n,v)
|
|
|
|
| n == "period" =
|
2017-03-29 18:00:30 +03:00
|
|
|
either (\e -> usageError $ "could not parse period option: "++parseErrorPretty e) (Just . fst) $
|
2016-07-30 05:19:44 +03:00
|
|
|
parsePeriodExpr nulldate (stripquotes $ T.pack v) -- reference date does not affect the interval
|
|
|
|
| n == "daily" = Just $ Days 1
|
|
|
|
| n == "weekly" = Just $ Weeks 1
|
|
|
|
| n == "monthly" = Just $ Months 1
|
|
|
|
| n == "quarterly" = Just $ Quarters 1
|
|
|
|
| n == "yearly" = Just $ Years 1
|
|
|
|
| otherwise = Nothing
|
|
|
|
|
|
|
|
-- | Get the cleared status, if any, specified by the last of -C/--cleared,
|
|
|
|
-- --pending, -U/--uncleared options.
|
|
|
|
clearedStatusFromRawOpts :: RawOpts -> Maybe ClearedStatus
|
|
|
|
clearedStatusFromRawOpts = lastMay . catMaybes . map clearedstatusfromrawopt
|
|
|
|
where
|
|
|
|
clearedstatusfromrawopt (n,_)
|
|
|
|
| n == "cleared" = Just Cleared
|
|
|
|
| n == "pending" = Just Pending
|
|
|
|
| n == "uncleared" = Just Uncleared
|
|
|
|
| otherwise = Nothing
|
2014-03-26 04:10:30 +04:00
|
|
|
|
|
|
|
type DisplayExp = String
|
|
|
|
|
|
|
|
maybedisplayopt :: Day -> RawOpts -> Maybe DisplayExp
|
|
|
|
maybedisplayopt d rawopts =
|
|
|
|
maybe Nothing (Just . regexReplaceBy "\\[.+?\\]" fixbracketeddatestr) $ maybestringopt "display" rawopts
|
|
|
|
where
|
|
|
|
fixbracketeddatestr "" = ""
|
2016-07-29 18:57:10 +03:00
|
|
|
fixbracketeddatestr s = "[" ++ fixSmartDateStr d (T.pack $ init $ tail s) ++ "]"
|
2014-03-26 04:10:30 +04:00
|
|
|
|
2016-07-30 05:19:44 +03:00
|
|
|
-- | Select the Transaction date accessor based on --date2.
|
|
|
|
transactionDateFn :: ReportOpts -> (Transaction -> Day)
|
|
|
|
transactionDateFn ReportOpts{..} = if date2_ then transactionDate2 else tdate
|
|
|
|
|
|
|
|
-- | Select the Posting date accessor based on --date2.
|
|
|
|
postingDateFn :: ReportOpts -> (Posting -> Day)
|
|
|
|
postingDateFn ReportOpts{..} = if date2_ then postingDate2 else postingDate
|
|
|
|
|
|
|
|
-- | Report which date we will report on based on --date2.
|
|
|
|
whichDateFromOpts :: ReportOpts -> WhichDate
|
|
|
|
whichDateFromOpts ReportOpts{..} = if date2_ then SecondaryDate else PrimaryDate
|
2014-03-20 04:11:48 +04:00
|
|
|
|
2014-12-05 23:56:33 +03:00
|
|
|
-- | Legacy-compatible convenience aliases for accountlistmode_.
|
|
|
|
tree_ :: ReportOpts -> Bool
|
|
|
|
tree_ = (==ALTree) . accountlistmode_
|
|
|
|
|
|
|
|
flat_ :: ReportOpts -> Bool
|
|
|
|
flat_ = (==ALFlat) . accountlistmode_
|
|
|
|
|
2014-03-20 04:11:48 +04:00
|
|
|
-- depthFromOpts :: ReportOpts -> Int
|
|
|
|
-- depthFromOpts opts = min (fromMaybe 99999 $ depth_ opts) (queryDepth $ queryFromOpts nulldate opts)
|
|
|
|
|
|
|
|
-- | Convert this journal's postings' amounts to the cost basis amounts if
|
|
|
|
-- specified by options.
|
|
|
|
journalSelectingAmountFromOpts :: ReportOpts -> Journal -> Journal
|
|
|
|
journalSelectingAmountFromOpts opts
|
|
|
|
| cost_ opts = journalConvertAmountsToCost
|
|
|
|
| otherwise = id
|
|
|
|
|
|
|
|
-- | Convert report options and arguments to a query.
|
|
|
|
queryFromOpts :: Day -> ReportOpts -> Query
|
2016-07-30 05:19:44 +03:00
|
|
|
queryFromOpts d ReportOpts{..} = simplifyQuery $ And $ [flagsq, argsq]
|
2014-03-20 04:11:48 +04:00
|
|
|
where
|
|
|
|
flagsq = And $
|
2016-07-30 05:19:44 +03:00
|
|
|
[(if date2_ then Date2 else Date) $ periodAsDateSpan period_]
|
2014-03-20 04:11:48 +04:00
|
|
|
++ (if real_ then [Real True] else [])
|
|
|
|
++ (if empty_ then [Empty True] else []) -- ?
|
2016-07-30 05:19:44 +03:00
|
|
|
++ (maybe [] ((:[]) . Status) clearedstatus_)
|
2014-03-20 04:11:48 +04:00
|
|
|
++ (maybe [] ((:[]) . Depth) depth_)
|
2016-07-29 18:57:10 +03:00
|
|
|
argsq = fst $ parseQuery d (T.pack query_)
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
-- | Convert report options to a query, ignoring any non-flag command line arguments.
|
|
|
|
queryFromOptsOnly :: Day -> ReportOpts -> Query
|
2016-07-30 05:19:44 +03:00
|
|
|
queryFromOptsOnly _d ReportOpts{..} = simplifyQuery flagsq
|
2014-03-20 04:11:48 +04:00
|
|
|
where
|
|
|
|
flagsq = And $
|
2016-07-30 05:19:44 +03:00
|
|
|
[(if date2_ then Date2 else Date) $ periodAsDateSpan period_]
|
2014-03-20 04:11:48 +04:00
|
|
|
++ (if real_ then [Real True] else [])
|
|
|
|
++ (if empty_ then [Empty True] else []) -- ?
|
2016-07-30 05:19:44 +03:00
|
|
|
++ (maybe [] ((:[]) . Status) clearedstatus_)
|
2014-03-20 04:11:48 +04:00
|
|
|
++ (maybe [] ((:[]) . Depth) depth_)
|
|
|
|
|
2014-03-26 04:10:30 +04:00
|
|
|
tests_queryFromOpts :: [Test]
|
2014-03-20 04:11:48 +04:00
|
|
|
tests_queryFromOpts = [
|
|
|
|
"queryFromOpts" ~: do
|
|
|
|
assertEqual "" Any (queryFromOpts nulldate defreportopts)
|
|
|
|
assertEqual "" (Acct "a") (queryFromOpts nulldate defreportopts{query_="a"})
|
|
|
|
assertEqual "" (Desc "a a") (queryFromOpts nulldate defreportopts{query_="desc:'a a'"})
|
|
|
|
assertEqual "" (Date $ mkdatespan "2012/01/01" "2013/01/01")
|
2016-07-30 05:19:44 +03:00
|
|
|
(queryFromOpts nulldate defreportopts{period_=PeriodFrom (parsedate "2012/01/01")
|
2014-03-20 04:11:48 +04:00
|
|
|
,query_="date:'to 2013'"
|
|
|
|
})
|
|
|
|
assertEqual "" (Date2 $ mkdatespan "2012/01/01" "2013/01/01")
|
2014-12-16 22:06:21 +03:00
|
|
|
(queryFromOpts nulldate defreportopts{query_="date2:'in 2012'"})
|
2014-03-20 04:11:48 +04:00
|
|
|
assertEqual "" (Or [Acct "a a", Acct "'b"])
|
|
|
|
(queryFromOpts nulldate defreportopts{query_="'a a' 'b"})
|
|
|
|
]
|
|
|
|
|
|
|
|
-- | Convert report options and arguments to query options.
|
|
|
|
queryOptsFromOpts :: Day -> ReportOpts -> [QueryOpt]
|
|
|
|
queryOptsFromOpts d ReportOpts{..} = flagsqopts ++ argsqopts
|
|
|
|
where
|
|
|
|
flagsqopts = []
|
2016-07-29 18:57:10 +03:00
|
|
|
argsqopts = snd $ parseQuery d (T.pack query_)
|
2014-03-20 04:11:48 +04:00
|
|
|
|
2014-03-26 04:10:30 +04:00
|
|
|
tests_queryOptsFromOpts :: [Test]
|
2014-03-20 04:11:48 +04:00
|
|
|
tests_queryOptsFromOpts = [
|
|
|
|
"queryOptsFromOpts" ~: do
|
|
|
|
assertEqual "" [] (queryOptsFromOpts nulldate defreportopts)
|
|
|
|
assertEqual "" [] (queryOptsFromOpts nulldate defreportopts{query_="a"})
|
2016-07-30 05:19:44 +03:00
|
|
|
assertEqual "" [] (queryOptsFromOpts nulldate defreportopts{period_=PeriodFrom (parsedate "2012/01/01")
|
2014-03-20 04:11:48 +04:00
|
|
|
,query_="date:'to 2013'"
|
|
|
|
})
|
|
|
|
]
|
|
|
|
|
2016-12-30 22:44:01 +03:00
|
|
|
-- | The effective report start date is the one specified by options or queries,
|
|
|
|
-- otherwise the earliest transaction or posting date in the journal,
|
|
|
|
-- otherwise (for an empty journal) nothing.
|
|
|
|
-- Needs IO to parse smart dates in options/queries.
|
|
|
|
reportStartDate :: Journal -> ReportOpts -> IO (Maybe Day)
|
|
|
|
reportStartDate j ropts = (fst <$>) <$> reportStartEndDates j ropts
|
|
|
|
|
|
|
|
-- | The effective report end date is the one specified by options or queries,
|
|
|
|
-- otherwise the latest transaction or posting date in the journal,
|
|
|
|
-- otherwise (for an empty journal) nothing.
|
|
|
|
-- Needs IO to parse smart dates in options/queries.
|
|
|
|
reportEndDate :: Journal -> ReportOpts -> IO (Maybe Day)
|
2016-12-31 01:25:19 +03:00
|
|
|
reportEndDate j ropts = (snd <$>) <$> reportStartEndDates j ropts
|
2016-12-30 22:44:01 +03:00
|
|
|
|
|
|
|
reportStartEndDates :: Journal -> ReportOpts -> IO (Maybe (Day,Day))
|
|
|
|
reportStartEndDates j ropts = do
|
|
|
|
today <- getCurrentDay
|
|
|
|
let
|
|
|
|
q = queryFromOpts today ropts
|
|
|
|
mrequestedstartdate = queryStartDate False q
|
|
|
|
mrequestedenddate = queryEndDate False q
|
|
|
|
return $
|
|
|
|
case journalDateSpan False j of -- don't bother with secondary dates
|
|
|
|
DateSpan (Just journalstartdate) (Just journalenddate) ->
|
|
|
|
Just (fromMaybe journalstartdate mrequestedstartdate, fromMaybe journalenddate mrequestedenddate)
|
|
|
|
_ -> Nothing
|
|
|
|
|
2014-03-20 04:11:48 +04:00
|
|
|
|
|
|
|
tests_Hledger_Reports_ReportOptions :: Test
|
|
|
|
tests_Hledger_Reports_ReportOptions = TestList $
|
|
|
|
tests_queryFromOpts
|
|
|
|
++ tests_queryOptsFromOpts
|