{-|
hledger - a ledger-compatible accounting tool.
Copyright (c) 2007-2011 Simon Michael <simon@joyful.com>
Released under GPL version 3 or later.

hledger is a partial haskell clone of John Wiegley's "ledger".  It
generates ledger-compatible register & balance reports from a plain text
journal, and demonstrates a functional implementation of ledger.
For more information, see http:\/\/hledger.org .

This module provides the main function for the hledger command-line
executable. It is exposed here so that it can be imported by eg benchmark
scripts.

You can use the command line:

> $ hledger --help

or ghci:

> $ ghci hledger
> > Right j <- readJournalFile definputopts "examples/sample.journal"
> > register [] ["income","expenses"] j
> 2008/01/01 income               income:salary                   $-1          $-1
> 2008/06/01 gift                 income:gifts                    $-1          $-2
> 2008/06/03 eat & shop           expenses:food                    $1          $-1
>                                 expenses:supplies                $1            0
> > balance [Depth "1"] [] l
>                  $-1  assets
>                   $2  expenses
>                  $-2  income
>                   $1  liabilities
> > j <- defaultJournal

etc.

-}

{-# LANGUAGE LambdaCase #-}

module Hledger.Cli.Main where

import Data.Char (isDigit)
import Data.List
import Safe
import qualified System.Console.CmdArgs.Explicit as C
import System.Environment
import System.Exit
import System.FilePath
import System.Process
import Text.Printf

import Hledger.Cli
import Data.Time.Clock.POSIX (getPOSIXTime)


-- | The overall cmdargs mode describing hledger's command-line options and subcommands.
mainmode :: [String] -> Mode RawOpts
mainmode [String]
addons = Mode RawOpts
defMode {
  modeNames :: [String]
modeNames = [String
progname forall a. [a] -> [a] -> [a]
++ String
" [CMD]"]
 ,modeArgs :: ([Arg RawOpts], Maybe (Arg RawOpts))
modeArgs = ([], forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ String -> Arg RawOpts
argsFlag String
"[ARGS]")
 ,modeHelp :: String
modeHelp = [String] -> String
unlines [String
"hledger's main command line interface. Runs builtin commands and other hledger executables. Type \"hledger\" to list available commands."]
 ,modeGroupModes :: Group (Mode RawOpts)
modeGroupModes = Group {
    -- subcommands in the unnamed group, shown first:
    groupUnnamed :: [Mode RawOpts]
groupUnnamed = [
     ]
    -- subcommands in named groups:
   ,groupNamed :: [(String, [Mode RawOpts])]
groupNamed = [
     ]
    -- subcommands handled but not shown in the help:
   ,groupHidden :: [Mode RawOpts]
groupHidden = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(Mode RawOpts, CliOpts -> Journal -> IO ())]
builtinCommands forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map String -> Mode RawOpts
addonCommandMode [String]
addons
   }
 ,modeGroupFlags :: Group (Flag RawOpts)
modeGroupFlags = Group {
     -- flags in named groups:
     groupNamed :: [(String, [Flag RawOpts])]
groupNamed = [
        (  String
"General input flags",     [Flag RawOpts]
inputflags)
       ,(String
"\nGeneral reporting flags", [Flag RawOpts]
reportflags)
       ,(String
"\nGeneral help flags",      [Flag RawOpts]
helpflags)
       ]
     -- flags in the unnamed group, shown last:
    ,groupUnnamed :: [Flag RawOpts]
groupUnnamed = []
     -- flags handled but not shown in the help:
    ,groupHidden :: [Flag RawOpts]
groupHidden =
        [Flag RawOpts
detailedversionflag]
        -- ++ inputflags -- included here so they'll not raise a confusing error if present with no COMMAND
    }
 ,modeHelpSuffix :: [String]
modeHelpSuffix = String
"Examples:" forall a. a -> [a] -> [a]
:
    forall a b. (a -> b) -> [a] -> [b]
map (String
progname forall a. [a] -> [a] -> [a]
++) [
     String
"                         list commands"
    ,String
" CMD [--] [OPTS] [ARGS]  run a command (use -- with addon commands)"
    ,String
"-CMD [OPTS] [ARGS]       or run addon commands directly"
    ,String
" -h                      show general usage"
    ,String
" CMD -h                  show command usage"
    ,String
" help [MANUAL]           show any of the hledger manuals in various formats"
    ]
 }

-- | Let's go!
main :: IO ()
main :: IO ()
main = do
  POSIXTime
starttime <- IO POSIXTime
getPOSIXTime

  -- Choose and run the appropriate internal or external command based
  -- on the raw command-line arguments, cmdarg's interpretation of
  -- same, and hledger-* executables in the user's PATH. A somewhat
  -- complex mishmash of cmdargs and custom processing, hence all the
  -- debugging support and tests. See also Hledger.Cli.CliOptions and
  -- command-line.test.

  -- some preliminary (imperfect) argument parsing to supplement cmdargs
  [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]
moveFlagsAfterCommand forall a b. (a -> b) -> a -> b
$ [String] -> [String]
replaceNumericFlags [String]
args
    isFlag :: String -> Bool
isFlag               = (String
"-" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf`)
    isNonEmptyNonFlag :: String -> Bool
isNonEmptyNonFlag String
s  = Bool -> Bool
not (String -> Bool
isFlag String
s) Bool -> Bool -> Bool
&& Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
s)
    rawcmd :: String
rawcmd               = forall a. a -> [a] -> a
headDef String
"" forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
takeWhile String -> Bool
isNonEmptyNonFlag [String]
args'
    isNullCommand :: Bool
isNullCommand        = forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
rawcmd
    ([String]
argsbeforecmd, [String]
argsaftercmd') = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
==String
rawcmd) [String]
args
    argsaftercmd :: [String]
argsaftercmd         = forall a. Int -> [a] -> [a]
drop Int
1 [String]
argsaftercmd'
    dbgIO :: Show a => String -> a -> IO ()
    dbgIO :: forall a. Show a => String -> a -> IO ()
dbgIO = forall (m :: * -> *) a.
(MonadIO m, Show a) =>
Int -> String -> a -> m ()
ptraceAtIO Int
8

  forall a. Show a => String -> a -> IO ()
dbgIO String
"running" String
prognameandversion
  forall a. Show a => String -> a -> IO ()
dbgIO String
"raw args" [String]
args
  forall a. Show a => String -> a -> IO ()
dbgIO String
"raw args rearranged for cmdargs" [String]
args'
  forall a. Show a => String -> a -> IO ()
dbgIO String
"raw command is probably" String
rawcmd
  forall a. Show a => String -> a -> IO ()
dbgIO String
"raw args before command" [String]
argsbeforecmd
  forall a. Show a => String -> a -> IO ()
dbgIO String
"raw args after command" [String]
argsaftercmd

  -- Search PATH for add-ons, excluding any that match built-in command names
  [String]
addons' <- IO [String]
hledgerAddons
  let addons :: [String]
addons = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
builtinCommandNames) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
dropExtension) [String]
addons'

  -- parse arguments with cmdargs
  CliOpts
opts' <- [String] -> [String] -> IO CliOpts
argsToCliOpts [String]
args [String]
addons
  let opts :: CliOpts
opts = CliOpts
opts'{progstarttime_ :: POSIXTime
progstarttime_=POSIXTime
starttime}

  -- select an action and run it.
  let
    cmd :: String
cmd                  = CliOpts -> String
command_ CliOpts
opts -- the full matched internal or external command name, if any
    isInternalCommand :: Bool
isInternalCommand    = String
cmd forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
builtinCommandNames -- not (null cmd) && not (cmd `elem` addons)
    isExternalCommand :: Bool
isExternalCommand    = Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
cmd) Bool -> Bool -> Bool
&& String
cmd forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
addons -- probably
    isBadCommand :: Bool
isBadCommand         = Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
rawcmd) Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
cmd
    hasVersion :: [String] -> Bool
hasVersion           = (String
"--version" forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem`)
    printUsage :: IO ()
printUsage           = String -> IO ()
putStr forall a b. (a -> b) -> a -> b
$ forall a. Mode a -> String
showModeUsage forall a b. (a -> b) -> a -> b
$ [String] -> Mode RawOpts
mainmode [String]
addons
    badCommandError :: IO b
badCommandError      = forall a. String -> a
error' (String
"command "forall a. [a] -> [a] -> [a]
++String
rawcmdforall a. [a] -> [a] -> [a]
++String
" is not recognized, run with no command to see a list") forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. IO a
exitFailure  -- PARTIAL:
    hasHelpFlag :: t String -> Bool
hasHelpFlag t String
args1     = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` t String
args1) [String
"-h",String
"--help"]
    hasManFlag :: t String -> Bool
hasManFlag t String
args1      = (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` t String
args1) String
"--man"
    hasInfoFlag :: t String -> Bool
hasInfoFlag t String
args1     = (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` t String
args1) String
"--info"
    IO ()
f orShowHelp :: IO () -> Mode a -> IO ()
`orShowHelp` Mode a
mode1
      | forall {t :: * -> *}. Foldable t => t String -> Bool
hasHelpFlag [String]
args = String -> IO ()
putStr forall a b. (a -> b) -> a -> b
$ forall a. Mode a -> String
showModeUsage Mode a
mode1
      | forall {t :: * -> *}. Foldable t => t String -> Bool
hasInfoFlag [String]
args = String -> Maybe String -> IO ()
runInfoForTopic String
"hledger" (forall a. [a] -> Maybe a
headMay forall a b. (a -> b) -> a -> b
$ forall a. Mode a -> [String]
modeNames Mode a
mode1)
      | forall {t :: * -> *}. Foldable t => t String -> Bool
hasManFlag [String]
args  = String -> Maybe String -> IO ()
runManForTopic String
"hledger" (forall a. [a] -> Maybe a
headMay forall a b. (a -> b) -> a -> b
$ forall a. Mode a -> [String]
modeNames Mode a
mode1)
      | Bool
otherwise        = IO ()
f
      -- where
      --   lastdocflag
  forall a. Show a => String -> a -> IO ()
dbgIO String
"processed opts" CliOpts
opts
  forall a. Show a => String -> a -> IO ()
dbgIO String
"command matched" String
cmd
  forall a. Show a => String -> a -> IO ()
dbgIO String
"isNullCommand" Bool
isNullCommand
  forall a. Show a => String -> a -> IO ()
dbgIO String
"isInternalCommand" Bool
isInternalCommand
  forall a. Show a => String -> a -> IO ()
dbgIO String
"isExternalCommand" Bool
isExternalCommand
  forall a. Show a => String -> a -> IO ()
dbgIO String
"isBadCommand" Bool
isBadCommand
  forall a. Show a => String -> a -> IO ()
dbgIO String
"period from opts" (ReportOpts -> Period
period_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportSpec -> ReportOpts
_rsReportOpts forall a b. (a -> b) -> a -> b
$ CliOpts -> ReportSpec
reportspec_ CliOpts
opts)
  forall a. Show a => String -> a -> IO ()
dbgIO String
"interval from opts" (ReportOpts -> Interval
interval_ forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReportSpec -> ReportOpts
_rsReportOpts forall a b. (a -> b) -> a -> b
$ CliOpts -> ReportSpec
reportspec_ CliOpts
opts)
  forall a. Show a => String -> a -> IO ()
dbgIO String
"query from opts & args" (ReportSpec -> Query
_rsQuery forall a b. (a -> b) -> a -> b
$ CliOpts -> ReportSpec
reportspec_ CliOpts
opts)
  let
    journallesserror :: a
journallesserror = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
cmdforall a. [a] -> [a] -> [a]
++String
" tried to read the journal but is not supposed to"
    runHledgerCommand :: IO ()
runHledgerCommand
      -- high priority flags and situations. -h, then --help, then --info are highest priority.
      | Bool
isNullCommand Bool -> Bool -> Bool
&& forall {t :: * -> *}. Foldable t => t String -> Bool
hasHelpFlag [String]
args = forall a. Show a => String -> a -> IO ()
dbgIO String
"" String
"-h/--help with no command, showing general help" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
printUsage
      | Bool
isNullCommand Bool -> Bool -> Bool
&& forall {t :: * -> *}. Foldable t => t String -> Bool
hasInfoFlag [String]
args = forall a. Show a => String -> a -> IO ()
dbgIO String
"" String
"--info with no command, showing general info manual" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Maybe String -> IO ()
runInfoForTopic String
"hledger" forall a. Maybe a
Nothing
      | Bool
isNullCommand Bool -> Bool -> Bool
&& forall {t :: * -> *}. Foldable t => t String -> Bool
hasManFlag [String]
args  = forall a. Show a => String -> a -> IO ()
dbgIO String
"" String
"--man with no command, showing general man page" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> Maybe String -> IO ()
runManForTopic String
"hledger" forall a. Maybe a
Nothing
      | Bool -> Bool
not (Bool
isExternalCommand Bool -> Bool -> Bool
|| forall {t :: * -> *}. Foldable t => t String -> Bool
hasHelpFlag [String]
args Bool -> Bool -> Bool
|| forall {t :: * -> *}. Foldable t => t String -> Bool
hasInfoFlag [String]
args Bool -> Bool -> Bool
|| forall {t :: * -> *}. Foldable t => t String -> Bool
hasManFlag [String]
args)
        Bool -> Bool -> Bool
&& ([String] -> Bool
hasVersion [String]
args) --  || (hasVersion argsaftercmd && isInternalCommand))
                                 = String -> IO ()
putStrLn String
prognameandversion
      -- \| (null externalcmd) && "binary-filename" `inRawOpts` rawopts = putStrLn $ binaryfilename progname
      -- \| "--browse-args" `elem` args     = System.Console.CmdArgs.Helper.execute "cmdargs-browser" mainmode' args >>= (putStr . show)
      | Bool
isNullCommand            = forall a. Show a => String -> a -> IO ()
dbgIO String
"" String
"no command, showing commands list" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> [String] -> IO ()
printCommandsList String
prognameandversion [String]
addons
      | Bool
isBadCommand             = forall a. IO a
badCommandError

      -- builtin commands
      | Just (Mode RawOpts
cmdmode, CliOpts -> Journal -> IO ()
cmdaction) <- String -> Maybe (Mode RawOpts, CliOpts -> Journal -> IO ())
findCommand String
cmd =
        (case Bool
True of
           -- these commands should not require or read the journal
          Bool
_ | String
cmd forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"test",String
"help"] -> CliOpts -> Journal -> IO ()
cmdaction CliOpts
opts forall {a}. a
journallesserror
          -- these commands should create the journal if missing
          Bool
_ | String
cmd forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"add",String
"import"] -> do
            String -> IO ()
ensureJournalFileExists forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
head forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< CliOpts -> IO [String]
journalFilePathFromOpts CliOpts
opts
            forall a. CliOpts -> (Journal -> IO a) -> IO a
withJournalDo CliOpts
opts (CliOpts -> Journal -> IO ()
cmdaction CliOpts
opts)
          -- other commands read the journal and should fail if it's missing
          Bool
_ -> forall a. CliOpts -> (Journal -> IO a) -> IO a
withJournalDo CliOpts
opts (CliOpts -> Journal -> IO ()
cmdaction CliOpts
opts)
        )
        forall {a}. IO () -> Mode a -> IO ()
`orShowHelp` Mode RawOpts
cmdmode

      -- addon commands
      | Bool
isExternalCommand = do
          let externalargs :: [String]
externalargs = [String]
argsbeforecmd forall a. [a] -> [a] -> [a]
++ forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/=String
"--") [String]
argsaftercmd
          let shellcmd :: String
shellcmd = forall r. PrintfType r => String -> r
printf String
"%s-%s %s" String
progname String
cmd ([String] -> String
unwords' [String]
externalargs) :: String
          forall a. Show a => String -> a -> IO ()
dbgIO String
"external command selected" String
cmd
          forall a. Show a => String -> a -> IO ()
dbgIO String
"external command arguments" (forall a b. (a -> b) -> [a] -> [b]
map String -> String
quoteIfNeeded [String]
externalargs)
          forall a. Show a => String -> a -> IO ()
dbgIO String
"running shell command" String
shellcmd
          String -> IO ExitCode
system String
shellcmd forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. ExitCode -> IO a
exitWith

      -- deprecated commands
      -- cmd == "convert"         = error' (modeHelp oldconvertmode) >> exitFailure

      -- shouldn't reach here
      | Bool
otherwise                = forall a. String -> a
usageError (String
"could not understand the arguments "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> String
show [String]
args) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. IO a
exitFailure

  IO ()
runHledgerCommand

-- | Parse hledger CLI options from these command line arguments and
-- add-on command names, or raise any error.
argsToCliOpts :: [String] -> [String] -> IO CliOpts
argsToCliOpts :: [String] -> [String] -> IO CliOpts
argsToCliOpts [String]
args [String]
addons = do
  let
    args' :: [String]
args'        = [String] -> [String]
moveFlagsAfterCommand forall a b. (a -> b) -> a -> b
$ [String] -> [String]
replaceNumericFlags [String]
args
    cmdargsopts :: RawOpts
cmdargsopts  = 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
C.process ([String] -> Mode RawOpts
mainmode [String]
addons) [String]
args'
  RawOpts -> IO CliOpts
rawOptsToCliOpts RawOpts
cmdargsopts

-- | A hacky workaround for cmdargs not accepting flags before the
-- subcommand name: try to detect and move such flags after the
-- command.  This allows the user to put them in either position.
-- The order of options is not preserved, but this should be ok.
--
-- Since we're not parsing flags as precisely as cmdargs here, this is
-- imperfect. We make a decent effort to:
-- - move all no-argument help/input/report flags
-- - move all required-argument help/input/report flags along with their values, space-separated or not
-- - not confuse things further or cause misleading errors.
moveFlagsAfterCommand :: [String] -> [String]
moveFlagsAfterCommand :: [String] -> [String]
moveFlagsAfterCommand [String]
args = [String] -> [String]
moveArgs forall a b. (a -> b) -> a -> b
$ [String] -> [String]
ensureDebugHasArg [String]
args
  where
    -- quickly! make sure --debug has a numeric argument, or this all goes to hell
    ensureDebugHasArg :: [String] -> [String]
ensureDebugHasArg [String]
as =
      case forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
==String
"--debug") [String]
as of
       ([String]
bs,String
"--debug":String
c:[String]
cs) | forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
c Bool -> Bool -> Bool
|| Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isDigit String
c) -> [String]
bsforall a. [a] -> [a] -> [a]
++String
"--debug=1"forall a. a -> [a] -> [a]
:String
cforall a. a -> [a] -> [a]
:[String]
cs
       ([String]
bs,[String
"--debug"])                                    -> [String]
bsforall a. [a] -> [a] -> [a]
++[String
"--debug=1"]
       ([String], [String])
_                                                   -> [String]
as

    moveArgs :: [String] -> [String]
moveArgs [String]
args1 = forall {a}. ([a], [a]) -> [a]
insertFlagsAfterCommand forall a b. (a -> b) -> a -> b
$ ([String], [String]) -> ([String], [String])
moveArgs' ([String]
args1, [])
      where
        -- -f FILE ..., --alias ALIAS ...
        moveArgs' :: ([String], [String]) -> ([String], [String])
moveArgs' ((String
f:String
v:String
a:[String]
as), [String]
flags) | String -> Bool
isMovableReqArgFlag String
f, String -> Bool
isValue String
v       = ([String], [String]) -> ([String], [String])
moveArgs' (String
aforall a. a -> [a] -> [a]
:[String]
as, [String]
flags forall a. [a] -> [a] -> [a]
++ [String
f,String
v])
        -- -fFILE ..., --alias=ALIAS ...
        moveArgs' ((String
fv:String
a:[String]
as), [String]
flags)  | String -> Bool
isMovableArgFlagAndValue String
fv            = ([String], [String]) -> ([String], [String])
moveArgs' (String
aforall a. a -> [a] -> [a]
:[String]
as, [String]
flags forall a. [a] -> [a] -> [a]
++ [String
fv])
        -- -f(missing arg)
        moveArgs' ((String
f:String
a:[String]
as), [String]
flags)   | String -> Bool
isMovableReqArgFlag String
f, Bool -> Bool
not (String -> Bool
isValue String
a) = ([String], [String]) -> ([String], [String])
moveArgs' (String
aforall a. a -> [a] -> [a]
:[String]
as, [String]
flags forall a. [a] -> [a] -> [a]
++ [String
f])
        -- -h ..., --version ...
        moveArgs' ((String
f:String
a:[String]
as), [String]
flags)   | String -> Bool
isMovableNoArgFlag String
f                   = ([String], [String]) -> ([String], [String])
moveArgs' (String
aforall a. a -> [a] -> [a]
:[String]
as, [String]
flags forall a. [a] -> [a] -> [a]
++ [String
f])
        -- anything else
        moveArgs' ([String]
as, [String]
flags) = ([String]
as, [String]
flags)

        insertFlagsAfterCommand :: ([a], [a]) -> [a]
insertFlagsAfterCommand ([],           [a]
flags) = [a]
flags
        insertFlagsAfterCommand (a
command1:[a]
args2, [a]
flags) = [a
command1] forall a. [a] -> [a] -> [a]
++ [a]
flags forall a. [a] -> [a] -> [a]
++ [a]
args2

isMovableNoArgFlag :: String -> Bool
isMovableNoArgFlag String
a  = String
"-" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
a Bool -> Bool -> Bool
&& forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
==Char
'-') String
a forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
optargflagstomove forall a. [a] -> [a] -> [a]
++ [String]
noargflagstomove

isMovableReqArgFlag :: String -> Bool
isMovableReqArgFlag String
a = String
"-" forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
a Bool -> Bool -> Bool
&& forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
==Char
'-') String
a forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
reqargflagstomove

isMovableArgFlagAndValue :: String -> Bool
isMovableArgFlagAndValue (Char
'-':Char
'-':Char
a:String
as) = case forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== Char
'=') (Char
aforall a. a -> [a] -> [a]
:String
as) of
    (Char
f:String
fs,Char
_:String
_) -> (Char
fforall a. a -> [a] -> [a]
:String
fs) forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
optargflagstomove forall a. [a] -> [a] -> [a]
++ [String]
reqargflagstomove
    (String, String)
_          -> Bool
False
isMovableArgFlagAndValue (Char
'-':Char
shortflag:Char
_:String
_) = [Char
shortflag] forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
reqargflagstomove
isMovableArgFlagAndValue String
_ = Bool
False

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

flagstomove :: [Flag RawOpts]
flagstomove = [Flag RawOpts]
inputflags forall a. [a] -> [a] -> [a]
++ [Flag RawOpts]
reportflags forall a. [a] -> [a] -> [a]
++ [Flag RawOpts]
helpflags
noargflagstomove :: [String]
noargflagstomove  = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a. Flag a -> [String]
flagNames forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
==FlagInfo
FlagNone)forall b c a. (b -> c) -> (a -> b) -> a -> c
.forall a. Flag a -> FlagInfo
flagInfo) [Flag RawOpts]
flagstomove
reqargflagstomove :: [String]
reqargflagstomove = -- filter (/= "debug") $
                    forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a. Flag a -> [String]
flagNames forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
==FlagInfo
FlagReq )forall b c a. (b -> c) -> (a -> b) -> a -> c
.forall a. Flag a -> FlagInfo
flagInfo) [Flag RawOpts]
flagstomove
optargflagstomove :: [String]
optargflagstomove = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall a. Flag a -> [String]
flagNames forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (FlagInfo -> Bool
isFlagOpt   forall b c a. (b -> c) -> (a -> b) -> a -> c
.forall a. Flag a -> FlagInfo
flagInfo) [Flag RawOpts]
flagstomove
  where
    isFlagOpt :: FlagInfo -> Bool
isFlagOpt = \case
      FlagOpt     String
_ -> Bool
True
      FlagOptRare String
_ -> Bool
True
      FlagInfo
_             -> Bool
False