freckle-app-1.1.0.0: Haskell application toolkit used at Freckle
Safe HaskellNone
LanguageHaskell2010

Freckle.App.Env

Description

Parse the shell environment for configuration

A minor extension of envparse.

Usage:

import Freckle.App.Env

data Config = Config -- Example
  { cBatchSize :: Natural
  , cDryRun :: Bool
  , cLogLevel :: LogLevel
  }

loadConfig :: IO Config
loadConfig = parse $ Config
  <$> var auto "BATCH_SIZE" (def 1)
  <*> switch "DRY_RUN" mempty
  <*> flag (Off LevelInfo) (On LevelDebug) "DEBUG" mempty
Synopsis

Documentation

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.

>>> [1,2,3] <> [4,5,6]
[1,2,3,4,5,6]

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

Left-to-right composition of Kleisli arrows.

'(bs >=> cs) a' can be understood as the do expression

do b <- bs a
   cs b

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

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

Note how this operator resembles function composition (.):

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

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

One or none.

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

The sum of a collection of actions, generalizing concat.

>>> asum [Just "Hello", Nothing, Just "World"]
Just "Hello"

parseOr :: (String -> IO a) -> (Info Error -> Info e) -> Parser e b -> IO (Either a b) #

Try to parse the environment

Use this if simply dying on failure (the behavior of parse) is inadequate for your needs.

parse :: (Info Error -> Info e) -> Parser e a -> IO a #

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"))

defaultErrorHandler :: (AsUnset e, AsEmpty e, AsUnread e) => ErrorHandler e #

The default error handler

handleError :: ErrorHandler e -> Info x -> Info e #

An error handler

footer :: String -> Info e -> Info e #

Set the help text footer (it usually includes examples)

desc :: String -> Info e -> Info e #

Set the short description

header :: String -> Info e -> Info e #

Set the help text header (it usually includes the application's name and version)

helpDoc :: Parser e a -> String #

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

data Info e #

Parser's metadata

type ErrorHandler e = String -> e -> Maybe String #

Given a variable name and an error value, try to produce a useful error message

keep :: forall (t :: Type -> Type) a. HasKeep t => Mod t a #

Keep a variable.

help :: forall (t :: Type -> Type) a. HasHelp t => String -> Mod t a #

Attach help text to the variable

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

Show the default value of the variable in help.

def :: a -> Mod Var a #

The default value of the variable

Note: specifying it means the parser won't ever fail.

splitOn :: Char -> Reader e [String] #

The reader that splits a string into a list of strings consuming the separator.

auto :: (AsUnread e, Read a) => Reader e a #

The reader that uses the Read instance of the type

nonempty :: (AsEmpty e, IsString s) => Reader e s #

The reader that accepts only non-empty strings

str :: IsString s => Reader e s #

The trivial reader

switch :: String -> Mod Flag Bool -> Parser e Bool #

A simple boolean flag

Note: this parser never fails.

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

Parse a particular variable from the environment

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

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

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

parsePure :: Parser e a -> [(String, String)] -> Either [(String, e)] a #

Try to parse a pure environment

data Parser e a #

An environment parser

Instances

Instances details
Functor (Parser e) 
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) 
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) 
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] #

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

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

data Mod (t :: Type -> Type) a #

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

Instances

Instances details
Semigroup (Mod t a) 
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) 
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 #

data Var a #

Environment variable metadata

Instances

Instances details
HasHelp Var 
Instance details

Defined in Env.Internal.Parser

Methods

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

HasKeep Var 
Instance details

Defined in Env.Internal.Parser

Methods

setKeep :: Var a -> Var a

data Flag a #

Flag metadata

Instances

Instances details
HasHelp Flag 
Instance details

Defined in Env.Internal.Parser

Methods

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

HasKeep Flag 
Instance details

Defined in Env.Internal.Parser

Methods

setKeep :: Flag a -> Flag a

class HasHelp (t :: Type -> Type) #

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

Minimal complete definition

setHelp

Instances

Instances details
HasHelp Var 
Instance details

Defined in Env.Internal.Parser

Methods

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

HasHelp Flag 
Instance details

Defined in Env.Internal.Parser

Methods

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

class HasKeep (t :: Type -> Type) #

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

Minimal complete definition

setKeep

Instances

Instances details
HasKeep Var 
Instance details

Defined in Env.Internal.Parser

Methods

setKeep :: Var a -> Var a

HasKeep Flag 
Instance details

Defined in Env.Internal.Parser

Methods

setKeep :: Flag a -> Flag a

data Error #

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 Read instance.

Instances

Instances details
Eq Error 
Instance details

Defined in Env.Internal.Error

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

Show Error 
Instance details

Defined in Env.Internal.Error

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

AsUnset Error 
Instance details

Defined in Env.Internal.Error

Methods

unset :: Error #

tryUnset :: Error -> Maybe () #

AsEmpty Error 
Instance details

Defined in Env.Internal.Error

Methods

empty :: Error #

tryEmpty :: Error -> Maybe () #

AsUnread Error 
Instance details

Defined in Env.Internal.Error

class AsUnset e where #

The class of types that contain and can be constructed from the error returned from parsing unset variables.

Methods

unset :: e #

tryUnset :: e -> Maybe () #

Instances

Instances details
AsUnset Error 
Instance details

Defined in Env.Internal.Error

Methods

unset :: Error #

tryUnset :: Error -> Maybe () #

class AsEmpty e where #

The class of types that contain and can be constructed from the error returned from parsing variables whose value is empty.

Methods

empty :: e #

tryEmpty :: e -> Maybe () #

Instances

Instances details
AsEmpty Error 
Instance details

Defined in Env.Internal.Error

Methods

empty :: Error #

tryEmpty :: Error -> Maybe () #

class AsUnread e where #

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.

Methods

unread :: String -> e #

tryUnread :: e -> Maybe String #

Instances

Instances details
AsUnread Error 
Instance details

Defined in Env.Internal.Error

Replacements

newtype Off a Source #

Designates the value of a parameter when a flag is not provided.

Constructors

Off a 

newtype On a Source #

Designates the value of a parameter when a flag is provided.

Constructors

On a 

flag :: Off a -> On a -> String -> Mod Flag a -> Parser Error a Source #

Parse a simple flag

If the variable is present and non-empty in the environment, the active value is returned, otherwise the default is used.

>>> import Control.Monad.Logger
>>> flag (Off LevelInfo) (On LevelDebug) "DEBUG" mempty `parsePure` [("DEBUG", "1")]
Right LevelDebug
>>> flag (Off LevelInfo) (On LevelDebug) "DEBUG" mempty `parsePure` [("DEBUG", "")]
Right LevelInfo
>>> flag (Off LevelInfo) (On LevelDebug) "DEBUG" mempty `parsePure` []
Right LevelInfo

N.B. only the empty string is falsey:

>>> flag (Off LevelInfo) (On LevelDebug) "DEBUG" mempty `parsePure` [("DEBUG", "false")]
Right LevelDebug
>>> flag (Off LevelInfo) (On LevelDebug) "DEBUG" mempty `parsePure` [("DEBUG", "no")]
Right LevelDebug

Extensions

eitherReader :: (String -> Either String a) -> Reader Error a Source #

Create a Reader from a simple parser function

This is a building-block for other Readers

time :: String -> Reader Error UTCTime Source #

Read a time value using the given format

>>> var (time "%Y-%m-%d") "TIME" mempty `parsePure` [("TIME", "1985-02-12")]
Right 1985-02-12 00:00:00 UTC
>>> var (time "%Y-%m-%d") "TIME" mempty `parsePure` [("TIME", "10:00PM")]
Left [("TIME",UnreadError "unable to parse time as %Y-%m-%d: \"10:00PM\"")]

keyValues :: Reader Error [(Text, Text)] Source #

Read key-value pairs

>>> var keyValues "TAGS" mempty `parsePure` [("TAGS", "foo:bar,baz:bat")]
Right [("foo","bar"),("baz","bat")]

Value-less keys are not supported:

>>> var keyValues "TAGS" mempty `parsePure` [("TAGS", "foo,baz:bat")]
Left [("TAGS",UnreadError "Key foo has no value: \"foo,baz:bat\"")]

Nor are key-less values:

>>> var keyValues "TAGS" mempty `parsePure` [("TAGS", "foo:bar,:bat")]
Left [("TAGS",UnreadError "Value bat has no key: \"foo:bar,:bat\"")]