Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Parser e a = Parser {}
- data VarF e a = VarF {}
- parsePure :: Parser e a -> [(String, String)] -> Either [(String, e)] a
- eachUnsetVar :: Applicative m => Parser e a -> (String -> m b) -> m ()
- newtype Mod t a = Mod (t a -> t a)
- prefixed :: String -> Parser e a -> Parser e a
- var :: AsUnset e => Reader e a -> String -> Mod Var a -> Parser e a
- data Var a = Var {}
- defaultVar :: Var a
- type Reader e a = String -> Either e a
- str :: IsString s => Reader e s
- nonempty :: (AsEmpty e, IsString s) => Reader e s
- splitOn :: Char -> Reader e [String]
- auto :: (AsUnread e, Read a) => Reader e a
- def :: a -> Mod Var a
- helpDef :: (a -> String) -> Mod Var a
- showDef :: Show a => Mod Var a
- flag :: a -> a -> String -> Mod Flag a -> Parser e a
- switch :: String -> Mod Flag Bool -> Parser e Bool
- data Flag a
- class HasHelp t
- help :: HasHelp t => String -> Mod t a
- class HasKeep t
- keep :: HasKeep t => Mod t a
Documentation
An environment parser
parsePure :: Parser e a -> [(String, String)] -> Either [(String, e)] a Source #
Try to parse a pure environment
eachUnsetVar :: Applicative m => Parser e a -> (String -> m b) -> m () Source #
This represents a modification of the properties of a particular Parser
.
Combine them using the Monoid
instance.
Mod (t a -> t a) |
prefixed :: String -> Parser e a -> Parser e a Source #
The string to prepend to the name of every declared environment variable
Environment variable metadata
defaultVar :: Var a Source #
type Reader e a = String -> Either e a Source #
An environment variable's value parser. Use (<=<)
and (>=>)
to combine these
nonempty :: (AsEmpty e, IsString s) => Reader e s Source #
The reader that accepts only non-empty strings
splitOn :: Char -> Reader e [String] Source #
The reader that splits a string into a list of strings consuming the separator.
auto :: (AsUnread e, Read a) => Reader e a Source #
The reader that uses the Read
instance of the type
def :: a -> Mod Var a Source #
The default value of the variable
Note: specifying it means the parser won't ever fail.
showDef :: Show a => Mod Var a Source #
Use the Show
instance to show the default value of the variable in help.
A flag that takes the active value if the environment variable is set and non-empty and the default value otherwise
Note: this parser never fails.
switch :: String -> Mod Flag Bool -> Parser e Bool Source #
A simple boolean flag
Note: this parser never fails.
Flag metadata
A class of things that can have a help message attached to them
setHelp
A class of things that can be still kept in an environment when the parsing has been completed.
setKeep