envparse-0.2.2: Parse environment variables

Safe HaskellSafe
LanguageHaskell2010

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

Documentation

parse :: Mod Info a -> Parser a -> IO a Source

Parse the environment or die

Prints the help text and exits with EXIT_FAILURE on encountering a parse error.

>>> parse (header "env-parse 0.2.0") (var str "USER" (def "nobody"))

parseOr :: (String -> IO a) -> Mod Info b -> Parser 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.

data Parser a Source

An environment parser

data Mod t a Source

This represents a modification of the properties of a particular Parser. Combine them using the Monoid instance.

Instances

Monoid (Mod t a) 

data Info a Source

Parser's metadata

header :: String -> Mod Info a Source

A help text header (it usually includes an application name and version)

desc :: String -> Mod Info a Source

A short program description

footer :: String -> Mod Info a Source

A help text footer (it usually includes examples)

prefixed :: String -> Parser a -> Parser a Source

The string to prepend to the name of every declared environment variable

var :: Reader a -> String -> Mod Var a -> Parser a Source

Parse a particular variable from the environment

>>> var str "EDITOR" (def "vim" <> helpDef show)

data Var a Source

Environment variable metadata

Instances

type Reader a = String -> Either String a Source

An environment variable's value parser. Use (<=<) and (>=>) to combine these

str :: IsString s => Reader s Source

The trivial reader

nonempty :: IsString s => Reader s Source

The reader that accepts only non-empty strings

auto :: Read a => Reader 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.

helpDef :: (a -> String) -> Mod Var a Source

Show the default value of the variable in the help text

flag Source

Arguments

:: a

default value

-> a

active value

-> String 
-> Mod Flag a 
-> Parser a 

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 Bool Source

A simple boolean flag

Note: the same caveats apply.

data Flag a Source

Flag metadata

Instances

class HasHelp t Source

A class of things that can have a help message attached to them

Minimal complete definition

setHelp

Instances

help :: HasHelp t => String -> Mod t a Source

Attach help text to the variable

helpDoc :: Parser a -> String Source

A pretty-printed list of recognized environment variables suitable for usage messages.

Re-exports

External functions that may be useful to the consumer of the library

pure :: Applicative f => forall a. a -> f a

Lift a value.

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

An infix synonym for fmap.

(<*>) :: Applicative f => forall a b. f (a -> b) -> f a -> f b

Sequential application.

(*>) :: Applicative f => forall a b. f a -> f b -> f b

Sequence actions, discarding the value of the first argument.

(<*) :: Applicative f => forall a b. f a -> f b -> f a

Sequence actions, discarding the value of the second argument.

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

One or none.

empty :: Alternative f => forall a. f a

The identity of <|>

(<|>) :: Alternative f => forall a. f a -> f a -> f a

An associative binary operation

(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c infixr 1

Right-to-left Kleisli composition of monads. (>=>), with the arguments flipped

(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1

Left-to-right Kleisli composition of monads.

(<>) :: Monoid m => m -> m -> m infixr 6

An infix synonym for mappend.

Since: 4.5.0.0

mempty :: Monoid a => a

Identity of mappend

mconcat :: Monoid a => [a] -> a

Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

asum :: (Foldable t, Alternative f) => t (f a) -> f a

The sum of a collection of actions, generalizing concat.

Testing

Utilities to test—without dabbling in IO—that your parsers do what you want them to do

parsePure :: Mod Info a -> Parser a -> [(String, String)] -> Either String a Source

Try to parse a pure environment