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 #

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.

Methods

record :: Parser e a #

record :: (r ~ Rep a, Generic a, GRecord e r) => Parser e a #

class Field e a where #

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.

Methods

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

field :: (AsUnset e, AsUnread e, Read a) => String -> Maybe String -> Parser e a #

Instances

Field e Bool #

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

Methods

field :: String -> Maybe String -> Parser e Bool #

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

Expects a single-character String value.

Methods

field :: String -> Maybe String -> Parser e Char #

AsUnset e => Field e String #

Uses the String value verbatim.

Methods

field :: String -> Maybe String -> Parser e String #

(AsUnset e, AsUnread e) => Field e Double # 

Methods

field :: String -> Maybe String -> Parser e Double #

(AsUnset e, AsUnread e) => Field e Float # 

Methods

field :: String -> Maybe String -> Parser e Float #

(AsUnset e, AsUnread e) => Field e Natural # 

Methods

field :: String -> Maybe String -> Parser e Natural #

(AsUnset e, AsUnread e) => Field e Word64 # 

Methods

field :: String -> Maybe String -> Parser e Word64 #

(AsUnset e, AsUnread e) => Field e Word32 # 

Methods

field :: String -> Maybe String -> Parser e Word32 #

(AsUnset e, AsUnread e) => Field e Word16 # 

Methods

field :: String -> Maybe String -> Parser e Word16 #

(AsUnset e, AsUnread e) => Field e Word8 # 

Methods

field :: String -> Maybe String -> Parser e Word8 #

(AsUnset e, AsUnread e) => Field e Word # 

Methods

field :: String -> Maybe String -> Parser e Word #

(AsUnset e, AsUnread e) => Field e Integer # 

Methods

field :: String -> Maybe String -> Parser e Integer #

(AsUnset e, AsUnread e) => Field e Int64 # 

Methods

field :: String -> Maybe String -> Parser e Int64 #

(AsUnset e, AsUnread e) => Field e Int32 # 

Methods

field :: String -> Maybe String -> Parser e Int32 #

(AsUnset e, AsUnread e) => Field e Int16 # 

Methods

field :: String -> Maybe String -> Parser e Int16 #

(AsUnset e, AsUnread e) => Field e Int8 # 

Methods

field :: String -> Maybe String -> Parser e Int8 #

(AsUnset e, AsUnread e) => Field e Int # 

Methods

field :: String -> Maybe String -> Parser e Int #

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

Augments the underlying field parser with the help message.

Methods

field :: String -> Maybe String -> Parser e ((Symbol ? a) tag) #

newtype a ? tag #

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

Instances

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

Augments the underlying field parser with the help message.

Methods

field :: String -> Maybe String -> Parser e ((Symbol ? a) tag) #

Functor ((?) * a) # 

Methods

fmap :: (a -> b) -> (* ? a) a -> (* ? a) b #

(<$) :: a -> (* ? a) b -> (* ? a) a #

Foldable ((?) * a) # 

Methods

fold :: Monoid m => (* ? a) m -> m #

foldMap :: Monoid m => (a -> m) -> (* ? a) a -> m #

foldr :: (a -> b -> b) -> b -> (* ? a) a -> b #

foldr' :: (a -> b -> b) -> b -> (* ? a) a -> b #

foldl :: (b -> a -> b) -> b -> (* ? a) a -> b #

foldl' :: (b -> a -> b) -> b -> (* ? a) a -> b #

foldr1 :: (a -> a -> a) -> (* ? a) a -> a #

foldl1 :: (a -> a -> a) -> (* ? a) a -> a #

toList :: (* ? a) a -> [a] #

null :: (* ? a) a -> Bool #

length :: (* ? a) a -> Int #

elem :: Eq a => a -> (* ? a) a -> Bool #

maximum :: Ord a => (* ? a) a -> a #

minimum :: Ord a => (* ? a) a -> a #

sum :: Num a => (* ? a) a -> a #

product :: Num a => (* ? a) a -> a #

Traversable ((?) * a) # 

Methods

traverse :: Applicative f => (a -> f b) -> (* ? a) a -> f ((* ? a) b) #

sequenceA :: Applicative f => (* ? a) (f a) -> f ((* ? a) a) #

mapM :: Monad m => (a -> m b) -> (* ? a) a -> m ((* ? a) b) #

sequence :: Monad m => (* ? a) (m a) -> m ((* ? a) a) #

Eq a => Eq ((?) k a tag) # 

Methods

(==) :: (k ? a) tag -> (k ? a) tag -> Bool #

(/=) :: (k ? a) tag -> (k ? a) tag -> Bool #

Show a => Show ((?) k a tag) # 

Methods

showsPrec :: Int -> (k ? a) tag -> ShowS #

show :: (k ? a) tag -> String #

showList :: [(k ? a) tag] -> ShowS #

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 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering 

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic () 

Associated Types

type Rep () :: * -> * #

Methods

from :: () -> Rep () x #

to :: Rep () x -> () #

Generic Version 

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic All 

Associated Types

type Rep All :: * -> * #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any 

Associated Types

type Rep Any :: * -> * #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Fixity 

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity 

Associated Types

type Rep Associativity :: * -> * #

Generic SourceUnpackedness 
Generic SourceStrictness 
Generic DecidedStrictness 
Generic [a] 

Associated Types

type Rep [a] :: * -> * #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Maybe a) 

Associated Types

type Rep (Maybe a) :: * -> * #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Generic (V1 p) 

Associated Types

type Rep (V1 p) :: * -> * #

Methods

from :: V1 p -> Rep (V1 p) x #

to :: Rep (V1 p) x -> V1 p #

Generic (U1 p) 

Associated Types

type Rep (U1 p) :: * -> * #

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Generic (Par1 p) 

Associated Types

type Rep (Par1 p) :: * -> * #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (ZipList a) 

Associated Types

type Rep (ZipList a) :: * -> * #

Methods

from :: ZipList a -> Rep (ZipList a) x #

to :: Rep (ZipList a) x -> ZipList a #

Generic (Dual a) 

Associated Types

type Rep (Dual a) :: * -> * #

Methods

from :: Dual a -> Rep (Dual a) x #

to :: Rep (Dual a) x -> Dual a #

Generic (Endo a) 

Associated Types

type Rep (Endo a) :: * -> * #

Methods

from :: Endo a -> Rep (Endo a) x #

to :: Rep (Endo a) x -> Endo a #

Generic (Sum a) 

Associated Types

type Rep (Sum a) :: * -> * #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Generic (Product a) 

Associated Types

type Rep (Product a) :: * -> * #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Generic (First a) 

Associated Types

type Rep (First a) :: * -> * #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a) 

Associated Types

type Rep (Last a) :: * -> * #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (Either a b) 

Associated Types

type Rep (Either a b) :: * -> * #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (Rec1 f p) 

Associated Types

type Rep (Rec1 f p) :: * -> * #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x #

to :: Rep (Rec1 f p) x -> Rec1 f p #

Generic (URec Char p) 

Associated Types

type Rep (URec Char p) :: * -> * #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

Generic (URec Double p) 

Associated Types

type Rep (URec Double p) :: * -> * #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

Generic (URec Float p) 

Associated Types

type Rep (URec Float p) :: * -> * #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

Generic (URec Int p) 

Associated Types

type Rep (URec Int p) :: * -> * #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

Generic (URec Word p) 

Associated Types

type Rep (URec Word p) :: * -> * #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Generic (URec (Ptr ()) p) 

Associated Types

type Rep (URec (Ptr ()) p) :: * -> * #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

Generic (a, b) 

Associated Types

type Rep (a, b) :: * -> * #

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (WrappedMonad m a) 

Associated Types

type Rep (WrappedMonad m a) :: * -> * #

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a #

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Generic (K1 i c p) 

Associated Types

type Rep (K1 i c p) :: * -> * #

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic ((:+:) f g p) 

Associated Types

type Rep ((:+:) f g p) :: * -> * #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

Generic ((:*:) f g p) 

Associated Types

type Rep ((:*:) f g p) :: * -> * #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

Generic ((:.:) f g p) 

Associated Types

type Rep ((:.:) f g p) :: * -> * #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

Generic (a, b, c) 

Associated Types

type Rep (a, b, c) :: * -> * #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (WrappedArrow a b c) 

Associated Types

type Rep (WrappedArrow a b c) :: * -> * #

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x #

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c #

Generic (Alt k f a) 

Associated Types

type Rep (Alt k f a) :: * -> * #

Methods

from :: Alt k f a -> Rep (Alt k f a) x #

to :: Rep (Alt k f a) x -> Alt k f a #

Generic (M1 i c f p) 

Associated Types

type Rep (M1 i c f p) :: * -> * #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Generic (a, b, c, d) 

Associated Types

type Rep (a, b, c, d) :: * -> * #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (a, b, c, d, e) 

Associated Types

type Rep (a, b, c, d, e) :: * -> * #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (a, b, c, d, e, f) 

Associated Types

type Rep (a, b, c, d, e, f) :: * -> * #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (a, b, c, d, e, f, g) 

Associated Types

type Rep (a, b, c, d, e, f, g) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #