| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Env
Contents
Description
Here's a simple example of a program that uses envparse's parser:
module Main (main) where
import Control.Monad (unless)
import Env
data Hello = Hello { name :: String, quiet :: Bool }
hello :: IO Hello
hello = Env.parse (header "envparse example") $
  Hello <$> var (str <=< nonempty) "NAME"  (help "Target for the greeting")
        <*> switch                 "QUIET" (help "Whether to actually print the greeting")
main :: IO ()
main = do
  Hello {name, quiet} <- hello
  unless quiet $
    putStrLn ("Hello, " ++ name ++ "!")
The NAME environment variable is mandatory and contains the name of the person to
 greet. QUIET, on the other hand, is an optional boolean flag, false by default, that
 decides whether the greeting should be silent.
If the NAME variable is undefined in the environment then running the program will
 result in the following help text:
envparse example
Available environment variables:
  NAME                   Target for the greeting
  QUIET                  Whether to actually print the
                         greeting
Parsing errors:
  NAME is unset
Synopsis
- parse :: (Info Error -> Info e) -> Parser e a -> IO a
- parseOr :: (String -> IO a) -> (Info Error -> Info e) -> Parser e b -> IO (Either a b)
- data Parser e a
- data Mod t a
- data Info e
- header :: String -> Info e -> Info e
- desc :: String -> Info e -> Info e
- footer :: String -> Info e -> Info e
- handleError :: ErrorHandler e -> Info x -> Info e
- type ErrorHandler e = String -> e -> Maybe String
- defaultErrorHandler :: (AsUnset e, AsEmpty e, AsUnread e) => ErrorHandler e
- prefixed :: String -> Parser e a -> Parser e a
- var :: AsUnset e => Reader e a -> String -> Mod Var a -> Parser e a
- data 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
- 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
- helpDoc :: Parser e a -> String
- data Error
- class AsUnset e where
- class AsEmpty e where
- class AsUnread e where
- optional :: Alternative f => f a -> f (Maybe a)
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- (<>) :: Semigroup a => a -> a -> a
- asum :: (Foldable t, Alternative f) => t (f a) -> f a
- parsePure :: Parser e a -> [(String, String)] -> Either [(String, e)] a
Documentation
parseOr :: (String -> IO a) -> (Info Error -> Info e) -> Parser e b -> IO (Either a b) Source #
Try to parse the environment
Use this if simply dying on failure (the behavior of parse) is inadequate for your needs.
An environment parser
This represents a modification of the properties of a particular Parser.
 Combine them using the Monoid instance.
header :: String -> Info e -> Info e Source #
Set the help text header (it usually includes the application's name and version)
footer :: String -> Info e -> Info e Source #
Set the help text footer (it usually includes examples)
handleError :: ErrorHandler e -> Info x -> Info e Source #
An error handler
type ErrorHandler e = String -> e -> Maybe String Source #
Given a variable name and an error value, try to produce a useful error message
defaultErrorHandler :: (AsUnset e, AsEmpty e, AsUnread e) => ErrorHandler e Source #
The default error handler
prefixed :: String -> Parser e a -> Parser e a Source #
The string to prepend to the name of every declared environment variable
Environment variable metadata
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.
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
Minimal complete definition
setHelp
A class of things that can be still kept in an environment when the parsing has been completed.
Minimal complete definition
setKeep
helpDoc :: Parser e a -> String Source #
A pretty-printed list of recognized environment variables suitable for usage messages
The type of errors returned by envparse's Readers. These fall into 3
 categories:
- Variables that are unset in the environment.
- Variables whose value is empty.
- Variables whose value cannot be parsed using the Readinstance.
Constructors
| UnsetError | |
| EmptyError | |
| UnreadError String | 
class AsUnset e where Source #
The class of types that contain and can be constructed from the error returned from parsing unset variables.
class AsEmpty e where Source #
The class of types that contain and can be constructed from the error returned from parsing variables whose value is empty.
class AsUnread e where Source #
The class of types that contain and can be constructed from
 the error returned from parsing variable whose value cannot
 be parsed using the Read instance.
Re-exports
External functions that may be useful to the consumer of the library
optional :: Alternative f => f a -> f (Maybe a) #
One or none.
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #
Left-to-right Kleisli composition of monads.
asum :: (Foldable t, Alternative f) => t (f a) -> f a #
Testing
Utilities to test—without dabbling in IO—that your parsers do what you want them to do