{-|

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]
     InputOpts -> Maybe StorageFormat
mformat_           :: Maybe StorageFormat  -- ^ a file/storage format to try, unless overridden
                                                --   by a filename prefix. Nothing means try all.
    ,InputOpts -> Maybe StorageFormat
mrules_file_       :: Maybe FilePath       -- ^ a conversion rules file to use (when reading CSV)
    ,InputOpts -> [StorageFormat]
aliases_           :: [String]             -- ^ account name aliases to apply
    ,InputOpts -> Bool
anon_              :: Bool                 -- ^ do light anonymisation/obfuscation of the data
    ,InputOpts -> Bool
new_               :: Bool                 -- ^ read only new transactions since this file was last read
    ,InputOpts -> Bool
new_save_          :: Bool                 -- ^ save latest new transactions state for next time
    ,InputOpts -> StorageFormat
pivot_             :: String               -- ^ use the given field's value as the account name
    ,InputOpts -> Maybe DateSpan
forecast_          :: Maybe DateSpan       -- ^ span in which to generate forecast transactions
    ,InputOpts -> DateSpan
reportspan_        :: DateSpan             -- ^ a dirty hack keeping the query dates in InputOpts. This rightfully lives in ReportSpec, but is duplicated here.
    ,InputOpts -> Bool
auto_              :: Bool                 -- ^ generate automatic postings when journal is parsed
    ,InputOpts -> BalancingOpts
balancingopts_     :: BalancingOpts        -- ^ options for balancing transactions
    ,InputOpts -> Bool
strict_            :: Bool                 -- ^ do extra error checking (eg, all posted accounts are declared, no prices are inferred)
    ,InputOpts -> Day
_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.
 } deriving (Int -> InputOpts -> ShowS
[InputOpts] -> ShowS
InputOpts -> StorageFormat
(Int -> InputOpts -> ShowS)
-> (InputOpts -> StorageFormat)
-> ([InputOpts] -> ShowS)
-> Show InputOpts
forall a.
(Int -> a -> ShowS)
-> (a -> StorageFormat) -> ([a] -> ShowS) -> Show a
showList :: [InputOpts] -> ShowS
$cshowList :: [InputOpts] -> ShowS
show :: InputOpts -> StorageFormat
$cshow :: InputOpts -> StorageFormat
showsPrec :: Int -> InputOpts -> ShowS
$cshowsPrec :: Int -> InputOpts -> ShowS
Show)

definputopts :: InputOpts
definputopts :: InputOpts
definputopts = InputOpts :: Maybe StorageFormat
-> Maybe StorageFormat
-> [StorageFormat]
-> Bool
-> Bool
-> Bool
-> StorageFormat
-> Maybe DateSpan
-> DateSpan
-> Bool
-> BalancingOpts
-> Bool
-> Day
-> InputOpts
InputOpts
    { mformat_ :: Maybe StorageFormat
mformat_           = Maybe StorageFormat
forall a. Maybe a
Nothing
    , mrules_file_ :: Maybe StorageFormat
mrules_file_       = Maybe StorageFormat
forall a. Maybe a
Nothing
    , aliases_ :: [StorageFormat]
aliases_           = []
    , anon_ :: Bool
anon_              = Bool
False
    , new_ :: Bool
new_               = Bool
False
    , new_save_ :: Bool
new_save_          = Bool
True
    , pivot_ :: StorageFormat
pivot_             = StorageFormat
""
    , forecast_ :: Maybe DateSpan
forecast_          = Maybe DateSpan
forall a. Maybe a
Nothing
    , reportspan_ :: DateSpan
reportspan_        = DateSpan
nulldatespan
    , auto_ :: Bool
auto_              = Bool
False
    , balancingopts_ :: BalancingOpts
balancingopts_     = BalancingOpts
defbalancingopts
    , strict_ :: Bool
strict_            = Bool
False
    , _ioDay :: Day
_ioDay             = Day
nulldate
    }

-- | 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 :: InputOpts -> Journal -> Maybe DateSpan
forecastPeriod InputOpts
iopts Journal
j = do
    DateSpan Maybe Day
requestedStart Maybe Day
requestedEnd <- InputOpts -> Maybe DateSpan
forecast_ InputOpts
iopts
    let forecastStart :: Maybe Day
forecastStart = Maybe Day
requestedStart Maybe Day -> Maybe Day -> Maybe Day
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Day -> Maybe Day -> Maybe Day
forall a. Ord a => a -> a -> a
max Maybe Day
mjournalend Maybe Day
reportStart Maybe Day -> Maybe Day -> Maybe Day
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Day -> Maybe Day
forall a. a -> Maybe a
Just (InputOpts -> Day
_ioDay InputOpts
iopts)
        forecastEnd :: Maybe Day
forecastEnd   = Maybe Day
requestedEnd Maybe Day -> Maybe Day -> Maybe Day
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Day
reportEnd Maybe Day -> Maybe Day -> Maybe Day
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Day -> Maybe Day
forall a. a -> Maybe a
Just (Integer -> Day -> Day
addDays Integer
180 (Day -> Day) -> Day -> Day
forall a b. (a -> b) -> a -> b
$ InputOpts -> Day
_ioDay InputOpts
iopts)
        mjournalend :: Maybe Day
mjournalend   = StorageFormat -> Maybe Day -> Maybe Day
forall a. Show a => StorageFormat -> a -> a
dbg2 StorageFormat
"journalEndDate" (Maybe Day -> Maybe Day) -> Maybe Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Bool -> Journal -> Maybe Day
journalEndDate Bool
False Journal
j  -- ignore secondary dates
        DateSpan Maybe Day
reportStart Maybe Day
reportEnd = InputOpts -> DateSpan
reportspan_ InputOpts
iopts
    DateSpan -> Maybe DateSpan
forall (m :: * -> *) a. Monad m => a -> m a
return (DateSpan -> Maybe DateSpan)
-> (DateSpan -> DateSpan) -> DateSpan -> Maybe DateSpan
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StorageFormat -> DateSpan -> DateSpan
forall a. Show a => StorageFormat -> a -> a
dbg2 StorageFormat
"forecastspan" (DateSpan -> Maybe DateSpan) -> DateSpan -> Maybe DateSpan
forall a b. (a -> b) -> a -> b
$ Maybe Day -> Maybe Day -> DateSpan
DateSpan Maybe Day
forecastStart Maybe Day
forecastEnd

-- ** Lenses

makeHledgerClassyLenses ''InputOpts

instance HasBalancingOpts InputOpts where
    balancingOpts :: (BalancingOpts -> f BalancingOpts) -> InputOpts -> f InputOpts
balancingOpts = (BalancingOpts -> f BalancingOpts) -> InputOpts -> f InputOpts
forall c. HasInputOpts c => Lens' c BalancingOpts
balancingopts