{-|
This is the root module of the @hledger@ package,
providing hledger's command-line interface.
The main function,
commands,
command-line options,
and utilities useful to other hledger command-line programs
are exported.
It also re-exports hledger-lib:Hledger
and cmdargs:System.Concole.CmdArgs.Explicit

See also:

- hledger-lib:Hledger
- [The README files](https://github.com/search?q=repo%3Asimonmichael%2Fhledger+path%3A**%2FREADME*&type=code&ref=advsearch)
- [The high-level developer docs](https://hledger.org/dev.html)

hledger is a Haskell rewrite of John Wiegley's "ledger".  
It generates financial reports from a plain text general journal.
You can use the command line:

> $ hledger

or ghci:

> $ make ghci
> ghci> Right j <- runExceptT $ readJournalFile definputopts "examples/sample.journal"  -- or: j <- defaultJournal
> ghci> :t j
> j :: Journal
> ghci> stats defcliopts j
> Main file                : examples/sample.journal
> Included files           : 
> Transactions span        : 2008-01-01 to 2009-01-01 (366 days)
> Last transaction         : 2008-12-31 (733772 days from now)
> Transactions             : 5 (0.0 per day)
> Transactions last 30 days: 0 (0.0 per day)
> Transactions last 7 days : 0 (0.0 per day)
> Payees/descriptions      : 5
> Accounts                 : 8 (depth 3)
> Commodities              : 1 ($)
> Market prices            : 0 ()
> 
> Run time (throughput)    : 1695276900.00s (0 txns/s)
> ghci> balance defcliopts j
>                   $1  assets:bank:saving
>                  $-2  assets:cash
>                   $1  expenses:food
>                   $1  expenses:supplies
>                  $-1  income:gifts
>                  $-1  income:salary
>                   $1  liabilities:debts
> --------------------
>                    0  
> ghci> 

etc.


SPDX-License-Identifier: GPL-3.0-or-later
Copyright (c) 2007-2025 (each year in this range) Simon Michael <simon@joyful.com> and contributors.

This program is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.

This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY;
without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
See the GNU General Public License for more details.
You should have received a copy of the GNU General Public License along with this program.
If not, see <https://www.gnu.org/licenses/>.

-}

{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
{-# HLINT ignore "Unused LANGUAGE pragma" #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}

module Hledger.Cli (
  main,
  mainmode,
  argsToCliOpts,
  -- * Re-exports
  module Hledger.Cli.CliOptions,
  module Hledger.Cli.Conf,
  module Hledger.Cli.Commands,
  module Hledger.Cli.DocFiles,
  module Hledger.Cli.Utils,
  module Hledger.Cli.Version,
  module Hledger,
  -- ** System.Console.CmdArgs.Explicit
  module CmdArgsWithoutName
)
where

#if MIN_VERSION_base(4,20,0)
import Control.Exception.Backtrace (setBacktraceMechanismState, BacktraceMechanism(..))
#endif
import Control.Monad (when, unless)
import Data.Bifunctor (second)
import Data.Char (isDigit)
import Data.Either (isRight)
import Data.Function ((&))
import Data.Functor ((<&>))
import Data.List
import qualified Data.List.NonEmpty as NE
import Data.Maybe (isJust, fromMaybe, fromJust)
import Data.Text (pack, Text)
import Data.Time.Clock.POSIX (getPOSIXTime)
import Safe
import System.Console.CmdArgs.Explicit
import System.Console.CmdArgs.Explicit as CmdArgsWithoutName hiding (Name)
import System.Environment
import System.Exit
import System.Process
import Text.Megaparsec (optional, takeWhile1P, eof)
import Text.Megaparsec.Char (char)
import Text.Printf

import Hledger
import Hledger.Cli.CliOptions
import Hledger.Cli.Conf
import Hledger.Cli.Commands
import Hledger.Cli.Commands.Run
import Hledger.Cli.DocFiles
import Hledger.Cli.Utils
import Hledger.Cli.Version


verboseDebugLevel :: Int
verboseDebugLevel = Int
8

-- | The overall cmdargs mode describing hledger's command-line options and subcommands.
-- The names of known addons are provided so they too can be recognised as commands.
mainmode :: [String] -> Mode RawOpts
mainmode [String]
addons = Mode RawOpts
defMode {
  modeNames = [progname ++ " [COMMAND]"]
 ,modeArgs = ([], Just $ argsFlag "[ARGS]")
 ,modeHelp = unlines ["hledger's main command line interface. Run with no ARGS to list commands."]
 ,modeGroupModes = Group {
    -- subcommands in the unnamed group, shown first:
    groupUnnamed = [
     ]
    -- subcommands in named groups:
   ,groupNamed = [
     ]
    -- subcommands handled but not shown in the help:
   ,groupHidden = map fst builtinCommands ++ map addonCommandMode addons
   }
 ,modeGroupFlags = Group {
     -- flags in named groups: (keep synced with Hledger.Cli.CliOptions.highlightHelp)
     groupNamed = cligeneralflagsgroups1
     -- flags in the unnamed group, shown last: (keep synced with dropUnsupportedOpts)
    ,groupUnnamed = confflags
     -- other flags handled but not shown in help:
    ,groupHidden = hiddenflagsformainmode
    }
 ,modeHelpSuffix = []
    -- "Examples:" :
    -- map (progname ++) [
    --  "                         list commands"
    -- ," CMD [--] [OPTS] [ARGS]  run a command (use -- with addon commands)"
    -- ,"-CMD [OPTS] [ARGS]       or run addon commands directly"
    -- ," -h                      show general usage"
    -- ," CMD -h                  show command usage"
    -- ," help [MANUAL]           show any of the hledger manuals in various formats"
    -- ]
 }
-- A dummy mode just for parsing --conf/--no-conf flags.
confflagsmode :: Mode RawOpts
confflagsmode = Mode RawOpts
defMode{
   modeGroupFlags=Group [] confflags []
  ,modeArgs = ([], Just $ argsFlag "")
  }

------------------------------------------------------------------------------
-- | hledger CLI's main procedure.
--
-- Here we will parse the command line, read any config file,
-- and search for hledger-* addon executables in the user's PATH,
-- then choose the appropriate builtin operation or addon operation to run,
-- then run it in the right way, usually reading input data (eg a journal) first.
--
-- When making a CLI usable and robust with main command, builtin subcommands,
-- various kinds of addon commands, and config files that add general and
-- command-specific options, while balancing circular dependencies, environment,
-- idioms, legacy, and libraries with their own requirements and limitations:
-- things get crazy, and there is a tradeoff against complexity and bug risk.
-- We try to provide the most intuitive, expressive and robust CLI that's feasible
-- while keeping the CLI processing below sufficiently comprehensible, troubleshootable,
-- and tested. It's an ongoing quest.
-- See also: Hledger.Cli.CliOptions, cli.test, addons.test, --debug and --debug=8.
--
-- Probably the biggest source of complexity here is that cmdargs can't parse
-- a command line containing undeclared flags, but this arises often with our
-- addon commands and builtin/custom commands which haven't implemented all options,
-- so we have to work hard to work around this.
-- https://github.com/ndmitchell/cmdargs/issues/36 is the wishlist issue;
-- implementing that would simplify hledger's CLI processing a lot.
--
main :: IO ()
main :: IO ()
main = IO () -> IO ()
exitOnError (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> IO ()
forall {a}. a -> a
withGhcDebug' (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do

#if MIN_VERSION_base(4,20,0)
  -- Control ghc 9.10+'s stack traces.
  -- CostCentreBacktrace   - collect cost-centre stack backtraces (only available when built with profiling)
  -- HasCallStackBacktrace - collect HasCallStack backtraces
  -- ExecutionBacktrace    - collect backtraces from native execution stack unwinding
  -- IPEBacktrace          - collect backtraces from Info Table Provenance Entries
#ifdef DEBUG
  setBacktraceMechanismState HasCallStackBacktrace True
#else
  setBacktraceMechanismState HasCallStackBacktrace False
#endif
#endif

  -- 0. let's go!

  let
    dbgio :: Show a => String -> a -> IO ()
    dbgio :: forall a. Show a => String -> a -> IO ()
dbgio  = Int -> String -> a -> IO ()
forall (m :: * -> *) a.
(MonadIO m, Show a) =>
Int -> String -> a -> m ()
dbgIO Int
verboseDebugLevel

  String -> String -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"running" String
prognameandversion
  POSIXTime
starttime <- IO POSIXTime
getPOSIXTime
  -- give ghc-debug a chance to take control
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (GhcDebugMode
ghcDebugMode GhcDebugMode -> GhcDebugMode -> Bool
forall a. Eq a => a -> a -> Bool
== GhcDebugMode
GDPauseAtStart) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO ()
ghcDebugPause'
  -- try to encourage user's $PAGER to display ANSI when supported
  Bool
usecolor <- IO Bool
useColorOnStdout
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
usecolor IO ()
setupPager
  -- Search PATH for addon commands. Exclude any that match builtin command names.
  [String]
addons <- IO [String]
addonCommandNames

  ---------------------------------------------------------------
  String -> () -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"\n1. Preliminary command line parsing" ()

  -- Naming notes:
  -- "arg" often has the most general meaning, including things like: -f, --flag, flagvalue, arg, >file, &, etc.
  -- confcmdarg, clicmdarg = the first non-flag argument, from config file or cli = the subcommand name
  -- cmdname = the full unabbreviated command name, or ""
  -- confcmdargs = arguments for the subcommand, from config file

  -- Do some argument preprocessing to help cmdargs
  [String]
cliargs <- IO [String]
getArgs
    IO [String] -> ([String] -> IO [String]) -> IO [String]
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [String] -> IO [String]
expandArgsAt         -- interpolate @ARGFILEs
    IO [String] -> ([String] -> [String]) -> IO [String]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> [String] -> [String]
replaceNumericFlags  -- convert -NUM to --depth=NUM
    IO [String] -> ([String] -> [String]) -> IO [String]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> [String] -> [String]
forall {a}. (Eq a, IsString a) => [a] -> [a]
argsAddDoubleDash    -- repeat the first -- arg, as a cmdargs workaround
  let
    (String
clicmdarg, [String]
cliargswithoutcmd, [String]
cliargswithcmdfirst) = [String] -> (String, [String], [String])
moveFlagsAfterCommand [String]
cliargs
    cliargswithcmdfirstwithoutclispecific :: [String]
cliargswithcmdfirstwithoutclispecific = [String] -> [String]
dropCliSpecificOpts [String]
cliargswithcmdfirst
    ([String]
cliargsbeforecmd, [String]
cliargsaftercmd) = ([String] -> [String])
-> ([String], [String]) -> ([String], [String])
forall b c a. (b -> c) -> (a, b) -> (a, c)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1) (([String], [String]) -> ([String], [String]))
-> ([String], [String]) -> ([String], [String])
forall a b. (a -> b) -> a -> b
$ (String -> Bool) -> [String] -> ([String], [String])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
==String
clicmdarg) [String]
cliargs
  String -> [String] -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio  String
"cli args with preprocessing" [String]
cliargs
  String -> [String] -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg1IO String
"cli args with preprocessing and options moved after command" [String]
cliargswithcmdfirst
  String -> String -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"cli command argument found" String
clicmdarg
  String -> [String] -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"cli args before command"    [String]
cliargsbeforecmd
  String -> [String] -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"cli args after command"     [String]
cliargsaftercmd
  -- dbgio "cli args without command"   cliargswithoutcmd

  ---------------------------------------------------------------
  String -> () -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"\n2. Read the config file if any" ()

  -- Identify any --conf/--no-conf options.
  -- Run cmdargs on just the args that look conf-related.
  let
    cliconfargs :: [String]
cliconfargs = Mode RawOpts -> [String] -> [String]
dropUnsupportedOpts Mode RawOpts
confflagsmode [String]
cliargswithoutcmd
    cliconfrawopts :: RawOpts
cliconfrawopts = String -> Mode RawOpts -> [String] -> RawOpts
cmdargsParse String
"for conf options" Mode RawOpts
confflagsmode [String]
cliconfargs

  -- Read extra general and command-specific args/opts from the config file, if any.
  (Conf
conf, Maybe String
mconffile) <-
    RawOpts -> IO (Conf, Maybe String) -> IO (Conf, Maybe String)
forall a b. a -> b -> b
seq RawOpts
cliconfrawopts (IO (Conf, Maybe String) -> IO (Conf, Maybe String))
-> IO (Conf, Maybe String) -> IO (Conf, Maybe String)
forall a b. (a -> b) -> a -> b
$  -- order debug output
    if String
clicmdargString -> String -> Bool
forall a. Eq a => a -> a -> Bool
==String
"setup"  -- the setup command checks config files, but never uses one itself
      then (Conf, Maybe String) -> IO (Conf, Maybe String)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Conf
nullconf,Maybe String
forall a. Maybe a
Nothing)
      else RawOpts -> IO (Conf, Maybe String)
getConf' RawOpts
cliconfrawopts

  ---------------------------------------------------------------
  String -> () -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"\n3. Identify a command name from config file or command line" ()

  -- Try to identify the subcommand name,
  -- from the first non-flag general argument in the config file,
  -- or if there is none, from the first non-flag argument on the command line.

  let
    confallgenargs :: [String]
confallgenargs = String -> Conf -> [String]
confLookup String
"general" Conf
conf [String] -> ([String] -> [String]) -> [String]
forall a b. a -> (a -> b) -> b
& [String] -> [String]
replaceNumericFlags
    -- we don't try to move flags/values preceding a command argument here;
    -- if a command name is written in the config file, it must be first
    (String
confcmdarg, [String]
confothergenargs) = case [String]
confallgenargs of
      String
a:[String]
as | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ String -> Bool
isFlagArg String
a -> (String
a,[String]
as)
      [String]
as                       -> (String
"",[String]
as)
    cmdarg :: String
cmdarg = if Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
confcmdarg then String
confcmdarg else String
clicmdarg
    nocmdprovided :: Bool
nocmdprovided = String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
cmdarg

    -- The argument may be an abbreviated command name, which we need to expand.

    -- Run cmdargs on conf + cli args to get the full command name.
    -- If no command argument was provided, or if cmdargs fails because 
    -- the command line contains a bad flag or wrongly present/missing flag value,
    -- cmdname will be "".
    args :: [String]
args = [String
confcmdarg | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
confcmdarg] [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
cliargswithcmdfirstwithoutclispecific
    cmdname :: String
cmdname = String -> RawOpts -> String
stringopt String
"command" (RawOpts -> String) -> RawOpts -> String
forall a b. (a -> b) -> a -> b
$ String -> Mode RawOpts -> [String] -> RawOpts
cmdargsParse String
"for command name" ([String] -> Mode RawOpts
mainmode [String]
addons) [String]
args

    badcmdprovided :: Bool
badcmdprovided = String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
cmdname Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
nocmdprovided
    isaddoncmd :: Bool
isaddoncmd     = Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
cmdname) Bool -> Bool -> Bool
&& String
cmdname String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
addons

    -- And get the builtin command's mode and action, if any.
    mbuiltincmdaction :: Maybe (Mode RawOpts, CliOpts -> Journal -> IO ())
mbuiltincmdaction = String -> Maybe (Mode RawOpts, CliOpts -> Journal -> IO ())
findBuiltinCommand String
cmdname
    effectivemode :: Mode RawOpts
effectivemode = Mode RawOpts
-> ((Mode RawOpts, CliOpts -> Journal -> IO ()) -> Mode RawOpts)
-> Maybe (Mode RawOpts, CliOpts -> Journal -> IO ())
-> Mode RawOpts
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([String] -> Mode RawOpts
mainmode []) (Mode RawOpts, CliOpts -> Journal -> IO ()) -> Mode RawOpts
forall a b. (a, b) -> a
fst Maybe (Mode RawOpts, CliOpts -> Journal -> IO ())
mbuiltincmdaction

  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
mconffile) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
confcmdarg) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      String -> String -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg1IO String
"using command name argument from config file" String
confcmdarg
  String -> [String] -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"cli args with command first and no cli-specific opts" [String]
cliargswithcmdfirstwithoutclispecific
  String -> String -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg1IO String
"command found" String
cmdname
  String -> Bool -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"no command provided" Bool
nocmdprovided
  String -> Bool -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"bad command provided" Bool
badcmdprovided
  String -> Bool -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"is addon command" Bool
isaddoncmd

  ---------------------------------------------------------------
  String -> () -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"\n4. Get applicable options/arguments from config file" ()

  -- Ignore any general opts or cli-specific opts not known to be supported by the command.
  let
    addoncmdssupportinggenopts :: [String]
addoncmdssupportinggenopts = [String
"ui", String
"web"]  -- addons known to support hledger general options
    supportedgenargsfromconf :: [String]
supportedgenargsfromconf
      | String
cmdname String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
addoncmdssupportinggenopts =
          [String
a | String
a <- [String]
confothergenargs, Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
a) [String]
addoncmdssupportinggenopts]
      | Bool
isaddoncmd = []
      | Bool
otherwise  = Mode RawOpts -> [String] -> [String]
dropUnsupportedOpts Mode RawOpts
effectivemode [String]
confothergenargs
    excludedgenargsfromconf :: [String]
excludedgenargsfromconf = [String]
confothergenargs [String] -> [String] -> [String]
forall a. Eq a => [a] -> [a] -> [a]
\\ [String]
supportedgenargsfromconf
    confcmdargs :: [String]
confcmdargs
      | String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
cmdname = []
      | Bool
otherwise =
          String -> Conf -> [String]
confLookup String
cmdname Conf
conf
          [String] -> ([String] -> [String]) -> [String]
forall a b. a -> (a -> b) -> b
& [String] -> [String]
replaceNumericFlags
          [String] -> ([String] -> [String]) -> [String]
forall a b. a -> (a -> b) -> b
& if Bool
isaddoncmd then (String
"--"String -> [String] -> [String]
forall a. a -> [a] -> [a]
:) else [String] -> [String]
forall {a}. a -> a
id

  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
mconffile) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
    String -> [String] -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg1IO String
"using general args from config file" [String]
confothergenargs
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
excludedgenargsfromconf) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      String -> [String] -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg1IO String
"excluded general args from config file, not supported by this command" [String]
excludedgenargsfromconf
    String -> [String] -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg1IO String
"using subcommand args from config file" [String]
confcmdargs

  ---------------------------------------------------------------
  String -> () -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"\n5. Combine config file and command line args" ()

  let
    finalargs :: [String]
finalargs =
      [String
cmdarg | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
cmdarg]
        [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
supportedgenargsfromconf
        [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
confcmdargs
        [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String
clicmdarg | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
confcmdarg]
        [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
cliargswithoutcmd
      [String] -> ([String] -> [String]) -> [String]
forall a b. a -> (a -> b) -> b
& [String] -> [String]
replaceNumericFlags                -- convert any -NUM opts from the config file

  -- finalargs' <- expandArgsAt finalargs  -- expand @ARGFILEs in the config file ? don't bother
  String -> [String] -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg1IO String
"final args" [String]
finalargs

  -- Run cmdargs on command name + supported conf general args + conf subcommand args + cli args to get the final options.
  -- A bad flag or flag argument will cause the program to exit with an error here.
  let rawopts :: RawOpts
rawopts = String -> Mode RawOpts -> [String] -> RawOpts
cmdargsParse String
"final command line" ([String] -> Mode RawOpts
mainmode [String]
addons) [String]
finalargs

  ---------------------------------------------------------------
  RawOpts -> IO () -> IO ()
forall a b. a -> b -> b
seq RawOpts
rawopts (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$  -- order debug output
    String -> () -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"\n6. Select an action and run it" ()

  -- We check for the help/doc/version flags first, since they are a high priority.
  -- (A perfectionist might think they should be so high priority that adding -h
  -- to an invalid command line would show help. But cmdargs tends to fail first,
  -- preventing this, and trying to detect them without cmdargs, and always do the
  -- right thing with builtin commands and addon commands, gets much too complicated.)
  let
    helpFlag :: Bool
helpFlag    = String -> RawOpts -> Bool
boolopt String
"help"    RawOpts
rawopts
    tldrFlag :: Bool
tldrFlag    = String -> RawOpts -> Bool
boolopt String
"tldr"    RawOpts
rawopts
    infoFlag :: Bool
infoFlag    = String -> RawOpts -> Bool
boolopt String
"info"    RawOpts
rawopts
    manFlag :: Bool
manFlag     = String -> RawOpts -> Bool
boolopt String
"man"     RawOpts
rawopts
    versionFlag :: Bool
versionFlag = String -> RawOpts -> Bool
boolopt String
"version" RawOpts
rawopts
    -- ignoredopts    cmd = error' $ cmd ++ " tried to read options but is not supposed to"
    ignoredjournal :: String -> a
ignoredjournal String
cmd = String -> a
forall a. String -> a
error' (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
cmd String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" tried to read the journal but is not supposed to"

  -- validate opts/args more and convert to CliOpts
  CliOpts
opts <- RawOpts -> IO CliOpts
rawOptsToCliOpts RawOpts
rawopts IO CliOpts -> (CliOpts -> IO CliOpts) -> IO CliOpts
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CliOpts
opts0 -> CliOpts -> IO CliOpts
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CliOpts
opts0{progstarttime_=starttime}
  String -> CliOpts -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg2IO String
"processed opts" CliOpts
opts
  String -> Period -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"period from opts" (ReportOpts -> Period
period_ (ReportOpts -> Period)
-> (ReportSpec -> ReportOpts) -> ReportSpec -> Period
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportSpec -> ReportOpts
_rsReportOpts (ReportSpec -> Period) -> ReportSpec -> Period
forall a b. (a -> b) -> a -> b
$ CliOpts -> ReportSpec
reportspec_ CliOpts
opts)
  String -> Interval -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"interval from opts" (ReportOpts -> Interval
interval_ (ReportOpts -> Interval)
-> (ReportSpec -> ReportOpts) -> ReportSpec -> Interval
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportSpec -> ReportOpts
_rsReportOpts (ReportSpec -> Interval) -> ReportSpec -> Interval
forall a b. (a -> b) -> a -> b
$ CliOpts -> ReportSpec
reportspec_ CliOpts
opts)
  String -> Query -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"query from opts & args" (ReportSpec -> Query
_rsQuery (ReportSpec -> Query) -> ReportSpec -> Query
forall a b. (a -> b) -> a -> b
$ CliOpts -> ReportSpec
reportspec_ CliOpts
opts)

  -- Ensure that anything calling getArgs later will see all args, including config file args.
  -- Some things (--color, --debug, some checks in journalFinalise) are detected by unsafePerformIO,
  -- eg in Hledger.Utils.IO.progArgs, which means they aren't be seen in a config file
  -- (because many things before this point have forced the one-time evaluation of progArgs).
  [String] -> IO () -> IO ()
forall a. [String] -> IO a -> IO a
withArgs (String
prognameString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
finalargs) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
   if
    -- 6.1. no command and a help/doc flag found - show general help/docs
    | Bool
nocmdprovided Bool -> Bool -> Bool
&& Bool
helpFlag -> String -> IO ()
runPager (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Mode RawOpts -> String
forall a. Mode a -> String
showModeUsage ([String] -> Mode RawOpts
mainmode []) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
    | Bool
nocmdprovided Bool -> Bool -> Bool
&& Bool
tldrFlag -> String -> IO ()
runTldrForPage  String
"hledger"
    | Bool
nocmdprovided Bool -> Bool -> Bool
&& Bool
infoFlag -> String -> Maybe String -> IO ()
runInfoForTopic String
"hledger" Maybe String
forall a. Maybe a
Nothing
    | Bool
nocmdprovided Bool -> Bool -> Bool
&& Bool
manFlag  -> String -> Maybe String -> IO ()
runManForTopic  String
"hledger" Maybe String
forall a. Maybe a
Nothing

    -- 6.2. --version flag found and none of these other conditions - show version
    | Bool
versionFlag Bool -> Bool -> Bool
&& Bool -> Bool
not (Bool
isaddoncmd Bool -> Bool -> Bool
|| Bool
helpFlag Bool -> Bool -> Bool
|| Bool
tldrFlag Bool -> Bool -> Bool
|| Bool
infoFlag Bool -> Bool -> Bool
|| Bool
manFlag) -> String -> IO ()
putStrLn String
prognameandversion

    -- 6.3. there's a command argument, but it's bad - show error
    | Bool
badcmdprovided -> String -> IO ()
forall a. String -> a
error' (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"command "String -> String -> String
forall a. [a] -> [a] -> [a]
++String
clicmdargString -> String -> String
forall a. [a] -> [a] -> [a]
++String
" is not recognized, run with no command to see a list"

    -- 6.4. no command found, nothing else to do - show the commands list
    | Bool
nocmdprovided -> do
        String -> () -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg1IO String
"no command, showing commands list" ()
        CliOpts -> Journal -> IO ()
commands CliOpts
opts (String -> Journal
forall a. String -> a
ignoredjournal String
"commands")

    -- 6.5. builtin command found
    | Just (Mode RawOpts
cmdmode, CliOpts -> Journal -> IO ()
cmdaction) <- Maybe (Mode RawOpts, CliOpts -> Journal -> IO ())
mbuiltincmdaction -> do
      let mmodecmdname :: Maybe String
mmodecmdname = [String] -> Maybe String
forall a. [a] -> Maybe a
headMay ([String] -> Maybe String) -> [String] -> Maybe String
forall a b. (a -> b) -> a -> b
$ Mode RawOpts -> [String]
forall a. Mode a -> [String]
modeNames Mode RawOpts
cmdmode
      String -> String -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg1IO String
"running builtin command mode" (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"" Maybe String
mmodecmdname

      -- run the builtin command according to its type
      if
        -- 6.5.1. help/doc flag - show command help/docs
        | Bool
helpFlag  -> String -> IO ()
runPager (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Mode RawOpts -> String
forall a. Mode a -> String
showModeUsage Mode RawOpts
cmdmode String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
        | Bool
tldrFlag  -> String -> IO ()
runTldrForPage (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> (String -> String) -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"hledger" ((String
"hledger-"String -> String -> String
forall a. Semigroup a => a -> a -> a
<>)) Maybe String
mmodecmdname
        | Bool
infoFlag  -> String -> Maybe String -> IO ()
runInfoForTopic String
"hledger" Maybe String
mmodecmdname
        | Bool
manFlag   -> String -> Maybe String -> IO ()
runManForTopic String
"hledger"  Maybe String
mmodecmdname

        -- 6.5.2. builtin command which should not require or read the journal - run it
        | String
cmdname String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"commands",String
"demo",String
"help",String
"setup",String
"test"] ->
          CliOpts -> Journal -> IO ()
cmdaction CliOpts
opts (String -> Journal
forall a. String -> a
ignoredjournal String
cmdname)

        -- 6.5.3. builtin command which should create the journal if missing - do that and run it
        | String
cmdname String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"add",String
"import"] -> do
          String -> IO ()
ensureJournalFileExists (String -> IO ())
-> (NonEmpty String -> String) -> NonEmpty String -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty String -> String
forall a. NonEmpty a -> a
NE.head (NonEmpty String -> IO ()) -> IO (NonEmpty String) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< CliOpts -> IO (NonEmpty String)
journalFilePathFromOpts CliOpts
opts
          CliOpts -> (Journal -> IO ()) -> IO ()
forall a. CliOpts -> (Journal -> IO a) -> IO a
withJournalDo CliOpts
opts (CliOpts -> Journal -> IO ()
cmdaction CliOpts
opts)

        -- 6.5.4. "run" and "repl" need findBuiltinCommands passed to it to avoid circular dependency in the code
        | String
cmdname String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"run"  -> Maybe DefaultRunJournal
-> (String -> Maybe (Mode RawOpts, CliOpts -> Journal -> IO ()))
-> [String]
-> CliOpts
-> IO ()
Hledger.Cli.Commands.Run.run Maybe DefaultRunJournal
forall a. Maybe a
Nothing String -> Maybe (Mode RawOpts, CliOpts -> Journal -> IO ())
findBuiltinCommand [String]
addons CliOpts
opts
        | String
cmdname String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"repl" -> (String -> Maybe (Mode RawOpts, CliOpts -> Journal -> IO ()))
-> [String] -> CliOpts -> IO ()
Hledger.Cli.Commands.Run.repl String -> Maybe (Mode RawOpts, CliOpts -> Journal -> IO ())
findBuiltinCommand [String]
addons CliOpts
opts

        -- 6.5.5. all other builtin commands - read the journal and if successful run the command with it
        | Bool
otherwise -> CliOpts -> (Journal -> IO ()) -> IO ()
forall a. CliOpts -> (Journal -> IO a) -> IO a
withJournalDo CliOpts
opts ((Journal -> IO ()) -> IO ()) -> (Journal -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ CliOpts -> Journal -> IO ()
cmdaction CliOpts
opts

    -- 6.6. external addon command found - run it,
    -- passing any cli arguments written after the command name
    -- and any command-specific opts from the config file.
    -- Any "--" arguments, which sometimes must be used in the command line
    -- to hide addon-specific opts from hledger's cmdargs parsing,
    -- (and are also accepted in the config file, though not required there),
    -- will be removed.
    -- (hledger does not preserve -- arguments)
    -- Arguments written before the command name, and general opts from the config file,
    -- are not passed since we can't be sure they're supported.
    | Bool
isaddoncmd -> do
        let
          addonargs0 :: [String]
addonargs0 = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/=String
"--") ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
supportedgenargsfromconf [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
confcmdargs [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
cliargswithoutcmd
          addonargs :: [String]
addonargs = [String] -> [String]
dropCliSpecificOpts [String]
addonargs0
          shellcmd :: String
shellcmd = String -> String -> String -> String -> String
forall r. PrintfType r => String -> r
printf String
"%s-%s %s" String
progname String
cmdname ([String] -> String
unwords' [String]
addonargs) :: String
        String -> String -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"addon command selected" String
cmdname
        String -> [String] -> IO ()
forall a. Show a => String -> a -> IO ()
dbgio String
"addon command arguments after removing cli-specific opts" ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
quoteIfNeeded [String]
addonargs)
        String -> String -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => String -> a -> m ()
dbg1IO String
"running addon" String
shellcmd
        String -> IO ExitCode
system String
shellcmd IO ExitCode -> (ExitCode -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith

    -- deprecated command found
    -- cmdname == "convert" = error' (modeHelp oldconvertmode)

    -- 6.7. something else (shouldn't happen) - show an error
    | Bool
otherwise -> String -> IO ()
forall a. String -> a
usageError (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
        String
"could not understand the arguments "String -> String -> String
forall a. [a] -> [a] -> [a]
++[String] -> String
forall a. Show a => a -> String
show [String]
finalargs
        String -> String -> String
forall a. Semigroup a => a -> a -> a
<> if [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
confothergenargs then String
"" else String
"\ngeneral arguments added from config file: "String -> String -> String
forall a. [a] -> [a] -> [a]
++[String] -> String
forall a. Show a => a -> String
show [String]
confothergenargs
        String -> String -> String
forall a. Semigroup a => a -> a -> a
<> if [String] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
confcmdargs then String
"" else String
"\ncommand arguments added from config file: "String -> String -> String
forall a. [a] -> [a] -> [a]
++[String] -> String
forall a. Show a => a -> String
show [String]
confcmdargs

  -- 7. And we're done.
  -- Give ghc-debug a final chance to take control.
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (GhcDebugMode
ghcDebugMode GhcDebugMode -> GhcDebugMode -> Bool
forall a. Eq a => a -> a -> Bool
== GhcDebugMode
GDPauseAtEnd) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ IO ()
ghcDebugPause'

------------------------------------------------------------------------------


-- | A helper for addons/scripts: this parses hledger CliOpts from these
-- command line arguments and add-on command names, roughly how hledger main does.
-- If option parsing/validating fails, it exits the program with usageError.
-- Unlike main, this does not read extra args from a config file
-- or search for addons; to do those things, mimic the code in main for now.
argsToCliOpts :: [String] -> [String] -> IO CliOpts
argsToCliOpts :: [String] -> [String] -> IO CliOpts
argsToCliOpts [String]
args [String]
addons = do
  let
    (String
_, [String]
_, [String]
args0) = [String] -> (String, [String], [String])
moveFlagsAfterCommand [String]
args
    args1 :: [String]
args1 = [String] -> [String]
replaceNumericFlags [String]
args0
    rawopts :: RawOpts
rawopts = String -> Mode RawOpts -> [String] -> RawOpts
cmdargsParse String
"for options" ([String] -> Mode RawOpts
mainmode [String]
addons) [String]
args1
  RawOpts -> IO CliOpts
rawOptsToCliOpts RawOpts
rawopts

-- | Parse the given command line arguments/options with the given cmdargs mode,
-- after adding values to any valueless --debug flags,
-- with debug logging showing the given description of this parsing pass
-- (useful when cmdargsParse is called more than once).
-- If parsing fails, exit the program with an informative error message.
cmdargsParse :: String -> Mode RawOpts -> [String] -> RawOpts
cmdargsParse :: String -> Mode RawOpts -> [String] -> RawOpts
cmdargsParse String
desc Mode RawOpts
m [String]
args0 = Mode RawOpts -> [String] -> Either String RawOpts
forall a. Mode a -> [String] -> Either String a
process Mode RawOpts
m ([String] -> [String]
ensureDebugFlagHasVal [String]
args0)
  Either String RawOpts
-> (Either String RawOpts -> RawOpts) -> RawOpts
forall a b. a -> (a -> b) -> b
& (String -> RawOpts)
-> (RawOpts -> RawOpts) -> Either String RawOpts -> RawOpts
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
    (\String
e -> String -> RawOpts
forall a. String -> a
error' (String -> RawOpts) -> String -> RawOpts
forall a b. (a -> b) -> a -> b
$ String
e String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\n* while parsing the following args, " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
desc String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
":\n*  " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> [String] -> String
unwords ((String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
quoteIfNeeded [String]
args0))
    (Int -> String -> RawOpts -> RawOpts
forall a. Int -> String -> a -> a
dbgMsg Int
verboseDebugLevel (String
"cmdargs: parsing " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
desc String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
": " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> [String] -> String
forall a. Show a => a -> String
show [String]
args0))
  -- XXX better error message when cmdargs fails (eg spaced/quoted/malformed flag values) ?

-- | cmdargs does not allow options to appear before the subcommand argument.
-- We prefer to hide this restriction from the user, providing a more forgiving CLI.
-- So this helper tries to move any pre-command flags/options, and their values if any, after the command argument.
-- If there is a "--"" argument, only the preceding args are rearranged.
-- To be precise: pre-command options will be moved to the end of the part of the command line preceding the first -- argument.
-- The pre-command options' relative order will be preserved, but since they may be moved after post-command options,
-- the overall order of options may change.
-- XXX moving them right after the command would probably be better.
--
-- For convenience of the caller, this currently returns a triple:
-- (
--  the command, if one was found (or ""),
--  the rearranged args without the command,
--  the command followed by the rearranged args
-- )
--
-- Notes:
--
-- Detecting the command argument is tricky because of the flexibility of traditional flag syntax.
-- Short flags can be joined together, some flags can have a value or no value,
-- flags and values can be separated by =, a space, or nothing, etc.
--
-- In this context, a "flag" is an argument beginning with - or --, followed by one or more non-space characters.
-- We decide if a flag, and possibly its subsequent value argument, are movable
-- by checking these cases in order:
--
-- - it exactly matches a known short or long no-value flag; move it
-- - it exactly matches a short or long requires-value flag; move it and the following argument
-- - it exactly matches a short optional-value flag; assume these don't exist or we don't have any
-- - it exactly matches a long optional-value flag; assume there's no value, move it
-- - it begins with a short requires-value flag; the value is joined to it, move it
-- - it begins with a long requires-value flag followed by =; likewise
-- - it begins with a long optional-value flag followed by =; likewise
--
-- This hackery increases the risk of misleading errors, bugs, and confusion.
-- It should be fairly robust now, being aware of all builtin flags.
-- The main tests are in hledger/test/cli/cli.test, but they are not exhaustive.
--
-- All general and builtin command flags (and their values) will be moved. It's clearer to
-- write command flags after the command, but if not we'll handle it (for greater robustness).
--
-- Long flags should be spelled in full; abbreviated long flags might not get moved.
--
-- Unknown flags (from addons) are assumed to be valueless or have a joined value,
-- and will be moved - but later rejected by cmdargs.
-- Instead these should be written to the right of a "--" argument, which hides them.
--
moveFlagsAfterCommand :: [String] -> (String, [String], [String])
moveFlagsAfterCommand :: [String] -> (String, [String], [String])
moveFlagsAfterCommand [String]
args =
  case ([String], [String]) -> ([String], [String])
moveFlagAndVal ([String]
as1, []) of
    ([],[String]
as1')                    -> (String
"", [String]
as, [String]
as) where as :: [String]
as = [String]
as1' [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
as2
    (unmoved :: [String]
unmoved@((Char
'-':String
_):[String]
_), [String]
moved) -> (String
"", [String]
as, [String]
as) where as :: [String]
as = [String]
unmoved [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
moved [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
as2
    (String
cmdarg:[String]
unmoved, [String]
moved)      -> (String
cmdarg, [String]
as, String
cmdargString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
as) where as :: [String]
as = [String]
unmoved [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
moved [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
as2
  where
    ([String]
as1, [String]
as2) = (String -> Bool) -> [String] -> ([String], [String])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"--") [String]
args
    -- Move the next argument to the end if it is a movable flag, along with its subsequent value argument if any.
    moveFlagAndVal :: ([String], [String]) -> ([String], [String])
    moveFlagAndVal :: ([String], [String]) -> ([String], [String])
moveFlagAndVal ((String
a:String
b:[String]
cs), [String]
moved) =
      case String -> Maybe String -> Int
isMovableFlagArg String
a (String -> Maybe String
forall a. a -> Maybe a
Just String
b) of
        Int
2 -> Int -> String -> ([String], [String]) -> ([String], [String])
forall a. Int -> String -> a -> a
dbgMsg Int
lvl (String
"moving 2: "String -> String -> String
forall a. Semigroup a => a -> a -> a
<>String
aString -> String -> String
forall a. Semigroup a => a -> a -> a
<>String
" "String -> String -> String
forall a. Semigroup a => a -> a -> a
<>String
b) (([String], [String]) -> ([String], [String]))
-> ([String], [String]) -> ([String], [String])
forall a b. (a -> b) -> a -> b
$ ([String], [String]) -> ([String], [String])
moveFlagAndVal ([String]
cs, [String]
moved[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++[String
a,String
b])
        Int
1 -> Int -> String -> ([String], [String]) -> ([String], [String])
forall a. Int -> String -> a -> a
dbgMsg Int
lvl (String
"moving 1: "String -> String -> String
forall a. Semigroup a => a -> a -> a
<>String
a) (([String], [String]) -> ([String], [String]))
-> ([String], [String]) -> ([String], [String])
forall a b. (a -> b) -> a -> b
$ ([String], [String]) -> ([String], [String])
moveFlagAndVal (String
bString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
cs, [String]
moved[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++[String
a])
        Int
_ -> (String
aString -> [String] -> [String]
forall a. a -> [a] -> [a]
:String
bString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
cs, [String]
moved)
    moveFlagAndVal ([String
a], [String]
moved) =
      case String -> Maybe String -> Int
isMovableFlagArg String
a Maybe String
forall a. Maybe a
Nothing of
        Int
1 -> Int -> String -> ([String], [String]) -> ([String], [String])
forall a. Int -> String -> a -> a
dbgMsg Int
lvl (String
"moving 1: "String -> String -> String
forall a. Semigroup a => a -> a -> a
<>String
a) ([], [String]
moved[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++[String
a])
        Int
_ -> ([String
a], [String]
moved)
    moveFlagAndVal ([], [String]
moved) = ([], [String]
moved)
    lvl :: Int
lvl = Int
8

-- Is this a short or long flag argument that should be moved,
-- and is its following argument a value that also should be moved ?
-- Returns:
-- 0 (not a flag; don't move this argument)
-- 1 (a valueless flag, or a long flag with joined argument, or multiple joined valueless short flags; move this argument)
-- 2 (a short or long flag with a value in the next argument; move this and next argument).
isMovableFlagArg :: String -> Maybe String -> Int
isMovableFlagArg :: String -> Maybe String -> Int
isMovableFlagArg String
a1 Maybe String
ma2
  | String
a1 String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
noValFlagArgs  = Int
1  -- short or long no-val flag
  | String
a1 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"--debug" Bool -> Bool -> Bool
&& Maybe String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
ma2 Bool -> Bool -> Bool
&& Bool -> Bool
not (String -> Bool
isDebugValue (String -> Bool) -> String -> Bool
forall a b. (a -> b) -> a -> b
$ Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust Maybe String
ma2) = Int
1  --debug without a value
  | String
a1 String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
reqValFlagArgs = Int
2  -- short or long req-val flag (or --debug) with a separate value
  | String
a1 String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
optValFlagArgs = Int
1  -- long (or short ?) opt-val flag, assume no value
  | (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
a1) [String]
shortReqValFlagArgs = Int
1  -- short req-val flag with a joined value
        -- or possibly multiple joined valueless short flags, we won't move those correctly
  | (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
a1) [String]
longReqValFlagArgs_ = Int
1  -- long req-val flag (or --debug) with a joined value
  | (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
a1) [String]
longOptValFlagArgs_ = Int
1  -- long opt-val flag with a joined value
  -- | isLongFlagArg a1 && any (takeWhile (/='=') `isPrefixOf`) longReqValFlagArgs_ ... -- try to move abbreviated long flags ?
  | String -> Bool
isFlagArg String
a1 = Int
1    -- an addon flag (or mistyped flag) we don't know, assume no value or value is joined
  | Bool
otherwise = Int
0    -- not a flag

-- Is this string a valid --debug value ?
isDebugValue :: String -> Bool
isDebugValue String
s = Either (ParseErrorBundle Text HledgerParseErrorData) Text -> Bool
forall a b. Either a b -> Bool
isRight (Either (ParseErrorBundle Text HledgerParseErrorData) Text -> Bool)
-> Either (ParseErrorBundle Text HledgerParseErrorData) Text
-> Bool
forall a b. (a -> b) -> a -> b
$ Parsec HledgerParseErrorData Text Text
-> Text
-> Either (ParseErrorBundle Text HledgerParseErrorData) Text
forall e a.
Parsec e Text a -> Text -> Either (ParseErrorBundle Text e) a
parsewith Parsec HledgerParseErrorData Text Text
forall {m :: * -> *}. TextParser m Text
isdebugvalp (Text -> Either (ParseErrorBundle Text HledgerParseErrorData) Text)
-> Text
-> Either (ParseErrorBundle Text HledgerParseErrorData) Text
forall a b. (a -> b) -> a -> b
$ String -> Text
pack String
s
  where isdebugvalp :: TextParser m Text
isdebugvalp = ParsecT HledgerParseErrorData Text m Char
-> ParsecT HledgerParseErrorData Text m (Maybe Char)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Token Text -> ParsecT HledgerParseErrorData Text m (Token Text)
forall e s (m :: * -> *).
(MonadParsec e s m, Token s ~ Char) =>
Token s -> m (Token s)
char Char
Token Text
'-') ParsecT HledgerParseErrorData Text m (Maybe Char)
-> ParsecT HledgerParseErrorData Text m Text
-> ParsecT HledgerParseErrorData Text m Text
forall a b.
ParsecT HledgerParseErrorData Text m a
-> ParsecT HledgerParseErrorData Text m b
-> ParsecT HledgerParseErrorData Text m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe String
-> (Token Text -> Bool)
-> ParsecT HledgerParseErrorData Text m (Tokens Text)
forall e s (m :: * -> *).
MonadParsec e s m =>
Maybe String -> (Token s -> Bool) -> m (Tokens s)
takeWhile1P Maybe String
forall a. Maybe a
Nothing Char -> Bool
Token Text -> Bool
isDigit ParsecT HledgerParseErrorData Text m Text
-> ParsecT HledgerParseErrorData Text m ()
-> ParsecT HledgerParseErrorData Text m Text
forall a b.
ParsecT HledgerParseErrorData Text m a
-> ParsecT HledgerParseErrorData Text m b
-> ParsecT HledgerParseErrorData Text m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT HledgerParseErrorData Text m ()
forall e s (m :: * -> *). MonadParsec e s m => m ()
eof :: TextParser m Text

-- Flag arguments are command line arguments beginning with - or --
-- (followed by a short of long flag name, and possibly joined short flags or a joined value).
isFlagArg, isShortFlagArg, isLongFlagArg :: String -> Bool
isFlagArg :: String -> Bool
isFlagArg String
a = String -> Bool
isShortFlagArg String
a Bool -> Bool -> Bool
|| String -> Bool
isLongFlagArg String
a

isShortFlagArg :: String -> Bool
isShortFlagArg (Char
'-':Char
c:String
_) = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'-'
isShortFlagArg String
_         = Bool
False

isLongFlagArg :: String -> Bool
isLongFlagArg (Char
'-':Char
'-':Char
_:String
_) = Bool
True
isLongFlagArg String
_             = Bool
False

-- | Add the leading hyphen(s) to a short or long flag name.
toFlagArg :: Name -> String
toFlagArg :: String -> String
toFlagArg String
f = if String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
f Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 then String
"-"String -> String -> String
forall a. [a] -> [a] -> [a]
++String
f else String
"--"String -> String -> String
forall a. [a] -> [a] -> [a]
++String
f

-- | Flatten a possibly multi-named Flag to (name, FlagInfo) pairs.
toFlagInfos :: Flag RawOpts -> [(Name, FlagInfo)]
toFlagInfos :: Flag RawOpts -> [(String, FlagInfo)]
toFlagInfos Flag RawOpts
f = [(String
n,FlagInfo
i) | let i :: FlagInfo
i = Flag RawOpts -> FlagInfo
forall a. Flag a -> FlagInfo
flagInfo Flag RawOpts
f, String
n <- Flag RawOpts -> [String]
forall a. Flag a -> [String]
flagNames Flag RawOpts
f]

-- | Is this flag's value optional ?
isOptVal :: FlagInfo -> Bool
isOptVal :: FlagInfo -> Bool
isOptVal = \case
  FlagOpt String
_     -> Bool
True
  FlagOptRare String
_ -> Bool
True
  FlagInfo
_             -> Bool
False

-- | All the general flags defined in hledger's main mode.
generalFlags :: [Flag RawOpts]
generalFlags :: [Flag RawOpts]
generalFlags = ((String, [Flag RawOpts]) -> [Flag RawOpts])
-> [(String, [Flag RawOpts])] -> [Flag RawOpts]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (String, [Flag RawOpts]) -> [Flag RawOpts]
forall a b. (a, b) -> b
snd [(String, [Flag RawOpts])]
groupNamed [Flag RawOpts] -> [Flag RawOpts] -> [Flag RawOpts]
forall a. Semigroup a => a -> a -> a
<> [Flag RawOpts]
groupHidden [Flag RawOpts] -> [Flag RawOpts] -> [Flag RawOpts]
forall a. Semigroup a => a -> a -> a
<> [Flag RawOpts]
groupUnnamed
  where Group{[(String, [Flag RawOpts])]
[Flag RawOpts]
groupUnnamed :: forall a. Group a -> [a]
groupNamed :: forall a. Group a -> [(String, [a])]
groupHidden :: forall a. Group a -> [a]
groupNamed :: [(String, [Flag RawOpts])]
groupHidden :: [Flag RawOpts]
groupUnnamed :: [Flag RawOpts]
..} = Mode RawOpts -> Group (Flag RawOpts)
forall a. Mode a -> Group (Flag a)
modeGroupFlags (Mode RawOpts -> Group (Flag RawOpts))
-> Mode RawOpts -> Group (Flag RawOpts)
forall a b. (a -> b) -> a -> b
$ [String] -> Mode RawOpts
mainmode []  

-- | All the general flag names.
generalFlagNames :: [Name]
generalFlagNames :: [String]
generalFlagNames = (Flag RawOpts -> [String]) -> [Flag RawOpts] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Flag RawOpts -> [String]
forall a. Flag a -> [String]
flagNames [Flag RawOpts]
generalFlags

-- | All hledger's builtin subcommand-specific flags.
commandFlags :: [Flag RawOpts]
commandFlags :: [Flag RawOpts]
commandFlags = (Mode RawOpts -> [Flag RawOpts])
-> [Mode RawOpts] -> [Flag RawOpts]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Group (Flag RawOpts) -> [Flag RawOpts]
forall a. Group a -> [a]
groupUnnamed(Group (Flag RawOpts) -> [Flag RawOpts])
-> (Mode RawOpts -> Group (Flag RawOpts))
-> Mode RawOpts
-> [Flag RawOpts]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Mode RawOpts -> Group (Flag RawOpts)
forall a. Mode a -> Group (Flag a)
modeGroupFlags) [Mode RawOpts]
commandModes
  where
    commandModes :: [Mode RawOpts]
commandModes = ((String, [Mode RawOpts]) -> [Mode RawOpts])
-> [(String, [Mode RawOpts])] -> [Mode RawOpts]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (String, [Mode RawOpts]) -> [Mode RawOpts]
forall a b. (a, b) -> b
snd [(String, [Mode RawOpts])]
groupNamed [Mode RawOpts] -> [Mode RawOpts] -> [Mode RawOpts]
forall a. Semigroup a => a -> a -> a
<> [Mode RawOpts]
groupUnnamed [Mode RawOpts] -> [Mode RawOpts] -> [Mode RawOpts]
forall a. Semigroup a => a -> a -> a
<> [Mode RawOpts]
groupHidden
      where Group{[(String, [Mode RawOpts])]
[Mode RawOpts]
groupUnnamed :: forall a. Group a -> [a]
groupNamed :: forall a. Group a -> [(String, [a])]
groupHidden :: forall a. Group a -> [a]
groupNamed :: [(String, [Mode RawOpts])]
groupUnnamed :: [Mode RawOpts]
groupHidden :: [Mode RawOpts]
..} = Mode RawOpts -> Group (Mode RawOpts)
forall a. Mode a -> Group (Mode a)
modeGroupModes (Mode RawOpts -> Group (Mode RawOpts))
-> Mode RawOpts -> Group (Mode RawOpts)
forall a b. (a -> b) -> a -> b
$ [String] -> Mode RawOpts
mainmode []

-- | The names of general options flags, grouped by whether they expect a value.
-- There may be some overlaps with command flag names.
noValGeneralFlagNames, reqValGeneralFlagNames, optValGeneralFlagNames :: [Name]
noValGeneralFlagNames :: [String]
noValGeneralFlagNames  = [String
f | (String
f,FlagInfo
i) <- (Flag RawOpts -> [(String, FlagInfo)])
-> [Flag RawOpts] -> [(String, FlagInfo)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Flag RawOpts -> [(String, FlagInfo)]
toFlagInfos [Flag RawOpts]
generalFlags, FlagInfo
i FlagInfo -> FlagInfo -> Bool
forall a. Eq a => a -> a -> Bool
== FlagInfo
FlagNone]
reqValGeneralFlagNames :: [String]
reqValGeneralFlagNames = [String
f | (String
f,FlagInfo
i) <- (Flag RawOpts -> [(String, FlagInfo)])
-> [Flag RawOpts] -> [(String, FlagInfo)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Flag RawOpts -> [(String, FlagInfo)]
toFlagInfos [Flag RawOpts]
generalFlags, FlagInfo
i FlagInfo -> FlagInfo -> Bool
forall a. Eq a => a -> a -> Bool
== FlagInfo
FlagReq]
optValGeneralFlagNames :: [String]
optValGeneralFlagNames = [String
f | (String
f,FlagInfo
i) <- (Flag RawOpts -> [(String, FlagInfo)])
-> [Flag RawOpts] -> [(String, FlagInfo)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Flag RawOpts -> [(String, FlagInfo)]
toFlagInfos [Flag RawOpts]
generalFlags, FlagInfo -> Bool
isOptVal FlagInfo
i]

-- | The names of builtin subcommand flags, grouped by whether they expect a value.
-- There may be some overlaps with general flag names.
noValCommandFlagNames, reqValCommandFlagNames, optValCommandFlagNames :: [Name]
noValCommandFlagNames :: [String]
noValCommandFlagNames  = [String
f | (String
f,FlagInfo
i) <- (Flag RawOpts -> [(String, FlagInfo)])
-> [Flag RawOpts] -> [(String, FlagInfo)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Flag RawOpts -> [(String, FlagInfo)]
toFlagInfos [Flag RawOpts]
commandFlags, FlagInfo
i FlagInfo -> FlagInfo -> Bool
forall a. Eq a => a -> a -> Bool
== FlagInfo
FlagNone]
reqValCommandFlagNames :: [String]
reqValCommandFlagNames = [String
f | (String
f,FlagInfo
i) <- (Flag RawOpts -> [(String, FlagInfo)])
-> [Flag RawOpts] -> [(String, FlagInfo)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Flag RawOpts -> [(String, FlagInfo)]
toFlagInfos [Flag RawOpts]
commandFlags, FlagInfo
i FlagInfo -> FlagInfo -> Bool
forall a. Eq a => a -> a -> Bool
== FlagInfo
FlagReq]
optValCommandFlagNames :: [String]
optValCommandFlagNames = [String
f | (String
f,FlagInfo
i) <- (Flag RawOpts -> [(String, FlagInfo)])
-> [Flag RawOpts] -> [(String, FlagInfo)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Flag RawOpts -> [(String, FlagInfo)]
toFlagInfos [Flag RawOpts]
commandFlags, FlagInfo -> Bool
isOptVal FlagInfo
i]

-- All flag arguments understood by hledger cli and builtin commands, grouped by whether they expect a value.
-- Any command flags which have the same name as a general flag are excluded.
noValFlagArgs :: [String]
noValFlagArgs  = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
toFlagArg ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
noValGeneralFlagNames  [String] -> [String] -> [String]
forall a. Eq a => [a] -> [a] -> [a]
`union` ([String]
noValCommandFlagNames  [String] -> [String] -> [String]
forall a. Eq a => [a] -> [a] -> [a]
\\ [String]
generalFlagNames)
reqValFlagArgs :: [String]
reqValFlagArgs = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
toFlagArg ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
reqValGeneralFlagNames [String] -> [String] -> [String]
forall a. Eq a => [a] -> [a] -> [a]
`union` ([String]
reqValCommandFlagNames [String] -> [String] -> [String]
forall a. Eq a => [a] -> [a] -> [a]
\\ [String]
generalFlagNames)
optValFlagArgs :: [String]
optValFlagArgs = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
toFlagArg ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
optValGeneralFlagNames [String] -> [String] -> [String]
forall a. Eq a => [a] -> [a] -> [a]
`union` ([String]
optValCommandFlagNames [String] -> [String] -> [String]
forall a. Eq a => [a] -> [a] -> [a]
\\ [String]
generalFlagNames)

-- Short flag args that expect a required value.
shortReqValFlagArgs :: [String]
shortReqValFlagArgs = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter String -> Bool
isShortFlagArg [String]
reqValFlagArgs

-- Long flag args that expect a required value, with = appended.
longReqValFlagArgs_ :: [String]
longReqValFlagArgs_ = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> String
forall a. [a] -> [a] -> [a]
++String
"=") ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter String -> Bool
isLongFlagArg [String]
reqValFlagArgs

-- Long flag args that expect an optional value, with = appended.
longOptValFlagArgs_ :: [String]
longOptValFlagArgs_ = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> String -> String
forall a. [a] -> [a] -> [a]
++String
"=") ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter String -> Bool
isLongFlagArg [String]
optValFlagArgs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"--debug"]

-- Drop any arguments which look like cli-specific options (--no-conf, --conf CONFFILE, etc.)
-- Keep synced with mainmode's groupUnnamed.
dropCliSpecificOpts :: [String] -> [String]
dropCliSpecificOpts :: [String] -> [String]
dropCliSpecificOpts = \case
  String
"--conf":String
_:[String]
as                   -> [String] -> [String]
dropCliSpecificOpts [String]
as
  String
a:[String]
as | String
"--conf=" String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
a -> [String] -> [String]
dropCliSpecificOpts [String]
as
  String
"--no-conf":[String]
as                  -> [String] -> [String]
dropCliSpecificOpts [String]
as
  String
"-n":[String]
as                         -> [String] -> [String]
dropCliSpecificOpts [String]
as
  String
a:[String]
as                            -> String
aString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String] -> [String]
dropCliSpecificOpts [String]
as
  []                              -> []

-- | Given a hledger cmdargs mode and a list of command line arguments, try to drop any of the
-- arguments which seem to be flags not supported by this mode. Also drop their values if any.
--
-- >>> dropUnsupportedOpts confflagsmode ["--debug","1","-f","file"]
-- []
-- >>> dropUnsupportedOpts confflagsmode ["--debug","-f","file"]
-- []
dropUnsupportedOpts :: Mode RawOpts -> [String] -> [String]
dropUnsupportedOpts :: Mode RawOpts -> [String] -> [String]
dropUnsupportedOpts Mode RawOpts
m = \case
  []   -> []
  String
"--debug":String
a:[String]
as | Bool -> Bool
not (Mode RawOpts
m Mode RawOpts -> String -> Bool
forall {a}. Mode a -> String -> Bool
`supportsFlag` String
"debug") ->
    [String] -> [String]
go ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ if String -> Bool
isDebugValue String
a then [String]
as else String
aString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
as
  String
a:[String]
as -> if
    | String -> Bool
isLongFlagArg String
a,
      let f :: String
f = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'=') String
a,
      let as' :: [String]
as' = if String -> Bool
isReqValFlagArg String
f Bool -> Bool -> Bool
&& Char
'=' Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` String
a then Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 [String]
as else [String]
as
      -> if Mode RawOpts
m Mode RawOpts -> String -> Bool
forall {a}. Mode a -> String -> Bool
`supportsFlag` String
f then String
a String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String] -> [String]
go [String]
as else [String] -> [String]
go [String]
as'
    | String -> Bool
isShortFlagArg String
a,
      let f :: String
f = Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
a,
      let as' :: [String]
as' = if String -> Bool
isReqValFlagArg String
f Bool -> Bool -> Bool
&& String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2 then Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 [String]
as else [String]
as
      -> if Mode RawOpts
m Mode RawOpts -> String -> Bool
forall {a}. Mode a -> String -> Bool
`supportsFlag` String
f then String
a String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String] -> [String]
go [String]
as else [String] -> [String]
go [String]
as'
    | Bool
otherwise -> String
a String -> [String] -> [String]
forall a. a -> [a] -> [a]
: Mode RawOpts -> [String] -> [String]
dropUnsupportedOpts Mode RawOpts
m [String]
as
  where
    go :: [String] -> [String]
go = Mode RawOpts -> [String] -> [String]
dropUnsupportedOpts Mode RawOpts
m
    isReqValFlagArg :: String -> Bool
isReqValFlagArg = (String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
reqValFlagArgs)
    supportsFlag :: Mode a -> String -> Bool
supportsFlag Mode a
m1 String
flagarg = String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem String
flagarg ([String] -> Bool) -> [String] -> Bool
forall a b. (a -> b) -> a -> b
$ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map String -> String
toFlagArg ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (Flag a -> [String]) -> [Flag a] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Flag a -> [String]
forall a. Flag a -> [String]
flagNames ([Flag a] -> [String]) -> [Flag a] -> [String]
forall a b. (a -> b) -> a -> b
$ Mode a -> [Flag a]
forall a. Mode a -> [Flag a]
modeAndSubmodeFlags Mode a
m1

-- | Get all the flags defined in a mode or its immediate subcommands,
-- whether in named, unnamed or hidden groups.
-- Does not recurse into subsubcommands,
-- and does not deduplicate (general flags are repeated on all hledger subcommands).
modeAndSubmodeFlags :: Mode a -> [Flag a]
modeAndSubmodeFlags :: forall a. Mode a -> [Flag a]
modeAndSubmodeFlags m :: Mode a
m@Mode{modeGroupModes :: forall a. Mode a -> Group (Mode a)
modeGroupModes=Group{[(String, [Mode a])]
[Mode a]
groupUnnamed :: forall a. Group a -> [a]
groupNamed :: forall a. Group a -> [(String, [a])]
groupHidden :: forall a. Group a -> [a]
groupUnnamed :: [Mode a]
groupHidden :: [Mode a]
groupNamed :: [(String, [Mode a])]
..}} =
  Mode a -> [Flag a]
forall a. Mode a -> [Flag a]
modeFlags Mode a
m [Flag a] -> [Flag a] -> [Flag a]
forall a. Semigroup a => a -> a -> a
<> (Mode a -> [Flag a]) -> [Mode a] -> [Flag a]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Mode a -> [Flag a]
forall a. Mode a -> [Flag a]
modeFlags (((String, [Mode a]) -> [Mode a])
-> [(String, [Mode a])] -> [Mode a]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (String, [Mode a]) -> [Mode a]
forall a b. (a, b) -> b
snd [(String, [Mode a])]
groupNamed [Mode a] -> [Mode a] -> [Mode a]
forall a. Semigroup a => a -> a -> a
<> [Mode a]
groupUnnamed [Mode a] -> [Mode a] -> [Mode a]
forall a. Semigroup a => a -> a -> a
<> [Mode a]
groupHidden)

-- unit tests (tests_Hledger_Cli) are defined in Hledger.Cli.Commands