Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- runSettingsParser :: HasParser a => Version -> String -> IO a
- class HasParser a where
- settingsParser :: Parser a
- data Parser a
- runParser :: Version -> String -> Parser a -> IO a
- setting :: HasCallStack => [Builder a] -> Parser a
- filePathSetting :: HasCallStack => [Builder FilePath] -> Parser (Path Abs File)
- directoryPathSetting :: HasCallStack => [Builder FilePath] -> Parser (Path Abs Dir)
- help :: String -> Builder a
- reader :: Reader a -> Builder a
- argument :: Builder a
- option :: Builder a
- switch :: a -> Builder a
- long :: String -> Builder a
- short :: Char -> Builder a
- env :: String -> Builder a
- conf :: HasCodec a => String -> Builder a
- confWith :: String -> ValueCodec void a -> Builder a
- confWith' :: String -> ValueCodec void (Maybe a) -> Builder a
- name :: HasCodec a => String -> Builder a
- value :: Show a => a -> Builder a
- hidden :: Builder a
- metavar :: String -> Builder a
- commands :: HasCallStack => [Command a] -> Parser a
- command :: HasCallStack => String -> String -> Parser a -> Command a
- optional :: Alternative f => f a -> f (Maybe a)
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<*>) :: Applicative f => f (a -> b) -> f a -> f b
- (<|>) :: Alternative f => f a -> f a -> f a
- many :: Alternative f => f a -> f [a]
- some :: Alternative f => f a -> f [a]
- select :: Selective f => f (Either a b) -> f (a -> b) -> f b
- subArgs :: String -> Parser a -> Parser a
- subArgs_ :: String -> Parser a -> Parser a
- subEnv :: String -> Parser a -> Parser a
- subEnv_ :: String -> Parser a -> Parser a
- subConfig :: String -> Parser a -> Parser a
- subConfig_ :: String -> Parser a -> Parser a
- subAll :: String -> Parser a -> Parser a
- subSettings :: HasCallStack => HasParser a => String -> Parser a
- allOrNothing :: HasCallStack => Parser a -> Parser a
- toArgCase :: String -> String
- toEnvCase :: String -> String
- toConfigCase :: String -> String
- someNonEmpty :: Parser a -> Parser (NonEmpty a)
- checkEither :: HasCallStack => (a -> Either String b) -> Parser a -> Parser b
- checkMaybe :: HasCallStack => (a -> Maybe a) -> Parser a -> Parser a
- checkMapEither :: HasCallStack => (a -> Either String b) -> Parser a -> Parser b
- checkMapIO :: HasCallStack => (a -> IO (Either String b)) -> Parser a -> Parser b
- checkMapMaybe :: HasCallStack => (a -> Maybe b) -> Parser a -> Parser b
- checkMapEitherForgivable :: HasCallStack => (a -> Either String b) -> Parser a -> Parser b
- checkMapIOForgivable :: HasCallStack => (a -> IO (Either String b)) -> Parser a -> Parser b
- checkMapMaybeForgivable :: HasCallStack => (a -> Maybe b) -> Parser a -> Parser b
- checkMapMaybe :: HasCallStack => (a -> Maybe b) -> Parser a -> Parser b
- mapIO :: HasCallStack => (a -> IO b) -> Parser a -> Parser b
- choice :: HasCallStack => [Parser a] -> Parser a
- withConfig :: HasCallStack => Parser (Maybe Object) -> Parser a -> Parser a
- withYamlConfig :: HasCallStack => Parser (Maybe (Path Abs File)) -> Parser a -> Parser a
- withFirstYamlConfig :: HasCallStack => Parser [Path Abs File] -> Parser a -> Parser a
- withCombinedYamlConfigs :: Parser [Path Abs File] -> Parser a -> Parser a
- withCombinedYamlConfigs' :: HasCallStack => (Object -> Object -> Object) -> Parser [Path Abs File] -> Parser a -> Parser a
- xdgYamlConfigFile :: HasCallStack => FilePath -> Parser (Path Abs File)
- withLocalYamlConfig :: HasCallStack => Parser a -> Parser a
- withConfigurableYamlConfig :: HasCallStack => Parser (Path Abs File) -> Parser a -> Parser a
- withoutConfig :: HasCallStack => Parser a -> Parser a
- enableDisableSwitch :: HasCallStack => [Builder Bool] -> Parser Bool
- yesNoSwitch :: HasCallStack => [Builder Bool] -> Parser Bool
- makeDoubleSwitch :: HasCallStack => String -> String -> String -> [Builder Bool] -> Parser Bool
- readSecretTextFile :: Path Abs File -> IO Text
- strOption :: HasCallStack => IsString string => [Builder string] -> Parser string
- strArgument :: HasCallStack => IsString string => [Builder string] -> Parser string
- str :: IsString s => Reader s
- auto :: Read a => Reader a
- exists :: Reader Bool
- maybeReader :: (String -> Maybe a) -> Reader a
- eitherReader :: (String -> Either String a) -> Reader a
- commaSeparatedList :: Reader a -> Reader [a]
- commaSeparated :: Reader a -> Reader (NonEmpty a)
- commaSeparatedSet :: Ord a => Reader a -> Reader (Set a)
- module OptEnvConf.Casing
- module OptEnvConf.Doc
- module OptEnvConf.Nix
- module OptEnvConf.Parser
- module OptEnvConf.Reader
- module OptEnvConf.Run
- module OptEnvConf.Setting
- module Control.Applicative
Running parsers
:: 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.
settingsParser :: 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
.
setting
s 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:
<$>
fromFunctor
to map overParser
s<*>
fromApplicative
to "and"Parser
s<|>
fromAlternative
to "or"Parser
soptional
fromAlternative
to optionally run a parsermany
andsome
fromAlternative
to run the same parser multiple times.
You can run a parser with runParser
, or give your type an instance of
HasParser
and run the parser with runSettingsParser
.
:: 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 scriptquery-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 #
setting
s are the building blocks of Parser
s.
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" , shortf
-- "-f" , value False -- The default value of the switch ] :: Parser BoolOption
setting [ help "Document your option" , reader str -- The argument is a string , long
foo
-- "--foo" , shortf
-- "-f" , option ] :: Parser StringEnvironment 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:
- Argument
- Switch
- Option
- Environment variable
- Configuration value
(Hence the name of the package.)
filePathSetting :: HasCallStack => [Builder FilePath] -> Parser (Path Abs File) Source #
directoryPathSetting :: HasCallStack => [Builder FilePath] -> Parser (Path Abs Dir) Source #
Building settings
reader :: Reader a -> Builder a Source #
Declare how to parse an argument, option, or environment variable.
conf :: HasCodec a => String -> Builder a Source #
Try to parse a configuration value at the given key.
Multiple conf
s will be tried in order.
confWith' :: String -> ValueCodec void (Maybe a) -> Builder a Source #
Like confWith
but allows interpreting Null
as a value other than "Not found".
value :: Show a => a -> Builder a Source #
Set the default value
Multiple value
s override eachother.
API Note: default
is not a valid identifier in Haskell.
I'd also have preferred default
instead.
Commands
:: 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
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
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an
Either
Int
Int
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
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.
Prefixing parsers
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
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.
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.
withCombinedYamlConfigs' :: HasCallStack => (Object -> Object -> Object) -> Parser [Path Abs File] -> Parser a -> Parser a Source #
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 #
Common settings
Switches
:: HasCallStack | |
=> [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.
If you pass in a value
value, it will use that as the default value.
:: HasCallStack | |
=> [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.
If you pass in a value
value, it will use that as the default value.
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
strArgument :: HasCallStack => IsString string => [Builder string] -> Parser string Source #
Readers
Common readers
Constructing your own 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
module OptEnvConf.Casing
module OptEnvConf.Doc
module OptEnvConf.Nix
module OptEnvConf.Parser
module OptEnvConf.Reader
module OptEnvConf.Run
module OptEnvConf.Setting
module Control.Applicative