envparse-0.4.1: Parse environment variables

Safe HaskellSafe
LanguageHaskell2010

Env.Internal.Parser

Synopsis

Documentation

newtype Parser e a Source #

An environment parser

Constructors

Parser 

Fields

Instances
Functor (Parser e) Source # 
Instance details

Defined in Env.Internal.Parser

Methods

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

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

Applicative (Parser e) Source # 
Instance details

Defined in Env.Internal.Parser

Methods

pure :: a -> Parser e a #

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

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

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

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

Alternative (Parser e) Source # 
Instance details

Defined in Env.Internal.Parser

Methods

empty :: Parser e a #

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

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

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

data VarF e a Source #

Instances
Functor (VarF e) Source # 
Instance details

Defined in Env.Internal.Parser

Methods

fmap :: (a -> b) -> VarF e a -> VarF e b #

(<$) :: a -> VarF e b -> VarF e a #

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 #

newtype Mod t a Source #

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

Constructors

Mod (t a -> t a) 
Instances
Semigroup (Mod t a) Source # 
Instance details

Defined in Env.Internal.Parser

Methods

(<>) :: Mod t a -> Mod t a -> Mod t a #

sconcat :: NonEmpty (Mod t a) -> Mod t a #

stimes :: Integral b => b -> Mod t a -> Mod t a #

Monoid (Mod t a) Source # 
Instance details

Defined in Env.Internal.Parser

Methods

mempty :: Mod t a #

mappend :: Mod t a -> Mod t a -> Mod t a #

mconcat :: [Mod t a] -> Mod t a #

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

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

var :: AsUnset e => Reader e a -> String -> Mod Var a -> Parser e a Source #

Parse a particular variable from the environment

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

data Var a Source #

Environment variable metadata

Constructors

Var 

Fields

Instances
HasKeep Var Source # 
Instance details

Defined in Env.Internal.Parser

Methods

setKeep :: Var a -> Var a

HasHelp Var Source # 
Instance details

Defined in Env.Internal.Parser

Methods

setHelp :: String -> Var a -> Var a

type Reader e a = String -> Either e a Source #

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

str :: IsString s => Reader e s Source #

The trivial reader

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.

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

Show the default value of the variable in help.

showDef :: Show a => Mod Var a Source #

Use the Show instance to show the default value of the variable in help.

flag Source #

Arguments

:: a

default value

-> a

active value

-> String 
-> Mod Flag a 
-> Parser e 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 e Bool Source #

A simple boolean flag

Note: this parser never fails.

data Flag a Source #

Flag metadata

Instances
HasKeep Flag Source # 
Instance details

Defined in Env.Internal.Parser

Methods

setKeep :: Flag a -> Flag a

HasHelp Flag Source # 
Instance details

Defined in Env.Internal.Parser

Methods

setHelp :: String -> Flag a -> Flag a

class HasHelp t Source #

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

Minimal complete definition

setHelp

Instances
HasHelp Flag Source # 
Instance details

Defined in Env.Internal.Parser

Methods

setHelp :: String -> Flag a -> Flag a

HasHelp Var Source # 
Instance details

Defined in Env.Internal.Parser

Methods

setHelp :: String -> Var a -> Var a

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

Attach help text to the variable

class HasKeep t Source #

A class of things that can be still kept in an environment when the parsing has been completed.

Minimal complete definition

setKeep

Instances
HasKeep Flag Source # 
Instance details

Defined in Env.Internal.Parser

Methods

setKeep :: Flag a -> Flag a

HasKeep Var Source # 
Instance details

Defined in Env.Internal.Parser

Methods

setKeep :: Var a -> Var a

keep :: HasKeep t => Mod t a Source #

Keep a variable.