opt-env-conf-0.3.0.0: Settings parsing for Haskell: command-line arguments, environment variables, and configuration values.
Safe HaskellSafe-Inferred
LanguageHaskell2010

OptEnvConf

Synopsis

Running parsers

runSettingsParser Source #

Arguments

:: HasParser a 
=> Version

Program version, get this from Paths_your_package_name

-> String

Program description

-> IO a 

Run runParser on your Settings' type's settingsParser.

This is most likely the function you want to be using.

class HasParser a where Source #

A class of types that have a canonical settings parser.

There are no laws. The closest rule to a law is that a user of an instance should not be surprised by its behaviour.

data Parser a Source #

A Parser structure

A Parser a value represents each of these all at once:

  • A way to run it to parse an a
  • A way to document it in various ways
  • A way to run it to perform shell completion

The basic building block of a Parser is a setting. settings represent individual settings that you can then compose into larger parsers.

Much of the way you compose parsers happens via its type class instances. In particular:

You can run a parser with runParser, or give your type an instance of HasParser and run the parser with runSettingsParser.

Instances

Instances details
Alternative Parser Source # 
Instance details

Defined in OptEnvConf.Parser

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

Applicative Parser Source # 
Instance details

Defined in OptEnvConf.Parser

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Functor Parser Source # 
Instance details

Defined in OptEnvConf.Parser

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Selective Parser Source # 
Instance details

Defined in OptEnvConf.Parser

Methods

select :: Parser (Either a b) -> Parser (a -> b) -> Parser b #

runParser Source #

Arguments

:: Version

Program version, get this from Paths_your_package_name

-> String

Program description

-> Parser a 
-> IO a 

Run a parser

This function with exit on:

  • Parse failure: show a nice error message.
  • -h|--help: Show help text
  • --version: Show version information
  • --render-man-page: Render a man page
  • --bash-completion-script: Render a bash completion script
  • --zsh-completion-script: Render a zsh completion script
  • --fish-completion-script: Render a fish completion script
  • query-opt-env-conf-completion: Perform a completion query

This gets the arguments and environment variables from the current process.

Building parsers

Settings

setting :: HasCallStack => [Builder a] -> Parser a Source #

settings are the building blocks of Parsers.

setting lets you put together different builders to define what to parse.

Here are some common examples:

  • Argument

    setting
       [ help "Document your argument"
       , reader str -- The argument is a string
       , argument
       ] :: Parser String
    
  • Switch

    setting
       [ help "Document your switch"
       , switch True -- The value of the switch when activated
       , long foo -- "--foo"
       , short f -- "-f"
       , value False -- The default value of the switch
       ] :: Parser Bool
    
  • Option

    setting
       [ help "Document your option"
       , reader str -- The argument is a string
       , long foo -- "--foo"
       , short f -- "-f"
       , option
       ] :: Parser String
    
  • Environment Variable

    setting
       [ help "Document your environment variable"
       , reader str -- The argument is a string
       , env FOO_BAR
       ] :: Parser String
    
  • Configuration Value

    setting
       [ help "Document your configuration value"
       , conf "foo-bar"
       ] :: Parser String
    
  • Some combination

    setting
       [ help "Document your configuration value"
       , conf "foo-bar"
       ] :: Parser String
    

    Note that parsing is always tried in this order when using a combined setting:

    1. Argument
    2. Switch
    3. Option
    4. Environment variable
    5. Configuration value

    (Hence the name of the package.)

filePathSetting :: HasCallStack => [Builder FilePath] -> Parser (Path Abs File) Source #

A setting for Path Abs File.

This takes care of setting the reader to str, setting the metavar to FILE_PATH, autocompletion, and parsing the FilePath into a Path Abs File.

directoryPathSetting :: HasCallStack => [Builder FilePath] -> Parser (Path Abs Dir) Source #

A setting for Path Abs dir.

This takes care of setting the reader to str, setting the metavar to DIRECTORY_PATH, autocompletion, and parsing the FilePath into a Path Abs Dir.

Building settings

help :: String -> Builder a Source #

Document a setting

Multiple helps concatenate help on new lines.

reader :: Reader a -> Builder a Source #

Declare how to parse an argument, option, or environment variable.

argument :: Builder a Source #

Try to parse an argument.

You'll also need to add a reader.

Multiple arguments are redundant.

option :: Builder a Source #

Try to parse an argument.

You'll also need to add a reader, at least one long or short, and a metavar.

Multiple options are redundant.

switch :: a -> Builder a Source #

Try to parse a switch, activate the given value when succesful

You'll also need to add at least one long or short.

Multiple switchs override eachother.

long :: String -> Builder a Source #

Try to parse this long option or switch.

long "foo" corresponds to --foo

Notes: * Parsing options with an empty name in the long is not supported. * Parsing options with an '=' sign in the long is not supported.

Multiple longs will be tried in order. Empty longs will be ignored.

short :: Char -> Builder a Source #

Try to parse this short option or switch.

short f corresponds to -f

Notes: * Parsing options with short - is not supported.

Multiple shorts will be tried in order.

env :: String -> Builder a Source #

Try to parse an environment variable.

You'll also need to add a reader and a metavar.

Multiple envs will be tried in order.

conf :: HasCodec a => String -> Builder a Source #

Try to parse a configuration value at the given key.

Multiple confs will be tried in order.

confWith :: String -> ValueCodec void a -> Builder a Source #

Like conf but with a custom Codec for parsing the value.

confWith' :: String -> ValueCodec void (Maybe a) -> Builder a Source #

Like confWith but allows interpreting Null as a value other than "Not found".

name :: HasCodec a => String -> Builder a Source #

Short-hand function for option, long, env, and conf at the same time.

Multiple names will be tried in order.

value :: Show a => a -> Builder a Source #

Set the default value

Multiple values override eachother.

API Note: default is not a valid identifier in Haskell. I'd also have preferred default instead.

hidden :: Builder a Source #

Don't show this setting in documentation

Multiple hiddens are redundant.

metavar :: String -> Builder a Source #

Document an option or env var.

Multiple metavars override eachother.

Commands

commands :: HasCallStack => [Command a] -> Parser a Source #

Declare multiple commands

Use command to define a Command.

command Source #

Arguments

:: HasCallStack 
=> String

Name

-> String

Documentation

-> Parser a

Parser

-> Command a 

Declare a single command with a name, documentation and parser

Composing settings with the usual type-classes

optional :: Alternative f => f a -> f (Maybe a) #

One or none.

It is useful for modelling any computation that is allowed to fail.

Examples

Expand

Using the Alternative instance of Control.Monad.Except, the following functions:

>>> import Control.Monad.Except
>>> canFail = throwError "it failed" :: Except String Int
>>> final = return 42                :: Except String Int

Can be combined by allowing the first function to fail:

>>> runExcept $ canFail *> final
Left "it failed"
>>> runExcept $ optional canFail *> final
Right 42

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #

An infix synonym for fmap.

The name of this operator is an allusion to $. Note the similarities between their types:

 ($)  ::              (a -> b) ->   a ->   b
(<$>) :: Functor f => (a -> b) -> f a -> f b

Whereas $ is function application, <$> is function application lifted over a Functor.

Examples

Expand

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

(<*>) :: Applicative f => f (a -> b) -> f a -> f b infixl 4 #

Sequential application.

A few functors support an implementation of <*> that is more efficient than the default one.

Example

Expand

Used in combination with (<$>), (<*>) can be used to build a record.

>>> data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
>>> produceFoo :: Applicative f => f Foo
>>> produceBar :: Applicative f => f Bar
>>> produceBaz :: Applicative f => f Baz
>>> mkState :: Applicative f => f MyState
>>> mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz

(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #

An associative binary operation

many :: Alternative f => f a -> f [a] #

Zero or more.

some :: Alternative f => f a -> f [a] #

One or more.

select :: Selective f => f (Either a b) -> f (a -> b) -> f b #

Prefixing parsers

subArgs :: String -> Parser a -> Parser a Source #

Prefix all longs and shorts with a given Value.

subArgs_ :: String -> Parser a -> Parser a Source #

Helper function for calling subArgs with toArgCase and a - appended.

subArgs_ s = subArgs (toArgCase s <> "-")

subEnv :: String -> Parser a -> Parser a Source #

Prefix all envs with a given Value.

subEnv_ :: String -> Parser a -> Parser a Source #

Helper function for calling subEnv with toEnvCase and a '_' appended.

subEnv_ s = subEnv (toEnvCase s <> "_")

subConfig :: String -> Parser a -> Parser a Source #

Prefix all confs with a given Value.

subConfig_ :: String -> Parser a -> Parser a Source #

Helper function for calling subConfig with toConfigCase.

subConfig_ s = subConfig (toConfigCase s)

subAll :: String -> Parser a -> Parser a Source #

Helper function for calling subArgs_, subEnv_ and subConfig_ with the same prefix.

subAll = subArgs_ prefix . subEnv_ prefix . subConfig_ prefix

Subparsers

subSettings :: HasCallStack => HasParser a => String -> Parser a Source #

Use the settingsParser of a given type, but prefixed with a subAll and allOrNothing.

subSettings prefix = allOrNothing $ subAll prefix settingsParser

allOrNothing :: HasCallStack => Parser a -> Parser a Source #

Parse either all or none of the parser below.

If you don't use this function, and only some of the settings below are defined, this parser will fail and the next alternative will be tried. If you do use this function, this parser will error unforgivably if at least one, but not all, of the settings below are defined.

If each setting has a corresponding forgivable error, consider this forgivable. Consider all other forgivable errors unforgivable

For example, the following will parser will fail intsead of succeed when given the arguments below:

( choice
    [ allOrNothing $
        (,)
          <$> setting [option, long "foo", reader auto, help "This one will exist", metavar "CHAR"]
          <*> setting [option, long "bar", reader auto, help "This one will not exist", metavar "CHAR"],
      pure ('a', 'b')
    ]
)
["--foo", "'a'"]

Casing helpers

toArgCase :: String -> String Source #

Turn a string into arg case for option names

Example: this-is-arg-case

toEnvCase :: String -> String Source #

Turn a string into env case for environment variable names

Example: THIS_IS_ENV_CASE

toConfigCase :: String -> String Source #

Turn a string into config case for configuration value names

Example: this-is-config-case

Helper functions

someNonEmpty :: Parser a -> Parser (NonEmpty a) Source #

Like some but with a more accurate type

checkEither :: HasCallStack => (a -> Either String b) -> Parser a -> Parser b Source #

Like checkMapEither but without changing the type

checkMaybe :: HasCallStack => (a -> Maybe a) -> Parser a -> Parser a Source #

Like checkMapMaybe but without changing the type

checkMapEither :: HasCallStack => (a -> Either String b) -> Parser a -> Parser b Source #

Check a Parser after the fact, purely.

checkMapIO :: HasCallStack => (a -> IO (Either String b)) -> Parser a -> Parser b Source #

Check a Parser after the fact, allowing IO.

checkMapMaybe :: HasCallStack => (a -> Maybe b) -> Parser a -> Parser b Source #

Like checkMapEither but without a helpful error message.

Prefer checkMapEither.

checkMapEitherForgivable :: HasCallStack => (a -> Either String b) -> Parser a -> Parser b Source #

Like checkMapEither, but allow trying the other side of any alternative if the result is Nothing.

checkMapIOForgivable :: HasCallStack => (a -> IO (Either String b)) -> Parser a -> Parser b Source #

Like checkMapIO, but allow trying the other side of any alternative if the result is Nothing. TODO add a SRCLoc here

checkMapMaybeForgivable :: HasCallStack => (a -> Maybe b) -> Parser a -> Parser b Source #

Like checkMapMaybe, but allow trying the other side of any alternative if the result is Nothing.

checkMapMaybe :: HasCallStack => (a -> Maybe b) -> Parser a -> Parser b Source #

Like checkMapEither but without a helpful error message.

Prefer checkMapEither.

mapIO :: HasCallStack => (a -> IO b) -> Parser a -> Parser b Source #

Apply a computation to the result of a parser

This is intended for use-cases like resolving a file to an absolute path. It is morally ok for read-only IO actions but you will have a bad time if the action is not read-only.

choice :: HasCallStack => [Parser a] -> Parser a Source #

Try a list of parsers in order

Loading configuration files

withConfig :: HasCallStack => Parser (Maybe Object) -> Parser a -> Parser a Source #

Load a configuration value and use it for the given parser

withYamlConfig :: HasCallStack => Parser (Maybe (Path Abs File)) -> Parser a -> Parser a Source #

Load a YAML config file and use it for the given parser

withFirstYamlConfig :: HasCallStack => Parser [Path Abs File] -> Parser a -> Parser a Source #

Load the Yaml config in the first of the filepaths that points to something that exists.

withCombinedYamlConfigs :: Parser [Path Abs File] -> Parser a -> Parser a Source #

Combine all Yaml config files that exist into a single combined config object.

xdgYamlConfigFile :: HasCallStack => FilePath -> Parser (Path Abs File) Source #

Load config.yaml from the given XDG configuration subdirectory

withLocalYamlConfig :: HasCallStack => Parser a -> Parser a Source #

Load a config file that is reconfigurable with an option and environment variable but config.yaml in the local working directory by default.

withConfigurableYamlConfig :: HasCallStack => Parser (Path Abs File) -> Parser a -> Parser a Source #

Use the given Parser for deciding which configuration file to load, but only if configuredConfigFile fails to define it first.

withoutConfig :: HasCallStack => Parser a -> Parser a Source #

Don't load any configuration, but still shut up lint errors about conf being used without defining any way to load configuration.

This may be useful if you use a library's Parser that uses conf but do not want to parse any configuration.

Common settings

Switches

enableDisableSwitch Source #

Arguments

:: HasCallStack 
=> Bool

Default value

-> [Builder Bool]

Builders

-> Parser Bool 

Define a setting for a Value with a given default value.

If you pass in long values, it will have --enable-foobar and --disable-foobar switches. If you pass in env values, it will read those environment variables too. If you pass in conf values, it will read those configuration values too.

yesNoSwitch Source #

Arguments

:: HasCallStack 
=> Bool

Default value

-> [Builder Bool]

Builders

-> Parser Bool 

Define a setting for a Value with a given default value.

If you pass in long values, it will have --foobar and --no-foobar switches. If you pass in env values, it will read those environment variables too. If you pass in conf values, it will read those configuration values too.

makeDoubleSwitch Source #

Arguments

:: HasCallStack 
=> String

Prefix for True longs

-> String

Prefix for False longs

-> String

Prefix for the documented longs

-> Bool

Default nvnalue

-> [Builder Bool]

Builders

-> Parser Bool 

Secrets

readSecretTextFile :: Path Abs File -> IO Text Source #

Read a text file but strip whitespace so it can be edited with an editor that messes with line endings.

Migration

strOption :: HasCallStack => IsString string => [Builder string] -> Parser string Source #

A setting with option, a reader set to str, and the metavar set to STR.

Note that you can override the metavar with another metavar in the given list of builders.

This function may help with easier migration from optparse-applicative.

strArgument :: HasCallStack => IsString string => [Builder string] -> Parser string Source #

A setting with argument, a reader set to str, and the metavar set to STR.

Note that you can override the metavar with another metavar in the given list of builders.

This function may help with easier migration from optparse-applicative.

Readers

Common readers

str :: IsString s => Reader s Source #

Read a string as-is.

This is the reader you will want to use for reading a String.

This is different from auto for strings because Read wants to parse quotes when parsing Strings.

auto :: Read a => Reader a Source #

Read via the Read instance

You cannot use this for bare strings, because Read for strings parses quotes.

exists :: Reader Bool Source #

Always return True

exists = Reader $ const $ pure True

Constructing your own reader

maybeReader :: (String -> Maybe a) -> Reader a Source #

Turn a Maybe parsing function into a Reader

eitherReader :: (String -> Either String a) -> Reader a Source #

Turn an Either parsing function into a Reader

API note: This is a forward-compatible alias for Reader.

Comma-separated readers

commaSeparatedList :: Reader a -> Reader [a] Source #

Like commaSeparated but uses a list type.

Note that this will never parse the empty list, so prefer commaSeparated if you want a more accurately typed function.

commaSeparated :: Reader a -> Reader (NonEmpty a) Source #

Turn a reader into one that parses comma separated values with that reader.

commaSeparatedSet :: Ord a => Reader a -> Reader (Set a) Source #

Like commaSeparated but uses a set type.

Note that this will never parse the empty list, so prefer commaSeparated if you want a more accurately typed function.

Note also that this function throws away any ordering information and ignores any duplicate values.

Re-exports, just in case