| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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" memptyN.B. Usage is meant to mimic envparse, but the implementation is greatly simplified (at loss of some features) and some bugs have been fixed.
Synopsis
- data Parser a
 - newtype Off a = Off a
 - newtype On a = On a
 - parse :: Parser a -> IO a
 - var :: Reader a -> String -> Mod a -> Parser a
 - flag :: Off a -> On a -> String -> Mod a -> Parser a
 - switch :: String -> Mod Bool -> Parser Bool
 - handleEither :: String -> Parser (Either String a) -> Parser a
 - str :: IsString a => Reader a
 - auto :: Read a => Reader a
 - time :: String -> Reader UTCTime
 - keyValues :: Reader [(Text, Text)]
 - eitherReader :: (String -> Either String a) -> Reader a
 - def :: a -> Mod a
 - nonEmpty :: Mod a
 
Parsing
Parse an Environment
Errors are accumulated into tuples mapping name to error.
Designates the value of a parameter when a flag is not provided.
Constructors
| Off 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 , which means you can use combinators
 like Alternative or optional.<|>
>>>import Control.Applicative
>>>exampleParse @(Maybe String) [] $ optional $ var str "EDITOR" nonEmptyRight 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" nonEmptyLeft [("EDITOR",InvalidError "value cannot be empty")]
>>>exampleParse @(Maybe String) [("EDITOR", "vim")] $ optional $ var str "EDITOR" nonEmptyRight (Just "vim")
>>>let p = var str "VISUAL" nonEmpty <|> var str "EDITOR" nonEmpty <|> pure "vi">>>exampleParse @String [("VISUAL", "vim"), ("EDITOR", "ed")] pRight "vim"
>>>exampleParse @String [("EDITOR", "ed")] pRight "ed"
>>>exampleParse @String [] pRight "vi"
Again, values that are present are still validated:
>>>exampleParse @String [("VISUAL", ""), ("EDITOR", "ed")] pLeft [("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" memptyRight LevelDebug
>>>exampleParse [("DEBUG", "")] $ flag (Off LevelInfo) (On LevelDebug) "DEBUG" memptyRight LevelInfo
>>>exampleParse [] $ flag (Off LevelInfo) (On LevelDebug) "DEBUG" memptyRight LevelInfo
N.B. only the empty string is falsey:
>>>exampleParse [("DEBUG", "false")] $ flag (Off LevelInfo) (On LevelDebug) "DEBUG" memptyRight LevelDebug
>>>exampleParse [("DEBUG", "no")] $ flag (Off LevelInfo) (On LevelDebug) "DEBUG" memptyRight LevelDebug
Handle parsers that may fail
Handling  parser results causes short circuiting in the parser
 results.Either
>>>exampleParse @String [("FOO", "")] $ handleEither "CONTEXT" $ pure $ Left "failed"Left [("CONTEXT",InvalidError "failed")]
>>>exampleParse @String [("FOO", "")] $ handleEither "CONTEXT" $ pure $ Right "stuff"Right "stuff"
Readers
auto :: Read a => Reader a Source #
Use a value's  instanceRead
>>>import Numeric.Natural
>>>exampleParse @Natural [("SIZE", "1")] $ var auto "SIZE" memptyRight 1
>>>exampleParse @Natural [("SIZE", "-1")] $ var auto "SIZE" memptyLeft [("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" memptyRight 1985-02-12 00:00:00 UTC
>>>exampleParse [("TIME", "10:00PM")] $ var (time "%Y-%m-%d") "TIME" memptyLeft [("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" memptyRight [("foo","bar"),("baz","bat")]
Value-less keys are not supported:
>>>exampleParse [("TAGS", "foo,baz:bat")] $ var keyValues "TAGS" memptyLeft [("TAGS",InvalidError "Key foo has no value: \"foo,baz:bat\"")]
Nor are key-less values:
>>>exampleParse [("TAGS", "foo:bar,:bat")] $ var keyValues "TAGS" memptyLeft [("TAGS",InvalidError "Value bat has no key: \"foo:bar,:bat\"")]