envparse-0.4: Parse environment variables

Safe HaskellSafe
LanguageHaskell2010

Env.Generic

Description

Using the Generic facility, this module can derive Parsers automatically.

If you have a simple record:

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}

import Env
import Env.Generic

data Hello = Hello
  { name  :: String
  , count :: Int
  , quiet :: Bool
  } deriving (Show, Eq, Generic)

instance Record Error Hello

main :: IO ()
main = do
  hello <- Env.parse (header "envparse example") record
  print (hello :: Hello)

The generic implementation of the record method translates named fields to field parsers:

% NAME=bob COUNT=3 runhaskell -isrc example/Generic0.hs
Hello {name = "bob", count = 3, quiet = False}

If you want to adorn the ugly default help message, augment the fields with descriptions:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}

import Env
import Env.Generic

data Hello = Hello
  { name  :: String ? "Whom shoud I greet?"
  , count :: Int    ? "How many times to greet them?"
  , quiet :: Bool   ? "Should I be quiet instead?"
  } deriving (Show, Eq, Generic)

instance Record Error Hello

main :: IO ()
main = do
  hello <- Env.parse (header "envparse example") record
  print (hello :: Hello)
% runhaskell -isrc example/Generic1.hs
envparse example

Available environment variables:

  COUNT                  How many times to greet them?
  NAME                   Whom shoud I greet?
  QUIET                  Should I be quiet instead?

Parsing errors:

  COUNT is unset
  NAME is unset

Note that this has an effect of wrapping the values in the Help constructor:

% NAME=bob COUNT=3 QUIET=YES runhaskell -isrc example/Generic1.hs
Hello {name = Help {unHelp = "bob"}, count = Help {unHelp = 3}, quiet = Help {unHelp = True}}

Synopsis

Documentation

class Record e a where Source

Given a Record e a instance, a value of the type a can be parsed from the environment. If the parsing fails, a value of an error type e is returned.

The record method has a default implementation for any type that has a Generic instance. If you need to choose a concrete type for e, the default error type Error is a good candidate. Otherwise, the features you'll use in your parsers will naturally guide GHC to compute the set of required constraints on e.

Minimal complete definition

Nothing

Methods

record :: Parser e a Source

class Field e a where Source

Given a Field e a instance, a value of the type a can be parsed from an environment variable. If the parsing fails, a value of an error type e is returned.

The field method has a default implementation for any type that has a Read instance. If you need to choose a concrete type for e, the default error type Error is a good candidate. Otherwise, the features you'll use in your parsers will naturally guide GHC to compute the set of required constraints on e.

The annotated instances do not use the default implementation.

Minimal complete definition

Nothing

Methods

field :: String -> Maybe String -> Parser e a Source

Instances

Field e Bool Source

Any set and non-empty value parses to a True; otherwise, it's a False. This parser never fails.

(AsUnset e, AsUnread e) => Field e Char Source

Expects a single-character String value.

AsUnset e => Field e String Source

Uses the String value verbatim.

(AsUnset e, AsUnread e) => Field e Double Source 
(AsUnset e, AsUnread e) => Field e Float Source 
(AsUnset e, AsUnread e) => Field e Natural Source 
(AsUnset e, AsUnread e) => Field e Word64 Source 
(AsUnset e, AsUnread e) => Field e Word32 Source 
(AsUnset e, AsUnread e) => Field e Word16 Source 
(AsUnset e, AsUnread e) => Field e Word8 Source 
(AsUnset e, AsUnread e) => Field e Word Source 
(AsUnset e, AsUnread e) => Field e Integer Source 
(AsUnset e, AsUnread e) => Field e Int64 Source 
(AsUnset e, AsUnread e) => Field e Int32 Source 
(AsUnset e, AsUnread e) => Field e Int16 Source 
(AsUnset e, AsUnread e) => Field e Int8 Source 
(AsUnset e, AsUnread e) => Field e Int Source 
(KnownSymbol tag, Field e a) => Field e ((?) Symbol a tag) Source

Augments the underlying field parser with the help message.

newtype a ? tag Source

A field annotation.

If you annotate a record field with a Symbol literal (that is, a statically known type level string) the derivation machinery will use the literal in the help message.

Please remember that the values of the annotated fields are wrapped in the Help constructor.

Constructors

Help 

Fields

unHelp :: a
 

Instances

(KnownSymbol tag, Field e a) => Field e ((?) Symbol a tag) Source

Augments the underlying field parser with the help message.

Functor ((?) * a) Source 
Foldable ((?) * a) Source 
Traversable ((?) * a) Source 
Eq a => Eq ((?) k a tag) Source 
Show a => Show ((?) k a tag) Source 

class Generic a

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 
Generic Char 
Generic Double 
Generic Float 
Generic Int 
Generic Ordering 
Generic () 
Generic Void 
Generic All 
Generic Any 
Generic Arity 
Generic Fixity 
Generic Associativity 
Generic [a] 
Generic (U1 p) 
Generic (Par1 p) 
Generic (Identity a) 
Generic (ZipList a) 
Generic (Dual a) 
Generic (Endo a) 
Generic (Sum a) 
Generic (Product a) 
Generic (First a) 
Generic (Last a) 
Generic (Maybe a) 
Generic (Either a b) 
Generic (Rec1 f p) 
Generic (a, b) 
Generic (Const a b) 
Generic (WrappedMonad m a) 
Generic (Proxy * t) 
Generic (K1 i c p) 
Generic ((:+:) f g p) 
Generic ((:*:) f g p) 
Generic ((:.:) f g p) 
Generic (a, b, c) 
Generic (WrappedArrow a b c) 
Generic (Alt k f a) 
Generic (M1 i c f p) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic (a, b, c, d, e, f) 
Generic (a, b, c, d, e, f, g)