| Copyright | (c) Dennis Gosnell 2023 |
|---|---|
| License | BSD3 |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Termonad.Cli
Description
This module exposes Termonad's CLI argument parsing functionality.
The main function for parsing CLI arguments is parseCliArgs. The function
that knows how to combine CLI arguments with normal ConfigOptions is
applyCliArgs.
Synopsis
- data CliArgs = CliArgs {}
- defaultCliArgs :: CliArgs
- data CliConfigOptions = CliConfigOptions {
- cliConfFontFamily :: !(Option Text)
- cliConfFontSize :: !(Option FontSize)
- cliConfShowScrollbar :: !(Option ShowScrollbar)
- cliConfScrollbackLen :: !(Option Integer)
- cliConfConfirmExit :: !(Option Bool)
- cliConfWordCharExceptions :: !(Option Text)
- cliConfShowMenu :: !(Option Bool)
- cliConfShowTabBar :: !(Option ShowTabBar)
- cliConfCursorBlinkMode :: !(Option CursorBlinkMode)
- cliConfBoldIsBright :: !(Option Bool)
- cliConfEnableSixel :: !(Option Bool)
- cliConfAllowBold :: !(Option Bool)
- defaultCliConfigOptions :: CliConfigOptions
- data ExtraCliArgs = ExtraCliArgs
- defaultExtraCliArgs :: ExtraCliArgs
- strOption' :: IsString s => Mod OptionFields (Option s) -> Parser (Option s)
- option' :: ReadM a -> Mod OptionFields (Option a) -> Parser (Option a)
- maybeTextReader :: (Text -> Maybe a) -> ReadM a
- optionFlag :: a -> a -> Char -> Char -> String -> String -> String -> Parser (Option a)
- cliConfigOptionsParser :: Parser CliConfigOptions
- fontFamilyParser :: Parser (Option Text)
- fontSizeParser :: Parser (Option FontSize)
- showScrollbarParser :: Parser (Option ShowScrollbar)
- scrollbackLenParser :: Parser (Option Integer)
- confirmExitParser :: Parser (Option Bool)
- wordCharExceptionsParser :: Parser (Option Text)
- showMenuParser :: Parser (Option Bool)
- showTabBarParser :: Parser (Option ShowTabBar)
- cursorBlinkModeParser :: Parser (Option CursorBlinkMode)
- boldIsBrightParser :: Parser (Option Bool)
- enableSixelParser :: Parser (Option Bool)
- allowBoldParser :: Parser (Option Bool)
- extraCliArgsParser :: Parser ExtraCliArgs
- cliArgsParser :: Parser CliArgs
- cliArgsParserInfo :: ParserInfo CliArgs
- parseCliArgs :: IO CliArgs
- applyCliArgs :: CliArgs -> ConfigOptions -> ConfigOptions
Documentation
A data type that contains arguments from the command line.
Constructors
| CliArgs | |
Fields | |
data CliConfigOptions Source #
CLI arguments that correspond to fields in ConfigOptions.
See ConfigOptions for what each of these options mean.
Constructors
| CliConfigOptions | |
Fields
| |
Instances
| Show CliConfigOptions Source # | |
Defined in Termonad.Cli Methods showsPrec :: Int -> CliConfigOptions -> ShowS # show :: CliConfigOptions -> String # showList :: [CliConfigOptions] -> ShowS # | |
| Eq CliConfigOptions Source # | |
Defined in Termonad.Cli Methods (==) :: CliConfigOptions -> CliConfigOptions -> Bool # (/=) :: CliConfigOptions -> CliConfigOptions -> Bool # | |
defaultCliConfigOptions :: CliConfigOptions Source #
The default CliConfigOptions. All Options are Unset, which means
they won't override options from ConfigOptions in applyCliArgs.
>>>:{let defCliConfOpt = CliConfigOptions { cliConfFontFamily = Unset , cliConfFontSize = Unset , cliConfShowScrollbar = Unset , cliConfScrollbackLen = Unset , cliConfConfirmExit = Unset , cliConfWordCharExceptions = Unset , cliConfShowMenu = Unset , cliConfShowTabBar = Unset , cliConfCursorBlinkMode = Unset , cliConfBoldIsBright = Unset , cliConfEnableSixel = Unset , cliConfAllowBold = Unset } in defaultCliConfigOptions == defCliConfOpt :} True
data ExtraCliArgs Source #
Extra CLI arguments for values that don't make sense in ConfigOptions.
Constructors
| ExtraCliArgs |
Instances
| Show ExtraCliArgs Source # | |
Defined in Termonad.Cli Methods showsPrec :: Int -> ExtraCliArgs -> ShowS # show :: ExtraCliArgs -> String # showList :: [ExtraCliArgs] -> ShowS # | |
| Eq ExtraCliArgs Source # | |
Defined in Termonad.Cli | |
defaultExtraCliArgs :: ExtraCliArgs Source #
The default ExtraCliArgs.
>>>:{let defExtraCliArgs = ExtraCliArgs in defaultExtraCliArgs == defExtraCliArgs :} True
strOption' :: IsString s => Mod OptionFields (Option s) -> Parser (Option s) Source #
maybeTextReader :: (Text -> Maybe a) -> ReadM a Source #
Similar to maybeReader, but work on Text instead
of String.
Arguments
| :: a | Value when specified without |
| -> a | Value when specified with |
| -> Char | Short flag for without |
| -> Char | Short flag for with |
| -> String | Long flag. |
| -> String | Help text for without |
| -> String | Help text for with |
| -> Parser (Option a) |
Helper for making a flag CLI argument that optionally takes a no- prefix.
Example:
'optionFlag' 'True' 'False' 'f' 'n' "foo" "Does foo" "Does not do foo" :: Parser (Option Bool)
This creates a Parser that accepts both a --foo and a --no-foo flag.
Passing --foo returns , while passing Set True--no-foo returns
. Passing neither Set False--foo nor --no-foo returns Unset.
TODO: This doesn't quite work. If the user passes both --foo and
--no-foo flags, this should ideally take the value of the last flag
passed. However, it appears that if you pass both flags, the second
flag is just not recognized and optparse-applicative raises an error.
parseCliArgs :: IO CliArgs Source #
Parse and return CliArguments.
applyCliArgs :: CliArgs -> ConfigOptions -> ConfigOptions Source #
Overwrite the arguments in ConfigOptions that have been Set in
CliArgs.
>>>import Termonad.Types (defaultConfigOptions)>>>let cliConfOpts = defaultCliConfigOptions { cliConfScrollbackLen = Set 50 }>>>let cliArgs = defaultCliArgs { cliConfigOptions = cliConfOpts }>>>let overwrittenConfOpts = defaultConfigOptions { scrollbackLen = 50 }>>>applyCliArgs cliArgs defaultConfigOptions == overwrittenConfOptsTrue