{-# LANGUAGE CPP #-}
{-|

-}

module Hledger.UI.UIOptions
where

import Data.Default (def)
import Data.List (intercalate)
import qualified Data.Map as M
import Data.Maybe (fromMaybe)
import Lens.Micro (set)
import System.Environment (getArgs)

import Hledger.Cli hiding (packageversion, progname, prognameandversion)
import Hledger.UI.Theme (themes, themeNames)

-- cf Hledger.Cli.Version

packageversion :: PackageVersion
packageversion :: String
packageversion =
#ifdef VERSION
  VERSION
#else
  ""
#endif

progname :: ProgramName
progname :: String
progname = String
"hledger-ui"

prognameandversion :: VersionString
prognameandversion :: String
prognameandversion = String -> String -> String
versionString String
progname String
packageversion

uiflags :: [Flag RawOpts]
uiflags = [
  -- flagNone ["debug-ui"] (setboolopt "rules-file") "run with no terminal output, showing console"
   forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"watch",String
"w"] (String -> RawOpts -> RawOpts
setboolopt String
"watch") String
"watch for data and date changes and reload automatically"
  ,forall a. [String] -> Update a -> String -> String -> Flag a
flagReq  [String
"theme"] (\String
s RawOpts
opts -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ String -> String -> RawOpts -> RawOpts
setopt String
"theme" String
s RawOpts
opts) String
"THEME" (String
"use this custom display theme ("forall a. [a] -> [a] -> [a]
++forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
themeNamesforall a. [a] -> [a] -> [a]
++String
")")
  ,forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"cash"] (String -> RawOpts -> RawOpts
setboolopt String
"cash") String
"start in the cash accounts screen"
  ,forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"bs"] (String -> RawOpts -> RawOpts
setboolopt String
"bs") String
"start in the balance sheet accounts screen"
  ,forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"is"] (String -> RawOpts -> RawOpts
setboolopt String
"is") String
"start in the income statement accounts screen"
  ,forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"all"] (String -> RawOpts -> RawOpts
setboolopt String
"all") String
"start in the all accounts screen"
  ,forall a. [String] -> Update a -> String -> String -> Flag a
flagReq  [String
"register"] (\String
s RawOpts
opts -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ String -> String -> RawOpts -> RawOpts
setopt String
"register" String
s RawOpts
opts) String
"ACCTREGEX" String
"start in the (first matched) account's register"
  ,forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"change"] (String -> RawOpts -> RawOpts
setboolopt String
"change")
    String
"show period balances (changes) at startup instead of historical balances"
  -- ,flagNone ["cumulative"] (setboolopt "cumulative")
  --   "show balance change accumulated across periods (in multicolumn reports)"
  -- ,flagNone ["historical","H"] (setboolopt "historical")
  --   "show historical ending balance in each period (includes postings before report start date)\n "
  ]
  forall a. [a] -> [a] -> [a]
++ Bool -> [Flag RawOpts]
flattreeflags Bool
False
--  ,flagNone ["present"] (setboolopt "present") "exclude transactions dated later than today (default)"
  -- ,flagReq ["drop"] (\s opts -> Right $ setopt "drop" s opts) "N" "with --flat, omit this many leading account name components"
  -- ,flagReq  ["format"] (\s opts -> Right $ setopt "format" s opts) "FORMATSTR" "use this custom line format"
  -- ,flagNone ["no-elide"] (setboolopt "no-elide") "don't compress empty parent accounts on one line"

--uimode :: Mode RawOpts
uimode :: Mode RawOpts
uimode =  (forall a. String -> a -> String -> Arg a -> [Flag a] -> Mode a
mode String
"hledger-ui" (String -> String -> RawOpts -> RawOpts
setopt String
"command" String
"ui" forall a. Default a => a
def)
            String
"browse accounts, postings and entries in a full-window TUI"
            (String -> Arg RawOpts
argsFlag String
"[--cash|--bs|--is|--all|--register=ACCT] [QUERY]") []){
              modeGroupFlags :: Group (Flag RawOpts)
modeGroupFlags = Group {
                                groupUnnamed :: [Flag RawOpts]
groupUnnamed = [Flag RawOpts]
uiflags
                               ,groupHidden :: [Flag RawOpts]
groupHidden = [Flag RawOpts]
hiddenflags
                                 forall a. [a] -> [a] -> [a]
++
                                 [forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"future"] (String -> RawOpts -> RawOpts
setboolopt String
"forecast") String
"old flag, use --forecast instead"
                                 ,forall a. [String] -> (a -> a) -> String -> Flag a
flagNone [String
"menu"] (String -> RawOpts -> RawOpts
setboolopt String
"menu") String
"old flag, menu screen is now the default"
                                 ]
                               ,groupNamed :: [(String, [Flag RawOpts])]
groupNamed = [((String, [Flag RawOpts])
generalflagsgroup1)]
                               }
             ,modeHelpSuffix :: [String]
modeHelpSuffix=[
                  -- "Reads your ~/.hledger.journal file, or another specified by $LEDGER_FILE or -f, and starts the full-window TUI."
                 ]
           }

-- hledger-ui options, used in hledger-ui and above
data UIOpts = UIOpts
  { UIOpts -> Bool
uoWatch    :: Bool
  , UIOpts -> Maybe String
uoTheme    :: Maybe String
  , UIOpts -> Maybe String
uoRegister :: Maybe String
  , UIOpts -> CliOpts
uoCliOpts  :: CliOpts
  } deriving (Int -> UIOpts -> String -> String
[UIOpts] -> String -> String
UIOpts -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UIOpts] -> String -> String
$cshowList :: [UIOpts] -> String -> String
show :: UIOpts -> String
$cshow :: UIOpts -> String
showsPrec :: Int -> UIOpts -> String -> String
$cshowsPrec :: Int -> UIOpts -> String -> String
Show)

defuiopts :: UIOpts
defuiopts = UIOpts
  { uoWatch :: Bool
uoWatch    = Bool
False
  , uoTheme :: Maybe String
uoTheme    = forall a. Maybe a
Nothing
  , uoRegister :: Maybe String
uoRegister = forall a. Maybe a
Nothing
  , uoCliOpts :: CliOpts
uoCliOpts  = CliOpts
defcliopts
  }

-- | Process a RawOpts into a UIOpts.
-- This will return a usage error if provided an invalid theme.
rawOptsToUIOpts :: RawOpts -> IO UIOpts
rawOptsToUIOpts :: RawOpts -> IO UIOpts
rawOptsToUIOpts RawOpts
rawopts = do
    CliOpts
cliopts <- forall s t a b. ASetter s t a b -> b -> s -> t
set forall c. HasReportOptsNoUpdate c => Lens' c BalanceAccumulation
balanceaccum BalanceAccumulation
accum forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RawOpts -> IO CliOpts
rawOptsToCliOpts RawOpts
rawopts
    forall (m :: * -> *) a. Monad m => a -> m a
return UIOpts
defuiopts {
                uoWatch :: Bool
uoWatch    = String -> RawOpts -> Bool
boolopt String
"watch" RawOpts
rawopts
               ,uoTheme :: Maybe String
uoTheme    = String -> String
checkTheme forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> RawOpts -> Maybe String
maybestringopt String
"theme" RawOpts
rawopts
               ,uoRegister :: Maybe String
uoRegister = String -> RawOpts -> Maybe String
maybestringopt String
"register" RawOpts
rawopts
               ,uoCliOpts :: CliOpts
uoCliOpts  = CliOpts
cliopts
               }
  where
    -- show historical balance by default (unlike hledger)
    accum :: BalanceAccumulation
accum = forall a. a -> Maybe a -> a
fromMaybe BalanceAccumulation
Historical forall a b. (a -> b) -> a -> b
$ RawOpts -> Maybe BalanceAccumulation
balanceAccumulationOverride RawOpts
rawopts
    checkTheme :: String -> String
checkTheme String
t = if String
t forall k a. Ord k => k -> Map k a -> Bool
`M.member` Map String AttrMap
themes then String
t else forall a. String -> a
usageError forall a b. (a -> b) -> a -> b
$ String
"invalid theme name: " forall a. [a] -> [a] -> [a]
++ String
t

-- XXX some refactoring seems due
getHledgerUIOpts :: IO UIOpts
--getHledgerUIOpts = processArgs uimode >>= return >>= rawOptsToUIOpts
getHledgerUIOpts :: IO UIOpts
getHledgerUIOpts = do
  [String]
args <- IO [String]
getArgs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [String] -> IO [String]
expandArgsAt
  let args' :: [String]
args' = [String] -> [String]
replaceNumericFlags forall a b. (a -> b) -> a -> b
$ forall {t :: * -> *}.
(Eq (t Char), IsString (t Char), Foldable t) =>
[t Char] -> [t Char]
ensureDebugHasArg [String]
args
  let cmdargopts :: RawOpts
cmdargopts = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. String -> a
usageError forall a. a -> a
id forall a b. (a -> b) -> a -> b
$ forall a. Mode a -> [String] -> Either String a
process Mode RawOpts
uimode [String]
args'
  RawOpts -> IO UIOpts
rawOptsToUIOpts RawOpts
cmdargopts

instance HasCliOpts UIOpts where
    cliOpts :: Lens' UIOpts CliOpts
cliOpts CliOpts -> f CliOpts
f UIOpts
uiopts = (\CliOpts
x -> UIOpts
uiopts{uoCliOpts :: CliOpts
uoCliOpts=CliOpts
x}) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CliOpts -> f CliOpts
f (UIOpts -> CliOpts
uoCliOpts UIOpts
uiopts)

instance HasInputOpts UIOpts where
    inputOpts :: Lens' UIOpts InputOpts
inputOpts = forall c. HasCliOpts c => Lens' c CliOpts
cliOptsforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall c. HasInputOpts c => Lens' c InputOpts
inputOpts

instance HasBalancingOpts UIOpts where
    balancingOpts :: Lens' UIOpts BalancingOpts
balancingOpts = forall c. HasCliOpts c => Lens' c CliOpts
cliOptsforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall c. HasBalancingOpts c => Lens' c BalancingOpts
balancingOpts

instance HasReportSpec UIOpts where
    reportSpec :: Lens' UIOpts ReportSpec
reportSpec = forall c. HasCliOpts c => Lens' c CliOpts
cliOptsforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall c. HasReportSpec c => Lens' c ReportSpec
reportSpec

instance HasReportOptsNoUpdate UIOpts where
    reportOptsNoUpdate :: Lens' UIOpts ReportOpts
reportOptsNoUpdate = forall c. HasCliOpts c => Lens' c CliOpts
cliOptsforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall c. HasReportOptsNoUpdate c => Lens' c ReportOpts
reportOptsNoUpdate

instance HasReportOpts UIOpts where
    reportOpts :: ReportableLens' UIOpts ReportOpts
reportOpts = forall c. HasCliOpts c => Lens' c CliOpts
cliOptsforall b c a. (b -> c) -> (a -> b) -> a -> c
.forall a. HasReportOpts a => ReportableLens' a ReportOpts
reportOpts