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

Freckle.App.Env

Description

Parse the shell environment for configuration

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

N.B. Usage is meant to mimic envparse, but the implementation is greatly simplified (at loss of some features) and some bugs have been fixed.

http://hackage.haskell.org/package/envparse

Synopsis

Parsing

data Parser a Source #

Parse an Environment

Errors are accumulated into tuples mapping name to error.

Instances

Instances details
Functor Parser Source # 
Instance details

Defined in Freckle.App.Env.Internal

Methods

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

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

Applicative Parser Source # 
Instance details

Defined in Freckle.App.Env.Internal

Methods

pure :: a -> Parser a #

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

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

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

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

Alternative Parser Source # 
Instance details

Defined in Freckle.App.Env.Internal

Methods

empty :: Parser a #

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

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

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

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 

parse :: Parser a -> IO a Source #

Parse the current environment in IO

The process will exit non-zero after printing any errors.

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

Parse a variable by name, using the given Reader and options

>>> exampleParse @String [("EDITOR", "vim")] $ var str "EDITOR" (def "vi")
Right "vim"
>>> exampleParse @String [] $ var str "EDITOR" (def "vi")
Right "vi"

Parsers are instances of Alternative, which means you can use combinators like optional or <|>.

>>> import Control.Applicative
>>> exampleParse @(Maybe String) [] $ optional $ var str "EDITOR" nonEmpty
Right Nothing

The above will no longer fail if the environment variable is missing, but it will still validate it if it is present:

>>> exampleParse @(Maybe String) [("EDITOR", "")] $ optional $ var str "EDITOR" nonEmpty
Left [("EDITOR",InvalidError "value cannot be empty")]
>>> exampleParse @(Maybe String) [("EDITOR", "vim")] $ optional $ var str "EDITOR" nonEmpty
Right (Just "vim")
>>> let p = var str "VISUAL" nonEmpty <|> var str "EDITOR" nonEmpty <|> pure "vi"
>>> exampleParse @String [("VISUAL", "vim"), ("EDITOR", "ed")] p
Right "vim"
>>> exampleParse @String [("EDITOR", "ed")] p
Right "ed"
>>> exampleParse @String [] p
Right "vi"

Again, values that are present are still validated:

>>> exampleParse @String [("VISUAL", ""), ("EDITOR", "ed")] p
Left [("VISUAL",InvalidError "value cannot be empty")]

flag :: Off a -> On a -> String -> Mod a -> Parser 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
>>> exampleParse [("DEBUG", "1")] $ flag (Off LevelInfo) (On LevelDebug) "DEBUG" mempty
Right LevelDebug
>>> exampleParse [("DEBUG", "")] $ flag (Off LevelInfo) (On LevelDebug) "DEBUG" mempty
Right LevelInfo
>>> exampleParse [] $ flag (Off LevelInfo) (On LevelDebug) "DEBUG" mempty
Right LevelInfo

N.B. only the empty string is falsey:

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

switch :: String -> Mod Bool -> Parser Bool Source #

A simplified version of flag for Bool values

>>> exampleParse [("VERBOSE", "1")] $ switch "VERBOSE" mempty
Right True
>>> exampleParse [] $ switch "VERBOSE" mempty
Right False

handleEither Source #

Arguments

:: String

Parser context reported on error

-> Parser (Either String a) 
-> Parser a 

Handle parsers that may fail

Handling Either parser results causes short circuiting in the parser results.

>>> exampleParse @String [("FOO", "")] $ handleEither "CONTEXT" $ pure $ Left "failed"
Left [("CONTEXT",InvalidError "failed")]
>>> exampleParse @String [("FOO", "")] $ handleEither "CONTEXT" $ pure $ Right "stuff"
Right "stuff"

Readers

str :: IsString a => Reader a Source #

Use a value's IsString instance

>>> import Data.Text (Text)
>>> exampleParse @Text [("FOO", "foo")] $ var str "FOO" mempty
Right "foo"

Take note: if this fails, it's basically error.

auto :: Read a => Reader a Source #

Use a value's Read instance

>>> import Numeric.Natural
>>> exampleParse @Natural [("SIZE", "1")] $ var auto "SIZE" mempty
Right 1
>>> exampleParse @Natural [("SIZE", "-1")] $ var auto "SIZE" mempty
Left [("SIZE",InvalidError "Prelude.read: no parse: \"-1\"")]

time :: String -> Reader UTCTime Source #

Read a time value using the given format

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

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

Read key-value pairs

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

Value-less keys are not supported:

>>> exampleParse [("TAGS", "foo,baz:bat")] $ var keyValues "TAGS" mempty
Left [("TAGS",InvalidError "Key foo has no value: \"foo,baz:bat\"")]

Nor are key-less values:

>>> exampleParse [("TAGS", "foo:bar,:bat")] $ var keyValues "TAGS" mempty
Left [("TAGS",InvalidError "Value bat has no key: \"foo:bar,:bat\"")]

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

Create a Reader from a simple parser function

This is a building-block for other Readers

Modifiers

def :: a -> Mod a Source #

Declare a default value for the parser

nonEmpty :: Mod a Source #

Modify parsing to fail on empty strings

>>> exampleParse @String [("FOO", "")] $ var str "FOO" nonEmpty
Left [("FOO",InvalidError "value cannot be empty")]