hledger/hledger-lib/Hledger/Read/InputOptions.hs
Michael Rees 62071bc4c2 feat: timeclock: Add support for multiple clocked in sessions (#2141)
We now support having multiple sessions clocked in. These are paired by
account name if given on the out entry, and otherwise an out closes the
most recent in entry.

Note that this breaks some backwards compatibility, in that we
previously ignored the description on the clock out entry. To mitigate
this, a new hidden flag --timeclock-old has been added, which reverts to
the old behavior.
2025-04-03 11:19:18 -10:00

99 lines
4.9 KiB
Haskell

{-|
Various options to use when reading journal files.
Similar to CliOptions.inputflags, simplifies the journal-reading functions.
-}
{-# LANGUAGE TemplateHaskell #-}
module Hledger.Read.InputOptions (
-- * Types and helpers for input options
InputOpts(..)
, HasInputOpts(..)
, definputopts
, forecastPeriod
) where
import Control.Applicative ((<|>))
import Data.Time (Day, addDays)
import Hledger.Data.Types
import Hledger.Data.Journal (journalEndDate)
import Hledger.Data.Dates (nulldate, nulldatespan)
import Hledger.Data.Balancing (BalancingOpts(..), HasBalancingOpts(..), defbalancingopts)
import Hledger.Utils (dbg2, makeHledgerClassyLenses)
data InputOpts = InputOpts {
-- files_ :: [FilePath]
mformat_ :: Maybe StorageFormat -- ^ a file/storage format to try, unless overridden
-- by a filename prefix. Nothing means try all.
,mrules_file_ :: Maybe FilePath -- ^ a conversion rules file to use (when reading CSV)
,aliases_ :: [String] -- ^ account name aliases to apply
,anon_ :: Bool -- ^ do light obfuscation of the data ? Now corresponds to --obfuscate, not the old --anon flag.
,new_ :: Bool -- ^ read only new transactions since this file was last read ?
,new_save_ :: Bool -- ^ save latest new transactions state for next time ?
,pivot_ :: String -- ^ use the given field's value as the account name
,forecast_ :: Maybe DateSpan -- ^ span in which to generate forecast transactions
,posting_account_tags_ :: Bool -- ^ propagate account tags to postings ?
,verbose_tags_ :: Bool -- ^ add user-visible tags when generating/modifying transactions & postings ?
,reportspan_ :: DateSpan -- ^ a dirty hack keeping the query dates in InputOpts. This rightfully lives in ReportSpec, but is duplicated here.
,auto_ :: Bool -- ^ generate extra postings according to auto posting rules ?
,infer_equity_ :: Bool -- ^ infer equity conversion postings from costs ?
,infer_costs_ :: Bool -- ^ infer costs from equity conversion postings ? distinct from BalancingOpts{infer_balancing_costs_}
,balancingopts_ :: BalancingOpts -- ^ options for transaction balancing
,strict_ :: Bool -- ^ do extra correctness checks ?
,_defer :: Bool -- ^ internal flag: postpone checks, because we are processing multiple files ?
,_ioDay :: Day -- ^ today's date, for use with forecast transactions XXX this duplicates _rsDay, and should eventually be removed when it's not needed anymore.
,_oldtimeclock :: Bool -- ^ parse with the old timeclock pairing rules?
} deriving (Eq, Ord, Show)
definputopts :: InputOpts
definputopts = InputOpts
{ mformat_ = Nothing
, mrules_file_ = Nothing
, aliases_ = []
, anon_ = False
, new_ = False
, new_save_ = True
, pivot_ = ""
, forecast_ = Nothing
, posting_account_tags_ = False
, verbose_tags_ = False
, reportspan_ = nulldatespan
, auto_ = False
, infer_equity_ = False
, infer_costs_ = False
, balancingopts_ = defbalancingopts
, strict_ = False
, _defer = False
, _ioDay = nulldate
, _oldtimeclock = False
}
-- | Get the Maybe the DateSpan to generate forecast options from.
-- This begins on:
-- - the start date supplied to the `--forecast` argument, if present
-- - otherwise, the later of
-- - the report start date if specified with -b/-p/date:
-- - the day after the latest normal (non-periodic) transaction in the journal, if any
-- - otherwise today.
-- It ends on:
-- - the end date supplied to the `--forecast` argument, if present
-- - otherwise the report end date if specified with -e/-p/date:
-- - otherwise 180 days (6 months) from today.
forecastPeriod :: InputOpts -> Journal -> Maybe DateSpan
forecastPeriod iopts j = do
DateSpan requestedStart requestedEnd <- forecast_ iopts
let forecastStart = fromEFDay <$> requestedStart <|> max mjournalend (fromEFDay <$> reportStart) <|> Just (_ioDay iopts)
forecastEnd = fromEFDay <$> requestedEnd <|> fromEFDay <$> reportEnd <|> (Just $ addDays 180 $ _ioDay iopts)
mjournalend = dbg2 "journalEndDate" $ journalEndDate False j -- ignore secondary dates
DateSpan reportStart reportEnd = reportspan_ iopts
return . dbg2 "forecastspan" $ DateSpan (Exact <$> forecastStart) (Exact <$> forecastEnd)
-- ** Lenses
makeHledgerClassyLenses ''InputOpts
instance HasBalancingOpts InputOpts where
balancingOpts = balancingopts