{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE LambdaCase            #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE RankNTypes            #-}
{-# LANGUAGE RecordWildCards       #-}
{-# LANGUAGE TemplateHaskell       #-}
{-# LANGUAGE TypeFamilies          #-}
module Hledger.Reports.ReportOptions (
  ReportOpts(..),
  HasReportOptsNoUpdate(..),
  HasReportOpts(..),
  ReportSpec(..),
  HasReportSpec(..),
  overEither,
  setEither,
  BalanceCalculation(..),
  BalanceAccumulation(..),
  AccountListMode(..),
  ValuationType(..),
  Layout(..),
  defreportopts,
  rawOptsToReportOpts,
  defreportspec,
  setDefaultConversionOp,
  reportOptsToSpec,
  updateReportSpec,
  updateReportSpecWith,
  rawOptsToReportSpec,
  balanceAccumulationOverride,
  flat_,
  tree_,
  reportOptsToggleStatus,
  simplifyStatuses,
  whichDate,
  journalValueAndFilterPostings,
  journalValueAndFilterPostingsWith,
  journalApplyValuationFromOpts,
  journalApplyValuationFromOptsWith,
  mixedAmountApplyValuationAfterSumFromOptsWith,
  valuationAfterSum,
  intervalFromRawOpts,
  queryFromFlags,
  transactionDateFn,
  postingDateFn,
  reportSpan,
  reportSpanBothDates,
  reportStartDate,
  reportEndDate,
  reportPeriodStart,
  reportPeriodOrJournalStart,
  reportPeriodLastDay,
  reportPeriodOrJournalLastDay,
  reportPeriodName
)
where
import Control.Applicative (Const(..), (<|>), liftA2)
import Control.Monad ((<=<), guard, join)
import Data.Char (toLower)
import Data.Either (fromRight)
import Data.Either.Extra (eitherToMaybe)
import Data.Functor.Identity (Identity(..))
import Data.List.Extra (find, isPrefixOf, nubSort)
import Data.Maybe (fromMaybe, isJust)
import qualified Data.Text as T
import Data.Time.Calendar (Day, addDays)
import Data.Default (Default(..))
import Safe (headMay, lastDef, lastMay, maximumMay, readMay)
import Text.Megaparsec.Custom
import Hledger.Data
import Hledger.Query
import Hledger.Utils
data BalanceCalculation =
    CalcChange      
  | CalcBudget      
  | CalcValueChange 
  | CalcGain        
  deriving (BalanceCalculation -> BalanceCalculation -> Bool
(BalanceCalculation -> BalanceCalculation -> Bool)
-> (BalanceCalculation -> BalanceCalculation -> Bool)
-> Eq BalanceCalculation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BalanceCalculation -> BalanceCalculation -> Bool
$c/= :: BalanceCalculation -> BalanceCalculation -> Bool
== :: BalanceCalculation -> BalanceCalculation -> Bool
$c== :: BalanceCalculation -> BalanceCalculation -> Bool
Eq, Int -> BalanceCalculation -> ShowS
[BalanceCalculation] -> ShowS
BalanceCalculation -> String
(Int -> BalanceCalculation -> ShowS)
-> (BalanceCalculation -> String)
-> ([BalanceCalculation] -> ShowS)
-> Show BalanceCalculation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BalanceCalculation] -> ShowS
$cshowList :: [BalanceCalculation] -> ShowS
show :: BalanceCalculation -> String
$cshow :: BalanceCalculation -> String
showsPrec :: Int -> BalanceCalculation -> ShowS
$cshowsPrec :: Int -> BalanceCalculation -> ShowS
Show)
instance Default BalanceCalculation where def :: BalanceCalculation
def = BalanceCalculation
CalcChange
data BalanceAccumulation =
    PerPeriod   
  | Cumulative  
  | Historical  
                
  deriving (BalanceAccumulation -> BalanceAccumulation -> Bool
(BalanceAccumulation -> BalanceAccumulation -> Bool)
-> (BalanceAccumulation -> BalanceAccumulation -> Bool)
-> Eq BalanceAccumulation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BalanceAccumulation -> BalanceAccumulation -> Bool
$c/= :: BalanceAccumulation -> BalanceAccumulation -> Bool
== :: BalanceAccumulation -> BalanceAccumulation -> Bool
$c== :: BalanceAccumulation -> BalanceAccumulation -> Bool
Eq,Int -> BalanceAccumulation -> ShowS
[BalanceAccumulation] -> ShowS
BalanceAccumulation -> String
(Int -> BalanceAccumulation -> ShowS)
-> (BalanceAccumulation -> String)
-> ([BalanceAccumulation] -> ShowS)
-> Show BalanceAccumulation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BalanceAccumulation] -> ShowS
$cshowList :: [BalanceAccumulation] -> ShowS
show :: BalanceAccumulation -> String
$cshow :: BalanceAccumulation -> String
showsPrec :: Int -> BalanceAccumulation -> ShowS
$cshowsPrec :: Int -> BalanceAccumulation -> ShowS
Show)
instance Default BalanceAccumulation where def :: BalanceAccumulation
def = BalanceAccumulation
PerPeriod
data AccountListMode = ALFlat | ALTree deriving (AccountListMode -> AccountListMode -> Bool
(AccountListMode -> AccountListMode -> Bool)
-> (AccountListMode -> AccountListMode -> Bool)
-> Eq AccountListMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountListMode -> AccountListMode -> Bool
$c/= :: AccountListMode -> AccountListMode -> Bool
== :: AccountListMode -> AccountListMode -> Bool
$c== :: AccountListMode -> AccountListMode -> Bool
Eq, Int -> AccountListMode -> ShowS
[AccountListMode] -> ShowS
AccountListMode -> String
(Int -> AccountListMode -> ShowS)
-> (AccountListMode -> String)
-> ([AccountListMode] -> ShowS)
-> Show AccountListMode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountListMode] -> ShowS
$cshowList :: [AccountListMode] -> ShowS
show :: AccountListMode -> String
$cshow :: AccountListMode -> String
showsPrec :: Int -> AccountListMode -> ShowS
$cshowsPrec :: Int -> AccountListMode -> ShowS
Show)
instance Default AccountListMode where def :: AccountListMode
def = AccountListMode
ALFlat
data Layout = LayoutWide (Maybe Int)
            | LayoutTall
            | LayoutBare
            | LayoutTidy
  deriving (Layout -> Layout -> Bool
(Layout -> Layout -> Bool)
-> (Layout -> Layout -> Bool) -> Eq Layout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Layout -> Layout -> Bool
$c/= :: Layout -> Layout -> Bool
== :: Layout -> Layout -> Bool
$c== :: Layout -> Layout -> Bool
Eq, Int -> Layout -> ShowS
[Layout] -> ShowS
Layout -> String
(Int -> Layout -> ShowS)
-> (Layout -> String) -> ([Layout] -> ShowS) -> Show Layout
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Layout] -> ShowS
$cshowList :: [Layout] -> ShowS
show :: Layout -> String
$cshow :: Layout -> String
showsPrec :: Int -> Layout -> ShowS
$cshowsPrec :: Int -> Layout -> ShowS
Show)
data ReportOpts = ReportOpts {
     
     ReportOpts -> Period
period_           :: Period
    ,ReportOpts -> Interval
interval_         :: Interval
    ,ReportOpts -> [Status]
statuses_         :: [Status]  
    ,ReportOpts -> Maybe ConversionOp
conversionop_     :: Maybe ConversionOp  
    ,ReportOpts -> Maybe ValuationType
value_            :: Maybe ValuationType  
    ,ReportOpts -> Bool
infer_prices_     :: Bool      
    ,ReportOpts -> Maybe Int
depth_            :: Maybe Int
    ,ReportOpts -> Bool
date2_            :: Bool
    ,ReportOpts -> Bool
empty_            :: Bool
    ,ReportOpts -> Bool
no_elide_         :: Bool
    ,ReportOpts -> Bool
real_             :: Bool
    ,ReportOpts -> StringFormat
format_           :: StringFormat
    ,ReportOpts -> Bool
pretty_           :: Bool
    ,ReportOpts -> [Text]
querystring_      :: [T.Text]
    
    ,ReportOpts -> Bool
average_          :: Bool
    
    ,ReportOpts -> Bool
related_          :: Bool
    
    ,ReportOpts -> Bool
txn_dates_        :: Bool
    
    ,ReportOpts -> BalanceCalculation
balancecalc_      :: BalanceCalculation  
    ,ReportOpts -> BalanceAccumulation
balanceaccum_     :: BalanceAccumulation 
    ,ReportOpts -> Maybe Text
budgetpat_        :: Maybe T.Text  
                                        
                                        
    ,ReportOpts -> AccountListMode
accountlistmode_  :: AccountListMode
    ,ReportOpts -> Int
drop_             :: Int
    ,ReportOpts -> Bool
declared_         :: Bool  
    ,ReportOpts -> Bool
row_total_        :: Bool
    ,ReportOpts -> Bool
no_total_         :: Bool
    ,ReportOpts -> Bool
show_costs_       :: Bool  
    ,ReportOpts -> Bool
sort_amount_      :: Bool
    ,ReportOpts -> Bool
percent_          :: Bool
    ,ReportOpts -> Bool
invert_           :: Bool  
    ,ReportOpts -> Maybe NormalSign
normalbalance_    :: Maybe NormalSign
      
      
      
      
      
      
      
    ,ReportOpts -> Bool
color_            :: Bool
      
      
      
      
    ,ReportOpts -> Bool
transpose_        :: Bool
    ,ReportOpts -> Layout
layout_           :: Layout
 } deriving (Int -> ReportOpts -> ShowS
[ReportOpts] -> ShowS
ReportOpts -> String
(Int -> ReportOpts -> ShowS)
-> (ReportOpts -> String)
-> ([ReportOpts] -> ShowS)
-> Show ReportOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReportOpts] -> ShowS
$cshowList :: [ReportOpts] -> ShowS
show :: ReportOpts -> String
$cshow :: ReportOpts -> String
showsPrec :: Int -> ReportOpts -> ShowS
$cshowsPrec :: Int -> ReportOpts -> ShowS
Show)
instance Default ReportOpts where def :: ReportOpts
def = ReportOpts
defreportopts
defreportopts :: ReportOpts
defreportopts :: ReportOpts
defreportopts = ReportOpts :: Period
-> Interval
-> [Status]
-> Maybe ConversionOp
-> Maybe ValuationType
-> Bool
-> Maybe Int
-> Bool
-> Bool
-> Bool
-> Bool
-> StringFormat
-> Bool
-> [Text]
-> Bool
-> Bool
-> Bool
-> BalanceCalculation
-> BalanceAccumulation
-> Maybe Text
-> AccountListMode
-> Int
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe NormalSign
-> Bool
-> Bool
-> Layout
-> ReportOpts
ReportOpts
    { period_ :: Period
period_           = Period
PeriodAll
    , interval_ :: Interval
interval_         = Interval
NoInterval
    , statuses_ :: [Status]
statuses_         = []
    , conversionop_ :: Maybe ConversionOp
conversionop_     = Maybe ConversionOp
forall a. Maybe a
Nothing
    , value_ :: Maybe ValuationType
value_            = Maybe ValuationType
forall a. Maybe a
Nothing
    , infer_prices_ :: Bool
infer_prices_     = Bool
False
    , depth_ :: Maybe Int
depth_            = Maybe Int
forall a. Maybe a
Nothing
    , date2_ :: Bool
date2_            = Bool
False
    , empty_ :: Bool
empty_            = Bool
False
    , no_elide_ :: Bool
no_elide_         = Bool
False
    , real_ :: Bool
real_             = Bool
False
    , format_ :: StringFormat
format_           = StringFormat
forall a. Default a => a
def
    , pretty_ :: Bool
pretty_           = Bool
False
    , querystring_ :: [Text]
querystring_      = []
    , average_ :: Bool
average_          = Bool
False
    , related_ :: Bool
related_          = Bool
False
    , txn_dates_ :: Bool
txn_dates_        = Bool
False
    , balancecalc_ :: BalanceCalculation
balancecalc_      = BalanceCalculation
forall a. Default a => a
def
    , balanceaccum_ :: BalanceAccumulation
balanceaccum_     = BalanceAccumulation
forall a. Default a => a
def
    , budgetpat_ :: Maybe Text
budgetpat_        = Maybe Text
forall a. Maybe a
Nothing
    , accountlistmode_ :: AccountListMode
accountlistmode_  = AccountListMode
ALFlat
    , drop_ :: Int
drop_             = Int
0
    , declared_ :: Bool
declared_         = Bool
False
    , row_total_ :: Bool
row_total_        = Bool
False
    , no_total_ :: Bool
no_total_         = Bool
False
    , show_costs_ :: Bool
show_costs_       = Bool
False
    , sort_amount_ :: Bool
sort_amount_      = Bool
False
    , percent_ :: Bool
percent_          = Bool
False
    , invert_ :: Bool
invert_           = Bool
False
    , normalbalance_ :: Maybe NormalSign
normalbalance_    = Maybe NormalSign
forall a. Maybe a
Nothing
    , color_ :: Bool
color_            = Bool
False
    , transpose_ :: Bool
transpose_        = Bool
False
    , layout_ :: Layout
layout_           = Maybe Int -> Layout
LayoutWide Maybe Int
forall a. Maybe a
Nothing
    }
rawOptsToReportOpts :: Day -> RawOpts -> ReportOpts
rawOptsToReportOpts :: Day -> RawOpts -> ReportOpts
rawOptsToReportOpts Day
d RawOpts
rawopts =
    let formatstring :: Maybe Text
formatstring = String -> Text
T.pack (String -> Text) -> Maybe String -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> RawOpts -> Maybe String
maybestringopt String
"format" RawOpts
rawopts
        querystring :: [Text]
querystring  = (String -> Text) -> [String] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map String -> Text
T.pack ([String] -> [Text]) -> [String] -> [Text]
forall a b. (a -> b) -> a -> b
$ String -> RawOpts -> [String]
listofstringopt String
"args" RawOpts
rawopts  
        pretty :: Bool
pretty = Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
False (Maybe Bool -> Bool) -> Maybe Bool -> Bool
forall a b. (a -> b) -> a -> b
$ String -> RawOpts -> Maybe Bool
alwaysneveropt String
"pretty" RawOpts
rawopts
        format :: StringFormat
format = case Text -> Either String StringFormat
parseStringFormat (Text -> Either String StringFormat)
-> Maybe Text -> Maybe (Either String StringFormat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
formatstring of
            Maybe (Either String StringFormat)
Nothing         -> StringFormat
defaultBalanceLineFormat
            Just (Right StringFormat
x)  -> StringFormat
x
            Just (Left String
err) -> String -> StringFormat
forall a. String -> a
usageError (String -> StringFormat) -> String -> StringFormat
forall a b. (a -> b) -> a -> b
$ String
"could not parse format option: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
err
    in ReportOpts
defreportopts
          {period_ :: Period
period_           = Day -> RawOpts -> Period
periodFromRawOpts Day
d RawOpts
rawopts
          ,interval_ :: Interval
interval_         = RawOpts -> Interval
intervalFromRawOpts RawOpts
rawopts
          ,statuses_ :: [Status]
statuses_         = RawOpts -> [Status]
statusesFromRawOpts RawOpts
rawopts
          ,conversionop_ :: Maybe ConversionOp
conversionop_     = RawOpts -> Maybe ConversionOp
conversionOpFromRawOpts RawOpts
rawopts
          ,value_ :: Maybe ValuationType
value_            = RawOpts -> Maybe ValuationType
valuationTypeFromRawOpts RawOpts
rawopts
          ,infer_prices_ :: Bool
infer_prices_     = String -> RawOpts -> Bool
boolopt String
"infer-market-prices" RawOpts
rawopts
          ,depth_ :: Maybe Int
depth_            = String -> RawOpts -> Maybe Int
maybeposintopt String
"depth" RawOpts
rawopts
          ,date2_ :: Bool
date2_            = String -> RawOpts -> Bool
boolopt String
"date2" RawOpts
rawopts
          ,empty_ :: Bool
empty_            = String -> RawOpts -> Bool
boolopt String
"empty" RawOpts
rawopts
          ,no_elide_ :: Bool
no_elide_         = String -> RawOpts -> Bool
boolopt String
"no-elide" RawOpts
rawopts
          ,real_ :: Bool
real_             = String -> RawOpts -> Bool
boolopt String
"real" RawOpts
rawopts
          ,format_ :: StringFormat
format_           = StringFormat
format
          ,querystring_ :: [Text]
querystring_      = [Text]
querystring
          ,average_ :: Bool
average_          = String -> RawOpts -> Bool
boolopt String
"average" RawOpts
rawopts
          ,related_ :: Bool
related_          = String -> RawOpts -> Bool
boolopt String
"related" RawOpts
rawopts
          ,txn_dates_ :: Bool
txn_dates_        = String -> RawOpts -> Bool
boolopt String
"txn-dates" RawOpts
rawopts
          ,balancecalc_ :: BalanceCalculation
balancecalc_      = RawOpts -> BalanceCalculation
balancecalcopt RawOpts
rawopts
          ,balanceaccum_ :: BalanceAccumulation
balanceaccum_     = RawOpts -> BalanceAccumulation
balanceaccumopt RawOpts
rawopts
          ,budgetpat_ :: Maybe Text
budgetpat_        = RawOpts -> Maybe Text
maybebudgetpatternopt RawOpts
rawopts
          ,accountlistmode_ :: AccountListMode
accountlistmode_  = RawOpts -> AccountListMode
accountlistmodeopt RawOpts
rawopts
          ,drop_ :: Int
drop_             = String -> RawOpts -> Int
posintopt String
"drop" RawOpts
rawopts
          ,declared_ :: Bool
declared_         = String -> RawOpts -> Bool
boolopt String
"declared" RawOpts
rawopts
          ,row_total_ :: Bool
row_total_        = String -> RawOpts -> Bool
boolopt String
"row-total" RawOpts
rawopts
          ,no_total_ :: Bool
no_total_         = String -> RawOpts -> Bool
boolopt String
"no-total" RawOpts
rawopts
          ,show_costs_ :: Bool
show_costs_       = String -> RawOpts -> Bool
boolopt String
"show-costs" RawOpts
rawopts
          ,sort_amount_ :: Bool
sort_amount_      = String -> RawOpts -> Bool
boolopt String
"sort-amount" RawOpts
rawopts
          ,percent_ :: Bool
percent_          = String -> RawOpts -> Bool
boolopt String
"percent" RawOpts
rawopts
          ,invert_ :: Bool
invert_           = String -> RawOpts -> Bool
boolopt String
"invert" RawOpts
rawopts
          ,pretty_ :: Bool
pretty_           = Bool
pretty
          ,color_ :: Bool
color_            = Bool
useColorOnStdout 
          ,transpose_ :: Bool
transpose_        = String -> RawOpts -> Bool
boolopt String
"transpose" RawOpts
rawopts
          ,layout_ :: Layout
layout_           = RawOpts -> Layout
layoutopt RawOpts
rawopts
          }
data ReportSpec = ReportSpec
  { ReportSpec -> ReportOpts
_rsReportOpts :: ReportOpts  
  , ReportSpec -> Day
_rsDay        :: Day         
  , ReportSpec -> Query
_rsQuery      :: Query       
  , ReportSpec -> [QueryOpt]
_rsQueryOpts  :: [QueryOpt]  
  } deriving (Int -> ReportSpec -> ShowS
[ReportSpec] -> ShowS
ReportSpec -> String
(Int -> ReportSpec -> ShowS)
-> (ReportSpec -> String)
-> ([ReportSpec] -> ShowS)
-> Show ReportSpec
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReportSpec] -> ShowS
$cshowList :: [ReportSpec] -> ShowS
show :: ReportSpec -> String
$cshow :: ReportSpec -> String
showsPrec :: Int -> ReportSpec -> ShowS
$cshowsPrec :: Int -> ReportSpec -> ShowS
Show)
instance Default ReportSpec where def :: ReportSpec
def = ReportSpec
defreportspec
defreportspec :: ReportSpec
defreportspec :: ReportSpec
defreportspec = ReportSpec :: ReportOpts -> Day -> Query -> [QueryOpt] -> ReportSpec
ReportSpec
    { _rsReportOpts :: ReportOpts
_rsReportOpts = ReportOpts
forall a. Default a => a
def
    , _rsDay :: Day
_rsDay        = Day
nulldate
    , _rsQuery :: Query
_rsQuery      = Query
Any
    , _rsQueryOpts :: [QueryOpt]
_rsQueryOpts  = []
    }
setDefaultConversionOp :: ConversionOp -> ReportSpec -> ReportSpec
setDefaultConversionOp :: ConversionOp -> ReportSpec -> ReportSpec
setDefaultConversionOp ConversionOp
def rspec :: ReportSpec
rspec@ReportSpec{_rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts} =
    ReportSpec
rspec{_rsReportOpts :: ReportOpts
_rsReportOpts=ReportOpts
ropts{conversionop_ :: Maybe ConversionOp
conversionop_=ReportOpts -> Maybe ConversionOp
conversionop_ ReportOpts
ropts Maybe ConversionOp -> Maybe ConversionOp -> Maybe ConversionOp
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ConversionOp -> Maybe ConversionOp
forall a. a -> Maybe a
Just ConversionOp
def}}
accountlistmodeopt :: RawOpts -> AccountListMode
accountlistmodeopt :: RawOpts -> AccountListMode
accountlistmodeopt =
  AccountListMode -> Maybe AccountListMode -> AccountListMode
forall a. a -> Maybe a -> a
fromMaybe AccountListMode
ALFlat (Maybe AccountListMode -> AccountListMode)
-> (RawOpts -> Maybe AccountListMode) -> RawOpts -> AccountListMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Maybe AccountListMode)
-> RawOpts -> Maybe AccountListMode
forall a. (String -> Maybe a) -> RawOpts -> Maybe a
choiceopt String -> Maybe AccountListMode
parse where
    parse :: String -> Maybe AccountListMode
parse = \case
      String
"tree" -> AccountListMode -> Maybe AccountListMode
forall a. a -> Maybe a
Just AccountListMode
ALTree
      String
"flat" -> AccountListMode -> Maybe AccountListMode
forall a. a -> Maybe a
Just AccountListMode
ALFlat
      String
_      -> Maybe AccountListMode
forall a. Maybe a
Nothing
maybebudgetpatternopt :: RawOpts -> Maybe T.Text
maybebudgetpatternopt :: RawOpts -> Maybe Text
maybebudgetpatternopt = (String -> Text) -> Maybe String -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack (Maybe String -> Maybe Text)
-> (RawOpts -> Maybe String) -> RawOpts -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> RawOpts -> Maybe String
maybestringopt String
"budget"
balancecalcopt :: RawOpts -> BalanceCalculation
balancecalcopt :: RawOpts -> BalanceCalculation
balancecalcopt =
  BalanceCalculation
-> Maybe BalanceCalculation -> BalanceCalculation
forall a. a -> Maybe a -> a
fromMaybe BalanceCalculation
CalcChange (Maybe BalanceCalculation -> BalanceCalculation)
-> (RawOpts -> Maybe BalanceCalculation)
-> RawOpts
-> BalanceCalculation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Maybe BalanceCalculation)
-> RawOpts -> Maybe BalanceCalculation
forall a. (String -> Maybe a) -> RawOpts -> Maybe a
choiceopt String -> Maybe BalanceCalculation
parse where
    parse :: String -> Maybe BalanceCalculation
parse = \case
      String
"sum"         -> BalanceCalculation -> Maybe BalanceCalculation
forall a. a -> Maybe a
Just BalanceCalculation
CalcChange
      String
"valuechange" -> BalanceCalculation -> Maybe BalanceCalculation
forall a. a -> Maybe a
Just BalanceCalculation
CalcValueChange
      String
"gain"        -> BalanceCalculation -> Maybe BalanceCalculation
forall a. a -> Maybe a
Just BalanceCalculation
CalcGain
      String
"budget"      -> BalanceCalculation -> Maybe BalanceCalculation
forall a. a -> Maybe a
Just BalanceCalculation
CalcBudget
      String
_             -> Maybe BalanceCalculation
forall a. Maybe a
Nothing
balanceaccumopt :: RawOpts -> BalanceAccumulation
balanceaccumopt :: RawOpts -> BalanceAccumulation
balanceaccumopt = BalanceAccumulation
-> Maybe BalanceAccumulation -> BalanceAccumulation
forall a. a -> Maybe a -> a
fromMaybe BalanceAccumulation
PerPeriod (Maybe BalanceAccumulation -> BalanceAccumulation)
-> (RawOpts -> Maybe BalanceAccumulation)
-> RawOpts
-> BalanceAccumulation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RawOpts -> Maybe BalanceAccumulation
balanceAccumulationOverride
alwaysneveropt :: String -> RawOpts -> Maybe Bool
alwaysneveropt :: String -> RawOpts -> Maybe Bool
alwaysneveropt String
opt RawOpts
rawopts = case String -> RawOpts -> Maybe String
maybestringopt String
opt RawOpts
rawopts of
    Just String
"always" -> Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
    Just String
"yes"    -> Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
    Just String
"y"      -> Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True
    Just String
"never"  -> Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
    Just String
"no"     -> Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
    Just String
"n"      -> Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
False
    Just String
_        -> String -> Maybe Bool
forall a. String -> a
usageError String
"--pretty's argument should be \"yes\" or \"no\" (or y, n, always, never)"
    Maybe String
_             -> Maybe Bool
forall a. Maybe a
Nothing
balanceAccumulationOverride :: RawOpts -> Maybe BalanceAccumulation
balanceAccumulationOverride :: RawOpts -> Maybe BalanceAccumulation
balanceAccumulationOverride RawOpts
rawopts = (String -> Maybe BalanceAccumulation)
-> RawOpts -> Maybe BalanceAccumulation
forall a. (String -> Maybe a) -> RawOpts -> Maybe a
choiceopt String -> Maybe BalanceAccumulation
parse RawOpts
rawopts Maybe BalanceAccumulation
-> Maybe BalanceAccumulation -> Maybe BalanceAccumulation
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe BalanceAccumulation
reportbal
  where
    parse :: String -> Maybe BalanceAccumulation
parse = \case
      String
"historical" -> BalanceAccumulation -> Maybe BalanceAccumulation
forall a. a -> Maybe a
Just BalanceAccumulation
Historical
      String
"cumulative" -> BalanceAccumulation -> Maybe BalanceAccumulation
forall a. a -> Maybe a
Just BalanceAccumulation
Cumulative
      String
"change"     -> BalanceAccumulation -> Maybe BalanceAccumulation
forall a. a -> Maybe a
Just BalanceAccumulation
PerPeriod
      String
_            -> Maybe BalanceAccumulation
forall a. Maybe a
Nothing
    reportbal :: Maybe BalanceAccumulation
reportbal = case RawOpts -> BalanceCalculation
balancecalcopt RawOpts
rawopts of
      BalanceCalculation
CalcValueChange -> BalanceAccumulation -> Maybe BalanceAccumulation
forall a. a -> Maybe a
Just BalanceAccumulation
PerPeriod
      BalanceCalculation
_               -> Maybe BalanceAccumulation
forall a. Maybe a
Nothing
layoutopt :: RawOpts -> Layout
layoutopt :: RawOpts -> Layout
layoutopt RawOpts
rawopts = Layout -> Maybe Layout -> Layout
forall a. a -> Maybe a -> a
fromMaybe (Maybe Int -> Layout
LayoutWide Maybe Int
forall a. Maybe a
Nothing) (Maybe Layout -> Layout) -> Maybe Layout -> Layout
forall a b. (a -> b) -> a -> b
$ Maybe Layout
layout Maybe Layout -> Maybe Layout -> Maybe Layout
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Layout
column
  where
    layout :: Maybe Layout
layout = String -> Layout
parse (String -> Layout) -> Maybe String -> Maybe Layout
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> RawOpts -> Maybe String
maybestringopt String
"layout" RawOpts
rawopts
    column :: Maybe Layout
column = Layout
LayoutBare Layout -> Maybe () -> Maybe Layout
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (String -> RawOpts -> Bool
boolopt String
"commodity-column" RawOpts
rawopts)
    parse :: String -> Layout
parse String
opt = Layout
-> ((String, Layout) -> Layout) -> Maybe (String, Layout) -> Layout
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Layout
forall a. a
err (String, Layout) -> Layout
forall a b. (a, b) -> b
snd (Maybe (String, Layout) -> Layout)
-> Maybe (String, Layout) -> Layout
forall a b. (a -> b) -> a -> b
$ Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
s) Maybe () -> Maybe (String, Layout) -> Maybe (String, Layout)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ((String, Layout) -> Bool)
-> [(String, Layout)] -> Maybe (String, Layout)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf String
s (String -> Bool)
-> ((String, Layout) -> String) -> (String, Layout) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, Layout) -> String
forall a b. (a, b) -> a
fst) [(String, Layout)]
checkNames
      where
        checkNames :: [(String, Layout)]
checkNames = [ (String
"wide", Maybe Int -> Layout
LayoutWide Maybe Int
w)
                     , (String
"tall", Layout
LayoutTall)
                     , (String
"bare", Layout
LayoutBare)
                     , (String
"tidy", Layout
LayoutTidy)
                     ]
        
        (String
s,String
n) = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
',') (String -> (String, String)) -> String -> (String, String)
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower String
opt
        w :: Maybe Int
w = case Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
1 String
n of
              String
"" -> Maybe Int
forall a. Maybe a
Nothing
              String
c | Just Int
w <- String -> Maybe Int
forall a. Read a => String -> Maybe a
readMay String
c -> Int -> Maybe Int
forall a. a -> Maybe a
Just Int
w
              String
_ -> String -> Maybe Int
forall a. String -> a
usageError String
"width in --layout=wide,WIDTH must be an integer"
        err :: a
err = String -> a
forall a. String -> a
usageError String
"--layout's argument should be \"wide[,WIDTH]\", \"tall\", \"bare\", or \"tidy\""
periodFromRawOpts :: Day -> RawOpts -> Period
periodFromRawOpts :: Day -> RawOpts -> Period
periodFromRawOpts Day
d RawOpts
rawopts =
  case (Maybe Day
mlastb, Maybe Day
mlaste) of
    (Maybe Day
Nothing, Maybe Day
Nothing) -> Period
PeriodAll
    (Just Day
b, Maybe Day
Nothing)  -> Day -> Period
PeriodFrom Day
b
    (Maybe Day
Nothing, Just Day
e)  -> Day -> Period
PeriodTo Day
e
    (Just Day
b, Just Day
e)   -> Period -> Period
simplifyPeriod (Period -> Period) -> Period -> Period
forall a b. (a -> b) -> a -> b
$ Day -> Day -> Period
PeriodBetween Day
b Day
e
  where
    mlastb :: Maybe Day
mlastb = case Day -> RawOpts -> [Day]
beginDatesFromRawOpts Day
d RawOpts
rawopts of
                   [] -> Maybe Day
forall a. Maybe a
Nothing
                   [Day]
bs -> Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ [Day] -> Day
forall a. [a] -> a
last [Day]
bs
    mlaste :: Maybe Day
mlaste = case Day -> RawOpts -> [Day]
endDatesFromRawOpts Day
d RawOpts
rawopts of
                   [] -> Maybe Day
forall a. Maybe a
Nothing
                   [Day]
es -> Day -> Maybe Day
forall a. a -> Maybe a
Just (Day -> Maybe Day) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ [Day] -> Day
forall a. [a] -> a
last [Day]
es
beginDatesFromRawOpts :: Day -> RawOpts -> [Day]
beginDatesFromRawOpts :: Day -> RawOpts -> [Day]
beginDatesFromRawOpts Day
d = ((String, String) -> Maybe Day) -> RawOpts -> [Day]
forall a. ((String, String) -> Maybe a) -> RawOpts -> [a]
collectopts (Day -> (String, String) -> Maybe Day
begindatefromrawopt Day
d)
  where
    begindatefromrawopt :: Day -> (String, String) -> Maybe Day
begindatefromrawopt Day
d (String
n,String
v)
      | String
n String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"begin" =
          (HledgerParseErrors -> Maybe Day)
-> (Day -> Maybe Day) -> Either HledgerParseErrors Day -> Maybe Day
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (\HledgerParseErrors
e -> String -> Maybe Day
forall a. String -> a
usageError (String -> Maybe Day) -> String -> Maybe Day
forall a b. (a -> b) -> a -> b
$ String
"could not parse "String -> ShowS
forall a. [a] -> [a] -> [a]
++String
nString -> ShowS
forall a. [a] -> [a] -> [a]
++String
" date: "String -> ShowS
forall a. [a] -> [a] -> [a]
++HledgerParseErrors -> String
customErrorBundlePretty HledgerParseErrors
e) Day -> Maybe Day
forall a. a -> Maybe a
Just (Either HledgerParseErrors Day -> Maybe Day)
-> Either HledgerParseErrors Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$
          Day -> Text -> Either HledgerParseErrors Day
fixSmartDateStrEither' Day
d (String -> Text
T.pack String
v)
      | String
n String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"period" =
        case
          (HledgerParseErrors -> (Interval, DateSpan))
-> ((Interval, DateSpan) -> (Interval, DateSpan))
-> Either HledgerParseErrors (Interval, DateSpan)
-> (Interval, DateSpan)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (\HledgerParseErrors
e -> String -> (Interval, DateSpan)
forall a. String -> a
usageError (String -> (Interval, DateSpan)) -> String -> (Interval, DateSpan)
forall a b. (a -> b) -> a -> b
$ String
"could not parse period option: "String -> ShowS
forall a. [a] -> [a] -> [a]
++HledgerParseErrors -> String
customErrorBundlePretty HledgerParseErrors
e) (Interval, DateSpan) -> (Interval, DateSpan)
forall a. a -> a
id (Either HledgerParseErrors (Interval, DateSpan)
 -> (Interval, DateSpan))
-> Either HledgerParseErrors (Interval, DateSpan)
-> (Interval, DateSpan)
forall a b. (a -> b) -> a -> b
$
          Day -> Text -> Either HledgerParseErrors (Interval, DateSpan)
parsePeriodExpr Day
d (Text -> Text
stripquotes (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
v)
        of
          (Interval
_, DateSpan (Just Day
b) Maybe Day
_) -> Day -> Maybe Day
forall a. a -> Maybe a
Just Day
b
          (Interval, DateSpan)
_                        -> Maybe Day
forall a. Maybe a
Nothing
      | Bool
otherwise = Maybe Day
forall a. Maybe a
Nothing
endDatesFromRawOpts :: Day -> RawOpts -> [Day]
endDatesFromRawOpts :: Day -> RawOpts -> [Day]
endDatesFromRawOpts Day
d = ((String, String) -> Maybe Day) -> RawOpts -> [Day]
forall a. ((String, String) -> Maybe a) -> RawOpts -> [a]
collectopts (Day -> (String, String) -> Maybe Day
enddatefromrawopt Day
d)
  where
    enddatefromrawopt :: Day -> (String, String) -> Maybe Day
enddatefromrawopt Day
d (String
n,String
v)
      | String
n String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"end" =
          (HledgerParseErrors -> Maybe Day)
-> (Day -> Maybe Day) -> Either HledgerParseErrors Day -> Maybe Day
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (\HledgerParseErrors
e -> String -> Maybe Day
forall a. String -> a
usageError (String -> Maybe Day) -> String -> Maybe Day
forall a b. (a -> b) -> a -> b
$ String
"could not parse "String -> ShowS
forall a. [a] -> [a] -> [a]
++String
nString -> ShowS
forall a. [a] -> [a] -> [a]
++String
" date: "String -> ShowS
forall a. [a] -> [a] -> [a]
++HledgerParseErrors -> String
customErrorBundlePretty HledgerParseErrors
e) Day -> Maybe Day
forall a. a -> Maybe a
Just (Either HledgerParseErrors Day -> Maybe Day)
-> Either HledgerParseErrors Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$
          Day -> Text -> Either HledgerParseErrors Day
fixSmartDateStrEither' Day
d (String -> Text
T.pack String
v)
      | String
n String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"period" =
        case
          (HledgerParseErrors -> (Interval, DateSpan))
-> ((Interval, DateSpan) -> (Interval, DateSpan))
-> Either HledgerParseErrors (Interval, DateSpan)
-> (Interval, DateSpan)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (\HledgerParseErrors
e -> String -> (Interval, DateSpan)
forall a. String -> a
usageError (String -> (Interval, DateSpan)) -> String -> (Interval, DateSpan)
forall a b. (a -> b) -> a -> b
$ String
"could not parse period option: "String -> ShowS
forall a. [a] -> [a] -> [a]
++HledgerParseErrors -> String
customErrorBundlePretty HledgerParseErrors
e) (Interval, DateSpan) -> (Interval, DateSpan)
forall a. a -> a
id (Either HledgerParseErrors (Interval, DateSpan)
 -> (Interval, DateSpan))
-> Either HledgerParseErrors (Interval, DateSpan)
-> (Interval, DateSpan)
forall a b. (a -> b) -> a -> b
$
          Day -> Text -> Either HledgerParseErrors (Interval, DateSpan)
parsePeriodExpr Day
d (Text -> Text
stripquotes (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
v)
        of
          (Interval
_, DateSpan Maybe Day
_ (Just Day
e)) -> Day -> Maybe Day
forall a. a -> Maybe a
Just Day
e
          (Interval, DateSpan)
_                        -> Maybe Day
forall a. Maybe a
Nothing
      | Bool
otherwise = Maybe Day
forall a. Maybe a
Nothing
intervalFromRawOpts :: RawOpts -> Interval
intervalFromRawOpts :: RawOpts -> Interval
intervalFromRawOpts = Interval -> [Interval] -> Interval
forall a. a -> [a] -> a
lastDef Interval
NoInterval ([Interval] -> Interval)
-> (RawOpts -> [Interval]) -> RawOpts -> Interval
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, String) -> Maybe Interval) -> RawOpts -> [Interval]
forall a. ((String, String) -> Maybe a) -> RawOpts -> [a]
collectopts (String, String) -> Maybe Interval
forall a. (Eq a, IsString a) => (a, String) -> Maybe Interval
intervalfromrawopt
  where
    intervalfromrawopt :: (a, String) -> Maybe Interval
intervalfromrawopt (a
n,String
v)
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"period" =
          (HledgerParseErrors -> Maybe Interval)
-> ((Interval, DateSpan) -> Maybe Interval)
-> Either HledgerParseErrors (Interval, DateSpan)
-> Maybe Interval
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
            (\HledgerParseErrors
e -> String -> Maybe Interval
forall a. String -> a
usageError (String -> Maybe Interval) -> String -> Maybe Interval
forall a b. (a -> b) -> a -> b
$ String
"could not parse period option: "String -> ShowS
forall a. [a] -> [a] -> [a]
++HledgerParseErrors -> String
customErrorBundlePretty HledgerParseErrors
e)
            (Interval, DateSpan) -> Maybe Interval
extractIntervalOrNothing (Either HledgerParseErrors (Interval, DateSpan) -> Maybe Interval)
-> Either HledgerParseErrors (Interval, DateSpan) -> Maybe Interval
forall a b. (a -> b) -> a -> b
$
            Day -> Text -> Either HledgerParseErrors (Interval, DateSpan)
parsePeriodExpr
              (String -> Day
forall a. String -> a
error' String
"intervalFromRawOpts: did not expect to need today's date here")  
              (Text -> Text
stripquotes (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
v)
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"daily"     = Interval -> Maybe Interval
forall a. a -> Maybe a
Just (Interval -> Maybe Interval) -> Interval -> Maybe Interval
forall a b. (a -> b) -> a -> b
$ Int -> Interval
Days Int
1
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"weekly"    = Interval -> Maybe Interval
forall a. a -> Maybe a
Just (Interval -> Maybe Interval) -> Interval -> Maybe Interval
forall a b. (a -> b) -> a -> b
$ Int -> Interval
Weeks Int
1
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"monthly"   = Interval -> Maybe Interval
forall a. a -> Maybe a
Just (Interval -> Maybe Interval) -> Interval -> Maybe Interval
forall a b. (a -> b) -> a -> b
$ Int -> Interval
Months Int
1
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"quarterly" = Interval -> Maybe Interval
forall a. a -> Maybe a
Just (Interval -> Maybe Interval) -> Interval -> Maybe Interval
forall a b. (a -> b) -> a -> b
$ Int -> Interval
Quarters Int
1
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"yearly"    = Interval -> Maybe Interval
forall a. a -> Maybe a
Just (Interval -> Maybe Interval) -> Interval -> Maybe Interval
forall a b. (a -> b) -> a -> b
$ Int -> Interval
Years Int
1
      | Bool
otherwise = Maybe Interval
forall a. Maybe a
Nothing
extractIntervalOrNothing :: (Interval, DateSpan) -> Maybe Interval
 (Interval
NoInterval, DateSpan
_) = Maybe Interval
forall a. Maybe a
Nothing
extractIntervalOrNothing (Interval
interval, DateSpan
_) = Interval -> Maybe Interval
forall a. a -> Maybe a
Just Interval
interval
statusesFromRawOpts :: RawOpts -> [Status]
statusesFromRawOpts :: RawOpts -> [Status]
statusesFromRawOpts = [Status] -> [Status]
forall a. Ord a => [a] -> [a]
simplifyStatuses ([Status] -> [Status])
-> (RawOpts -> [Status]) -> RawOpts -> [Status]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, String) -> Maybe Status) -> RawOpts -> [Status]
forall a. ((String, String) -> Maybe a) -> RawOpts -> [a]
collectopts (String, String) -> Maybe Status
forall a b. (Eq a, IsString a) => (a, b) -> Maybe Status
statusfromrawopt
  where
    statusfromrawopt :: (a, b) -> Maybe Status
statusfromrawopt (a
n,b
_)
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"unmarked"  = Status -> Maybe Status
forall a. a -> Maybe a
Just Status
Unmarked
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"pending"   = Status -> Maybe Status
forall a. a -> Maybe a
Just Status
Pending
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"cleared"   = Status -> Maybe Status
forall a. a -> Maybe a
Just Status
Cleared
      | Bool
otherwise        = Maybe Status
forall a. Maybe a
Nothing
simplifyStatuses :: [a] -> [a]
simplifyStatuses [a]
l
  | [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
l' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
numstatuses = []
  | Bool
otherwise                = [a]
l'
  where
    l' :: [a]
l' = [a] -> [a]
forall a. Ord a => [a] -> [a]
nubSort [a]
l
    numstatuses :: Int
numstatuses = [Status] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Status
forall a. Bounded a => a
minBound .. Status
forall a. Bounded a => a
maxBound :: Status]
reportOptsToggleStatus :: Status -> ReportOpts -> ReportOpts
reportOptsToggleStatus Status
s ropts :: ReportOpts
ropts@ReportOpts{statuses_ :: ReportOpts -> [Status]
statuses_=[Status]
ss}
  | Status
s Status -> [Status] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Status]
ss = ReportOpts
ropts{statuses_ :: [Status]
statuses_=(Status -> Bool) -> [Status] -> [Status]
forall a. (a -> Bool) -> [a] -> [a]
filter (Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
/= Status
s) [Status]
ss}
  | Bool
otherwise   = ReportOpts
ropts{statuses_ :: [Status]
statuses_=[Status] -> [Status]
forall a. Ord a => [a] -> [a]
simplifyStatuses (Status
sStatus -> [Status] -> [Status]
forall a. a -> [a] -> [a]
:[Status]
ss)}
valuationTypeFromRawOpts :: RawOpts -> Maybe ValuationType
valuationTypeFromRawOpts :: RawOpts -> Maybe ValuationType
valuationTypeFromRawOpts RawOpts
rawopts = case (RawOpts -> BalanceCalculation
balancecalcopt RawOpts
rawopts, Maybe ValuationType
directval) of
    (BalanceCalculation
CalcValueChange, Maybe ValuationType
Nothing       ) -> ValuationType -> Maybe ValuationType
forall a. a -> Maybe a
Just (ValuationType -> Maybe ValuationType)
-> ValuationType -> Maybe ValuationType
forall a b. (a -> b) -> a -> b
$ Maybe Text -> ValuationType
AtEnd Maybe Text
forall a. Maybe a
Nothing  
    (BalanceCalculation
CalcValueChange, Just (AtEnd Maybe Text
_)) -> Maybe ValuationType
directval             
    (BalanceCalculation
CalcValueChange, Maybe ValuationType
_             ) -> String -> Maybe ValuationType
forall a. String -> a
usageError String
"--valuechange only produces sensible results with --value=end"
    (BalanceCalculation
CalcGain,        Maybe ValuationType
Nothing       ) -> ValuationType -> Maybe ValuationType
forall a. a -> Maybe a
Just (ValuationType -> Maybe ValuationType)
-> ValuationType -> Maybe ValuationType
forall a b. (a -> b) -> a -> b
$ Maybe Text -> ValuationType
AtEnd Maybe Text
forall a. Maybe a
Nothing  
    (BalanceCalculation
_,               Maybe ValuationType
_             ) -> Maybe ValuationType
directval             
  where
    directval :: Maybe ValuationType
directval = [ValuationType] -> Maybe ValuationType
forall a. [a] -> Maybe a
lastMay ([ValuationType] -> Maybe ValuationType)
-> [ValuationType] -> Maybe ValuationType
forall a b. (a -> b) -> a -> b
$ ((String, String) -> Maybe ValuationType)
-> RawOpts -> [ValuationType]
forall a. ((String, String) -> Maybe a) -> RawOpts -> [a]
collectopts (String, String) -> Maybe ValuationType
forall a. (Eq a, IsString a) => (a, String) -> Maybe ValuationType
valuationfromrawopt RawOpts
rawopts
    valuationfromrawopt :: (a, String) -> Maybe ValuationType
valuationfromrawopt (a
n,String
v)  
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"V"     = ValuationType -> Maybe ValuationType
forall a. a -> Maybe a
Just (ValuationType -> Maybe ValuationType)
-> ValuationType -> Maybe ValuationType
forall a b. (a -> b) -> a -> b
$ Maybe Text -> ValuationType
AtEnd Maybe Text
forall a. Maybe a
Nothing
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"X"     = ValuationType -> Maybe ValuationType
forall a. a -> Maybe a
Just (ValuationType -> Maybe ValuationType)
-> ValuationType -> Maybe ValuationType
forall a b. (a -> b) -> a -> b
$ Maybe Text -> ValuationType
AtEnd (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
v)
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"value" = String -> Maybe ValuationType
valueopt String
v
      | Bool
otherwise    = Maybe ValuationType
forall a. Maybe a
Nothing
    valueopt :: String -> Maybe ValuationType
valueopt String
v
      | String
t String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"cost",String
"c"]  = Maybe Text -> ValuationType
AtEnd (Maybe Text -> ValuationType)
-> (Text -> Maybe Text) -> Text -> ValuationType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> ValuationType) -> Maybe Text -> Maybe ValuationType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
mc  
      | String
t String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"then" ,String
"t"] = ValuationType -> Maybe ValuationType
forall a. a -> Maybe a
Just (ValuationType -> Maybe ValuationType)
-> ValuationType -> Maybe ValuationType
forall a b. (a -> b) -> a -> b
$ Maybe Text -> ValuationType
AtThen Maybe Text
mc
      | String
t String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"end" ,String
"e"]  = ValuationType -> Maybe ValuationType
forall a. a -> Maybe a
Just (ValuationType -> Maybe ValuationType)
-> ValuationType -> Maybe ValuationType
forall a b. (a -> b) -> a -> b
$ Maybe Text -> ValuationType
AtEnd  Maybe Text
mc
      | String
t String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"now" ,String
"n"]  = ValuationType -> Maybe ValuationType
forall a. a -> Maybe a
Just (ValuationType -> Maybe ValuationType)
-> ValuationType -> Maybe ValuationType
forall a b. (a -> b) -> a -> b
$ Maybe Text -> ValuationType
AtNow  Maybe Text
mc
      | Bool
otherwise = case String -> Maybe Day
parsedateM String
t of
            Just Day
d  -> ValuationType -> Maybe ValuationType
forall a. a -> Maybe a
Just (ValuationType -> Maybe ValuationType)
-> ValuationType -> Maybe ValuationType
forall a b. (a -> b) -> a -> b
$ Day -> Maybe Text -> ValuationType
AtDate Day
d Maybe Text
mc
            Maybe Day
Nothing -> String -> Maybe ValuationType
forall a. String -> a
usageError (String -> Maybe ValuationType) -> String -> Maybe ValuationType
forall a b. (a -> b) -> a -> b
$ String
"could not parse \""String -> ShowS
forall a. [a] -> [a] -> [a]
++String
tString -> ShowS
forall a. [a] -> [a] -> [a]
++String
"\" as valuation type, should be: then|end|now|t|e|n|YYYY-MM-DD"
      where
        
        (String
t,String
c') = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
',') String
v
        mc :: Maybe Text
mc     = case Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
1 String
c' of
                   String
"" -> Maybe Text
forall a. Maybe a
Nothing
                   String
c  -> Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
c
conversionOpFromRawOpts :: RawOpts -> Maybe ConversionOp
conversionOpFromRawOpts :: RawOpts -> Maybe ConversionOp
conversionOpFromRawOpts RawOpts
rawopts
    | Maybe ConversionOp -> Bool
forall a. Maybe a -> Bool
isJust Maybe ConversionOp
costFlag Bool -> Bool -> Bool
&& RawOpts -> BalanceCalculation
balancecalcopt RawOpts
rawopts BalanceCalculation -> BalanceCalculation -> Bool
forall a. Eq a => a -> a -> Bool
== BalanceCalculation
CalcGain = String -> Maybe ConversionOp
forall a. String -> a
usageError String
"--gain cannot be combined with --cost"
    | Bool
otherwise = Maybe ConversionOp
costFlag
  where
    costFlag :: Maybe ConversionOp
costFlag = [ConversionOp] -> Maybe ConversionOp
forall a. [a] -> Maybe a
lastMay ([ConversionOp] -> Maybe ConversionOp)
-> [ConversionOp] -> Maybe ConversionOp
forall a b. (a -> b) -> a -> b
$ ((String, String) -> Maybe ConversionOp)
-> RawOpts -> [ConversionOp]
forall a. ((String, String) -> Maybe a) -> RawOpts -> [a]
collectopts (String, String) -> Maybe ConversionOp
forall a. (Eq a, IsString a) => (a, String) -> Maybe ConversionOp
conversionopfromrawopt RawOpts
rawopts
    conversionopfromrawopt :: (a, String) -> Maybe ConversionOp
conversionopfromrawopt (a
n,String
v)  
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"B"                                    = ConversionOp -> Maybe ConversionOp
forall a. a -> Maybe a
Just ConversionOp
ToCost
      | a
n a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
"value", (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
',') String
v String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"cost", String
"c"] = ConversionOp -> Maybe ConversionOp
forall a. a -> Maybe a
Just ConversionOp
ToCost  
      | Bool
otherwise                                   = Maybe ConversionOp
forall a. Maybe a
Nothing
transactionDateFn :: ReportOpts -> (Transaction -> Day)
transactionDateFn :: ReportOpts -> Transaction -> Day
transactionDateFn ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe Text
Maybe NormalSign
Maybe ValuationType
Maybe ConversionOp
Interval
Period
StringFormat
Layout
AccountListMode
BalanceAccumulation
BalanceCalculation
layout_ :: Layout
transpose_ :: Bool
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
show_costs_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
declared_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
budgetpat_ :: Maybe Text
balanceaccum_ :: BalanceAccumulation
balancecalc_ :: BalanceCalculation
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
pretty_ :: Bool
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_prices_ :: Bool
value_ :: Maybe ValuationType
conversionop_ :: Maybe ConversionOp
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
layout_ :: ReportOpts -> Layout
transpose_ :: ReportOpts -> Bool
color_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
invert_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
show_costs_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
row_total_ :: ReportOpts -> Bool
declared_ :: ReportOpts -> Bool
drop_ :: ReportOpts -> Int
accountlistmode_ :: ReportOpts -> AccountListMode
budgetpat_ :: ReportOpts -> Maybe Text
balanceaccum_ :: ReportOpts -> BalanceAccumulation
balancecalc_ :: ReportOpts -> BalanceCalculation
txn_dates_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
average_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [Text]
pretty_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
real_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
date2_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
infer_prices_ :: ReportOpts -> Bool
value_ :: ReportOpts -> Maybe ValuationType
conversionop_ :: ReportOpts -> Maybe ConversionOp
statuses_ :: ReportOpts -> [Status]
interval_ :: ReportOpts -> Interval
period_ :: ReportOpts -> Period
..} = if Bool
date2_ then Transaction -> Day
transactionDate2 else Transaction -> Day
tdate
postingDateFn :: ReportOpts -> (Posting -> Day)
postingDateFn :: ReportOpts -> Posting -> Day
postingDateFn ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe Text
Maybe NormalSign
Maybe ValuationType
Maybe ConversionOp
Interval
Period
StringFormat
Layout
AccountListMode
BalanceAccumulation
BalanceCalculation
layout_ :: Layout
transpose_ :: Bool
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
show_costs_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
declared_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
budgetpat_ :: Maybe Text
balanceaccum_ :: BalanceAccumulation
balancecalc_ :: BalanceCalculation
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
pretty_ :: Bool
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_prices_ :: Bool
value_ :: Maybe ValuationType
conversionop_ :: Maybe ConversionOp
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
layout_ :: ReportOpts -> Layout
transpose_ :: ReportOpts -> Bool
color_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
invert_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
show_costs_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
row_total_ :: ReportOpts -> Bool
declared_ :: ReportOpts -> Bool
drop_ :: ReportOpts -> Int
accountlistmode_ :: ReportOpts -> AccountListMode
budgetpat_ :: ReportOpts -> Maybe Text
balanceaccum_ :: ReportOpts -> BalanceAccumulation
balancecalc_ :: ReportOpts -> BalanceCalculation
txn_dates_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
average_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [Text]
pretty_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
real_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
date2_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
infer_prices_ :: ReportOpts -> Bool
value_ :: ReportOpts -> Maybe ValuationType
conversionop_ :: ReportOpts -> Maybe ConversionOp
statuses_ :: ReportOpts -> [Status]
interval_ :: ReportOpts -> Interval
period_ :: ReportOpts -> Period
..} = if Bool
date2_ then Posting -> Day
postingDate2 else Posting -> Day
postingDate
whichDate :: ReportOpts -> WhichDate
whichDate :: ReportOpts -> WhichDate
whichDate ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe Text
Maybe NormalSign
Maybe ValuationType
Maybe ConversionOp
Interval
Period
StringFormat
Layout
AccountListMode
BalanceAccumulation
BalanceCalculation
layout_ :: Layout
transpose_ :: Bool
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
show_costs_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
declared_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
budgetpat_ :: Maybe Text
balanceaccum_ :: BalanceAccumulation
balancecalc_ :: BalanceCalculation
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
pretty_ :: Bool
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_prices_ :: Bool
value_ :: Maybe ValuationType
conversionop_ :: Maybe ConversionOp
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
layout_ :: ReportOpts -> Layout
transpose_ :: ReportOpts -> Bool
color_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
invert_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
show_costs_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
row_total_ :: ReportOpts -> Bool
declared_ :: ReportOpts -> Bool
drop_ :: ReportOpts -> Int
accountlistmode_ :: ReportOpts -> AccountListMode
budgetpat_ :: ReportOpts -> Maybe Text
balanceaccum_ :: ReportOpts -> BalanceAccumulation
balancecalc_ :: ReportOpts -> BalanceCalculation
txn_dates_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
average_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [Text]
pretty_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
real_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
date2_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
infer_prices_ :: ReportOpts -> Bool
value_ :: ReportOpts -> Maybe ValuationType
conversionop_ :: ReportOpts -> Maybe ConversionOp
statuses_ :: ReportOpts -> [Status]
interval_ :: ReportOpts -> Interval
period_ :: ReportOpts -> Period
..} = if Bool
date2_ then WhichDate
SecondaryDate else WhichDate
PrimaryDate
tree_ :: ReportOpts -> Bool
tree_ :: ReportOpts -> Bool
tree_ ReportOpts{accountlistmode_ :: ReportOpts -> AccountListMode
accountlistmode_ = AccountListMode
ALTree} = Bool
True
tree_ ReportOpts{accountlistmode_ :: ReportOpts -> AccountListMode
accountlistmode_ = AccountListMode
ALFlat} = Bool
False
flat_ :: ReportOpts -> Bool
flat_ :: ReportOpts -> Bool
flat_ = Bool -> Bool
not (Bool -> Bool) -> (ReportOpts -> Bool) -> ReportOpts -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportOpts -> Bool
tree_
journalValueAndFilterPostings :: ReportSpec -> Journal -> Journal
journalValueAndFilterPostings :: ReportSpec -> Journal -> Journal
journalValueAndFilterPostings ReportSpec
rspec Journal
j = ReportSpec -> Journal -> PriceOracle -> Journal
journalValueAndFilterPostingsWith ReportSpec
rspec Journal
j PriceOracle
priceoracle
  where priceoracle :: PriceOracle
priceoracle = Bool -> Journal -> PriceOracle
journalPriceOracle (ReportOpts -> Bool
infer_prices_ (ReportOpts -> Bool) -> ReportOpts -> Bool
forall a b. (a -> b) -> a -> b
$ ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec) Journal
j
journalValueAndFilterPostingsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
journalValueAndFilterPostingsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
journalValueAndFilterPostingsWith rspec :: ReportSpec
rspec@ReportSpec{_rsQuery :: ReportSpec -> Query
_rsQuery=Query
q, _rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts} Journal
j =
    
      Query -> Journal -> Journal
filterJournal Query
reportq
    
    (Journal -> Journal)
-> (PriceOracle -> Journal) -> PriceOracle -> Journal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportSpec -> Journal -> PriceOracle -> Journal
journalApplyValuationFromOptsWith ReportSpec
rspec
    
      (if Query -> Bool
queryIsNull Query
amtsymq then Journal
j else Query -> Journal -> Journal
filterJournalAmounts Query
amtsymq Journal
j)
  where
    
    filterJournal :: Query -> Journal -> Journal
filterJournal = if ReportOpts -> Bool
related_ ReportOpts
ropts then Query -> Journal -> Journal
filterJournalRelatedPostings else Query -> Journal -> Journal
filterJournalPostings
    amtsymq :: Query
amtsymq = String -> Query -> Query
forall a. Show a => String -> a -> a
dbg3 String
"amtsymq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> Query -> Query
filterQuery Query -> Bool
queryIsAmtOrSym Query
q
    reportq :: Query
reportq = String -> Query -> Query
forall a. Show a => String -> a -> a
dbg3 String
"reportq" (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ (Query -> Bool) -> Query -> Query
filterQuery (Bool -> Bool
not (Bool -> Bool) -> (Query -> Bool) -> Query -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> Bool
queryIsAmtOrSym) Query
q
    queryIsAmtOrSym :: Query -> Bool
queryIsAmtOrSym = (Bool -> Bool -> Bool)
-> (Query -> Bool) -> (Query -> Bool) -> Query -> Bool
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Bool -> Bool -> Bool
(||) Query -> Bool
queryIsAmt Query -> Bool
queryIsSym
journalApplyValuationFromOpts :: ReportSpec -> Journal -> Journal
journalApplyValuationFromOpts :: ReportSpec -> Journal -> Journal
journalApplyValuationFromOpts ReportSpec
rspec Journal
j =
    ReportSpec -> Journal -> PriceOracle -> Journal
journalApplyValuationFromOptsWith ReportSpec
rspec Journal
j PriceOracle
priceoracle
  where priceoracle :: PriceOracle
priceoracle = Bool -> Journal -> PriceOracle
journalPriceOracle (ReportOpts -> Bool
infer_prices_ (ReportOpts -> Bool) -> ReportOpts -> Bool
forall a b. (a -> b) -> a -> b
$ ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec) Journal
j
journalApplyValuationFromOptsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
journalApplyValuationFromOptsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
journalApplyValuationFromOptsWith rspec :: ReportSpec
rspec@ReportSpec{_rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts} Journal
j PriceOracle
priceoracle =
    case ReportOpts -> BalanceCalculation
balancecalc_ ReportOpts
ropts of
      BalanceCalculation
CalcGain -> (Posting -> Posting) -> Journal -> Journal
journalMapPostings (\Posting
p -> (MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount (Posting -> MixedAmount -> MixedAmount
gain Posting
p) Posting
p) Journal
j
      BalanceCalculation
_        -> (Posting -> Posting) -> Journal -> Journal
journalMapPostings (\Posting
p -> (MixedAmount -> MixedAmount) -> Posting -> Posting
postingTransformAmount (Posting -> MixedAmount -> MixedAmount
valuation Posting
p) Posting
p) (Journal -> Journal) -> Journal -> Journal
forall a b. (a -> b) -> a -> b
$ Journal -> Journal
costing Journal
j
  where
    valuation :: Posting -> MixedAmount -> MixedAmount
valuation Posting
p = (MixedAmount -> MixedAmount)
-> (ValuationType -> MixedAmount -> MixedAmount)
-> Maybe ValuationType
-> MixedAmount
-> MixedAmount
forall b a. b -> (a -> b) -> Maybe a -> b
maybe MixedAmount -> MixedAmount
forall a. a -> a
id (PriceOracle
-> Map Text AmountStyle
-> Day
-> Day
-> Day
-> ValuationType
-> MixedAmount
-> MixedAmount
mixedAmountApplyValuation PriceOracle
priceoracle Map Text AmountStyle
styles (Posting -> Day
periodEnd Posting
p) (ReportSpec -> Day
_rsDay ReportSpec
rspec) (Posting -> Day
postingDate Posting
p)) (ReportOpts -> Maybe ValuationType
value_ ReportOpts
ropts)
    gain :: Posting -> MixedAmount -> MixedAmount
gain      Posting
p = (MixedAmount -> MixedAmount)
-> (ValuationType -> MixedAmount -> MixedAmount)
-> Maybe ValuationType
-> MixedAmount
-> MixedAmount
forall b a. b -> (a -> b) -> Maybe a -> b
maybe MixedAmount -> MixedAmount
forall a. a -> a
id (PriceOracle
-> Map Text AmountStyle
-> Day
-> Day
-> Day
-> ValuationType
-> MixedAmount
-> MixedAmount
mixedAmountApplyGain      PriceOracle
priceoracle Map Text AmountStyle
styles (Posting -> Day
periodEnd Posting
p) (ReportSpec -> Day
_rsDay ReportSpec
rspec) (Posting -> Day
postingDate Posting
p)) (ReportOpts -> Maybe ValuationType
value_ ReportOpts
ropts)
    costing :: Journal -> Journal
costing     = ConversionOp -> Journal -> Journal
journalToCost (ConversionOp -> Maybe ConversionOp -> ConversionOp
forall a. a -> Maybe a -> a
fromMaybe ConversionOp
NoConversionOp (Maybe ConversionOp -> ConversionOp)
-> Maybe ConversionOp -> ConversionOp
forall a b. (a -> b) -> a -> b
$ ReportOpts -> Maybe ConversionOp
conversionop_ ReportOpts
ropts)
    
    periodEnd :: Posting -> Day
periodEnd  = Integer -> Day -> Day
addDays (-Integer
1) (Day -> Day) -> (Posting -> Day) -> Posting -> Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> Maybe Day -> Day
forall a. a -> Maybe a -> a
fromMaybe Day
forall a. a
err (Maybe Day -> Day) -> (Posting -> Maybe Day) -> Posting -> Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> Maybe Day
mPeriodEnd (Day -> Maybe Day) -> (Posting -> Day) -> Posting -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WhichDate -> Posting -> Day
postingDateOrDate2 (ReportOpts -> WhichDate
whichDate ReportOpts
ropts)
    mPeriodEnd :: Day -> Maybe Day
mPeriodEnd = case ReportOpts -> Interval
interval_ ReportOpts
ropts of
        Interval
NoInterval -> Maybe Day -> Day -> Maybe Day
forall a b. a -> b -> a
const (Maybe Day -> Day -> Maybe Day)
-> ((DateSpan, [DateSpan]) -> Maybe Day)
-> (DateSpan, [DateSpan])
-> Day
-> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DateSpan -> Maybe Day
spanEnd (DateSpan -> Maybe Day)
-> ((DateSpan, [DateSpan]) -> DateSpan)
-> (DateSpan, [DateSpan])
-> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DateSpan, [DateSpan]) -> DateSpan
forall a b. (a, b) -> a
fst ((DateSpan, [DateSpan]) -> Day -> Maybe Day)
-> (DateSpan, [DateSpan]) -> Day -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpan Journal
j ReportSpec
rspec
        Interval
_          -> DateSpan -> Maybe Day
spanEnd (DateSpan -> Maybe Day)
-> (Day -> Maybe DateSpan) -> Day -> Maybe Day
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< [DateSpan] -> Day -> Maybe DateSpan
latestSpanContaining (DateSpan
historical DateSpan -> [DateSpan] -> [DateSpan]
forall a. a -> [a] -> [a]
: [DateSpan]
spans)
    historical :: DateSpan
historical = Maybe Day -> Maybe Day -> DateSpan
DateSpan Maybe Day
forall a. Maybe a
Nothing (Maybe Day -> DateSpan) -> Maybe Day -> DateSpan
forall a b. (a -> b) -> a -> b
$ DateSpan -> Maybe Day
spanStart (DateSpan -> Maybe Day) -> Maybe DateSpan -> Maybe Day
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [DateSpan] -> Maybe DateSpan
forall a. [a] -> Maybe a
headMay [DateSpan]
spans
    spans :: [DateSpan]
spans = (DateSpan, [DateSpan]) -> [DateSpan]
forall a b. (a, b) -> b
snd ((DateSpan, [DateSpan]) -> [DateSpan])
-> (DateSpan, [DateSpan]) -> [DateSpan]
forall a b. (a -> b) -> a -> b
$ Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpanBothDates Journal
j ReportSpec
rspec
    styles :: Map Text AmountStyle
styles = Journal -> Map Text AmountStyle
journalCommodityStyles Journal
j
    err :: a
err = String -> a
forall a. HasCallStack => String -> a
error String
"journalApplyValuationFromOpts: expected all spans to have an end date"
mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceOracle
                                              -> (DateSpan -> MixedAmount -> MixedAmount)
mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts
-> Journal -> PriceOracle -> DateSpan -> MixedAmount -> MixedAmount
mixedAmountApplyValuationAfterSumFromOptsWith ReportOpts
ropts Journal
j PriceOracle
priceoracle =
    case ReportOpts -> Maybe (Maybe Text)
valuationAfterSum ReportOpts
ropts of
        Just Maybe Text
mc -> case ReportOpts -> BalanceCalculation
balancecalc_ ReportOpts
ropts of
            BalanceCalculation
CalcGain -> Maybe Text -> DateSpan -> MixedAmount -> MixedAmount
gain Maybe Text
mc
            BalanceCalculation
_        -> \DateSpan
span -> Maybe Text -> DateSpan -> MixedAmount -> MixedAmount
valuation Maybe Text
mc DateSpan
span (MixedAmount -> MixedAmount)
-> (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MixedAmount -> MixedAmount
costing
        Maybe (Maybe Text)
Nothing      -> (MixedAmount -> MixedAmount)
-> DateSpan -> MixedAmount -> MixedAmount
forall a b. a -> b -> a
const MixedAmount -> MixedAmount
forall a. a -> a
id
  where
    valuation :: Maybe Text -> DateSpan -> MixedAmount -> MixedAmount
valuation Maybe Text
mc DateSpan
span = PriceOracle
-> Map Text AmountStyle
-> Maybe Text
-> Day
-> MixedAmount
-> MixedAmount
mixedAmountValueAtDate PriceOracle
priceoracle Map Text AmountStyle
styles Maybe Text
mc (Day -> (Day -> Day) -> Maybe Day -> Day
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Day
forall a. a
err (Integer -> Day -> Day
addDays (-Integer
1)) (Maybe Day -> Day) -> Maybe Day -> Day
forall a b. (a -> b) -> a -> b
$ DateSpan -> Maybe Day
spanEnd DateSpan
span)
    gain :: Maybe Text -> DateSpan -> MixedAmount -> MixedAmount
gain Maybe Text
mc DateSpan
span = PriceOracle
-> Map Text AmountStyle
-> Maybe Text
-> Day
-> MixedAmount
-> MixedAmount
mixedAmountGainAtDate PriceOracle
priceoracle Map Text AmountStyle
styles Maybe Text
mc (Day -> (Day -> Day) -> Maybe Day -> Day
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Day
forall a. a
err (Integer -> Day -> Day
addDays (-Integer
1)) (Maybe Day -> Day) -> Maybe Day -> Day
forall a b. (a -> b) -> a -> b
$ DateSpan -> Maybe Day
spanEnd DateSpan
span)
    costing :: MixedAmount -> MixedAmount
costing = case ConversionOp -> Maybe ConversionOp -> ConversionOp
forall a. a -> Maybe a -> a
fromMaybe ConversionOp
NoConversionOp (Maybe ConversionOp -> ConversionOp)
-> Maybe ConversionOp -> ConversionOp
forall a b. (a -> b) -> a -> b
$ ReportOpts -> Maybe ConversionOp
conversionop_ ReportOpts
ropts of
        ConversionOp
NoConversionOp -> MixedAmount -> MixedAmount
forall a. a -> a
id
        ConversionOp
ToCost         -> Map Text AmountStyle -> MixedAmount -> MixedAmount
styleMixedAmount Map Text AmountStyle
styles (MixedAmount -> MixedAmount)
-> (MixedAmount -> MixedAmount) -> MixedAmount -> MixedAmount
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MixedAmount -> MixedAmount
mixedAmountCost
    styles :: Map Text AmountStyle
styles = Journal -> Map Text AmountStyle
journalCommodityStyles Journal
j
    err :: a
err = String -> a
forall a. HasCallStack => String -> a
error String
"mixedAmountApplyValuationAfterSumFromOptsWith: expected all spans to have an end date"
valuationAfterSum :: ReportOpts -> Maybe (Maybe CommoditySymbol)
valuationAfterSum :: ReportOpts -> Maybe (Maybe Text)
valuationAfterSum ReportOpts
ropts = case ReportOpts -> Maybe ValuationType
value_ ReportOpts
ropts of
    Just (AtEnd Maybe Text
mc) | Bool
valueAfterSum -> Maybe Text -> Maybe (Maybe Text)
forall a. a -> Maybe a
Just Maybe Text
mc
    Maybe ValuationType
_                               -> Maybe (Maybe Text)
forall a. Maybe a
Nothing
  where valueAfterSum :: Bool
valueAfterSum = ReportOpts -> BalanceCalculation
balancecalc_  ReportOpts
ropts BalanceCalculation -> BalanceCalculation -> Bool
forall a. Eq a => a -> a -> Bool
== BalanceCalculation
CalcValueChange
                     Bool -> Bool -> Bool
|| ReportOpts -> BalanceCalculation
balancecalc_  ReportOpts
ropts BalanceCalculation -> BalanceCalculation -> Bool
forall a. Eq a => a -> a -> Bool
== BalanceCalculation
CalcGain
                     Bool -> Bool -> Bool
|| ReportOpts -> BalanceAccumulation
balanceaccum_ ReportOpts
ropts BalanceAccumulation -> BalanceAccumulation -> Bool
forall a. Eq a => a -> a -> Bool
/= BalanceAccumulation
PerPeriod
queryFromFlags :: ReportOpts -> Query
queryFromFlags :: ReportOpts -> Query
queryFromFlags ReportOpts{Bool
Int
[Text]
[Status]
Maybe Int
Maybe Text
Maybe NormalSign
Maybe ValuationType
Maybe ConversionOp
Interval
Period
StringFormat
Layout
AccountListMode
BalanceAccumulation
BalanceCalculation
layout_ :: Layout
transpose_ :: Bool
color_ :: Bool
normalbalance_ :: Maybe NormalSign
invert_ :: Bool
percent_ :: Bool
sort_amount_ :: Bool
show_costs_ :: Bool
no_total_ :: Bool
row_total_ :: Bool
declared_ :: Bool
drop_ :: Int
accountlistmode_ :: AccountListMode
budgetpat_ :: Maybe Text
balanceaccum_ :: BalanceAccumulation
balancecalc_ :: BalanceCalculation
txn_dates_ :: Bool
related_ :: Bool
average_ :: Bool
querystring_ :: [Text]
pretty_ :: Bool
format_ :: StringFormat
real_ :: Bool
no_elide_ :: Bool
empty_ :: Bool
date2_ :: Bool
depth_ :: Maybe Int
infer_prices_ :: Bool
value_ :: Maybe ValuationType
conversionop_ :: Maybe ConversionOp
statuses_ :: [Status]
interval_ :: Interval
period_ :: Period
layout_ :: ReportOpts -> Layout
transpose_ :: ReportOpts -> Bool
color_ :: ReportOpts -> Bool
normalbalance_ :: ReportOpts -> Maybe NormalSign
invert_ :: ReportOpts -> Bool
percent_ :: ReportOpts -> Bool
sort_amount_ :: ReportOpts -> Bool
show_costs_ :: ReportOpts -> Bool
no_total_ :: ReportOpts -> Bool
row_total_ :: ReportOpts -> Bool
declared_ :: ReportOpts -> Bool
drop_ :: ReportOpts -> Int
accountlistmode_ :: ReportOpts -> AccountListMode
budgetpat_ :: ReportOpts -> Maybe Text
balanceaccum_ :: ReportOpts -> BalanceAccumulation
balancecalc_ :: ReportOpts -> BalanceCalculation
txn_dates_ :: ReportOpts -> Bool
related_ :: ReportOpts -> Bool
average_ :: ReportOpts -> Bool
querystring_ :: ReportOpts -> [Text]
pretty_ :: ReportOpts -> Bool
format_ :: ReportOpts -> StringFormat
real_ :: ReportOpts -> Bool
no_elide_ :: ReportOpts -> Bool
empty_ :: ReportOpts -> Bool
date2_ :: ReportOpts -> Bool
depth_ :: ReportOpts -> Maybe Int
infer_prices_ :: ReportOpts -> Bool
value_ :: ReportOpts -> Maybe ValuationType
conversionop_ :: ReportOpts -> Maybe ConversionOp
statuses_ :: ReportOpts -> [Status]
interval_ :: ReportOpts -> Interval
period_ :: ReportOpts -> Period
..} = Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [Query]
flagsq
  where
    flagsq :: [Query]
flagsq = (Bool -> Query) -> Bool -> [Query] -> [Query]
forall a. (Bool -> a) -> Bool -> [a] -> [a]
consIf   Bool -> Query
Real  Bool
real_
           ([Query] -> [Query]) -> ([Query] -> [Query]) -> [Query] -> [Query]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Query) -> Maybe Int -> [Query] -> [Query]
forall a a. (a -> a) -> Maybe a -> [a] -> [a]
consJust Int -> Query
Depth Maybe Int
depth_
           ([Query] -> [Query]) -> [Query] -> [Query]
forall a b. (a -> b) -> a -> b
$   [ (if Bool
date2_ then DateSpan -> Query
Date2 else DateSpan -> Query
Date) (DateSpan -> Query) -> DateSpan -> Query
forall a b. (a -> b) -> a -> b
$ Period -> DateSpan
periodAsDateSpan Period
period_
               , [Query] -> Query
Or ([Query] -> Query) -> [Query] -> Query
forall a b. (a -> b) -> a -> b
$ (Status -> Query) -> [Status] -> [Query]
forall a b. (a -> b) -> [a] -> [b]
map Status -> Query
StatusQ [Status]
statuses_
               ]
    consIf :: (Bool -> a) -> Bool -> [a] -> [a]
consIf Bool -> a
f Bool
b = if Bool
b then (Bool -> a
f Bool
Truea -> [a] -> [a]
forall a. a -> [a] -> [a]
:) else [a] -> [a]
forall a. a -> a
id
    consJust :: (a -> a) -> Maybe a -> [a] -> [a]
consJust a -> a
f = ([a] -> [a]) -> (a -> [a] -> [a]) -> Maybe a -> [a] -> [a]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [a] -> [a]
forall a. a -> a
id ((:) (a -> [a] -> [a]) -> (a -> a) -> a -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a
f)
reportSpan :: Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpan :: Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpan = Bool -> Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpanHelper Bool
False
reportSpanBothDates :: Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpanBothDates :: Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpanBothDates = Bool -> Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpanHelper Bool
True
reportSpanHelper :: Bool -> Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpanHelper :: Bool -> Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpanHelper Bool
bothdates Journal
j ReportSpec{_rsQuery :: ReportSpec -> Query
_rsQuery=Query
query, _rsReportOpts :: ReportSpec -> ReportOpts
_rsReportOpts=ReportOpts
ropts} =
    (DateSpan
reportspan, [DateSpan]
intervalspans)
  where
    
    requestedspan :: DateSpan
requestedspan  = String -> DateSpan -> DateSpan
forall a. Show a => String -> a -> a
dbg3 String
"requestedspan" (DateSpan -> DateSpan) -> DateSpan -> DateSpan
forall a b. (a -> b) -> a -> b
$ if Bool
bothdates then Query -> DateSpan
queryDateSpan' Query
query else Bool -> Query -> DateSpan
queryDateSpan (ReportOpts -> Bool
date2_ ReportOpts
ropts) Query
query
    
    
    journalspan :: DateSpan
journalspan = String -> DateSpan -> DateSpan
forall a. Show a => String -> a -> a
dbg3 String
"journalspan" (DateSpan -> DateSpan) -> DateSpan -> DateSpan
forall a b. (a -> b) -> a -> b
$ if Bool
bothdates then Journal -> DateSpan
journalDateSpanBothDates Journal
j else Bool -> Journal -> DateSpan
journalDateSpan (ReportOpts -> Bool
date2_ ReportOpts
ropts) Journal
j
    pricespan :: DateSpan
pricespan = String -> DateSpan -> DateSpan
forall a. Show a => String -> a -> a
dbg3 String
"pricespan" (DateSpan -> DateSpan)
-> (Maybe Day -> DateSpan) -> Maybe Day -> DateSpan
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Day -> Maybe Day -> DateSpan
DateSpan Maybe Day
forall a. Maybe a
Nothing (Maybe Day -> DateSpan) -> Maybe Day -> DateSpan
forall a b. (a -> b) -> a -> b
$ case ReportOpts -> Maybe ValuationType
value_ ReportOpts
ropts of
        Just (AtEnd Maybe Text
_) -> (Day -> Day) -> Maybe Day -> Maybe Day
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer -> Day -> Day
addDays Integer
1) (Maybe Day -> Maybe Day)
-> ([PriceDirective] -> Maybe Day) -> [PriceDirective] -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Day] -> Maybe Day
forall a. Ord a => [a] -> Maybe a
maximumMay ([Day] -> Maybe Day)
-> ([PriceDirective] -> [Day]) -> [PriceDirective] -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PriceDirective -> Day) -> [PriceDirective] -> [Day]
forall a b. (a -> b) -> [a] -> [b]
map PriceDirective -> Day
pddate ([PriceDirective] -> Maybe Day) -> [PriceDirective] -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Journal -> [PriceDirective]
jpricedirectives Journal
j
        Maybe ValuationType
_              -> Maybe Day
forall a. Maybe a
Nothing
    
    
    requestedspan' :: DateSpan
requestedspan' = String -> DateSpan -> DateSpan
forall a. Show a => String -> a -> a
dbg3 String
"requestedspan'" (DateSpan -> DateSpan) -> DateSpan -> DateSpan
forall a b. (a -> b) -> a -> b
$ DateSpan
requestedspan DateSpan -> DateSpan -> DateSpan
`spanDefaultsFrom` (DateSpan
journalspan DateSpan -> DateSpan -> DateSpan
`spanUnion` DateSpan
pricespan)
    
    
    
    
    intervalspans :: [DateSpan]
intervalspans  = String -> [DateSpan] -> [DateSpan]
forall a. Show a => String -> a -> a
dbg3 String
"intervalspans" ([DateSpan] -> [DateSpan]) -> [DateSpan] -> [DateSpan]
forall a b. (a -> b) -> a -> b
$ Interval -> DateSpan -> [DateSpan]
splitSpan (ReportOpts -> Interval
interval_ ReportOpts
ropts) DateSpan
requestedspan'
    
    
    reportspan :: DateSpan
reportspan = String -> DateSpan -> DateSpan
forall a. Show a => String -> a -> a
dbg3 String
"reportspan" (DateSpan -> DateSpan) -> DateSpan -> DateSpan
forall a b. (a -> b) -> a -> b
$ Maybe Day -> Maybe Day -> DateSpan
DateSpan (DateSpan -> Maybe Day
spanStart (DateSpan -> Maybe Day) -> Maybe DateSpan -> Maybe Day
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [DateSpan] -> Maybe DateSpan
forall a. [a] -> Maybe a
headMay [DateSpan]
intervalspans)
                                              (DateSpan -> Maybe Day
spanEnd (DateSpan -> Maybe Day) -> Maybe DateSpan -> Maybe Day
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [DateSpan] -> Maybe DateSpan
forall a. [a] -> Maybe a
lastMay [DateSpan]
intervalspans)
reportStartDate :: Journal -> ReportSpec -> Maybe Day
reportStartDate :: Journal -> ReportSpec -> Maybe Day
reportStartDate Journal
j = DateSpan -> Maybe Day
spanStart (DateSpan -> Maybe Day)
-> (ReportSpec -> DateSpan) -> ReportSpec -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DateSpan, [DateSpan]) -> DateSpan
forall a b. (a, b) -> a
fst ((DateSpan, [DateSpan]) -> DateSpan)
-> (ReportSpec -> (DateSpan, [DateSpan])) -> ReportSpec -> DateSpan
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpan Journal
j
reportEndDate :: Journal -> ReportSpec -> Maybe Day
reportEndDate :: Journal -> ReportSpec -> Maybe Day
reportEndDate Journal
j = DateSpan -> Maybe Day
spanEnd (DateSpan -> Maybe Day)
-> (ReportSpec -> DateSpan) -> ReportSpec -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DateSpan, [DateSpan]) -> DateSpan
forall a b. (a, b) -> a
fst ((DateSpan, [DateSpan]) -> DateSpan)
-> (ReportSpec -> (DateSpan, [DateSpan])) -> ReportSpec -> DateSpan
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Journal -> ReportSpec -> (DateSpan, [DateSpan])
reportSpan Journal
j
reportPeriodStart :: ReportSpec -> Maybe Day
reportPeriodStart :: ReportSpec -> Maybe Day
reportPeriodStart = Bool -> Query -> Maybe Day
queryStartDate Bool
False (Query -> Maybe Day)
-> (ReportSpec -> Query) -> ReportSpec -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportSpec -> Query
_rsQuery
reportPeriodOrJournalStart :: ReportSpec -> Journal -> Maybe Day
reportPeriodOrJournalStart :: ReportSpec -> Journal -> Maybe Day
reportPeriodOrJournalStart ReportSpec
rspec Journal
j =
  ReportSpec -> Maybe Day
reportPeriodStart ReportSpec
rspec Maybe Day -> Maybe Day -> Maybe Day
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Journal -> Maybe Day
journalStartDate Bool
False Journal
j
reportPeriodLastDay :: ReportSpec -> Maybe Day
reportPeriodLastDay :: ReportSpec -> Maybe Day
reportPeriodLastDay = (Day -> Day) -> Maybe Day -> Maybe Day
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer -> Day -> Day
addDays (-Integer
1)) (Maybe Day -> Maybe Day)
-> (ReportSpec -> Maybe Day) -> ReportSpec -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Query -> Maybe Day
queryEndDate Bool
False (Query -> Maybe Day)
-> (ReportSpec -> Query) -> ReportSpec -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportSpec -> Query
_rsQuery
reportPeriodOrJournalLastDay :: ReportSpec -> Journal -> Maybe Day
reportPeriodOrJournalLastDay :: ReportSpec -> Journal -> Maybe Day
reportPeriodOrJournalLastDay ReportSpec
rspec Journal
j = ReportSpec -> Maybe Day
reportPeriodLastDay ReportSpec
rspec Maybe Day -> Maybe Day -> Maybe Day
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Day
journalOrPriceEnd
  where
    journalOrPriceEnd :: Maybe Day
journalOrPriceEnd = case ReportOpts -> Maybe ValuationType
value_ (ReportOpts -> Maybe ValuationType)
-> ReportOpts -> Maybe ValuationType
forall a b. (a -> b) -> a -> b
$ ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec of
        Just (AtEnd Maybe Text
_) -> Maybe Day -> Maybe Day -> Maybe Day
forall a. Ord a => a -> a -> a
max (Bool -> Journal -> Maybe Day
journalLastDay Bool
False Journal
j) Maybe Day
lastPriceDirective
        Maybe ValuationType
_              -> Bool -> Journal -> Maybe Day
journalLastDay Bool
False Journal
j
    lastPriceDirective :: Maybe Day
lastPriceDirective = (Day -> Day) -> Maybe Day -> Maybe Day
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer -> Day -> Day
addDays Integer
1) (Maybe Day -> Maybe Day)
-> ([PriceDirective] -> Maybe Day) -> [PriceDirective] -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Day] -> Maybe Day
forall a. Ord a => [a] -> Maybe a
maximumMay ([Day] -> Maybe Day)
-> ([PriceDirective] -> [Day]) -> [PriceDirective] -> Maybe Day
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PriceDirective -> Day) -> [PriceDirective] -> [Day]
forall a b. (a -> b) -> [a] -> [b]
map PriceDirective -> Day
pddate ([PriceDirective] -> Maybe Day) -> [PriceDirective] -> Maybe Day
forall a b. (a -> b) -> a -> b
$ Journal -> [PriceDirective]
jpricedirectives Journal
j
reportPeriodName :: BalanceAccumulation -> [DateSpan] -> DateSpan -> T.Text
reportPeriodName :: BalanceAccumulation -> [DateSpan] -> DateSpan -> Text
reportPeriodName BalanceAccumulation
balanceaccumulation [DateSpan]
spans =
  case BalanceAccumulation
balanceaccumulation of
    BalanceAccumulation
PerPeriod -> if Bool
multiyear then DateSpan -> Text
showDateSpan else DateSpan -> Text
showDateSpanMonthAbbrev
      where
        multiyear :: Bool
multiyear = (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
1) (Int -> Bool) -> Int -> Bool
forall a b. (a -> b) -> a -> b
$ [Maybe Integer] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Maybe Integer] -> Int) -> [Maybe Integer] -> Int
forall a b. (a -> b) -> a -> b
$ [Maybe Integer] -> [Maybe Integer]
forall a. Ord a => [a] -> [a]
nubSort ([Maybe Integer] -> [Maybe Integer])
-> [Maybe Integer] -> [Maybe Integer]
forall a b. (a -> b) -> a -> b
$ (DateSpan -> Maybe Integer) -> [DateSpan] -> [Maybe Integer]
forall a b. (a -> b) -> [a] -> [b]
map DateSpan -> Maybe Integer
spanStartYear [DateSpan]
spans
    BalanceAccumulation
_ -> Text -> (Day -> Text) -> Maybe Day -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" (Day -> Text
showDate (Day -> Text) -> (Day -> Day) -> Day -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> Day
prevday) (Maybe Day -> Text) -> (DateSpan -> Maybe Day) -> DateSpan -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DateSpan -> Maybe Day
spanEnd
class Functor f => Reportable f e where
    report :: a -> f (Either e a) -> f a
instance Reportable (Const r) e where
    report :: a -> Const r (Either e a) -> Const r a
report a
_ (Const r
x) = r -> Const r a
forall k a (b :: k). a -> Const a b
Const r
x
instance Reportable Identity e where
    report :: a -> Identity (Either e a) -> Identity a
report a
a (Identity Either e a
i) = a -> Identity a
forall a. a -> Identity a
Identity (a -> Identity a) -> a -> Identity a
forall a b. (a -> b) -> a -> b
$ a -> Either e a -> a
forall b a. b -> Either a b -> b
fromRight a
a Either e a
i
instance Reportable Maybe e where
    report :: a -> Maybe (Either e a) -> Maybe a
report a
_ = (Either e a -> Maybe a
forall a b. Either a b -> Maybe b
eitherToMaybe (Either e a -> Maybe a) -> Maybe (Either e a) -> Maybe a
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<<)
instance (e ~ a) => Reportable (Either a) e where
    report :: a -> Either a (Either e a) -> Either a a
report a
_ = Either a (Either e a) -> Either a a
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
overEither :: ((a -> Either e b) -> s -> Either e t) -> (a -> b) -> s -> Either e t
overEither :: ((a -> Either e b) -> s -> Either e t)
-> (a -> b) -> s -> Either e t
overEither (a -> Either e b) -> s -> Either e t
l a -> b
f = (a -> Either e b) -> s -> Either e t
l (b -> Either e b
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> Either e b) -> (a -> b) -> a -> Either e b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f)
setEither :: ((a -> Either e b) -> s -> Either e t) -> b -> s -> Either e t
setEither :: ((a -> Either e b) -> s -> Either e t) -> b -> s -> Either e t
setEither (a -> Either e b) -> s -> Either e t
l = ((a -> Either e b) -> s -> Either e t)
-> (a -> b) -> s -> Either e t
forall a e b s t.
((a -> Either e b) -> s -> Either e t)
-> (a -> b) -> s -> Either e t
overEither (a -> Either e b) -> s -> Either e t
l ((a -> b) -> s -> Either e t)
-> (b -> a -> b) -> b -> s -> Either e t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> a -> b
forall a b. a -> b -> a
const
type ReportableLens' s a = forall f. Reportable f String => (a -> f a) -> s -> f s
makeHledgerClassyLenses ''ReportOpts
makeHledgerClassyLenses ''ReportSpec
class HasReportOptsNoUpdate a => HasReportOpts a where
    reportOpts :: ReportableLens' a ReportOpts
    reportOpts = (ReportOpts -> f ReportOpts) -> a -> f a
forall c. HasReportOptsNoUpdate c => Lens' c ReportOpts
reportOptsNoUpdate
    {-# INLINE reportOpts #-}
    period :: ReportableLens' a Period
    period = (ReportOpts -> f ReportOpts) -> a -> f a
forall a. HasReportOpts a => ReportableLens' a ReportOpts
reportOpts((ReportOpts -> f ReportOpts) -> a -> f a)
-> ((Period -> f Period) -> ReportOpts -> f ReportOpts)
-> (Period -> f Period)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Period -> f Period) -> ReportOpts -> f ReportOpts
forall c. HasReportOptsNoUpdate c => Lens' c Period
periodNoUpdate
    {-# INLINE period #-}
    statuses :: ReportableLens' a [Status]
    statuses = (ReportOpts -> f ReportOpts) -> a -> f a
forall a. HasReportOpts a => ReportableLens' a ReportOpts
reportOpts((ReportOpts -> f ReportOpts) -> a -> f a)
-> (([Status] -> f [Status]) -> ReportOpts -> f ReportOpts)
-> ([Status] -> f [Status])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([Status] -> f [Status]) -> ReportOpts -> f ReportOpts
forall c. HasReportOptsNoUpdate c => Lens' c [Status]
statusesNoUpdate
    {-# INLINE statuses #-}
    depth :: ReportableLens' a (Maybe Int)
    depth = (ReportOpts -> f ReportOpts) -> a -> f a
forall a. HasReportOpts a => ReportableLens' a ReportOpts
reportOpts((ReportOpts -> f ReportOpts) -> a -> f a)
-> ((Maybe Int -> f (Maybe Int)) -> ReportOpts -> f ReportOpts)
-> (Maybe Int -> f (Maybe Int))
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Maybe Int -> f (Maybe Int)) -> ReportOpts -> f ReportOpts
forall c. HasReportOptsNoUpdate c => Lens' c (Maybe Int)
depthNoUpdate
    {-# INLINE depth #-}
    date2 :: ReportableLens' a Bool
    date2 = (ReportOpts -> f ReportOpts) -> a -> f a
forall a. HasReportOpts a => ReportableLens' a ReportOpts
reportOpts((ReportOpts -> f ReportOpts) -> a -> f a)
-> ((Bool -> f Bool) -> ReportOpts -> f ReportOpts)
-> (Bool -> f Bool)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Bool -> f Bool) -> ReportOpts -> f ReportOpts
forall c. HasReportOptsNoUpdate c => Lens' c Bool
date2NoUpdate
    {-# INLINE date2 #-}
    real :: ReportableLens' a Bool
    real = (ReportOpts -> f ReportOpts) -> a -> f a
forall a. HasReportOpts a => ReportableLens' a ReportOpts
reportOpts((ReportOpts -> f ReportOpts) -> a -> f a)
-> ((Bool -> f Bool) -> ReportOpts -> f ReportOpts)
-> (Bool -> f Bool)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Bool -> f Bool) -> ReportOpts -> f ReportOpts
forall c. HasReportOptsNoUpdate c => Lens' c Bool
realNoUpdate
    {-# INLINE real #-}
    querystring :: ReportableLens' a [T.Text]
    querystring = (ReportOpts -> f ReportOpts) -> a -> f a
forall a. HasReportOpts a => ReportableLens' a ReportOpts
reportOpts((ReportOpts -> f ReportOpts) -> a -> f a)
-> (([Text] -> f [Text]) -> ReportOpts -> f ReportOpts)
-> ([Text] -> f [Text])
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.([Text] -> f [Text]) -> ReportOpts -> f ReportOpts
forall c. HasReportOptsNoUpdate c => Lens' c [Text]
querystringNoUpdate
    {-# INLINE querystring #-}
instance HasReportOpts ReportOpts
instance HasReportOptsNoUpdate ReportSpec where
    reportOptsNoUpdate :: (ReportOpts -> f ReportOpts) -> ReportSpec -> f ReportSpec
reportOptsNoUpdate = (ReportOpts -> f ReportOpts) -> ReportSpec -> f ReportSpec
forall c. HasReportSpec c => Lens' c ReportOpts
rsReportOpts
instance HasReportOpts ReportSpec where
    reportOpts :: (ReportOpts -> f ReportOpts) -> ReportSpec -> f ReportSpec
reportOpts ReportOpts -> f ReportOpts
f ReportSpec
rspec = ReportSpec -> f (Either String ReportSpec) -> f ReportSpec
forall (f :: * -> *) e a.
Reportable f e =>
a -> f (Either e a) -> f a
report (String -> ReportSpec
forall a. String -> a
error' String
"Updating ReportSpec failed: try using overEither instead of over or setEither instead of set") (f (Either String ReportSpec) -> f ReportSpec)
-> f (Either String ReportSpec) -> f ReportSpec
forall a b. (a -> b) -> a -> b
$  
      Day -> ReportOpts -> Either String ReportSpec
reportOptsToSpec (ReportSpec -> Day
_rsDay ReportSpec
rspec) (ReportOpts -> Either String ReportSpec)
-> f ReportOpts -> f (Either String ReportSpec)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReportOpts -> f ReportOpts
f (ReportSpec -> ReportOpts
_rsReportOpts ReportSpec
rspec)
    {-# INLINE reportOpts #-}
reportOptsToSpec :: Day -> ReportOpts -> Either String ReportSpec
reportOptsToSpec :: Day -> ReportOpts -> Either String ReportSpec
reportOptsToSpec Day
day ReportOpts
ropts = do
    (Query
argsquery, [QueryOpt]
queryopts) <- Day -> [Text] -> Either String (Query, [QueryOpt])
parseQueryList Day
day ([Text] -> Either String (Query, [QueryOpt]))
-> [Text] -> Either String (Query, [QueryOpt])
forall a b. (a -> b) -> a -> b
$ ReportOpts -> [Text]
querystring_ ReportOpts
ropts
    ReportSpec -> Either String ReportSpec
forall (m :: * -> *) a. Monad m => a -> m a
return ReportSpec :: ReportOpts -> Day -> Query -> [QueryOpt] -> ReportSpec
ReportSpec
      { _rsReportOpts :: ReportOpts
_rsReportOpts = ReportOpts
ropts
      , _rsDay :: Day
_rsDay        = Day
day
      , _rsQuery :: Query
_rsQuery      = Query -> Query
simplifyQuery (Query -> Query) -> Query -> Query
forall a b. (a -> b) -> a -> b
$ [Query] -> Query
And [ReportOpts -> Query
queryFromFlags ReportOpts
ropts, Query
argsquery]
      , _rsQueryOpts :: [QueryOpt]
_rsQueryOpts  = [QueryOpt]
queryopts
      }
updateReportSpec :: ReportOpts -> ReportSpec -> Either String ReportSpec
updateReportSpec :: ReportOpts -> ReportSpec -> Either String ReportSpec
updateReportSpec = ((ReportOpts -> Either String ReportOpts)
 -> ReportSpec -> Either String ReportSpec)
-> ReportOpts -> ReportSpec -> Either String ReportSpec
forall a e b s t.
((a -> Either e b) -> s -> Either e t) -> b -> s -> Either e t
setEither (ReportOpts -> Either String ReportOpts)
-> ReportSpec -> Either String ReportSpec
forall a. HasReportOpts a => ReportableLens' a ReportOpts
reportOpts
updateReportSpecWith :: (ReportOpts -> ReportOpts) -> ReportSpec -> Either String ReportSpec
updateReportSpecWith :: (ReportOpts -> ReportOpts)
-> ReportSpec -> Either String ReportSpec
updateReportSpecWith = ((ReportOpts -> Either String ReportOpts)
 -> ReportSpec -> Either String ReportSpec)
-> (ReportOpts -> ReportOpts)
-> ReportSpec
-> Either String ReportSpec
forall a e b s t.
((a -> Either e b) -> s -> Either e t)
-> (a -> b) -> s -> Either e t
overEither (ReportOpts -> Either String ReportOpts)
-> ReportSpec -> Either String ReportSpec
forall a. HasReportOpts a => ReportableLens' a ReportOpts
reportOpts
rawOptsToReportSpec :: Day -> RawOpts -> Either String ReportSpec
rawOptsToReportSpec :: Day -> RawOpts -> Either String ReportSpec
rawOptsToReportSpec Day
day = Day -> ReportOpts -> Either String ReportSpec
reportOptsToSpec Day
day (ReportOpts -> Either String ReportSpec)
-> (RawOpts -> ReportOpts) -> RawOpts -> Either String ReportSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Day -> RawOpts -> ReportOpts
rawOptsToReportOpts Day
day